MODULE infotrac_phy ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included INTEGER, SAVE :: nqtot !$OMP THREADPRIVATE(nqtot) !CR: on ajoute le nombre de traceurs de l eau INTEGER, SAVE :: nqo !$OMP THREADPRIVATE(nqo) ! nbtr : number of tracers not including higher order of moment or water vapor or liquid ! number of tracers used in the physics INTEGER, SAVE :: nbtr !$OMP THREADPRIVATE(nbtr) ! Name variables CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics !$OMP THREADPRIVATE(tname) CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics !$OMP THREADPRIVATE(ttext) ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code. INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique !$OMP THREADPRIVATE(niadv) ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg !$OMP THREADPRIVATE(pbl_flg) ! conv_flg(it)=0 : convection desactivated for tracer number it INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg !$OMP THREADPRIVATE(conv_flg) CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym !$OMP THREADPRIVATE(solsym) CHARACTER(len=4),SAVE :: type_trac !$OMP THREADPRIVATE(type_trac) CONTAINS SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,tname_,ttext_,type_trac_,& niadv_,conv_flg_,pbl_flg_,solsym_) IMPLICIT NONE INTEGER,INTENT(IN) :: nqtot_ INTEGER,INTENT(IN) :: nqo_ INTEGER,INTENT(IN) :: nbtr_ CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics CHARACTER(len=4),INTENT(IN) :: type_trac_ INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique INTEGER,INTENT(IN) :: conv_flg_(nbtr_) INTEGER,INTENT(IN) :: pbl_flg_(nbtr_) CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_) nqtot=nqtot_ nqo=nqo_ nbtr=nbtr_ ALLOCATE(tname(nqtot)) tname(:) = tname_(:) ALLOCATE(ttext(nqtot)) ttext(:) = ttext_(:) type_trac = type_trac_ ALLOCATE(niadv(nqtot)) niadv(:)=niadv_(:) ALLOCATE(conv_flg(nbtr)) conv_flg(:)=conv_flg_(:) ALLOCATE(pbl_flg(nbtr)) pbl_flg(:)=pbl_flg_(:) ALLOCATE(solsym(nbtr)) solsym(:)=solsym_(:) write(*,*) "init_infotrac_phy: nqtot,nqo,nbtr",nqtot,nqo,nbtr END SUBROUTINE init_infotrac_phy END MODULE infotrac_phy