1 | MODULE compar1d_mod_h |
---|
2 | IMPLICIT NONE; PRIVATE |
---|
3 | PUBLIC nat_surf, tsurf, beta_surf, rugos, rugosh, & |
---|
4 | xqsol, qsurf, psurf, zsurf, albedo, time, time_ini, xlat, xlon, airefi, & |
---|
5 | wtsurf, wqsurf, restart_runoff, xagesno, qsolinp, zpicinp, & |
---|
6 | forcing_type, tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo, & |
---|
7 | nudge_u, nudge_v, nudge_w, nudge_t, nudge_q, & |
---|
8 | iflag_nudge, snowmass, & |
---|
9 | restart, ok_old_disvert, & |
---|
10 | nb_ter_srf, alpha_soil_ter_srf, period_ter_srf, frac_ter_srf, & |
---|
11 | rugos_ter_srf, ratio_z0m_z0h_ter_srf, albedo_ter_srf, beta_ter_srf, & |
---|
12 | inertie_ter_srf, hcond_ter_srf, tsurf_ter_srf, tsoil_ter_srf, & |
---|
13 | tsoil_depths, nb_tsoil_depths, & |
---|
14 | tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, & |
---|
15 | trad, forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar, & |
---|
16 | nudging_u, nudging_v, nudging_t, nudging_qv, nudging_w, & |
---|
17 | p_nudging_u, p_nudging_v, p_nudging_t, p_nudging_qv, p_nudging_w |
---|
18 | |
---|
19 | INTEGER :: forcing_type |
---|
20 | INTEGER :: tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo |
---|
21 | REAL :: nudge_u, nudge_v, nudge_w, nudge_t, nudge_q |
---|
22 | INTEGER :: iflag_nudge |
---|
23 | REAL :: nat_surf |
---|
24 | REAL :: tsurf |
---|
25 | REAL :: beta_surf |
---|
26 | REAL :: rugos |
---|
27 | REAL :: rugosh |
---|
28 | REAL :: xqsol(1:2) |
---|
29 | REAL :: qsurf |
---|
30 | REAL :: psurf |
---|
31 | REAL :: zsurf |
---|
32 | REAL :: albedo |
---|
33 | REAL :: snowmass |
---|
34 | |
---|
35 | REAL :: time |
---|
36 | REAL :: time_ini |
---|
37 | REAL :: xlat |
---|
38 | REAL :: xlon |
---|
39 | REAL :: airefi |
---|
40 | REAL :: wtsurf |
---|
41 | REAL :: wqsurf |
---|
42 | REAL :: restart_runoff |
---|
43 | REAL :: xagesno |
---|
44 | REAL :: qsolinp |
---|
45 | REAL :: zpicinp |
---|
46 | |
---|
47 | LOGICAL :: restart |
---|
48 | LOGICAL :: ok_old_disvert |
---|
49 | |
---|
50 | INTEGER :: nb_ter_srf |
---|
51 | REAL :: alpha_soil_ter_srf |
---|
52 | REAL :: period_ter_srf |
---|
53 | REAL, DIMENSION(5) :: frac_ter_srf |
---|
54 | REAL, DIMENSION(5) :: rugos_ter_srf |
---|
55 | REAL, DIMENSION(5) :: ratio_z0m_z0h_ter_srf |
---|
56 | REAL, DIMENSION(5) :: albedo_ter_srf |
---|
57 | REAL, DIMENSION(5) :: beta_ter_srf |
---|
58 | REAL, DIMENSION(5) :: inertie_ter_srf |
---|
59 | REAL, DIMENSION(5) :: hcond_ter_srf |
---|
60 | REAL, DIMENSION(5) :: tsurf_ter_srf |
---|
61 | REAL, DIMENSION(5*5) :: tsoil_ter_srf |
---|
62 | REAL, DIMENSION(5*5) :: tsoil_depths |
---|
63 | INTEGER :: nb_tsoil_depths |
---|
64 | |
---|
65 | ! Pour les forcages communs: ces entiers valent 0 ou 1 |
---|
66 | ! tadv= advection tempe, tadvv= adv tempe verticale, tadvh= adv tempe horizontale |
---|
67 | ! idem pour l advection en theta |
---|
68 | ! qadv= advection q, qadvv= adv q verticale, qadvh= adv q horizontale |
---|
69 | ! trad= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les tadv) |
---|
70 | ! forcages en omega, w, vent geostrophique ou ustar |
---|
71 | ! Parametres de nudging en u,v,t,q valent 0 ou 1 ou le temps de nudging |
---|
72 | |
---|
73 | INTEGER :: tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, trad |
---|
74 | INTEGER :: forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar |
---|
75 | REAL :: nudging_u, nudging_v, nudging_w, nudging_t, nudging_qv |
---|
76 | REAL :: p_nudging_u, p_nudging_v, p_nudging_w, p_nudging_t, p_nudging_qv |
---|
77 | |
---|
78 | |
---|
79 | !$OMP THREADPRIVATE(nat_surf, tsurf, beta_surf, rugos, rugosh, & |
---|
80 | !$OMP xqsol, qsurf, psurf, zsurf, albedo, time, time_ini, xlat, xlon, airefi, & |
---|
81 | !$OMP wtsurf, wqsurf, restart_runoff, xagesno, qsolinp, zpicinp, & |
---|
82 | !$OMP forcing_type, tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo, & |
---|
83 | !$OMP nudge_u, nudge_v, nudge_w, nudge_t, nudge_q, & |
---|
84 | !$OMP iflag_nudge, snowmass, & |
---|
85 | !$OMP restart, ok_old_disvert, & |
---|
86 | !$OMP nb_ter_srf, frac_ter_srf, rugos_ter_srf, albedo_ter_srf, & |
---|
87 | !$OMP beta_ter_srf, inertie_ter_srf, alpha_soil_ter_srf, & |
---|
88 | !$OMP period_ter_srf, hcond_ter_srf, ratio_z0m_z0h_ter_srf, & |
---|
89 | !$OMP tsurf_ter_srf, tsoil_ter_srf, tsoil_depths, nb_tsoil_depths, & |
---|
90 | !$OMP tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, & |
---|
91 | !$OMP trad, forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar, & |
---|
92 | !$OMP nudging_u, nudging_v, nudging_t, nudging_qv, nudging_w, & |
---|
93 | !$OMP p_nudging_u, p_nudging_v, p_nudging_t, p_nudging_qv, p_nudging_w) |
---|
94 | |
---|
95 | END MODULE compar1d_mod_h |
---|