/[MITgcm]/MITgcm/pkg/thsice/thsice_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/thsice/thsice_readparms.F

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

revision 1.1 by jmc, Sun Nov 23 01:20:13 2003 UTC revision 1.16 by jmc, Wed Jul 8 23:35:05 2009 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "THSICE_OPTIONS.h"  #include "THSICE_OPTIONS.h"
5    
6    CBOP
7    C     !ROUTINE: THSICE_READPARMS
8    C     !INTERFACE:
9        SUBROUTINE THSICE_READPARMS( myThid )        SUBROUTINE THSICE_READPARMS( myThid )
10  C     /==========================================================*  
11  C     | SUBROUTINE THSICE_READPARMS  C     !DESCRIPTION: \bv
12    C     *==========================================================*
13    C     | S/R THSICE_READPARMS
14  C     | o Routine to initialize THSICE parameters and constants  C     | o Routine to initialize THSICE parameters and constants
15  C     |==========================================================*  C     *==========================================================*
16  C     | Initialize Th-Sea-ICE parameters, read in data.ice  C     | Initialize Th-Sea-ICE parameters, read in data.ice
17  C     \==========================================================*  C     *==========================================================*
18    C     \ev
19    
20    C     !USES:
21        IMPLICIT NONE        IMPLICIT NONE
22    
23  C     === Global variables ===  C     === Global variables ===
# Line 18  C     === Global variables === Line 26  C     === Global variables ===
26  #include "PARAMS.h"  #include "PARAMS.h"
27  #include "GRID.h"  #include "GRID.h"
28  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
29  c #include "THSICE.h"  #ifdef ALLOW_MNC
30    #include "MNC_PARAMS.h"
31    #endif
32    
33    C     !INPUT/OUTPUT PARAMETERS:
34  C     === Routine arguments ===  C     === Routine arguments ===
35    C     myThid    :: My Thread Id. number
36        INTEGER myThid        INTEGER myThid
37    CEOP
38    
39  #ifdef ALLOW_THSICE  #ifdef ALLOW_THSICE
40    
41  C     === Local variables ===  C     === Local variables ===
42  C     msgBuf      - Informational/error meesage buffer  C     msgBuf    :: Informational/error message buffer
43  C     iUnit       - Work variable for IO unit number  C     iUnit     :: Work variable for IO unit number
44        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
45        INTEGER iUnit        INTEGER iUnit
46    
47  C--   Th-Sea-ICE parameter  C--   Th-Sea-ICE parameter
48        NAMELIST /THSICE_CONST/        NAMELIST /THSICE_CONST/
49       &  rhos, rhoi, rhosw, rhofw,       &  rhos, rhoi, rhosw, rhofw,
50       &  cpice, cpwater,       &  cpIce, cpWater,
51       &  kice, ksnow,       &  kIce, kSnow,
52       &  transcoef, Lfresh, qsnow,       &  bMeltCoef, Lfresh, qsnow,
53       &  albsnodry, albsnowet, albicemax, albicemin, halb,       &  albColdSnow, albWarmSnow, tempSnowAlb,
54       &  i0, ksolar,       &  albOldSnow, hNewSnowAge, snowAgTime,
55       &  saltice, S_winton, mu_Tf,       &  albIceMax, albIceMin, hAlbIce, hAlbSnow,
56       &  Tf0kel,       &  i0swFrac, ksolar, dhSnowLin,
57       &  himin, Terrmax, nitMaxTsf, hiMax, hsMax,       &  saltIce, S_winton, mu_Tf,
58       &  iceMaskmax, iceMaskmin, himin0,       &  Tf0kel, Terrmax, nitMaxTsf,
59       &  frac_energy, hihig       &  hIceMin, hiMax, hsMax, iceMaskMax, iceMaskMin,
60         &  fracEnMelt, fracEnFreez, hThinIce, hThickIce, hNewIceMax
61    
62        NAMELIST /THSICE_PARM01/        NAMELIST /THSICE_PARM01/
63       &         startIceModel,       &     startIceModel, stepFwd_oceMxL, thSIce_calc_albNIR,
64       &         thSIce_deltaT,       &     thSIce_deltaT, thSIce_dtTemp,
65       &         stressReduction,       &     ocean_deltaT, tauRelax_MxL,
66       &         thSIce_taveFreq, thSIce_diagFreq, thSIce_monFreq       &     hMxL_default, sMxL_default, vMxL_default,
67         &     thSIce_diffK, thSIceAdvScheme, stressReduction,
68         &     thSIce_taveFreq, thSIce_diagFreq, thSIce_monFreq,
69         &     thSIce_tave_mnc, thSIce_snapshot_mnc, thSIce_mon_mnc,
70         &     thSIce_pickup_read_mnc, thSIce_pickup_write_mnc,
71         &     thSIceFract_InitFile, thSIceThick_InitFile,
72         &     thSIceSnowH_InitFile, thSIceSnowA_InitFile,
73         &     thSIceEnthp_InitFile, thSIceTsurf_InitFile
74    
75        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
76    
77        WRITE(msgBuf,'(A)') ' THSICE_READPARMS: opening data.ice'        WRITE(msgBuf,'(A)') ' THSICE_READPARMS: opening data.ice'
78        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
79       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
80        
81        CALL OPEN_COPY_DATA_FILE(        CALL OPEN_COPY_DATA_FILE(
82       I                          'data.ice', 'THSICE_READPARMS',       I                          'data.ice', 'THSICE_READPARMS',
83       O                          iUnit,       O                          iUnit,
# Line 67  C--   Default values (constants) Line 88  C--   Default values (constants)
88        rhoi     = 900. _d 0        rhoi     = 900. _d 0
89        rhosw    = rhoConst        rhosw    = rhoConst
90        rhofw    = rhoConstFresh        rhofw    = rhoConstFresh
91        cpice    = 2106. _d 0        cpIce    = 2106. _d 0
92        cpwater  = HeatCapacity_Cp        cpWater  = HeatCapacity_Cp
93        kice     = 2.03 _d 0        kIce     = 2.03 _d 0
94        ksnow    = 0.30 _d 0        kSnow    = 0.30 _d 0
95        transcoef=0.006 _d 0        bMeltCoef=0.006 _d 0
96        Lfresh   = 3.34 _d 5        Lfresh   = 3.34 _d 5
97        qsnow    = Lfresh        qsnow    = Lfresh
98        albsnodry= 0.85 _d 0        albColdSnow= 0.85 _d 0
99        albsnowet= 0.75 _d 0        albWarmSnow= 0.70 _d 0
100        albicemax= 0.65 _d 0        tempSnowAlb= -10. _d 0
101        albicemin= 0.20 _d 0        albOldSnow = 0.55 _d 0
102        halb     = 0.5 _d 0        albIceMax  = 0.65 _d 0
103        i0       = 0.3 _d 0        albIceMin  = 0.20 _d 0
104          hAlbIce    = 0.50 _d 0
105          hAlbSnow   = 0.30 _d 0
106          hNewSnowAge= 2. _d -3
107          snowAgTime = 50. _d 0 * 86400. _d 0
108          i0swFrac = 0.3 _d 0
109        ksolar   = 1.5 _d 0        ksolar   = 1.5 _d 0
110        saltice  = 4. _d 0        dhSnowLin= 0. _d 0
111          saltIce  = 4. _d 0
112        S_winton = 1. _d 0        S_winton = 1. _d 0
113        mu_Tf    = 0.054 _d 0        mu_Tf    = 0.054 _d 0
114        Tf0kel   = celsius2K        Tf0kel   = celsius2K
       himin    = 0.01 _d 0  
115        Terrmax  = 5.0 _d -1        Terrmax  = 5.0 _d -1
116        nitMaxTsf= 20        nitMaxTsf= 20
117          hIceMin    = 1. _d -2
118        hiMax      = 10. _d 0        hiMax      = 10. _d 0
119        hsMax      = 10. _d 0        hsMax      = 10. _d 0
120        iceMaskmax = 1.  _d 0        iceMaskMax =  1. _d 0
121        iceMaskmin =  .1 _d 0        iceMaskMin = 0.1 _d 0
122        himin0     = 0.2 _d 0        fracEnMelt = 0.4 _d 0
123        frac_energy=  .4 _d 0        fracEnFreez=  0. _d 0
124        hihig      = 2.5 _d 0        hThinIce   = 0.2 _d 0
125          hThickIce  = 2.5 _d 0
126          hNewIceMax = UNSET_RL
127    
128  C--   Default values (parameters)  C--   Default values (parameters)
129        startIceModel  = 0        stepFwd_oceMxL  = .FALSE.
130        thSIce_deltaT   = deltaTtracer        thSIce_calc_albNIR  = .FALSE.
131          startIceModel   = 0
132          thSIce_deltaT   = dTtracerLev(1)
133          thSIce_dtTemp  = UNSET_RL
134          ocean_deltaT    = dTtracerLev(1)
135          tauRelax_MxL    = 0. _d 0
136          hMxL_default    = 50. _d 0
137          sMxL_default    = 35. _d 0
138          vMxL_default    = 5. _d -2
139          thSIce_diffK    = 0. _d 0
140          thSIceAdvScheme = 0
141        stressReduction = 1. _d 0        stressReduction = 1. _d 0
142        thSIce_taveFreq = taveFreq        IF ( useSEAICE ) stressReduction = 0. _d 0
143          thSIce_taveFreq = taveFreq
144        thSIce_diagFreq = dumpFreq        thSIce_diagFreq = dumpFreq
145        thSIce_monFreq  = monitorFreq        thSIce_monFreq  = monitorFreq
146    #ifdef ALLOW_MNC
147          thSIce_tave_mnc     = timeave_mnc
148          thSIce_snapshot_mnc = snapshot_mnc
149          thSIce_mon_mnc      = monitor_mnc
150          thSIce_pickup_read_mnc  = pickup_read_mnc
151          thSIce_pickup_write_mnc = pickup_write_mnc
152    #else
153          thSIce_tave_mnc     = .FALSE.
154          thSIce_snapshot_mnc = .FALSE.
155          thSIce_mon_mnc      = .FALSE.
156          thSIce_pickup_read_mnc  = .FALSE.
157          thSIce_pickup_write_mnc = .FALSE.
158    #endif
159          thSIceFract_InitFile = ' '
160          thSIceThick_InitFile = ' '
161          thSIceSnowH_InitFile = ' '
162          thSIceSnowA_InitFile = ' '
163          thSIceEnthp_InitFile = ' '
164          thSIceTsurf_InitFile = ' '
165    
166    
167  C--   Read parameters from open data file  C--   Read parameters from open data file
168        READ(UNIT=iUnit,NML=THSICE_CONST)        READ(UNIT=iUnit,NML=THSICE_CONST)
# Line 118  C--   Read parameters from open data fil Line 178  C--   Read parameters from open data fil
178  C--   Close the open data file  C--   Close the open data file
179        CLOSE(iUnit)        CLOSE(iUnit)
180    
181    C-    neutral default:
182          IF ( hNewIceMax .EQ. UNSET_RL ) hNewIceMax = hiMax
183    
184    C     If using the same time step for both icetop temp solver
185    C     and ice thickness/growth, use thSIce_deltaT value
186          IF ( thSIce_dtTemp .EQ. UNSET_RL ) thSIce_dtTemp=thSIce_deltaT
187    
188  C-    Define other constants (from previous ones):  C-    Define other constants (from previous ones):
189        Tmlt1=-mu_Tf*S_winton        Tmlt1=-mu_Tf*S_winton
190        rhoiw = rhosw - rhoi        floodFac = (rhosw - rhoi)/rhos
191    
192    C     Set I/O parameters
193          thSIce_tave_mdsio     = .TRUE.
194          thSIce_snapshot_mdsio = .TRUE.
195          thSIce_mon_stdio      = .TRUE.
196          thSIce_pickup_write_mdsio = .TRUE.
197    #ifdef ALLOW_MNC
198          IF (useMNC) THEN
199            IF ( .NOT.outputTypesInclusive
200         &       .AND. thSIce_tave_mnc ) thSIce_tave_mdsio = .FALSE.
201            IF ( .NOT.outputTypesInclusive
202         &       .AND. thSIce_snapshot_mnc )
203         &       thSIce_snapshot_mdsio = .FALSE.
204            IF ( .NOT.outputTypesInclusive
205         &       .AND. thSIce_mon_mnc  ) thSIce_mon_stdio  = .FALSE.
206            IF ( .NOT.outputTypesInclusive
207         &       .AND. thSIce_pickup_write_mnc  )
208         &       thSIce_pickup_write_mdsio = .FALSE.
209          ENDIF
210    #endif
211    
212    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
213    C--   Check parameter consistency:
214          IF ( thSIceAdvScheme.EQ.0 .AND. thSIce_diffK.NE.0. ) THEN
215            WRITE(msgBuf,'(2A)')
216         &   'THSICE_READPARMS: to use thSIce_diffK, needs to select',
217         &   ' one advection scheme (thSIceAdvScheme<>0)'
218            CALL PRINT_ERROR( msgBuf , myThid )
219            STOP 'ABNORMAL END: THSICE_READPARMS'
220          ENDIF
221    #ifndef ALLOW_GENERIC_ADVDIFF
222          IF ( thSIceAdvScheme.NE.0 ) THEN
223            WRITE(msgBuf,'(2A)')
224         &   'THSICE_READPARMS: Need to compile "generic_advdiff" pkg',
225         &   ' in order to use thSIceAdvScheme'
226            CALL PRINT_ERROR( msgBuf , myThid )
227            STOP 'ABNORMAL END: THSICE_READPARMS'
228          ENDIF
229    #endif /* ndef ALLOW_GENERIC_ADVDIFF */
230    
231          IF ( useSEAICE .AND. stressReduction.NE.0. _d 0 ) THEN
232    C--     If useSEAICE=.true., the stress is computed in seaice_model,
233    C--     so that it does not need any further reduction
234            WRITE(msgBuf,'(2A)')
235         &   'THSICE_READPARMS: if useSEAICE, stress will be computed',
236         &   ' by SEAICE pkg => no reduction'
237            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
238         &                    SQUEEZE_RIGHT , myThid)
239            WRITE(msgBuf,'(A)')
240         &   'THSICE_READPARMS: WARNING: reset stressReduction to zero'
241            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
242         &                    SQUEEZE_RIGHT , myThid)
243            stressReduction = 0. _d 0
244          ENDIF
245    
246  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
247        iUnit = standardMessageUnit        iUnit = standardMessageUnit
248  c     iUnit = 88  c     CALL MDSFINDUNIT( iUnit, mythid )
249  c     OPEN(iUnit,file='thsice_check_params',status='unknown')  c     OPEN(iUnit,file='thsice_check_params',status='unknown')
250        WRITE(iUnit,*) 'ThSI: rhos    =',rhos        WRITE(iUnit,*) 'ThSI: rhos      =',rhos
251        WRITE(iUnit,*) 'ThSI: rhoi    =',rhoi        WRITE(iUnit,*) 'ThSI: rhoi      =',rhoi
252        WRITE(iUnit,*) 'ThSI: rhosw   =',rhosw        WRITE(iUnit,*) 'ThSI: rhosw     =',rhosw
253        WRITE(iUnit,*) 'ThSI: rhofw   =',rhofw        WRITE(iUnit,*) 'ThSI: rhofw     =',rhofw
254        WRITE(iUnit,*) 'ThSI: rhoiw   =',rhoiw        WRITE(iUnit,*) 'ThSI: floodFac  =',floodFac
255        WRITE(iUnit,*) 'ThSI: cpice   =',cpice        WRITE(iUnit,*) 'ThSI: cpIce     =',cpIce
256        WRITE(iUnit,*) 'ThSI: cpwater =',cpwater        WRITE(iUnit,*) 'ThSI: cpWater   =',cpWater
257        WRITE(iUnit,*) 'ThSI: kice    =',kice        WRITE(iUnit,*) 'ThSI: kIce      =',kIce
258        WRITE(iUnit,*) 'ThSI: ksnow   =',ksnow        WRITE(iUnit,*) 'ThSI: kSnow     =',kSnow
259        WRITE(iUnit,*) 'ThSI: transcoef=',transcoef        WRITE(iUnit,*) 'ThSI: bMeltCoef =',bMeltCoef
260        WRITE(iUnit,*) 'ThSI: Lfresh  =',Lfresh        WRITE(iUnit,*) 'ThSI: Lfresh    =',Lfresh
261        WRITE(iUnit,*) 'ThSI: qsnow   =',qsnow        WRITE(iUnit,*) 'ThSI: qsnow     =',qsnow
262        WRITE(iUnit,*) 'ThSI: albsnodry=',albsnodry        WRITE(iUnit,*) 'ThSI: albColdSnow=',albColdSnow
263        WRITE(iUnit,*) 'ThSI: albsnowet=',albsnowet        WRITE(iUnit,*) 'ThSI: albWarmSnow=',albWarmSnow
264        WRITE(iUnit,*) 'ThSI: albicemax=',albicemax        WRITE(iUnit,*) 'ThSI: tempSnowAlb=',tempSnowAlb
265        WRITE(iUnit,*) 'ThSI: albicemin=',albicemin        WRITE(iUnit,*) 'ThSI: albOldSnow =',albOldSnow
266        WRITE(iUnit,*) 'ThSI: halb    =',halb        WRITE(iUnit,*) 'ThSI: hNewSnowAge=',hNewSnowAge
267        WRITE(iUnit,*) 'ThSI: i0      =',i0        WRITE(iUnit,*) 'ThSI: snowAgTime =',snowAgTime
268        WRITE(iUnit,*) 'ThSI: ksolar  =',ksolar        WRITE(iUnit,*) 'ThSI: albIceMax =',albIceMax
269        WRITE(iUnit,*) 'ThSI: saltice =',saltice        WRITE(iUnit,*) 'ThSI: albIceMin =',albIceMin
270        WRITE(iUnit,*) 'ThSI: S_winton=',S_winton        WRITE(iUnit,*) 'ThSI: hAlbIce   =',hAlbIce
271        WRITE(iUnit,*) 'ThSI: mu_Tf   =',mu_Tf        WRITE(iUnit,*) 'ThSI: hAlbSnow  =',hAlbSnow
272        WRITE(iUnit,*) 'ThSI: Tf0kel  =',Tf0kel        WRITE(iUnit,*) 'ThSI: i0swFrac  =',i0swFrac
273        WRITE(iUnit,*) 'ThSI: Tmlt1   =',Tmlt1        WRITE(iUnit,*) 'ThSI: ksolar    =',ksolar
274        WRITE(iUnit,*) 'ThSI: himin   =',himin        WRITE(iUnit,*) 'ThSI: dhSnowLin =',dhSnowLin
275        WRITE(iUnit,*) 'ThSI: Terrmax =',Terrmax        WRITE(iUnit,*) 'ThSI: saltIce   =',saltIce
276        WRITE(iUnit,*) 'ThSI: nitMaxTsf=',nitMaxTsf        WRITE(iUnit,*) 'ThSI: S_winton  =',S_winton
277        WRITE(iUnit,*) 'ThSI: hiMax   =',hiMax        WRITE(iUnit,*) 'ThSI: mu_Tf     =',mu_Tf
278        WRITE(iUnit,*) 'ThSI: hsMax   =',hsMax        WRITE(iUnit,*) 'ThSI: Tf0kel    =',Tf0kel
279        WRITE(iUnit,*) 'ThSI: iceMaskmax=',iceMaskmax        WRITE(iUnit,*) 'ThSI: Tmlt1     =',Tmlt1
280        WRITE(iUnit,*) 'ThSI: iceMaskmin=',iceMaskmin        WRITE(iUnit,*) 'ThSI: Terrmax   =',Terrmax
281        WRITE(iUnit,*) 'ThSI: himin0  =',himin0        WRITE(iUnit,*) 'ThSI: nitMaxTsf =',nitMaxTsf
282        WRITE(iUnit,*) 'ThSI: frac_energy',frac_energy        WRITE(iUnit,*) 'ThSI: hIceMin   =',hIceMin
283        WRITE(iUnit,*) 'ThSI: hihig   =',hihig        WRITE(iUnit,*) 'ThSI: hiMax     =',hiMax
284          WRITE(iUnit,*) 'ThSI: hsMax     =',hsMax
285          WRITE(iUnit,*) 'ThSI: iceMaskMax =',iceMaskMax
286          WRITE(iUnit,*) 'ThSI: iceMaskMin =',iceMaskMin
287          WRITE(iUnit,*) 'ThSI: fracEnMelt =',fracEnMelt
288          WRITE(iUnit,*) 'ThSI: fracEnFreez=',fracEnFreez
289          WRITE(iUnit,*) 'ThSI: hThinIce   =',hThinIce
290          WRITE(iUnit,*) 'ThSI: hThickIce  =',hThickIce
291          WRITE(iUnit,*) 'ThSI: hNewIceMax =',hNewIceMax
292        WRITE(iUnit,*) 'ThSI: stressReduction =',stressReduction        WRITE(iUnit,*) 'ThSI: stressReduction =',stressReduction
293        WRITE(iUnit,*) 'ThSI: thSIce_deltaT  =',thSIce_deltaT        WRITE(iUnit,*) 'ThSI: thSIceAdvScheme =',thSIceAdvScheme
294          WRITE(iUnit,*) 'ThSI: thSIce_diffK  =',thSIce_diffK
295          WRITE(iUnit,*) 'ThSI: thSIce_deltaT =',thSIce_deltaT
296          WRITE(iUnit,*) 'ThSI: ocean_deltaT  =',ocean_deltaT
297          WRITE(iUnit,*) 'ThSI: stepFwd_oceMxL=',stepFwd_oceMxL
298          WRITE(iUnit,*) 'ThSI: tauRelax_MxL  =',tauRelax_MxL
299          WRITE(iUnit,*) 'ThSI: hMxL_default  =',hMxL_default
300          WRITE(iUnit,*) 'ThSI: sMxL_default  =',sMxL_default
301          WRITE(iUnit,*) 'ThSI: vMxL_default  =',vMxL_default
302        WRITE(iUnit,*) 'ThSI: thSIce_taveFreq=',thSIce_taveFreq        WRITE(iUnit,*) 'ThSI: thSIce_taveFreq=',thSIce_taveFreq
303        WRITE(iUnit,*) 'ThSI: thSIce_diagFreq=',thSIce_diagFreq        WRITE(iUnit,*) 'ThSI: thSIce_diagFreq=',thSIce_diagFreq
304        WRITE(iUnit,*) 'ThSI: thSIce_monFreq =',thSIce_monFreq        WRITE(iUnit,*) 'ThSI: thSIce_monFreq =',thSIce_monFreq
305        WRITE(iUnit,*) 'ThSI: startIceModel =',startIceModel        WRITE(iUnit,*) 'ThSI: startIceModel =',startIceModel
306        IF (iUnit.EQ.88) CLOSE(iUnit)        IF (iUnit.NE.standardMessageUnit) CLOSE(iUnit)
307  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
308    
309        _END_MASTER(myThid)        _END_MASTER(myThid)

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22