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

Contents 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.6 - (show annotations) (download)
Fri Jul 29 12:44:52 2016 UTC (8 years, 11 months ago) by ksnow
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65y, checkpoint67a, checkpoint67b, checkpoint67d, HEAD
Changes since 1.5: +7 -7 lines
emoving Rminsurf from pickup

1 C $Header: /u/gcmpack/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_write_pickup.F,v 1.5 2016/05/05 18:16:04 dgoldberg Exp $
2 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 #include "SURFACE.h"
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 #ifdef ALLOW_SHELFICE_REMESHING
86
87 j = j + 1
88 nj = nj-1
89
90 CALL WRITE_REC_3D_RL( fn, fp, 1, R_shelfice,
91 & nj, myIter, myThid )
92 IF (j.LE.listDim) wrFldList(j) = 'R_Shelfi'
93
94 C j = j + 1
95 C nj = nj-1
96 C
97 C CALL WRITE_REC_3D_RL( fn, fp, 1, Rmin_surf,
98 C & nj, myIter, myThid )
99 C IF (j.LE.listDim) wrFldList(j) = 'RMinSurf'
100
101 #endif
102
103
104 c nj = nj-1
105 c CALL WRITE_REC_3D_RL( fn, fp, 1, myPa_Surf2,
106 c & nj, myIter, myThid )
107 c IF (j.LE.listDim) wrFldList(j) = 'myPaSur2'
108
109 C--------------------------
110 nWrFlds = j
111 IF ( nWrFlds.GT.listDim ) THEN
112 WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
113 & 'trying to write ',nWrFlds,' fields'
114 CALL PRINT_ERROR( msgBuf, myThid )
115 WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
116 & 'field-list dimension (listDim=',listDim,') too small'
117 CALL PRINT_ERROR( msgBuf, myThid )
118 CALL ALL_PROC_DIE( myThid )
119 STOP 'ABNORMAL END: S/R SHELFICE_WRITE_PICKUP (list-size Pb)'
120 ENDIF
121 #ifdef ALLOW_MDSIO
122 C uses this specific S/R to write (with more informations) only meta files
123 j = 1
124 nj = ABS(nj)
125 IF ( nWrFlds*Nr .EQ. nj ) THEN
126 j = Nr
127 nj = nWrFlds
128 ENDIF
129 glf = globalFiles
130 timList(1) = myTime
131 CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
132 & 0, 0, j, ' ',
133 & nWrFlds, wrFldList,
134 & 1, timList, oneRL,
135 & nj, myIter, myThid )
136 #endif /* ALLOW_MDSIO */
137 C--------------------------
138 ENDIF ! shelficeMassStepping
139
140 #endif /* ALLOW_SHELFICE */
141
142 RETURN
143 END

  ViewVC Help
Powered by ViewVC 1.1.22