/[MITgcm]/MITgcm/pkg/atm_compon_interf/cpl_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/atm_compon_interf/cpl_readparms.F

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


Revision 1.6 - (show annotations) (download)
Tue Apr 28 23:27:24 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.5: +2 -2 lines
call WRITE_0D_RL (instead of WRITE_0D_R8) to print "RL" parameters

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_compon_interf/cpl_readparms.F,v 1.5 2007/10/01 15:15:05 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CPL_READPARMS
8 C !INTERFACE:
9 SUBROUTINE CPL_READPARMS( myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | S/R CPL_READPARMS
14 C | o Read Coupling parameters that control import/export
15 C | from/to the coupler layer
16 C *==========================================================*
17 C | this version is specific to 1 component (atmos)
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23
24 C == Global variables ===
25
26 #include "SIZE.h"
27
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "CPL_PARAMS.h"
31 #include "ATMIDS.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine Arguments ==
35 C myThid - Number of this instance
36 INTEGER myThid
37 CEOP
38
39 #ifdef COMPONENT_MODULE
40
41 C Functions
42 INTEGER ILNBLNK
43
44 C == Local Variables ==
45 C msgBuf :: Informational/error meesage buffer
46 C iUnit :: Work variable for IO unit number
47 C k :: loop counter
48 C iL :: Work variable for length of file-name
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 INTEGER iUnit, k, iL
51 _RL cpl_atmSendFrq
52
53 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
54
55 C-- Coupling parameters:
56 C cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
57 C cpl_oldPickup :: restart from an old pickup (= until checkpoint 59h)
58 C useImportMxlD :: True => use Imported Mix.Layer Detph from coupler
59 C useImportSST :: True => use the Imported SST from coupler
60 C useImportSSS :: True => use the Imported SSS from coupler
61 C useImportVsq :: True => use the Imported Surf. velocity^2
62 C useImportFlxCO2 :: True => use the Imported air-sea CO2 fluxes from coupler
63 C cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
64 NAMELIST /CPL_ATM_PARAM/
65 & cpl_earlyExpImpCall,
66 & cpl_oldPickup,
67 & useImportMxlD, useImportSST, useImportSSS,
68 & useImportVsq, useImportFlxCO2,
69 & cpl_atmSendFrq
70
71 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
72
73 C- Set default value:
74 cpl_earlyExpImpCall = .TRUE.
75 cpl_oldPickup = .FALSE.
76 useImportMxlD = .TRUE.
77 useImportSST = .TRUE.
78 useImportSSS = .TRUE.
79 useImportVsq = .TRUE.
80 IF ( atmCpl_exchange_DIC ) THEN
81 useImportFlxCO2 = .TRUE.
82 ELSE
83 useImportFlxCO2 = .FALSE.
84 ENDIF
85 cpl_atmSendFrq= deltaTClock
86
87 _BEGIN_MASTER(myThid)
88
89 WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
90 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
91
92 CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
93 O iUnit, myThid )
94
95 C-- Read parameters from open data file:
96
97 C- Parameters for coupling interface:
98 READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
99
100 WRITE(msgBuf,'(A)')
101 & ' CPL_READPARMS: finished reading data.cpl'
102 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
103
104 C-- Close the open data file
105 CLOSE(iUnit)
106
107 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108 C-- Check parameters and model configuration
109 IF ( useImportFlxCO2 .AND. .NOT.atmCpl_exchange_DIC ) THEN
110 WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',
111 & ' requires atmCpl_exchange_DIC TRUE'
112 CALL PRINT_ERROR( msgBuf, myThid)
113 STOP 'ABNORMAL END: S/R CPL_READPARMS'
114 ENDIF
115
116 C- derive other parameters:
117 cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
118 IF ( cplSendFrq_iter .LT. 1) cplSendFrq_iter = 1
119
120 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
121 C-- Print out parameter values :
122
123 iUnit = standardMessageUnit
124 WRITE(msgBuf,'(A)') ' '
125 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
126 WRITE(msgBuf,'(A)') '// ==================================='
127 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
128 WRITE(msgBuf,'(A)') '// Coupling package parameters :'
129 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
130 WRITE(msgBuf,'(A)') '// ==================================='
131 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
132
133 C- namelist CPL_ATM_PARAM:
134 CALL WRITE_0D_L( cpl_earlyExpImpCall, INDEX_NONE,
135 & 'cpl_earlyExpImpCall=',
136 & ' /* call coupler early in the time-stepping */')
137 CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
138 & 'cpl_oldPickup =',
139 & ' /* restart from old pickup on/off flag */')
140 CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
141 & 'useImportMxlD =',
142 & ' /* use Imported MxL. Depth from Coupler flag */')
143 CALL WRITE_0D_L( useImportSST , INDEX_NONE,
144 & 'useImportSST =',
145 & ' /* use Imported SST from Coupler on/off flag */')
146 CALL WRITE_0D_L( useImportSSS , INDEX_NONE,
147 & 'useImportSSS =',
148 & ' /* use Imported SSS from Coupler on/off flag */')
149 CALL WRITE_0D_L( useImportVsq , INDEX_NONE,
150 & 'useImportVsq =',
151 & ' /* use Imported surf.Vel^2 from Coupler flag */')
152 CALL WRITE_0D_L( useImportFlxCO2 , INDEX_NONE,
153 & 'useImportFlxCO2 =',
154 & ' /* use Imported air-sea CO2 flux from Coupler flag */')
155 CALL WRITE_0D_RL( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
156 & ' /* Frequency^o-1 for sending data to Coupler (s) */')
157 C cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
158 CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
159 &' /* send data to coupler every "cplSendFrq" iter */')
160
161 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
162
163 _END_MASTER(myThid)
164
165 C-- Everyone else must wait for the parameters to be loaded
166 _BARRIER
167
168 #endif /* COMPONENT_MODULE */
169
170 RETURN
171 END

  ViewVC Help
Powered by ViewVC 1.1.22