Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:37:25 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
d676f916b2 Jean*0001 #include "AIM_OPTIONS.h"
                0002 
                0003       SUBROUTINE INPHYS (HSG, myThid)
                0004 
                0005       IMPLICIT NONE
                0006 
                0007 C--
                0008 C--   SUBROUTINE INPHYS (HSG,PPL,RLAT)
                0009 C--
                0010 C--   Purpose: Initialize common blocks for physical parametrization routines 
                0011 C--   Input :  HSG  : sigma at half levels
                0012 C--            PPL  : pressure levels for post-processing
                0013 C--            RLAT : gaussian-grid latitudes
                0014 C--   Initialized common blocks: PHYCON, FSIGLT, FORCON,
                0015 C--                              CNVCON, LSCCON, RADCON, SFLCON, VDICON
                0016 C--
                0017 C     Resolution parameters
                0018 
                0019 C-- size for MITgcm & Physics package :
                0020 #include "AIM_SIZE.h" 
                0021 
                0022 #include "GRID.h"
                0023 #include "EEPARAMS.h"
                0024 #include "PARAMS.h"
                0025 
                0026 c #include "AIM_GRID.h"
                0027 
                0028 C     Physical constants + functions of sigma and latitude
                0029 
                0030 #include "com_physcon.h"
                0031 
                0032 C     Constants for sub-grid-scale physics
                0033 
                0034 #include "com_forcon.h"
                0035 #include "com_cnvcon.h"
                0036 #include "com_lsccon.h"
                0037 #include "com_radcon.h"  
                0038 #include "com_sflcon.h"
                0039 #include "com_vdicon.h"  
                0040 
                0041 C     == Routine Arguments ==
                0042       INTEGER myThid
                0043 c     REAL HSG(0:NLEV), PPL(NLEV), RLAT(NLAT)  
                0044       _RL  HSG(0:NLEV)
                0045 
                0046 #ifdef ALLOW_AIM
                0047 
                0048 C     == Local Variables ==
                0049       INTEGER K
                0050 
                0051       _BEGIN_MASTER(myThid)  
                0052 
                0053 C---  1. Time independent parameters and arrays
                0054 C
                0055 C     1.1 Physical constants
                0056 
                0057 c     P0 = 1. _d +5
                0058 c     GG = 9.81 _d 0
                0059 c     RD = 287. _d 0
                0060 c     CP = 1004. _d 0
65007c221b Jean*0061       P0 = atm_Po
d676f916b2 Jean*0062       GG = gravity
65007c221b Jean*0063       RD = atm_Rd
                0064       CP = atm_Cp
d676f916b2 Jean*0065 C     Latent heat is in J/g for consistency with spec.hum. in g/Kg
                0066       ALHC = 2501. _d 0
b3097ed02d Jean*0067       ALHF =  334. _d 0
d676f916b2 Jean*0068       SBC = 5.67 _d -8
b3097ed02d Jean*0069 C     Heat capacity of rain is also in J/g/K for the same reasons
                0070 c     rainCP = HeatCapacity_Cp / 1000. _d 0 
                0071       rainCP = 4200. _d 0 / 1000. _d 0 
                0072       tFreeze= celsius2K
d676f916b2 Jean*0073 C
                0074 C     1.2 Functions of sigma and latitude
                0075 C
                0076       SIGH(0)=HSG(0)
                0077 C
                0078       DO K=1,NLEV
                0079        SIG(K)  = 0.5*(HSG(K)+HSG(K-1))
                0080        SIGL(K) = LOG(SIG(K))
                0081        SIGH(K) = HSG(K)
                0082        DSIG(K) = HSG(K)-HSG(K-1)
                0083 c      POUT(K) = PPL(K)
                0084        GRDSIG(K) = GG/(DSIG(K)*P0)
                0085        GRDSCP(K) = GRDSIG(K)/CP  
                0086       ENDDO
                0087 C
                0088 C     Weights for vertical interpolation at half-levels(1,nlev) and surface
                0089 C     Note that for phys.par. half-lev(k) is between full-lev k and k+1 
                0090 C     Fhalf(k) = Ffull(k)+WVI(K,2)*(Ffull(k+1)-Ffull(k))
                0091 C     Fsurf = Ffull(nlev)+WVI(nlev,2)*(Ffull(nlev)-Ffull(nlev-1))
                0092 C
                0093       DO K=1,NLEV-1
                0094        WVI(K,1)=1./(SIGL(K+1)-SIGL(K))
                0095        WVI(K,2)=(LOG(SIGH(K))-SIGL(K))*WVI(K,1)
                0096       ENDDO
                0097 C
                0098       WVI(NLEV,1)=0.
                0099       WVI(NLEV,2)=-SIGL(NLEV)*WVI(NLEV-1,2)
                0100  
                0101 c--- jmc: write WVI to check:
                0102       WRITE(standardMessageUnit,'(A)')
                0103      &     '- INPHYS: k,SIG, SIGH,   SIGL,   WVI(1),  WVI(2):'
                0104       DO K=1,NLEV
                0105        WRITE(standardMessageUnit,'(I3,6F9.4)') 
                0106      &      k,SIG(k),SIGH(k),SIGL(k),WVI(K,1),WVI(K,2)
                0107       ENDDO
                0108       WRITE(standardMessageUnit,'(A)') '- INPHYS: end setup WVI.'
                0109 c--- jmc.
                0110 
                0111 c- jmc: initialize SLAT & CLAT in aim_dyn2aim.F
                0112 c     DO J=1,NLAT
                0113 c      SLAT(J)=SIN(RLAT(J))
                0114 c      CLAT(J)=COS(RLAT(J))
                0115 c     ENDDO
                0116 
                0117 C--   2. Constants for physical parametrization routines:
                0118  
                0119 c_FM  include "cls_inphys.h"
                0120 #include "phy_const.h"
                0121  
e749d70ece Jean*0122 C-     pot. temp. increment for computing stability function derivative
                0123 C      note: use the discrete form: F(Ts+dTstab)-F(Ts-dTstab)/2.dTstab 
                0124        dTstab = 1. _d 0
                0125 
d676f916b2 Jean*0126       _END_MASTER(myThid)
                0127 
                0128 #endif /* ALLOW_AIM */ 
                0129 
                0130       RETURN
                0131       END