1 | MODULE iniphyparam_mod |
---|
2 | #include "use_logging.h" |
---|
3 | IMPLICIT NONE |
---|
4 | PRIVATE |
---|
5 | |
---|
6 | REAL, PARAMETER :: perfect_gas_const = 8314.46261815324 ! NB using g instead of kg for mass |
---|
7 | |
---|
8 | PUBLIC :: iniphyparam |
---|
9 | |
---|
10 | CONTAINS |
---|
11 | |
---|
12 | SUBROUTINE read_params() BIND(C, name='phyparam_setup') |
---|
13 | !$cython header void phyparam_setup(); |
---|
14 | !$cython wrapper def setup() : phy.phyparam_setup() |
---|
15 | USE read_param_mod |
---|
16 | USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours,mugaz |
---|
17 | USE astronomy |
---|
18 | USE planet, ONLY : coefir, coefvis |
---|
19 | USE turbulence, ONLY : lmixmin, emin_turb |
---|
20 | USE soil_mod |
---|
21 | USE callkeys |
---|
22 | |
---|
23 | CALL read_param('planet_rad',6.4e6 ,planet_rad,'planet_rad') |
---|
24 | CALL read_param('g',9.8 ,g,'g') |
---|
25 | CALL read_param('cpp',1004. ,cpp,'cpp') |
---|
26 | CALL read_param('mugaz',28. ,mugaz,'mugaz') |
---|
27 | r=perfect_gas_const/mugaz |
---|
28 | rcp=r/cpp |
---|
29 | |
---|
30 | CALL read_param('unjours', 86400., unjours,'unjours') |
---|
31 | CALL read_param('year_day',360. ,year_day,'year_day') |
---|
32 | CALL read_param('periheli',150. ,periheli,'periheli') |
---|
33 | CALL read_param('aphelie',150. ,aphelie,'aphelie') |
---|
34 | CALL read_param('peri_day',0. ,peri_day,'peri_day') |
---|
35 | CALL read_param('obliquit',23. ,obliquit,'obliquit') |
---|
36 | |
---|
37 | CALL read_param('Cd_mer',.01 ,Cd_mer,'Cd_mer') |
---|
38 | CALL read_param('Cd_ter',.01 ,Cd_ter,'Cd_ter') |
---|
39 | CALL read_param('I_mer',3000. ,I_mer,'I_mer') |
---|
40 | CALL read_param('I_ter',3000. ,I_ter,'I_ter') |
---|
41 | CALL read_param('alb_ter',.112 ,alb_ter,'alb_ter') |
---|
42 | CALL read_param('alb_mer',.112 ,alb_mer,'alb_mer') |
---|
43 | CALL read_param('emi_mer',1. ,emi_mer,'emi_mer') |
---|
44 | CALL read_param('emi_ter',1. ,emi_ter,'emi_ter') |
---|
45 | CALL read_param('emin_turb',1.e-16 ,emin_turb,'emin_turb') |
---|
46 | CALL read_param('lmixmin',100. ,lmixmin,'lmixmin') |
---|
47 | |
---|
48 | CALL read_param('coefvis',.99 ,coefvis,'coefvis') |
---|
49 | CALL read_param('coefir',.08 ,coefir,'coefir') |
---|
50 | |
---|
51 | CALL read_param('callrad', .true., callrad, 'appel rayonnement') |
---|
52 | CALL read_param('calldifv', .true., calldifv, 'appel difv') |
---|
53 | CALL read_param('calladj', .true., calladj, 'appel adj') |
---|
54 | CALL read_param('callsoil', .true., callsoil, 'appel soil') |
---|
55 | CALL read_param('season', .true., season, 'with seasonal cycle') |
---|
56 | CALL read_param('diurnal', .false., diurnal, 'with diurnal cycle') |
---|
57 | CALL read_param('lverbose', .true., lverbose, 'lverbose') |
---|
58 | CALL read_param('period_sort', 1., period_sort, 'period sorties en jour') |
---|
59 | |
---|
60 | END SUBROUTINE read_params |
---|
61 | |
---|
62 | SUBROUTINE iniphyparam(ptimestep, punjours, prad, pg, pr, pcpp) |
---|
63 | USE comgeomfi, ONLY : nsoilmx |
---|
64 | USE soil_mod, ONLY : init_soil |
---|
65 | USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours |
---|
66 | USE callkeys |
---|
67 | REAL, INTENT(IN) :: ptimestep, punjours, prad, pg, pr, pcpp |
---|
68 | |
---|
69 | CALL read_params |
---|
70 | ! choice of the frequency of the computation of radiations |
---|
71 | IF(diurnal) THEN |
---|
72 | iradia=NINT(unjours/(20.*ptimestep)) |
---|
73 | ELSE |
---|
74 | iradia=NINT(unjours/(4.*ptimestep)) |
---|
75 | ENDIF |
---|
76 | iradia=1 |
---|
77 | dtphys=ptimestep |
---|
78 | |
---|
79 | CALL check_mismatch('day lenght (s)', punjours, unjours) |
---|
80 | CALL check_mismatch('planetary radius (km)', prad/1000., planet_rad/1000.) |
---|
81 | CALL check_mismatch('gravity', pg, g) |
---|
82 | CALL check_mismatch('specific R', pr, r) |
---|
83 | CALL check_mismatch('specific heat capacity', pcpp, cpp) |
---|
84 | LOG_WARN('iniphyparam') |
---|
85 | |
---|
86 | WRITELOG(*,*) 'Activation de la physique:' |
---|
87 | WRITELOG(*,*) ' R=',r |
---|
88 | WRITELOG(*,*) ' Rayonnement ',callrad |
---|
89 | WRITELOG(*,*) ' Diffusion verticale turbulente ', calldifv |
---|
90 | WRITELOG(*,*) ' Ajustement convectif ',calladj |
---|
91 | WRITELOG(*,*) ' Sol ',callsoil |
---|
92 | WRITELOG(*,*) ' Cycle diurne ',diurnal |
---|
93 | |
---|
94 | WRITELOG(*,*) 'unjours',unjours |
---|
95 | WRITELOG(*,*) 'The radiative transfer is computed each ', & |
---|
96 | & iradia,' physical time-step or each ', & |
---|
97 | & iradia*ptimestep,' seconds' |
---|
98 | |
---|
99 | LOG_INFO('iniphyparam') |
---|
100 | |
---|
101 | CALL init_soil(nsoilmx) |
---|
102 | END SUBROUTINE iniphyparam |
---|
103 | |
---|
104 | SUBROUTINE check_mismatch(name, a,b) |
---|
105 | CHARACTER(*), INTENT(IN) :: name |
---|
106 | REAL, INTENT(IN) :: a,b |
---|
107 | IF(a /= b) THEN |
---|
108 | WRITELOG(*,*) 'Phys/dyn mismatch for ', name, ' : ',a,b |
---|
109 | END IF |
---|
110 | END SUBROUTINE check_mismatch |
---|
111 | |
---|
112 | END MODULE iniphyparam_mod |
---|