source: dynamico_lmdz/simple_physics/phyparam/physics/iniphyparam_mod.F90 @ 4225

Last change on this file since 4225 was 4223, checked in by dubos, 6 years ago

simple_physics : cleanup phyparam and iniphyparam

File size: 3.9 KB
Line 
1MODULE iniphyparam_mod
2  IMPLICIT NONE
3  PRIVATE
4
5  REAL, PARAMETER :: perfect_gas_const = 8314.46261815324 ! NB using g instead of kg for mass
6
7  PUBLIC :: iniphyparam
8
9CONTAINS
10 
11  SUBROUTINE iniphyparam(ngrid,nlayer, &
12       &           punjours,              &
13       &           pdayref,ptimestep,     &
14       &           prad,pg,pr,pcpp)
15    USE callkeys
16    USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours,mugaz
17    USE planet, ONLY : coefir, coefvis
18    USE astronomy
19    USE turbulence, ONLY : lmixmin, emin_turb
20    USE surface
21    USE read_param_mod
22
23    INTEGER, INTENT(IN) :: &
24         ngrid, &       ! Size of the horizontal grid
25         nlayer, &      ! Number of vertical layers.
26         pdayref        ! Day of reference for the simulation
27    REAL, INTENT(IN)  :: ptimestep, prad, pg, pr, pcpp, punjours
28   
29    print*,'INIPHYPARAM'
30    print*,'Avant les getpar '
31
32    CALL read_param('unjours', 86400., unjours,'unjours')
33    CALL read_param('planet_rad',prad,planet_rad,'planet_rad')
34    CALL read_param('g',9.8           ,g,'g')
35    CALL read_param('cpp',1004.       ,cpp,'cpp')
36    CALL read_param('mugaz',28.       ,mugaz,'mugaz')
37    r=perfect_gas_const/mugaz
38    rcp=r/cpp
39
40    CALL read_param('year_day',360.   ,year_day,'year_day')
41    CALL read_param('periheli',150.   ,periheli,'periheli')
42    CALL read_param('aphelie',150.    ,aphelie,'aphelie')
43    CALL read_param('peri_day',0.     ,peri_day,'peri_day')
44    CALL read_param('obliquit',23.    ,obliquit,'obliquit')
45    CALL read_param('Cd_mer',.01      ,Cd_mer,'Cd_mer')
46    CALL read_param('Cd_ter',.01      ,Cd_ter,'Cd_ter')
47    CALL read_param('I_mer',30000.    ,I_mer,'I_mer')
48    CALL read_param('I_ter',30000.    ,I_ter,'I_ter')
49    CALL read_param('alb_ter',.112    ,alb_ter,'alb_ter')
50    CALL read_param('alb_mer',.112    ,alb_mer,'alb_mer')
51    CALL read_param('emi_mer',1.      ,emi_mer,'emi_mer')
52    CALL read_param('emi_mer',1.      ,emi_mer,'emi_mer')
53    CALL read_param('emin_turb',1.e-16 ,emin_turb,'emin_turb')
54    CALL read_param('lmixmin',100.    ,lmixmin,'lmixmin')
55    CALL read_param('coefvis',.99     ,coefvis,'coefvis')
56    CALL read_param('coefir',.08      ,coefir,'coefir')
57   
58    CALL read_param('callrad',.true.,callrad,'appel rayonnemen')
59    CALL read_param('calldifv',.true.,calldifv,'appel difv')
60    CALL read_param('calladj',.true.,calladj,'appel adj')
61    CALL read_param('callcond',.true.,callcond,'appel cond')
62    CALL read_param('callsoil',.true.,callsoil,'appel soil')
63    CALL read_param('season',.true.,season,'appel soil')
64    CALL read_param('diurnal',.false.,diurnal,'appel soil')
65    CALL read_param('lverbose',.true.,lverbose,'appel soil')
66    CALL read_param('period_sort',1.,period_sort,'period sorties en jour')
67   
68    CALL check_mismatch('unjours', punjours, unjours)
69    CALL check_mismatch('rad', prad, planet_rad)
70    CALL check_mismatch('g', pg, g)
71    CALL check_mismatch('R', pr, r)
72    CALL check_mismatch('cpp', pcpp, cpp)
73   
74    print*,'Activation de la physique:'
75    print*,' R=',r
76    print*,' Rayonnement ',callrad
77    print*,' Diffusion verticale turbulente ', calldifv
78    print*,' Ajustement convectif ',calladj
79    print*,' Sol ',callsoil
80    print*,' Cycle diurne ',diurnal
81   
82    !   choice of the frequency of the computation of radiations
83    IF(diurnal) THEN
84       iradia=NINT(punjours/(20.*ptimestep))
85    ELSE
86       iradia=NINT(punjours/(4.*ptimestep))
87    ENDIF
88    iradia=1
89    PRINT*,'unjours',punjours
90    PRINT*,'The radiative transfer is computed each ', &
91         &   iradia,' physical time-step or each ', &
92         &   iradia*ptimestep,' seconds'
93
94    dtphys=ptimestep
95
96  END SUBROUTINE iniphyparam
97
98  SUBROUTINE check_mismatch(name, a,b)
99    CHARACTER(*), INTENT(IN) :: name
100    REAL, INTENT(IN) :: a,b
101    IF(a /= b) THEN
102       PRINT *, 'Phys/dyn mismatch for ', name, ' : ',a,b
103    END IF
104  END SUBROUTINE check_mismatch
105
106END MODULE iniphyparam_mod
Note: See TracBrowser for help on using the repository browser.