/[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.6 - (hide annotations) (download)
Sun Apr 11 20:59:27 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.5: +32 -5 lines
change DIC atmos-CO2 box (method 3, dic_int1=3) initialisation & restart:
- use binary pickup file for restart ;
- initialise atmos-CO2 box from dic_pCO2 parameter.
- fix multi-threaded.

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_write_pickup.F,v 1.5 2008/04/07 20:31:16 dfer Exp $
2 dfer 1.1 C $Name: $
3    
4     #include "DIC_OPTIONS.h"
5    
6 jmc 1.4 CBOP
7     C !ROUTINE: DIC_WRITE_PICKUP
8 dfer 1.1
9 jmc 1.4 C !INTERFACE: ==========================================================
10     SUBROUTINE DIC_WRITE_PICKUP( permPickup,
11     I suff, myTime, myIter, myThid )
12    
13     C !DESCRIPTION:
14     C Writes DIC arrays (needed for a restart) to a pickup file
15    
16     C !USES: ===============================================================
17 dfer 1.1 IMPLICIT NONE
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22 dfer 1.2 #include "DIC_VARS.h"
23 jmc 1.6 #include "DIC_ATMOS.h"
24 dfer 1.1
25 jmc 1.4 C !INPUT PARAMETERS: ===================================================
26 dfer 1.1 C permPickup :: write a permanent pickup
27 jmc 1.4 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
28     C myTime :: Current time in simulation
29     C myIter :: Current iteration number in simulation
30     C myThid :: My Thread Id number
31 dfer 1.1 LOGICAL permPickup
32     CHARACTER*(*) suff
33     _RL myTime
34     INTEGER myIter
35     INTEGER myThid
36 jmc 1.4 CEOP
37 dfer 1.1
38     #ifdef ALLOW_DIC
39    
40     C !LOCAL VARIABLES:
41     C == Local variables ==
42     CHARACTER*(MAX_LEN_FNAM) fn
43 jmc 1.6 INTEGER prec
44     #ifndef USE_ATMOSCO2
45     INTEGER ioUnit
46     _RL tmpFld(2)
47     _RS dummyRS(1)
48     #endif
49     #ifdef DIC_BIOTIC
50 jmc 1.3 LOGICAL glf
51 jmc 1.6 INTEGER j, nj
52 jmc 1.3 INTEGER listDim, nWrFlds
53     PARAMETER( listDim = 2 )
54     CHARACTER*(8) wrFldList(listDim)
55     CHARACTER*(MAX_LEN_MBUF) msgBuf
56 jmc 1.6 #endif
57    
58 dfer 1.1
59 jmc 1.3 c IF ( DIC_pickup_write_mdsio ) THEN
60     prec = precFloat64
61 jmc 1.6
62     #ifndef USE_ATMOSCO2
63     IF ( dic_int1.EQ.3 ) THEN
64     WRITE(fn,'(A,A)') 'pickup_dic_co2atm.',suff
65     ioUnit = 0
66     tmpFld(1) = total_atmos_carbon
67     tmpFld(2) = atpco2
68     #ifdef ALLOW_MDSIO
69     CALL MDS_WRITEVEC_LOC(
70     I fn, prec, ioUnit,
71     I 'RL', 2, tmpFld, dummyRS,
72     I 0, 0, 1, myIter, myThid )
73     #endif
74     ENDIF
75     #endif /* ndef USE_ATMOSCO2 */
76    
77     #ifdef DIC_BIOTIC
78 jmc 1.3 WRITE(fn,'(A,A)') 'pickup_dic.',suff
79     j = 0
80    
81     C Firstly, write 3-D fields as consecutive records,
82    
83     C- switch to 2-D fields:
84     nj = -j*Nr
85    
86     C record number < 0 : a hack not to write meta files now:
87     j = j + 1
88     nj = nj-1
89     CALL WRITE_REC_3D_RL( fn, prec, 1, pH, nj, myIter, myThid )
90     IF (j.LE.listDim) wrFldList(j) = 'DIC_pH2d'
91    
92     C--------------------------
93     nWrFlds = j
94     IF ( nWrFlds.GT.listDim ) THEN
95     WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
96     & 'trying to write ',nWrFlds,' fields'
97     CALL PRINT_ERROR( msgBuf, myThid )
98     WRITE(msgBuf,'(2A,I5,A)') 'DIC_WRITE_PICKUP: ',
99     & 'field-list dimension (listDim=',listDim,') too small'
100     CALL PRINT_ERROR( msgBuf, myThid )
101     STOP 'ABNORMAL END: S/R DIC_WRITE_PICKUP (list-size Pb)'
102     ENDIF
103    
104     #ifdef ALLOW_MDSIO
105     C uses this specific S/R to write (with more informations) only meta
106     C files
107     j = 1
108     nj = ABS(nj)
109     IF ( nWrFlds*Nr .EQ. nj ) THEN
110     j = Nr
111     nj = nWrFlds
112     ENDIF
113     glf = globalFiles
114     CALL MDS_WR_METAFILES( fn, prec, glf, .FALSE.,
115     & 0, 0, j, ' ',
116     & nWrFlds, wrFldList,
117     & 1, myTime,
118     & nj, myIter, myThid )
119     #endif /* ALLOW_MDSIO */
120     C--------------------------
121 dfer 1.1
122 jmc 1.6 #endif /* DIC_BIOTIC */
123    
124 jmc 1.3 c ENDIF /* DIC_pickup_write_mdsio */
125 dfer 1.1
126 jmc 1.6 #endif /* ALLOW_DIC */
127 dfer 1.1
128     RETURN
129     END

  ViewVC Help
Powered by ViewVC 1.1.22