/[MITgcm]/MITgcm/pkg/flt/flt_write_pickup.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_write_pickup.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.8 - (show annotations) (download)
Wed Dec 22 21:25:18 2010 UTC (13 years, 5 months ago) by jahn
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint63b, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.7: +2 -1 lines
add FLT_SIZE.h

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_write_pickup.F,v 1.7 2009/09/01 19:32:27 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6
7 SUBROUTINE FLT_WRITE_PICKUP(
8 I suff, myTime, myIter, myThid )
9
10 C ==================================================================
11 C SUBROUTINE FLT_WRITE_PICKUP
12 C ==================================================================
13 C o This routine writes the actual float positions to a local files
14 C that can be used as restarts
15 C ==================================================================
16
17 C !USES:
18 IMPLICIT NONE
19
20 C == global variables ==
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "FLT_SIZE.h"
25 #include "FLT.h"
26
27 C == routine arguments ==
28 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
29 C myTime :: current time
30 C myIter :: time-step number
31 C myThid :: my Thread Id number
32 CHARACTER*(*) suff
33 _RL myTime
34 INTEGER myIter, myThid
35
36 C == Functions ==
37 INTEGER ILNBLNK
38 EXTERNAL ILNBLNK
39
40 C == local variables ==
41 CHARACTER*(MAX_LEN_FNAM) fn
42 CHARACTER*(MAX_LEN_MBUF) msgBuf
43 INTEGER ioUnit, irecord
44 INTEGER bi, bj, imax, iLen
45 PARAMETER(imax=9)
46 INTEGER ip
47 _RL tmp(imax)
48 _RL npart_dist
49 _RS dummyRS(1)
50
51 C == end of interface ==
52
53 iLen = ILNBLNK(suff)
54 WRITE(fn,'(A,A)') 'pickup_flt.', suff(1:iLen)
55 npart_dist = 0.
56
57 DO bj=myByLo(myThid),myByHi(myThid)
58 DO bi=myBxLo(myThid),myBxHi(myThid)
59
60 C the standard routine mds_writevec_loc can be used here
61 C (1) write actual number floats and time into file
62
63 tmp(1) = npart_tile(bi,bj)
64 tmp(2) = myIter
65 tmp(3) = myTime
66 tmp(4) = 0.
67 tmp(5) = 0.
68 tmp(6) = max_npart
69 tmp(7) = 0.
70 tmp(8) = 0.
71 tmp(9) = 0.
72
73 ioUnit = -1
74 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
75 & 'RL', imax, tmp, dummyRS,
76 & bi,bj,-1, myIter, myThid )
77
78 DO ip=1,npart_tile(bi,bj)
79
80 tmp(1) = npart(ip,bi,bj)
81 tmp(2) = tstart(ip,bi,bj)
82 tmp(3) = ipart(ip,bi,bj)
83 tmp(4) = jpart(ip,bi,bj)
84 tmp(5) = kpart(ip,bi,bj)
85 tmp(6) = kfloat(ip,bi,bj)
86 tmp(7) = iup(ip,bi,bj)
87 tmp(8) = itop(ip,bi,bj)
88 tmp(9) = tend(ip,bi,bj)
89
90 C (2) write float positions into file
91 irecord = ip+1
92 IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
93 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
94 & 'RL', imax, tmp, dummyRS,
95 & bi,bj,irecord, myIter, myThid )
96
97 ENDDO
98 CLOSE( ioUnit )
99
100 npart_dist = npart_dist + DBLE(npart_tile(bi,bj))
101
102 ENDDO
103 ENDDO
104
105 _GLOBAL_SUM_RL( npart_dist, myThid )
106 _BEGIN_MASTER( myThid )
107 WRITE(msgBuf,*) 'FLT_WRITE_PICKUP:',
108 & npart_dist, ' floats written'
109 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
110 & SQUEEZE_RIGHT, myThid )
111 _END_MASTER( myThid )
112
113 RETURN
114 END

  ViewVC Help
Powered by ViewVC 1.1.22