/[MITgcm]/MITgcm/pkg/aim_v23/aim_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/aim_v23/aim_readparms.F

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

revision 1.10 by edhill, Sun Sep 11 04:35:31 2005 UTC revision 1.11 by jmc, Thu Aug 3 21:21:23 2006 UTC
# Line 13  C     *================================= Line 13  C     *=================================
13  C     | S/R AIM_READPARMS  C     | S/R AIM_READPARMS
14  C     | o Read AIM physics package parameters  C     | o Read AIM physics package parameters
15  C     *==========================================================*  C     *==========================================================*
16  C     | Initialized parameter in common blocks:  C     | Initialized parameter in common blocks:
17  C     |  FORCON, SFLCON, CNVCON, LSCCON, RADCON, VDICON  C     |  FORCON, SFLCON, CNVCON, LSCCON, RADCON, VDICON
18  C     *==========================================================*  C     *==========================================================*
19  C     \ev  C     \ev
20    
21  C     !USES:  C     !USES:
22        IMPLICIT NONE        IMPLICIT NONE
23    
# Line 34  C-   Constants for sub-grid-scale physic Line 34  C-   Constants for sub-grid-scale physic
34  #include "com_sflcon.h"  #include "com_sflcon.h"
35  #include "com_cnvcon.h"  #include "com_cnvcon.h"
36  #include "com_lsccon.h"  #include "com_lsccon.h"
37  #include "com_radcon.h"    #include "com_radcon.h"
38  #include "com_vdicon.h"    #include "com_vdicon.h"
39    
40  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
41  C     == Routine Arguments ==        C     == Routine Arguments ==
42  C     myThid -  Number of this instance  C     myThid :: my Thread Id number
43        INTEGER myThid        INTEGER myThid
44  CEOP  CEOP
45    
46  #ifdef ALLOW_AIM  #ifdef ALLOW_AIM
47    
48  C     == Local Variables ==  C     == Local Variables ==
49  C     msgBuf      - Informational/error meesage buffer  C     msgBuf      :: Informational/error meesage buffer
50  C     iUnit       - Work variable for IO unit number  C     iUnit       :: Work variable for IO unit number
51        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
52        INTEGER iUnit        INTEGER iUnit
53    
# Line 76  C     aim_taveFreq :: Frequency^-1 for t Line 76  C     aim_taveFreq :: Frequency^-1 for t
76  C     aim_diagFreq :: Frequency^-1 for diagnostic output (s)  C     aim_diagFreq :: Frequency^-1 for diagnostic output (s)
77  C     aim_tendFreq :: Frequency^-1 for tendencies output (s)  C     aim_tendFreq :: Frequency^-1 for tendencies output (s)
78        NAMELIST /AIM_PARAMS/        NAMELIST /AIM_PARAMS/
79       &    aim_useFMsurfBC, aim_useMMsurfFc,       &    aim_useFMsurfBC, aim_useMMsurfFc,
80       &    aim_surfPotTemp, aim_energPrecip, aim_splitSIOsFx,       &    aim_surfPotTemp, aim_energPrecip, aim_splitSIOsFx,
81       &    aim_MMsufx, aim_MMsufxLength,       &    aim_MMsufx, aim_MMsufxLength,
82       &    aim_LandFile, aim_albFile, aim_vegFile,       &    aim_LandFile, aim_albFile, aim_vegFile,
# Line 111  C      hSnowWetness :: snow depth (m) co Line 111  C      hSnowWetness :: snow depth (m) co
111       &    SOLC, ALBSEA, ALBICE, ALBSN,       &    SOLC, ALBSEA, ALBICE, ALBSN,
112       &    SDALB, SWCAP, SWWIL, hSnowWetness       &    SDALB, SWCAP, SWWIL, hSnowWetness
113    
114  C--   Constants for surface fluxes (common SFLCON) :  C--   Constants for surface fluxes (common SFLCON) :
115  C      FWIND0 = ratio of near-sfc wind to lowest-level wind  C      FWIND0 = ratio of near-sfc wind to lowest-level wind
116  C      FTEMP0 = weight for near-sfc temperature extrapolation (0-1) :  C      FTEMP0 = weight for near-sfc temperature extrapolation (0-1) :
117  C               1 : linear extrapolation from two lowest levels  C               1 : linear extrapolation from two lowest levels
# Line 147  C      SMF    = ratio between secondary Line 147  C      SMF    = ratio between secondary
147       &    PSMIN, TRCNV, QBL, RHBL, RHIL, ENTMAX, SMF       &    PSMIN, TRCNV, QBL, RHBL, RHIL, ENTMAX, SMF
148    
149    
150  C--   Constants for large-scale condendation (common LSCCON) :  C--   Constants for large-scale condendation (common LSCCON) :
151  C      TRLSC  = Relaxation time (in hours) for specific humidity  C      TRLSC  = Relaxation time (in hours) for specific humidity
152  C      RHLSC  = Maximum relative humidity threshold (at sigma=1)  C      RHLSC  = Maximum relative humidity threshold (at sigma=1)
153  C      DRHLSC = Vertical range of relative humidity threshold  C      DRHLSC = Vertical range of relative humidity threshold
# Line 182  C      ABLCL2 = abs. of clouds       in Line 182  C      ABLCL2 = abs. of clouds       in
182       &    RHCL1,  RHCL2,  QACL1,  QACL2,  ALBCL,       &    RHCL1,  RHCL2,  QACL1,  QACL2,  ALBCL,
183       &    EPSSW,  EPSLW,  EMISFC,       &    EPSSW,  EPSLW,  EMISFC,
184       &    ABSDRY, ABSAER, ABSWV1, ABSWV2, ABSCL1, ABSCL2,       &    ABSDRY, ABSAER, ABSWV1, ABSWV2, ABSCL1, ABSCL2,
185       &    ABLWIN, ABLCO2, ABLWV1, ABLWV2, ABLCL1, ABLCL2       &    ABLWIN, ABLCO2, ABLWV1, ABLWV2, ABLCL1, ABLCL2
186    
187  C--   Constants for vertical dif. and sh. conv. (common VDICON) :  C--   Constants for vertical dif. and sh. conv. (common VDICON) :
188  C      TRSHC  = relaxation time (in hours) for shallow convection  C      TRSHC  = relaxation time (in hours) for shallow convection
189  C      TRVDI  = relaxation time (in hours) for moisture diffusion  C      TRVDI  = relaxation time (in hours) for moisture diffusion
190  C      TRVDS  = relaxation time (in hours) for super-adiab. conditions  C      TRVDS  = relaxation time (in hours) for super-adiab. conditions
# Line 196  C      SEGRAD = minimum gradient of dry Line 196  C      SEGRAD = minimum gradient of dry
196  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
197    
198        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
199          
200        WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'        WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'
201        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
202    
# Line 213  C-    Constants for boundary forcing Line 213  C-    Constants for boundary forcing
213    
214  C-    Constants for surface fluxes  C-    Constants for surface fluxes
215        READ(UNIT=iUnit,NML=AIM_PAR_SFL)        READ(UNIT=iUnit,NML=AIM_PAR_SFL)
216    
217  C-    Constants for convection  C-    Constants for convection
218        READ(UNIT=iUnit,NML=AIM_PAR_CNV)        READ(UNIT=iUnit,NML=AIM_PAR_CNV)
219    
# Line 226  C-    Constants for radiation Line 226  C-    Constants for radiation
226  C-    Constants for vertical diffusion and sh. conv.  C-    Constants for vertical diffusion and sh. conv.
227        READ(UNIT=iUnit,NML=AIM_PAR_VDI)        READ(UNIT=iUnit,NML=AIM_PAR_VDI)
228    
229        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
230       &   ' AIM_READ_PHYSPARMS: finished reading data.aimphys'       &   ' AIM_READ_PHYSPARMS: finished reading data.aimphys'
231        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
232    
233  C--   Close the open data file  C--   Close the open data file
234        CLOSE(iUnit)        CLOSE(iUnit)
235    
# Line 263  C-    If aim_taveFreq is positive, then Line 263  C-    If aim_taveFreq is positive, then
263  #endif /* ALLOW_AIM_TAVE */  #endif /* ALLOW_AIM_TAVE */
264    
265  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
266        aim_timeave_mnc      =        aim_timeave_mnc        = useMNC .AND. aim_timeave_mnc
267       &     aim_timeave_mnc .AND. useMNC        aim_snapshot_mnc       = useMNC .AND. aim_snapshot_mnc
268        aim_snapshot_mnc     =        aim_pickup_write_mnc   = useMNC .AND. aim_pickup_write_mnc
269       &     aim_snapshot_mnc .AND. useMNC        aim_pickup_read_mnc    = useMNC .AND. aim_pickup_read_mnc
270        aim_pickup_write_mnc =  #else /* ALLOW_MNC */
      &     aim_pickup_write_mnc .AND. useMNC  
       aim_pickup_read_mnc  =  
      &     aim_pickup_read_mnc .AND. useMNC  
   
       aim_timeave_mdsio      = (.NOT. aim_timeave_mnc)  
      &     .OR. outputTypesInclusive  
       aim_snapshot_mdsio     = (.NOT. aim_snapshot_mnc)  
      &     .OR. outputTypesInclusive  
       aim_pickup_write_mdsio = (.NOT. aim_pickup_write_mnc)  
      &     .OR. outputTypesInclusive  
       aim_pickup_read_mdsio  = (.NOT. aim_pickup_read_mnc)  
      &     .OR. outputTypesInclusive  
 #else  
 C     Stop if MNC is not compiled-in and aim_*_mnc=.TRUE.  
       IF ( aim_timeave_mnc .OR. aim_snapshot_mnc  
      &     .OR. aim_pickup_write_mnc .OR. aim_pickup_read_mnc ) THEN  
         WRITE(msgBuf,'(2A)')  
      &       'AIM_READPARMS: one or more aim_*_mnc vars is .TRUE. ',  
      &       'but ALLOW_MNC is undefined'  
         CALL PRINT_ERROR( msgBuf, myThid)  
         WRITE(msgBuf,'(2A)') 'Please re-compile with the MNC ',  
      &       'package enabled'  
         CALL PRINT_ERROR( msgBuf, myThid)  
         STOP 'ABNORMAL END: S/R AIM_READPARMS'  
       ENDIF  
