1 | MODULE infotrac_phy |
---|
2 | |
---|
3 | |
---|
4 | ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included |
---|
5 | INTEGER, SAVE :: nqtot |
---|
6 | !$OMP THREADPRIVATE(nqtot) |
---|
7 | |
---|
8 | !CR: on ajoute le nombre de traceurs de l eau |
---|
9 | INTEGER, SAVE :: nqo |
---|
10 | !$OMP THREADPRIVATE(nqo) |
---|
11 | |
---|
12 | ! nbtr : number of tracers not including higher order of moment or water vapor or liquid |
---|
13 | ! number of tracers used in the physics |
---|
14 | INTEGER, SAVE :: nbtr |
---|
15 | !$OMP THREADPRIVATE(nbtr) |
---|
16 | |
---|
17 | ! Name variables |
---|
18 | CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics |
---|
19 | !$OMP THREADPRIVATE(tname) |
---|
20 | |
---|
21 | CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics |
---|
22 | !$OMP THREADPRIVATE(ttext) |
---|
23 | ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the |
---|
24 | ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code. |
---|
25 | INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique |
---|
26 | !$OMP THREADPRIVATE(niadv) |
---|
27 | |
---|
28 | ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it |
---|
29 | INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg |
---|
30 | !$OMP THREADPRIVATE(pbl_flg) |
---|
31 | |
---|
32 | ! conv_flg(it)=0 : convection desactivated for tracer number it |
---|
33 | INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg |
---|
34 | !$OMP THREADPRIVATE(conv_flg) |
---|
35 | |
---|
36 | CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym |
---|
37 | !$OMP THREADPRIVATE(solsym) |
---|
38 | |
---|
39 | CHARACTER(len=4),SAVE :: type_trac |
---|
40 | !$OMP THREADPRIVATE(type_trac) |
---|
41 | |
---|
42 | CONTAINS |
---|
43 | |
---|
44 | SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,tname_,ttext_,type_trac_,& |
---|
45 | niadv_,conv_flg_,pbl_flg_,solsym_) |
---|
46 | IMPLICIT NONE |
---|
47 | INTEGER,INTENT(IN) :: nqtot_ |
---|
48 | INTEGER,INTENT(IN) :: nqo_ |
---|
49 | INTEGER,INTENT(IN) :: nbtr_ |
---|
50 | CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics |
---|
51 | CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics |
---|
52 | CHARACTER(len=4),INTENT(IN) :: type_trac_(nqtot_) |
---|
53 | INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique |
---|
54 | INTEGER,INTENT(IN) :: conv_flg_(nbtr_) |
---|
55 | INTEGER,INTENT(IN) :: pbl_flg_(nbtr_) |
---|
56 | CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_) |
---|
57 | |
---|
58 | nqtot=nqtot_ |
---|
59 | nqo=nqo_ |
---|
60 | nbtr=nbtr_ |
---|
61 | ALLOCATE(tname(nqtot)) |
---|
62 | tname(:) = tname_(:) |
---|
63 | ALLOCATE(ttext(nqtot)) |
---|
64 | ttext(:) = ttext_(:) |
---|
65 | ALLOCATE(niadv(nqtot)) |
---|
66 | niadv(:)=niadv_(:) |
---|
67 | ALLOCATE(conv_flg(nbtr)) |
---|
68 | conv_flg(:)=conv_flg_(:) |
---|
69 | ALLOCATE(pbl_flg(nbtr)) |
---|
70 | pbl_flg(:)=pbl_flg_(:) |
---|
71 | ALLOCATE(solsym(nbtr)) |
---|
72 | solsym(:)=solsym_(:) |
---|
73 | |
---|
74 | write(*,*) "init_infotrac_phy: nqtot,nqo,nbtr",nqtot,nqo,nbtr |
---|
75 | |
---|
76 | END SUBROUTINE init_infotrac_phy |
---|
77 | |
---|
78 | |
---|
79 | END MODULE infotrac_phy |
---|