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

Contents of /MITgcm_contrib/shelfice_remeshing/CPL1/code/shelfice_write_pickup.F

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


Revision 1.1 - (show annotations) (download)
Mon Oct 26 15:22:48 2015 UTC (9 years, 9 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Added R_shelfice to pickup

1 C $Header: /u/gcmpack/MITgcm/pkg/shelfice/shelfice_write_pickup.F,v 1.1 2015/01/20 14:54:36 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
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 IF (j.LE.listDim) wrFldList(j) = 'SHI_Rshelfice'
91
92 c nj = nj-1
93 c CALL WRITE_REC_3D_RL( fn, fp, 1, myPa_Surf2,
94 c & nj, myIter, myThid )
95 c IF (j.LE.listDim) wrFldList(j) = 'myPaSur2'
96
97 C--------------------------
98 nWrFlds = j
99 IF ( nWrFlds.GT.listDim ) THEN
100 WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
101 & 'trying to write ',nWrFlds,' fields'
102 CALL PRINT_ERROR( msgBuf, myThid )
103 WRITE(msgBuf,'(2A,I5,A)') 'SHELFICE_WRITE_PICKUP: ',
104 & 'field-list dimension (listDim=',listDim,') too small'
105 CALL PRINT_ERROR( msgBuf, myThid )
106 CALL ALL_PROC_DIE( myThid )
107 STOP 'ABNORMAL END: S/R SHELFICE_WRITE_PICKUP (list-size Pb)'
108 ENDIF
109 #ifdef ALLOW_MDSIO
110 C uses this specific S/R to write (with more informations) only meta files
111 j = 1
112 nj = ABS(nj)
113 IF ( nWrFlds*Nr .EQ. nj ) THEN
114 j = Nr
115 nj = nWrFlds
116 ENDIF
117 glf = globalFiles
118 timList(1) = myTime
119 CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
120 & 0, 0, j, ' ',
121 & nWrFlds, wrFldList,
122 & 1, timList, oneRL,
123 & nj, myIter, myThid )
124 #endif /* ALLOW_MDSIO */
125 C--------------------------
126 ENDIF ! shelficeMassStepping
127
128 #endif /* ALLOW_SHELFICE */
129
130 RETURN
131 END

  ViewVC Help
Powered by ViewVC 1.1.22