/[MITgcm]/MITgcm/pkg/land/land_write_pickup.F
ViewVC logotype

Annotation of /MITgcm/pkg/land/land_write_pickup.F

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


Revision 1.4 - (hide annotations) (download)
Sat Sep 17 03:17:06 2005 UTC (18 years, 9 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57s_post, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.3: +2 -1 lines
 o fix mnc checkpoint writing problem reported by Baylor -- now works
   correctly with all the MLAdjust inputs

1 edhill 1.4 C $Header: /u/gcmpack/MITgcm/pkg/land/land_write_pickup.F,v 1.3 2005/09/10 20:40:27 edhill Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "LAND_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: LAND_WRITE_PICKUP
8     C !INTERFACE:
9 edhill 1.3 SUBROUTINE LAND_WRITE_PICKUP( isperm, suff,
10     & myTime, myIter, myThid )
11 jmc 1.1
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | S/R LAND_WRITE_PICKUP
15     C | o Writes current state of land package to a pickup file
16     C *==========================================================*
17     C \ev
18    
19     C !USES:
20     IMPLICIT NONE
21    
22     C == Global variables ===
23     #include "LAND_SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "LAND_PARAMS.h"
27     #include "LAND_VARS.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C == Routine Arguments ==
31 edhill 1.3 C isperm :: flag for permanent or rolling checkpoint
32 jmc 1.1 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
33     C myTime :: current time
34     C myIter :: time-step number
35     C myThid :: Number of this instance
36 edhill 1.3 LOGICAL isperm
37 jmc 1.1 CHARACTER*(*) suff
38     _RL myTime
39     INTEGER myIter
40     INTEGER myThid
41    
42     #ifdef ALLOW_LAND
43    
44     C !LOCAL VARIABLES:
45     C fn :: character buffer for creating filename
46     C prec :: precision of pickup files
47     C lgf :: flag to write "global" files
48 jmc 1.2 c INTEGER prec, iChar, lChar, k
49     INTEGER prec, lChar, k
50 jmc 1.1 CHARACTER*(MAX_LEN_FNAM) fn
51     LOGICAL lgf
52 jmc 1.2
53     INTEGER ILNBLNK
54     EXTERNAL ILNBLNK
55    
56 jmc 1.1 CEOP
57    
58     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
59    
60 jmc 1.2 lChar = ILNBLNK(suff)
61 edhill 1.3
62     IF ( land_pickup_write_mdsio ) THEN
63    
64     C-- Write fields as consecutive records
65 jmc 1.1 WRITE(fn,'(A,A)') 'pickup_land.',suff(1:lChar)
66     prec = precFloat64
67     lgf = globalFiles
68    
69     CALL MDSWRITEFIELD(fn,prec,lgf,'RL',land_nLev,
70 jmc 1.2 & land_enthalp,1,myIter,myThid)
71 jmc 1.1 CALL MDSWRITEFIELD(fn,prec,lgf,'RL',land_nLev,
72     & land_groundW,2,myIter,myThid)
73 jmc 1.2 k=2*land_nLev
74     CALL MDSWRITEFIELD(fn,prec,lgf,'RL',1,
75     & land_skinT, k+1,myIter,myThid)
76     CALL MDSWRITEFIELD(fn,prec,lgf,'RL',1,
77     & land_hSnow, k+2,myIter,myThid)
78     CALL MDSWRITEFIELD(fn,prec,lgf,'RL',1,
79     & land_snowAge,k+3,myIter,myThid)
80 jmc 1.1
81 edhill 1.3 ENDIF
82    
83     #ifdef ALLOW_MNC
84     IF ( land_pickup_write_mnc ) THEN
85    
86     DO k = 1,MAX_LEN_FNAM
87     fn(k:k) = ' '
88     ENDDO
89     IF ( isperm ) THEN
90     WRITE(fn,'(A)') 'pickup_land'
91     ELSE
92     WRITE(fn,'(A,A)') 'pickup_land.',suff(1:lChar)
93     ENDIF
94     CALL MNC_FILE_CLOSE_ALL_MATCHING(fn, myThid)
95     CALL MNC_CW_SET_UDIM(fn, 1, myThid)
96     IF ( isperm ) THEN
97     CALL MNC_CW_SET_CITER(fn, 3, 3, myIter, 0, myThid)
98     ELSE
99     CALL MNC_CW_SET_CITER(fn, 2, -1, -1, -1, myThid)
100     ENDIF
101 edhill 1.4 CALL MNC_CW_SET_UDIM(fn, 1, myThid)
102 edhill 1.3
103     CALL MNC_CW_RL_W_S('D',fn,0,0,'T', myTime, myThid)
104     CALL MNC_CW_I_W_S('I',fn,0,0,'iter', myIter, myThid)
105    
106     CALL MNC_CW_RL_W('D',fn,0,0,
107     & 'land_enthalp', land_enthalp, myThid)
108     CALL MNC_CW_RL_W('D',fn,0,0,
109     & 'land_groundW', land_groundW, myThid)
110    
111     CALL MNC_CW_RL_W('D',fn,0,0,
112     & 'land_skinT', land_skinT, myThid)
113     CALL MNC_CW_RL_W('D',fn,0,0,
114     & 'land_hSnow', land_hSnow, myThid)
115     CALL MNC_CW_RL_W('D',fn,0,0,
116     & 'land_snAge', land_snowAge, myThid)
117    
118     ENDIF
119     #endif /* ALLOW_MNC */
120    
121 jmc 1.1 #endif /* ALLOW_LAND */
122    
123     RETURN
124     END

  ViewVC Help
Powered by ViewVC 1.1.22