271        aim_timeave_mnc        = .FALSE.        aim_timeave_mnc        = .FALSE.
272        aim_snapshot_mnc       = .FALSE.        aim_snapshot_mnc       = .FALSE.
273        aim_pickup_write_mnc   = .FALSE.        aim_pickup_write_mnc   = .FALSE.
274        aim_pickup_read_mnc    = .FALSE.        aim_pickup_read_mnc    = .FALSE.
       aim_timeave_mdsio      = .TRUE.  
       aim_snapshot_mdsio     = .TRUE.  
       aim_pickup_write_mdsio = .TRUE.  
       aim_pickup_read_mdsio  = .TRUE.  
275  #endif /* ALLOW_MNC */  #endif /* ALLOW_MNC */
276          aim_snapshot_mnc       = .FALSE.
277    C jmc: temporary turn off aim_snapshot_mnc, until the 2 Pbs get fixed:
278    C     1) multi-tiles set-up, files "aim_state.t*.nc" are all identical
279    C     2) error when writing "aim_tend": "vtype 'aim_dT_RSW' is not defined"
280          aim_timeave_mdsio      = (.NOT. aim_timeave_mnc)
281         &                     .OR. outputTypesInclusive
282          aim_snapshot_mdsio     = (.NOT. aim_snapshot_mnc)
283         &                     .OR. outputTypesInclusive
284          aim_pickup_write_mdsio = (.NOT. aim_pickup_write_mnc)
285         &                     .OR. outputTypesInclusive
286          aim_pickup_read_mdsio  = (.NOT. aim_pickup_read_mnc)
287         &                     .OR. outputTypesInclusive
288    
289    
290  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 318  C--   Print out parameter values : Line 301  C--   Print out parameter values :
301    
302         CALL WRITE_0D_L( useLand, INDEX_NONE,         CALL WRITE_0D_L( useLand, INDEX_NONE,
303       &                 'useLand =',       &                 'useLand =',
304       &'   /* use Land package for surf.BC over land  */')             &'   /* use Land package for surf.BC over land  */')
305    
306  C- namelist AIM_PARAMS:  C- namelist AIM_PARAMS:
307         CALL WRITE_0D_L( aim_useFMsurfBC, INDEX_NONE,         CALL WRITE_0D_L( aim_useFMsurfBC, INDEX_NONE,
308       &                 'aim_useFMsurfBC =',       &                 'aim_useFMsurfBC =',
309       &'   /* F.Molteni surf. BC scheme on/off flag */')             &'   /* F.Molteni surf. BC scheme on/off flag */')
310         CALL WRITE_0D_L( aim_useMMsurfFc, INDEX_NONE,         CALL WRITE_0D_L( aim_useMMsurfFc, INDEX_NONE,
311       &                 'aim_useMMsurfFc =',       &                 'aim_useMMsurfFc =',
312       &'   /* Monthly Mean surf. Forcing on/off flag */')             &'   /* Monthly Mean surf. Forcing on/off flag */')
313         CALL WRITE_0D_L( aim_surfPotTemp, INDEX_NONE,         CALL WRITE_0D_L( aim_surfPotTemp, INDEX_NONE,
314       &                 'aim_surfPotTemp =',       &                 'aim_surfPotTemp =',
315       &'   /* Surf Temp file in Pot.Temp on/off flag */')             &'   /* Surf Temp file in Pot.Temp on/off flag */')
316         CALL WRITE_0D_L( aim_energPrecip, INDEX_NONE,         CALL WRITE_0D_L( aim_energPrecip, INDEX_NONE,
317       &                 'aim_energPrecip =',       &                 'aim_energPrecip =',
318       &  ' /* account for energy of precip. on/off flag */')             &  ' /* account for energy of precip. on/off flag */')
319         CALL WRITE_0D_L( aim_splitSIOsFx, INDEX_NONE,         CALL WRITE_0D_L( aim_splitSIOsFx, INDEX_NONE,
320       &                 'aim_splitSIOsFx =',       &                 'aim_splitSIOsFx =',
321       &  ' /* separate Sea-Ice & Ocean Flux on/off flag */')             &  ' /* separate Sea-Ice & Ocean Flux on/off flag */')
322         CALL WRITE_0D_R8(aim_dragStrato,INDEX_NONE,'aim_dragStrato=',         CALL WRITE_0D_R8(aim_dragStrato,INDEX_NONE,'aim_dragStrato=',
323       &    ' /* stratospheric-drag damping time scale (s) */')       &    ' /* stratospheric-drag damping time scale (s) */')
324         CALL WRITE_0D_L( aim_clrSkyDiag, INDEX_NONE,         CALL WRITE_0D_L( aim_clrSkyDiag, INDEX_NONE,
325       &                 'aim_clrSkyDiag =',       &                 'aim_clrSkyDiag =',
326       &  ' /* do clear-sky radiation diagnostics */')             &  ' /* do clear-sky radiation diagnostics */')
327         CALL WRITE_0D_R8( aim_taveFreq, INDEX_NONE,'aim_taveFreq =',         CALL WRITE_0D_R8( aim_taveFreq, INDEX_NONE,'aim_taveFreq =',
328       &  '   /* Frequency^-1 for time-Aver. output (s) */')       &  '   /* Frequency^-1 for time-Aver. output (s) */')
329         CALL WRITE_0D_R8( aim_diagFreq, INDEX_NONE,'aim_diagFreq =',         CALL WRITE_0D_R8( aim_diagFreq, INDEX_NONE,'aim_diagFreq =',
# Line 435  C- namelist AIM_PAR_RAD: Line 418  C- namelist AIM_PAR_RAD:
418         CALL WRITE_0D_R8( ALBCL, INDEX_NONE,'AIM_RAD:  ALBCL =',         CALL WRITE_0D_R8( ALBCL, INDEX_NONE,'AIM_RAD:  ALBCL =',
419       &  '   /*  cloud albedo (for cloud cover = 1) */')       &  '   /*  cloud albedo (for cloud cover = 1) */')
420         CALL WRITE_0D_R8( EPSSW, INDEX_NONE,'AIM_RAD:  EPSSW =',         CALL WRITE_0D_R8( EPSSW, INDEX_NONE,'AIM_RAD:  EPSSW =',
421       &  '   /*  fract. of inc.solar rad. absorbed by ozone */')         &  '   /*  fract. of inc.solar rad. absorbed by ozone */')
422         CALL WRITE_0D_R8( EPSLW, INDEX_NONE,'AIM_RAD:  EPSLW =',         CALL WRITE_0D_R8( EPSLW, INDEX_NONE,'AIM_RAD:  EPSLW =',
423       &  '   /*  fract. of sfc LW emitted directly to space */')         &  '   /*  fract. of sfc LW emitted directly to space */')
424         CALL WRITE_0D_R8( EMISFC,INDEX_NONE,'AIM_RAD: EMISFC =',         CALL WRITE_0D_R8( EMISFC,INDEX_NONE,'AIM_RAD: EMISFC =',
425       &  '   /*  longwave surface emissivity */')         &  '   /*  longwave surface emissivity */')
426    
427         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
428       &  ' AIM_RAD : ShortWave absorptivities (for dp = 10^5 Pa) :'       &  ' AIM_RAD : ShortWave absorptivities (for dp = 10^5 Pa) :'
# Line 487  C- namelist AIM_PAR_VDI: Line 470  C- namelist AIM_PAR_VDI:
470  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
471    
472        _END_MASTER(myThid)        _END_MASTER(myThid)
473    
474  C--   Everyone else must wait for the parameters to be loaded  C--   Everyone else must wait for the parameters to be loaded
475        _BARRIER        _BARRIER
476    

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22