/[MITgcm]/MITgcm_contrib/darwin2/pkg/darwin/dic_write_pickup.F
ViewVC logotype

Contents of /MITgcm_contrib/darwin2/pkg/darwin/dic_write_pickup.F

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


Revision 1.1 - (show annotations) (download)
Wed Apr 13 18:56:24 2011 UTC (14 years, 6 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt63l_20120405, ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt63f_20111201, ctrb_darwin2_ckpt64a_20121116, ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt62x_20110513, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_ckpt63o_20120629, ctrb_darwin2_ckpt63c_20111011, ctrb_darwin2_ckpt63i_20120124, ctrb_darwin2_ckpt63m_20120506, ctrb_darwin2_ckpt63s_20120908, ctrb_darwin2_ckpt63e_20111107, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt63h_20111230, ctrb_darwin2_ckpt63p_20120707, ctrb_darwin2_ckpt63d_20111107, ctrb_darwin2_ckpt63q_20120731, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_ckpt64b_20121224, ctrb_darwin2_ckpt64_20121012, ctrb_darwin2_baseline, ctrb_darwin2_ckpt63n_20120604, ctrb_darwin2_ckpt63k_20120317, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 #include "CPP_OPTIONS.h"
2 #include "PTRACERS_OPTIONS.h"
3 #include "DARWIN_OPTIONS.h"
4
5 #ifdef ALLOW_PTRACERS
6 #ifdef ALLOW_DARWIN
7
8 #ifdef ALLOW_CARBON
9
10 CBOP
11 C !ROUTINE: DIC_WRITE_PICKUP
12
13 C !INTERFACE: ==========================================================
14 SUBROUTINE DIC_WRITE_PICKUP( permPickup,
15 I suff, myTime, myIter, myThid )
16
17 C !DESCRIPTION:
18 C Writes DIC arrays (needed for a restart) to a pickup file
19
20 C !USES: ===============================================================
21 IMPLICIT NONE
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "DARWIN_FLUX.h"
27
28 C !INPUT PARAMETERS: ===================================================
29 C permPickup :: write a permanent pickup
30 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
31 C myTime :: Current time in simulation
32 C myIter :: Current iteration number in simulation
33 C myThid :: My Thread Id number
34 LOGICAL permPickup
35 CHARACTER*(*) suff
36 _RL myTime
37 INTEGER myIter
38 INTEGER myThid
39 CEOP
40
41 C !LOCAL VARIABLES:
42 C == Local variables ==
43 CHARACTER*(MAX_LEN_FNAM) fn
44 LOGICAL glf
45 INTEGER prec, j, nj
46 INTEGER listDim, nWrFlds
47 PARAMETER( listDim = 2 )
48 CHARACTER*(8) wrFldList(listDim)
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50
51 c IF ( DIC_pickup_write_mdsio ) THEN
52 prec = precFloat64
53 WRITE(fn,'(A,A)') 'pickup_dic.',suff
54 j = 0
55
56 C Firstly, write 3-D fields as consecutive records,
57
58 C- switch to 2-D fields:
59 nj = -j*Nr
60
61 C record number < 0 : a hack not to write meta files now:
62 j = j + 1
63 nj = nj-1
64 CALL WRITE_REC_3D_RL( fn, prec, 1, pH, nj, myIter, myThid )
65 IF (j.LE.listDim) wrFldList(j) = 'DIC_pH2d'
66
67 C--------------------------
68 nWrFlds = j
69 IF ( nWrFlds.GT.listDim ) THEN
70 WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
71 & 'trying to write ',nWrFlds,' fields'
72 CALL PRINT_ERROR( msgBuf, myThid )
73 WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
74 & 'field-list dimension (listDim=',listDim,') too small'
75 CALL PRINT_ERROR( msgBuf, myThid )
76 STOP 'ABNORMAL END: S/R DIC_WRITE_PICKUP (list-size Pb)'
77 ENDIF
78
79 #ifdef ALLOW_MDSIO
80 C uses this specific S/R to write (with more informations) only meta
81 C files
82 j = 1
83 nj = ABS(nj)
84 IF ( nWrFlds*Nr .EQ. nj ) THEN
85 j = Nr
86 nj = nWrFlds
87 ENDIF
88 glf = globalFiles
89 CALL MDS_WR_METAFILES( fn, prec, glf, .FALSE.,
90 & 0, 0, j, ' ',
91 & nWrFlds, wrFldList,
92 & 1, myTime,
93 & nj, myIter, myThid )
94 #endif /* ALLOW_MDSIO */
95 C--------------------------
96
97 c ENDIF /* DIC_pickup_write_mdsio */
98
99
100 RETURN
101 END
102 #endif /*ALLOW_CARBON*/
103
104 #endif /*DARWIN*/
105 #endif /*ALLOW_PTRACERS*/
106 c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22