/[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.5 - (hide annotations) (download)
Mon Apr 7 20:31:16 2008 UTC (16 years, 1 month ago) by dfer
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.4: +1 -2 lines
Moving dic options to DIC_OPTIONS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22