/[MITgcm]/MITgcm/pkg/ptracers/ptracers_write_pickup.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_write_pickup.F

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


Revision 1.7 - (hide annotations) (download)
Thu May 8 19:50:09 2008 UTC (16 years, 1 month ago) by jahn
Branch: MAIN
Changes since 1.6: +48 -2 lines
add second-order moment advection schemes (80 and 81);
this uses a dynamically allocated internal state data structure
(#define PTRACERS_ALLOW_DYN_STATE in PTRACERS_OPTIONS.h)
and requires a fortran 90 compiler

1 jahn 1.7 C $Header: /u/gcmpack/MITgcm/verification/tutorial_advection_in_gyre/code/ptracers_write_pickup.F,v 1.2 2008/04/06 02:02:20 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 jahn 1.7 #include "GAD_OPTIONS.h"
5 jmc 1.1 #include "PTRACERS_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: PTRACERS_WRITE_PICKUP
9    
10     C !INTERFACE: ==========================================================
11 jmc 1.2 SUBROUTINE PTRACERS_WRITE_PICKUP( permCheckPoint,
12 jmc 1.6 & suff, myTime, myIter, myThid )
13 jmc 1.1
14     C !DESCRIPTION:
15     C Writes current state of passive tracers to a pickup file
16    
17     C !USES: ===============================================================
18 jahn 1.7 #include "PTRACERS_MOD.h"
19 jmc 1.1 IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "PARAMS.h"
23 jahn 1.7 #include "GAD.h"
24 jmc 1.1 #include "PTRACERS_SIZE.h"
25 jmc 1.4 #include "PTRACERS_PARAMS.h"
26 jmc 1.5 #include "PTRACERS_RESTART.h"
27 jmc 1.4 #include "PTRACERS_FIELDS.h"
28 jmc 1.1
29     C !INPUT PARAMETERS: ===================================================
30     C permCheckPoint :: permanent or a rolling checkpoint
31     C suff :: suffix for pickup file (eg. ckptA or 0000000010)
32 jmc 1.6 C myTime :: model time
33 jmc 1.1 C myIter :: time-step number
34     C myThid :: thread number
35     LOGICAL permCheckPoint
36     CHARACTER*(*) suff
37 jmc 1.6 _RL myTime
38 jmc 1.1 INTEGER myIter
39     INTEGER myThid
40    
41     C !OUTPUT PARAMETERS: ==================================================
42     C none
43    
44     #ifdef ALLOW_PTRACERS
45    
46 jmc 1.2 C === Functions ====
47     INTEGER ILNBLNK
48     EXTERNAL ILNBLNK
49    
50 jmc 1.1 C !LOCAL VARIABLES: ====================================================
51 jmc 1.5 C iTracer :: tracer index
52     C j :: loop index / field number
53     C prec :: pickup-file precision
54     C glf :: local flag for "globalFiles"
55     C fn :: character buffer for creating filename
56     C nWrFlds :: number of fields being written
57     C listDim :: dimension of "wrFldList" local array
58     C wrFldList :: list of written fields
59     C msgBuf :: Informational/error message buffer
60 jahn 1.7 INTEGER iTracer, j, prec, lChar, n, iRec
61 jmc 1.5 LOGICAL glf
62 jmc 1.1 CHARACTER*(MAX_LEN_FNAM) fn
63 jmc 1.5 INTEGER listDim, nWrFlds
64     PARAMETER( listDim = 3*PTRACERS_num )
65     CHARACTER*(8) wrFldList(listDim)
66     CHARACTER*(MAX_LEN_MBUF) msgBuf
67 jmc 1.1 CEOP
68    
69     #ifdef ALLOW_MNC
70     IF ( PTRACERS_pickup_write_mnc ) THEN
71     IF ( permCheckPoint ) THEN
72 jmc 1.2 WRITE(fn,'(A)') 'pickup_ptracers'
73 jmc 1.1 ELSE
74     lChar = ILNBLNK(suff)
75 jmc 1.2 WRITE(fn,'(2A)') 'pickup_ptracers.', suff(1:lChar)
76 jmc 1.1 ENDIF
77     CALL MNC_FILE_CLOSE_ALL_MATCHING(fn, myThid)
78     C First ***define*** the file group name
79     CALL MNC_CW_SET_UDIM(fn, 1, myThid)
80     IF ( permCheckPoint ) THEN
81     CALL MNC_CW_SET_CITER(fn, 3, 3, myIter, -1, myThid)
82     ELSE
83     CALL MNC_CW_SET_CITER(fn, 2, -1, -1, -1, myThid)
84     ENDIF
85     C Then set the actual unlimited dimension
86     CALL MNC_CW_SET_UDIM(fn, 1, myThid)
87     C The following two values should probably be for the n-1 time
88 jmc 1.4 C step since we're saving the gpTrNm1 variable first
89 jmc 1.1 CALL MNC_CW_RL_W_S('D',fn,0,0,'T', myTime, myThid)
90     CALL MNC_CW_I_W_S('I',fn,0,0,'iter', myIter, myThid)
91     DO iTracer = 1,PTRACERS_numInUse
92     CALL MNC_CW_RL_W('D',fn,0,0, PTRACERS_names(iTracer),
93 jmc 1.4 & gpTrNm1(1-OLx,1-OLy,1,1,1,iTracer),myThid)
94 jmc 1.1 ENDDO
95     CALL MNC_CW_SET_UDIM(fn, 2, myThid)
96     CALL MNC_CW_RL_W_S('D',fn,0,0,'T', myTime, myThid)
97     CALL MNC_CW_I_W_S('I',fn,0,0,'iter', myIter, myThid)
98     DO iTracer = 1,PTRACERS_numInUse
99     CALL MNC_CW_RL_W('D',fn,0,0, PTRACERS_names(iTracer),
100     & pTracer(1-OLx,1-OLy,1,1,1,iTracer),myThid)
101     ENDDO
102     ENDIF
103 jahn 1.7 #ifdef GAD_ALLOW_SOM_ADVECT
104     IF ( useMNC .AND. PTRACERS_pickup_write_mnc ) THEN
105     DO iTracer = 1, PTRACERS_numInUse
106     IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
107     WRITE(msgBuf,'(3A)')'PTRACERS_WRITE_PICKUP: MNC not yet coded',
108     & ' for SOM advection',
109     & ' => write bin file instead'
110     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
111     & SQUEEZE_RIGHT, myThid)
112     ENDIF
113     ENDDO
114     ENDIF
115     #endif /* GAD_ALLOW_SOM_ADVECT */
116 jmc 1.1 #endif /* ALLOW_MNC */
117 jmc 1.2
118 jmc 1.1 IF ( PTRACERS_pickup_write_mdsio ) THEN
119    
120 jmc 1.2 lChar = ILNBLNK(suff)
121     IF ( lChar.EQ.0 ) THEN
122     WRITE(fn,'(2A)') 'pickup_ptracers'
123     ELSE
124     WRITE(fn,'(2A)') 'pickup_ptracers.',suff(1:lChar)
125     ENDIF
126 jmc 1.1 prec = precFloat64
127    
128 jmc 1.5 C Firstly, write ptracer fields as consecutive records,
129     C one tracer after the other, for all tracers "InUse".
130    
131     j = 0
132     C record number < 0 : a hack not to write meta files now:
133     DO iTracer = 1, PTRACERS_numInUse
134     j = j + 1
135 jmc 1.2 CALL WRITE_REC_3D_RL( fn, prec, Nr,
136 jmc 1.1 & pTracer(1-Olx,1-Oly,1,1,1,iTracer),
137 jmc 1.5 & -j, myIter, myThid )
138     IF (j.LE.listDim)
139     & wrFldList(j) = 'pTr'//PTRACERS_ioLabel(iTracer)//' '
140     ENDDO
141    
142     C Then write ptracer tendencies (if this tracer is using AB time-stepping)
143     DO iTracer = 1, PTRACERS_numInUse
144     IF ( PTRACERS_AdamsBashGtr(iTracer) ) THEN
145     j = j + 1
146 jmc 1.2 CALL WRITE_REC_3D_RL( fn, prec, Nr,
147 jmc 1.4 & gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
148 jmc 1.5 & -j, myIter, myThid )
149     IF (j.LE.listDim)
150     & wrFldList(j) = 'gPtr'//PTRACERS_ioLabel(iTracer)//'m1'
151     ENDIF
152    
153 jmc 1.1 ENDDO
154    
155 jmc 1.5 C--------------------------
156     nWrFlds = j
157     IF ( nWrFlds.GT.listDim ) THEN
158     WRITE(msgBuf,'(2A,I5,A)') 'PTRACERS_WRITE_PICKUP: ',
159     & 'trying to write ',nWrFlds,' fields'
160     CALL PRINT_ERROR( msgBuf, myThid )
161     WRITE(msgBuf,'(2A,I5,A)') 'PTRACERS_WRITE_PICKUP: ',
162     & 'field-list dimension (listDim=',listDim,') too small'
163     CALL PRINT_ERROR( msgBuf, myThid )
164     STOP 'ABNORMAL END: S/R PTRACERS_WRITE_PICKUP (list-size Pb)'
165     ENDIF
166     #ifdef ALLOW_MDSIO
167     C uses this specific S/R to write (with more informations) only meta files
168     glf = globalFiles
169     CALL MDS_WR_METAFILES( fn, prec, glf, .FALSE.,
170     & 0, 0, Nr, ' ',
171     & nWrFlds, wrFldList,
172     & 1, myTime,
173     & j, myIter, myThid )
174     #endif /* ALLOW_MDSIO */
175     C--------------------------
176 jahn 1.7 #if defined(GAD_ALLOW_SOM_ADVECT) && defined(PTRACERS_ALLOW_DYN_STATE)
177     C write pickup for 2nd-order moment fields
178     C we write a separate file for each Ptracer that uses SOM advection
179     DO iTracer = 1, PTRACERS_numInUse
180     IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
181     IF ( lChar.EQ.0 ) THEN
182     WRITE(fn,'(2A)') 'pickup_somTRAC',PTRACERS_ioLabel(iTracer)
183     ELSE
184     WRITE(fn,'(4A)') 'pickup_somTRAC',PTRACERS_ioLabel(iTracer),
185     & '.',suff(1:lChar)
186     ENDIF
187     WRITE(msgBuf,'(A,I3,A)')'PTRACERS_WRITE_PICKUP: iTracer = ',
188     & iTracer,
189     & ' : writing 2nd-order moments to file '
190     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
191     & SQUEEZE_RIGHT, myThid)
192     CALL PRINT_MESSAGE( fn, standardMessageUnit,
193     & SQUEEZE_RIGHT, myThid)
194     prec = precFloat64
195     C Write 2nd Order moments as consecutive records
196     DO n=1,nSOM
197     iRec = n
198     CALL WRITE_REC_3D_RL( fn, prec, Nr,
199     I _Ptracers_som(1-Olx,1-Oly,1,1,1,n,iTracer),
200     I iRec, myIter, myThid )
201     ENDDO
202     ENDIF
203     ENDDO
204     #endif /* GAD_ALLOW_SOM_ADVECT && PTRACERS_ALLOW_DYN_STATE */
205     C--------------------------
206 jmc 1.1 ENDIF
207    
208     #endif /* ALLOW_PTRACERS */
209    
210     RETURN
211     END

  ViewVC Help
Powered by ViewVC 1.1.22