Ignore:
Timestamp:
Apr 17, 2015, 10:30:37 PM (10 years ago)
Author:
millour
Message:

Further cleanup and removal of references to iniprint.h.
Also added bench testcase 48x36x19.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phytrac_mod.F90

    r3816 r3817  
    2020!=================================================================================
    2121
    22 
    23   IMPLICIT NONE
    24 ! tracer settings, inherited from the dynamics (see ini_trac_mod)
    25 ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
    26   INTEGER, SAVE :: nqtot
    27 ! nqo: numbre of water tracers
    28   INTEGER, SAVE :: nqo
    29 ! nbtr : number of tracers not including higher order of moment or water vapor or liquid
    30 !        number of tracers used in the physics
    31   INTEGER, SAVE :: nbtr
    32 !$OMP THREADRIVATE(nqtot,nqo,nbtr)
    33 ! Name variables
    34   CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    35   CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
    36 ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
    37 !         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
    38   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
    39 !$OMP THREADRIVATE(tname,ttext,niadv)
    40 ! conv_flg(it)=0 : convection desactivated for tracer number it
    41   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
    42 ! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
    43   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
    44   CHARACTER(len=4),SAVE :: type_trac
    45   CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
    46 !$OMP THREADRIVATE(conv_flg,pbl_flg,type_trac,solsym)
    4722!
    4823! Tracer tendencies, for outputs
     
    7954CONTAINS
    8055
    81   SUBROUTINE ini_phytrac_mod(nqtot_dyn,nqo_dyn,nbtr_dyn, &
    82                              tname_dyn,ttext_dyn,type_trac_dyn, &
    83                              niadv_dyn,conv_flg_dyn,pbl_flg_dyn,solsym_dyn)
    84   IMPLICIT NONE
    85  
    86   INTEGER,INTENT(IN) :: nqtot_dyn
    87   INTEGER,INTENT(IN) :: nqo_dyn
    88   INTEGER,INTENT(IN) :: nbtr_dyn
    89   CHARACTER(len=*),INTENT(IN) :: tname_dyn(nqtot_dyn)
    90   CHARACTER(len=*),INTENT(IN) :: ttext_dyn(nqtot_dyn)
    91   CHARACTER(len=*),INTENT(IN) :: type_trac_dyn
    92   INTEGER,INTENT(IN) :: niadv_dyn(nqtot_dyn)
    93   INTEGER,INTENT(IN) :: conv_flg_dyn(nbtr_dyn)
    94   INTEGER,INTENT(IN) :: pbl_flg_dyn(nbtr_dyn)
    95   CHARACTER(len=*),INTENT(IN) :: solsym_dyn(nbtr_dyn)
    96  
    97   INTEGER :: i
    98  
    99   nqtot=nqtot_dyn
    100   nqo=nqo_dyn
    101   nbtr=nbtr_dyn
    102   type_trac=type_trac_dyn
    103  
    104   allocate(tname(nqtot))
    105   allocate(ttext(nqtot))
    106   allocate(niadv(nqtot))
    107   allocate(conv_flg(nbtr))
    108   allocate(pbl_flg(nbtr))
    109   allocate(solsym(nbtr))
    110  
    111   DO i=1,nqtot_dyn
    112     tname(i)=tname_dyn(i)
    113     ttext(i)=ttext_dyn(i)
    114     niadv(i)=niadv_dyn(i)
    115   ENDDO
    116   DO i=1,nbtr_dyn
    117     conv_flg(i)=conv_flg_dyn(i)
    118     pbl_flg(i)=pbl_flg_dyn(i)
    119     solsym(i)=solsym_dyn(i)
    120   ENDDO
    121  
    122   END SUBROUTINE ini_phytrac_mod
    123 
    12456  SUBROUTINE phytrac(                                 &
    12557       nstep,     julien,   gmtime,   debutphy,       &
     
    15789    USE phys_cal_mod, only : hour
    15890    USE dimphy
    159     !USE infotrac_phy
     91    USE infotrac_phy, ONLY: nbtr, pbl_flg, conv_flg, type_trac, solsym
    16092    USE mod_grid_phy_lmdz
    16193    USE mod_phys_lmdz_para
     
    16597    USE tracreprobus_mod
    16698    !USE control_phy_mod
    167     USE inifis_mod, ONLY: config_inca
     99    USE inifis_mod, ONLY: config_inca, lunout
    168100   
    169101    USE indice_sol_mod
     
    177109    INCLUDE "clesphys.h"
    178110    INCLUDE "thermcell.h"
    179     INCLUDE "iniprint.h"
    180111    !==========================================================================
    181112    !                   -- ARGUMENT DESCRIPTION --
Note: See TracChangeset for help on using the changeset viewer.