/[MITgcm]/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_write_pickup.F
ViewVC logotype

Annotation of /MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_write_pickup.F

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


Revision 1.3 - (hide annotations) (download)
Tue Jan 26 15:19:13 2016 UTC (9 years, 5 months ago) by dgoldberg
Branch: MAIN
Changes since 1.2: +9 -2 lines
Added Rmin_surf to pickup

1 dgoldberg 1.3 C $Header: /u/gcmpack/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_write_pickup.F,v 1.2 2016/01/22 16:09:34 dgoldberg Exp $
2 dgoldberg 1.1 C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SHELFICE_WRITE_PICKUP
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE SHELFICE_WRITE_PICKUP( permPickup,
11     & suff, myTime, myIter, myThid )
12    
13     C !DESCRIPTION:
14     C Writes current state of passive tracers to a pickup file
15    
16     C !USES: ===============================================================
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "SHELFICE.h"
22    
23     C !INPUT PARAMETERS: ===================================================
24     C permPickup :: write a permanent pickup
25     C suff :: suffix for pickup file (eg. ckptA or 0000000010)
26     C myTime :: model time
27     C myIter :: time-step number
28     C myThid :: thread number
29     LOGICAL permPickup
30     CHARACTER*(*) suff
31     _RL myTime
32     INTEGER myIter
33     INTEGER myThid
34    
35     C !OUTPUT PARAMETERS: ==================================================
36     C none
37    
38     #ifdef ALLOW_SHELFICE
39     C === Functions ====
40     INTEGER ILNBLNK
41     EXTERNAL ILNBLNK
42    
43     C !LOCAL VARIABLES: ====================================================
44     C j :: loop index / field number
45     C nj :: record number
46     C fp :: pickup-file precision
47     C glf :: local flag for "globalFiles"
48     C fn :: character buffer for creating filename
49     C nWrFlds :: number of fields being written
50     C listDim :: dimension of "wrFldList" local array
51     C wrFldList :: list of written fields
52     C msgBuf :: Informational/error message buffer
53     INTEGER j, nj, fp, lChar
54     LOGICAL glf
55     _RL timList(1)
56     CHARACTER*(MAX_LEN_FNAM) fn
57     INTEGER listDim, nWrFlds
58     PARAMETER( listDim = 12 )
59     CHARACTER*(8) wrFldList(listDim)
60     CHARACTER*(MAX_LEN_MBUF) msgBuf
61     CEOP
62    
63     lChar = ILNBLNK(suff)
64     IF ( lChar.EQ.0 ) THEN
65     WRITE(fn,'(2A)') 'pickup_shelfice'
66     ELSE
67     WRITE(fn,'(2A)') 'pickup_shelfice.',suff(1:lChar)
68     ENDIF
69     fp = precFloat64
70     j = 0
71    
72     C Firstly, write 3-D fields as consecutive records,
73    
74     IF (shelficeMassStepping) then
75    
76     C- switch to 2-D fields:
77     nj = -j*Nr
78    
79     j = j + 1
80     nj = nj-1
81     CALL WRITE_REC_3D_RL( fn, fp, 1, ShelficeMass,
82     & nj, myIter, myThid )
83     IF (j.LE.listDim) wrFldList(j) = 'SHI_mass'
84    
85     j = j + 1
86     nj = nj-1
87    
88     CALL WRITE_REC_3D_RL( fn, fp, 1, R_shelfice,
89     & nj, myIter, myThid )
90 dgoldberg 1.3 IF (j.LE.listDim) wrFldList(j) = 'RSHELF'
91    
92     CALL WRITE_REC_3D_RL( fn, fp, 1, Rmin_surf,
93     & nj, myIter, myThid )
94     IF (j.LE.listDim) wrFldList(j) = 'RMinSurf'
95    
96    
97    
98 dgoldberg 1.1
99     c nj = nj-1
100     c CALL WRITE_REC_3D_RL( fn, fp, 1, myPa_Surf2,
101     c & nj, myIter, myThid )
102     c IF (j.LE.listDim) wrFldList(j) = 'myPaSur2'
103    
104     C--------------------------
105     nWrFlds = j
106     IF ( nWrFlds.GT.listDim ) THEN
107     WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
108     & 'trying to write ',nWrFlds,' fields'
109     CALL PRINT_ERROR( msgBuf, myThid )
110     WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
111     & 'field-list dimension (listDim=',listDim,') too small'
112     CALL PRINT_ERROR( msgBuf, myThid )
113     CALL ALL_PROC_DIE( myThid )
114     STOP 'ABNORMAL END: S/R SHELFICE_WRITE_PICKUP (list-size Pb)'
115     ENDIF
116     #ifdef ALLOW_MDSIO
117     C uses this specific S/R to write (with more informations) only meta files
118     j = 1
119     nj = ABS(nj)
120     IF ( nWrFlds*Nr .EQ. nj ) THEN
121     j = Nr
122     nj = nWrFlds
123     ENDIF
124     glf = globalFiles
125     timList(1) = myTime
126     CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
127     & 0, 0, j, ' ',
128     & nWrFlds, wrFldList,
129     & 1, timList, oneRL,
130     & nj, myIter, myThid )
131     #endif /* ALLOW_MDSIO */
132     C--------------------------
133     ENDIF ! shelficeMassStepping
134    
135     #endif /* ALLOW_SHELFICE */
136    
137     RETURN
138     END

  ViewVC Help
Powered by ViewVC 1.1.22