/[MITgcm]/MITgcm/pkg/ptracers/ptracers_write_checkpoint.F
ViewVC logotype

Contents of /MITgcm/pkg/ptracers/ptracers_write_checkpoint.F

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


Revision 1.9 - (show annotations) (download)
Sat Sep 17 03:17:06 2005 UTC (19 years ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint58l_post, checkpoint58e_post, checkpoint57v_post, checkpoint57s_post, checkpoint58b_post, checkpoint58m_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint58n_post, checkpoint58h_post, checkpoint58j_post, checkpoint57y_pre, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint57w_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint58o_post, checkpoint57z_post, checkpoint58c_post, checkpoint58k_post, checkpoint58p_post, checkpoint58q_post
Changes since 1.8: +4 -1 lines
 o fix mnc checkpoint writing problem reported by Baylor -- now works
   correctly with all the MLAdjust inputs

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_write_checkpoint.F,v 1.8 2005/09/11 15:06:48 edhill Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PTRACERS_WRITE_CHECKPOINT
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE PTRACERS_WRITE_CHECKPOINT( permCheckPoint,
11 & suff,myIter,myTime,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 "PTRACERS_SIZE.h"
22 #include "PTRACERS.h"
23
24 C !INPUT PARAMETERS: ===================================================
25 C permCheckPoint :: permanent or a rolling checkpoint
26 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
27 C myIter :: time-step number
28 C myTime :: model time
29 C myThid :: thread number
30 LOGICAL permCheckPoint
31 CHARACTER*(*) suff
32 INTEGER myIter
33 _RL myTime
34 INTEGER myThid
35
36 C !OUTPUT PARAMETERS: ==================================================
37 C none
38
39 #ifdef ALLOW_PTRACERS
40
41 C !LOCAL VARIABLES: ====================================================
42 C iTracer :: loop indices
43 C iRec :: record number
44 C fn :: character buffer for creating filename
45 C prec :: precision of pickup files
46 C lgf :: flag to write "global" files
47 INTEGER i,iTracer,prec,iRec,iChar,lChar
48 CHARACTER*(MAX_LEN_FNAM) fn
49 LOGICAL lgf
50 INTEGER ILNBLNK
51 EXTERNAL ILNBLNK
52 CEOP
53
54 DO i = 1,MAX_LEN_FNAM
55 fn(i:i) = ' '
56 ENDDO
57
58 #ifdef ALLOW_MNC
59 IF ( PTRACERS_pickup_write_mnc ) THEN
60 IF ( permCheckPoint ) THEN
61 WRITE(fn,'(a)') 'pickup_ptracers'
62 ELSE
63 lChar = ILNBLNK(suff)
64 WRITE(fn,'(2a)') 'pickup_ptracers.', suff(1:lChar)
65 ENDIF
66 CALL MNC_FILE_CLOSE_ALL_MATCHING(fn, myThid)
67 C First ***define*** the file group name
68 CALL MNC_CW_SET_UDIM(fn, 1, myThid)
69 IF ( permCheckPoint ) THEN
70 CALL MNC_CW_SET_CITER(fn, 3, 3, myIter, -1, myThid)
71 ELSE
72 CALL MNC_CW_SET_CITER(fn, 2, -1, -1, -1, myThid)
73 ENDIF
74 C Then set the actual unlimited dimension
75 CALL MNC_CW_SET_UDIM(fn, 1, myThid)
76 C The following two values should probably be for the n-1 time
77 C step since we're saving the gPtrNm1 variable first
78 CALL MNC_CW_RL_W_S('D',fn,0,0,'T', myTime, myThid)
79 CALL MNC_CW_I_W_S('I',fn,0,0,'iter', myIter, myThid)
80 DO iTracer = 1,PTRACERS_numInUse
81 CALL MNC_CW_RL_W('D',fn,0,0, PTRACERS_names(iTracer),
82 & gPtrNm1(1-OLx,1-OLy,1,1,1,iTracer),myThid)
83 ENDDO
84 CALL MNC_CW_SET_UDIM(fn, 2, myThid)
85 CALL MNC_CW_RL_W_S('D',fn,0,0,'T', myTime, myThid)
86 CALL MNC_CW_I_W_S('I',fn,0,0,'iter', myIter, myThid)
87 DO iTracer = 1,PTRACERS_numInUse
88 CALL MNC_CW_RL_W('D',fn,0,0, PTRACERS_names(iTracer),
89 & pTracer(1-OLx,1-OLy,1,1,1,iTracer),myThid)
90 ENDDO
91 ENDIF
92 #endif /* ALLOW_MNC */
93
94 IF ( PTRACERS_pickup_write_mdsio ) THEN
95
96 lChar = 0
97 DO iChar = 1,len(suff)
98 IF ( suff(iChar:iChar) .NE. ' ') lChar=iChar
99 ENDDO
100 WRITE(fn,'(A,A)') 'pickup_ptracers.',suff(1:lChar)
101 prec = precFloat64
102 lgf = globalFiles
103
104 C Write fields & tendancies (needed for AB) as consecutive
105 C records, one tracer after the other, for all available tracers.
106 C note: this allow to restart from a pickup with a different
107 C number of tracers, with read_pickup reading only the tracers
108 C "InUse".
109 DO iTracer=1,PTRACERS_num
110 iRec = 2*iTracer - 1
111 CALL MDSWRITEFIELD(fn,prec,lgf,'RL',Nr,
112 & pTracer(1-Olx,1-Oly,1,1,1,iTracer),
113 & iRec,myIter,myThid)
114 iRec = 2*iTracer
115 CALL MDSWRITEFIELD(fn,prec,lgf,'RL',Nr,
116 & gPtrNm1(1-Olx,1-Oly,1,1,1,iTracer),
117 & iRec,myIter,myThid)
118 ENDDO
119
120 ENDIF
121
122 #endif /* ALLOW_PTRACERS */
123
124 RETURN
125 END

  ViewVC Help
Powered by ViewVC 1.1.22