/[MITgcm]/MITgcm_contrib/AITCZ/code/mitphys_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/AITCZ/code/mitphys_readparms.F

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 20 15:24:59 2003 UTC (21 years, 11 months ago) by czaja
Branch: MAIN
CVS Tags: HEAD
Initial creation of Arnaud's simple coupled simulation.

1 czaja 1.1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/mitphys/mitphys_readparms.F 2001/09/04 19:09:23 omp Exp $
2     C $Name: $
3    
4     C modified from shap_filt_readparms.F
5     #include "CPP_OPTIONS.h"
6    
7     SUBROUTINE MITPHYS_READPARMS( myThid )
8     C /==========================================================\
9     C | SUBROUTINE SHAP_FILT_READPARMS |
10     C | o Routine to initialize Shapiro Filter parameters |
11     C |==========================================================|
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C === Global variables ===
16    
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "MITPHYS_PARAMS.h"
21    
22     C === Routine arguments ===
23     INTEGER myThid
24    
25     #ifdef ALLOW_MITPHYS
26    
27     NAMELIST /MITPHYS_PARM01/
28     & CDM, CD, US0, VS0, WS0,
29     & RADINT, CRFINT, CLEARSKY, RADFREQ,
30     & PBL_MIX, CONV_MOM_TRANS,
31     & CONV_ADJ, K_PBL, LOG_CORRECT,
32     & DARAD, RAD_LAT, RAD_LON, RAD_TIME,
33     & RAD_START_TIME, LINEAR_FRICTION,
34     & LIN_FR_VEL, PHYS_CALL
35    
36     NAMELIST /MITPHYS_PARM02/
37     & PRESC_SST, SST_BACK, PRESC_STL, PRESC_BKT,
38     & DELT_EQ_PO, DELT_EQ_BND,
39     & DELT_LH, LAT_LH,
40     & DELT_PERT, LAT_PERT, DEL_LAT,
41     & DELT_STL_EQU, DELT_STL_HEM, DEL_LAT_STL,
42     & DELT_PERT_NTA, LAT_PERT_NTA, DEL_LAT_NTA,
43     & DELT_PERT_MO, LAT_PERT_MO, DEL_LAT_MO,
44     & LON_PERT_MO, DEL_LON_MO,
45     & ANNUAL_CYCLE, SST_DELAY,
46     & RELAX_SST, SST_RELAX_TIME, SEA_THICK,
47     & HEATCAPOCEA, HEATCAPLAND, BKT0,
48     & DELL_STAR, DELQ_STAR, QSTAR_BACK,
49     & DELL_OCEAN, DELQ_OCEAN, LOE_OCEAN, LOW_OCEAN
50    
51     C === Local variables ===
52     C msgBuf - Informational/error meesage buffer
53     C iUnit - Work variable for IO unit number
54     CHARACTER*(MAX_LEN_MBUF) msgBuf
55     INTEGER iUnit
56    
57     C-- MITPHYS_READPARMS has been called so we know that
58     C the package is active.
59    
60    
61     _BEGIN_MASTER(myThid)
62    
63     WRITE(msgBuf,'(A)') ' MITPHYS_READPARMS: opening data.mitphys'
64     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65     & SQUEEZE_RIGHT , 1)
66    
67     CALL OPEN_COPY_DATA_FILE(
68     I 'data.mitphys', 'MITPHYS_READPARMS',
69     O iUnit,
70     I myThid )
71    
72     C-- Default flags and values for MITPHYS
73    
74     C MITPHYS_PARM01: parameters used mostly by MITPHY_DRIVER
75    
76     CD = 1.2d-3
77     CDM = 1.2d-3
78     US0 = 0.0
79     VS0 = 0.0
80     WS0 = 2.0
81     DARAD = .TRUE. ! TRUE= no diurnal cycle
82     RAD_LAT = .FALSE. ! TRUE= latitudinal variation of insolation
83     RAD_LON = .FALSE. ! TRUE= longitudinal variation of insolation
84     RAD_TIME =.FALSE. ! FALSE = radiation constant with time.
85     RAD_START_TIME = 0.
86     ! starting time for radiation calc, default value
87     ! corresponds to March 1st of january
88     C RAD_START_TIME = 24. * 3600. * (30. + 30. + 20.)
89     ! starting time for radiation calc, default value
90     ! corresponds to March 21st
91     RADINT=.TRUE. ! TRUE=interactive radiation
92     CRFINT=.TRUE. ! TRUE=interactive cld rad forcing
93     CLEARSKY=.FALSE. ! TRUE=ignore cld-rad interactions
94     CONV_MOM_TRANS = .FALSE. ! FALSE= no momentum transport by
95     ! moist convection
96     CONV_ADJ = .FALSE. ! FALSE:instantaneous dry convective adjustment
97     ! and does not affect the zonal wind
98     ! TRUE: the adjustment is performed through
99     ! time tendencies. It also affects
100     ! the horizontal wind.
101     PBL_MIX = .TRUE. ! FALSE = mixing of momentum in the PBL
102     ! TRUE = Diffusion of momentum in the PBL
103     K_PBL = 4 ! Thickness of the 'PBL' in model layers
104     LOG_CORRECT = 1.0 ! Correction term for surface wind
105     RADFREQ = 6. * 3600. ! Time interval between radiation calls
106     LINEAR_FRICTION = .FALSE.
107     LIN_FR_VEL = 6.0
108     PHYS_CALL = 1 ! call physics every PHYS_CALL time step(s).
109    
110    
111     C MITPHYS_PARM02: paramters controlling the SST
112    
113     PRESC_SST = .TRUE.
114     PRESC_STL = .TRUE.
115     SST_BACK = 298.15d0
116     DELT_EQ_PO = 0.0
117     DELT_EQ_BND = 0.0
118     DELT_LH = 0.0
119     LAT_LH = 0.0
120     DELT_PERT = 0.0
121     LAT_PERT = 0.0
122     DEL_LAT = 20.0
123     DELT_STL_EQU = 0.0
124     DELT_STL_HEM = 0.0
125     DEL_LAT_STL = 30.0
126     DELT_PERT_NTA = 0.0
127     LAT_PERT_NTA = 0.0
128     DEL_LAT_NTA = 15.0
129     DELT_PERT_MO = 0.0
130     LAT_PERT_MO = 0.0
131     DEL_LAT_MO = 20.0
132     LON_PERT_MO = 0.0
133     DEL_LON_MO= 20.0
134     ANNUAL_CYCLE = .FALSE. ! No annual cycle in SST
135     SST_DELAY = 30. ! Delay between SST cycle and solar cycle (in days)
136     C Interactive SST --- not used if PRESC_SST is .TRUE.
137     RELAX_SST = .TRUE. ! SST relaxed to prescribe profile
138     SST_RELAX_TIME = 10.* 86400. !
139     SEA_THICK = 10.d3 !
140     HEATCAPOCEA = 4.d8 !
141    
142     C Interactive STL --- not used if PRESC_STL is .TRUE.
143     HEATCAPLAND = 4.d5 !
144    
145     C Interactive soil moisture --- not used if PRESC_BKT is .TRUE.
146     PRESC_BKT = .FALSE. !
147     BKT0 = 15. !
148    
149     C QFLUX forcing
150     DELL_STAR = 30.
151     DELQ_STAR = 100.
152     QSTAR_BACK = 50.
153     DELL_OCEAN = 20.
154     DELQ_OCEAN = 10.
155     LOW_OCEAN = 120.
156     LOE_OCEAN = 300.
157    
158     C-- Read parameters from open data file
159     READ(UNIT=iUnit,NML=MITPHYS_PARM01)
160     READ(UNIT=iUnit,NML=MITPHYS_PARM02)
161    
162     WRITE(msgBuf,'(A)')
163     & ' MITPHYS_FILT_READPARMS: finished reading data.shap'
164     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
165     & SQUEEZE_RIGHT , 1)
166    
167     write(*,*) 'RADINT =', RADINT,'; CRFINT = ',
168     & CRFINT
169     write(*,*) 'CREARSKY =', CLEARSKY,'; RADFREQ =', RADFREQ
170    
171     write(*,*) 'CD =', CD, '; CDM =', CDM
172     write(*,*) 'CONV_ADJ =', CONV_ADJ, 'PBL_MIX =', PBL_MIX
173     write(*,*) 'WS0 =',WS0, '; K_PBL =', K_PBL
174     write(*,*) ' LOG_CORRECT =', LOG_CORRECT
175     C-- Close the open data file
176     CLOSE(iUnit)
177     _END_MASTER(myThid)
178    
179     C-- Everyone else must wait for the parameters to be loaded
180     _BARRIER
181    
182     #endif /* ALLOW_MITPHYS */
183     RETURN
184     END

  ViewVC Help
Powered by ViewVC 1.1.22