/[MITgcm]/MITgcm/pkg/dic/dic_write_pickup.F
ViewVC logotype

Annotation of /MITgcm/pkg/dic/dic_write_pickup.F

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


Revision 1.3 - (hide annotations) (download)
Sun Apr 6 03:26:01 2008 UTC (16 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.2: +53 -6 lines
test for "pickup_dic" file when restarting ; if no pickup-file, restart
 with a re-initialised pH (same as it did before)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_write_pickup.F,v 1.2 2008/04/04 21:37:06 dfer Exp $
2 dfer 1.1 C $Name: $
3    
4     #include "GCHEM_OPTIONS.h"
5     #include "DIC_OPTIONS.h"
6    
7     SUBROUTINE DIC_WRITE_PICKUP( permPickup, suff,
8     I myTime, myIter, myThid )
9    
10     IMPLICIT NONE
11     C === Global variables ===
12     #include "SIZE.h"
13     #include "EEPARAMS.h"
14     #include "PARAMS.h"
15 dfer 1.2 #include "DIC_VARS.h"
16 dfer 1.1
17     C == Routine arguments ==
18     C permPickup :: write a permanent pickup
19     C suff :: suffix for pickup file (eg. ckptA or 0000000010)
20     C myTime :: Current time in simulation
21     C myIter :: Current iteration number in simulation
22     C myThid :: My Thread Id number
23     LOGICAL permPickup
24     CHARACTER*(*) suff
25     _RL myTime
26     INTEGER myIter
27     INTEGER myThid
28    
29     #ifdef ALLOW_DIC
30     #ifdef DIC_BIOTIC
31    
32     C !LOCAL VARIABLES:
33     C == Local variables ==
34     CHARACTER*(MAX_LEN_FNAM) fn
35 jmc 1.3 LOGICAL glf
36     INTEGER prec, j, nj
37     INTEGER listDim, nWrFlds
38     PARAMETER( listDim = 2 )
39     CHARACTER*(8) wrFldList(listDim)
40     CHARACTER*(MAX_LEN_MBUF) msgBuf
41 dfer 1.1 CEOP
42    
43 jmc 1.3 c IF ( DIC_pickup_write_mdsio ) THEN
44     prec = precFloat64
45     WRITE(fn,'(A,A)') 'pickup_dic.',suff
46     j = 0
47    
48     C Firstly, write 3-D fields as consecutive records,
49    
50     C- switch to 2-D fields:
51     nj = -j*Nr
52    
53     C record number < 0 : a hack not to write meta files now:
54     j = j + 1
55     nj = nj-1
56     CALL WRITE_REC_3D_RL( fn, prec, 1, pH, nj, myIter, myThid )
57     IF (j.LE.listDim) wrFldList(j) = 'DIC_pH2d'
58    
59     C--------------------------
60     nWrFlds = j
61     IF ( nWrFlds.GT.listDim ) THEN
62     WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
63     & 'trying to write ',nWrFlds,' fields'
64     CALL PRINT_ERROR( msgBuf, myThid )
65     WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
66     & 'field-list dimension (listDim=',listDim,') too small'
67     CALL PRINT_ERROR( msgBuf, myThid )
68     STOP 'ABNORMAL END: S/R DIC_WRITE_PICKUP (list-size Pb)'
69     ENDIF
70    
71     #ifdef ALLOW_MDSIO
72     C uses this specific S/R to write (with more informations) only meta
73     C files
74     j = 1
75     nj = ABS(nj)
76     IF ( nWrFlds*Nr .EQ. nj ) THEN
77     j = Nr
78     nj = nWrFlds
79     ENDIF
80     glf = globalFiles
81     CALL MDS_WR_METAFILES( fn, prec, glf, .FALSE.,
82     & 0, 0, j, ' ',
83     & nWrFlds, wrFldList,
84     & 1, myTime,
85     & nj, myIter, myThid )
86     #endif /* ALLOW_MDSIO */
87     C--------------------------
88 dfer 1.1
89 jmc 1.3 c ENDIF /* DIC_pickup_write_mdsio */
90 dfer 1.1
91     #endif /* DIC_BIOTIC */
92     #endif /* ALLOW_DIC */
93    
94     RETURN
95     END

  ViewVC Help
Powered by ViewVC 1.1.22