Ignore:
Timestamp:
Sep 22, 2017, 12:47:14 PM (7 years ago)
Author:
millour
Message:

Add capability to read tracer names from a "traceur.def" file in the Dynamico-LMDZ interface.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/src/phylmd/interface_icosa_lmdz.f90

    r4028 r4047  
    3030  INTEGER :: count_clock=0
    3131 
    32   REAL :: day_length
    33 
     32!  REAL,SAVE :: day_length ! length of a day (s)
    3433 
    3534  INTEGER,SAVE :: nbp_phys
     
    5453  USE mod_grid_phy_lmdz, ONLY : unstructured
    5554  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    56   USE time_phylmdz_mod, ONLY: init_time_lmdz => init_time
    5755  USE transfert_mod
    5856  USE physics_distribution_mod, ONLY : init_physics_distribution
    59 !  USE geometry_mod, ONLY : init_geometry
    60 !  USE vertical_layers_mod, ONLY : init_vertical_layers
    61 !  USE infotrac_phy, ONLY : init_infotrac_phy
    62 !  USE inifis_mod, ONLY : inifis
    63 !  USE phyaqua_mod, ONLY : iniaqua
    6457   
    6558 
     
    7467  REAL(rstd),ALLOCATABLE :: bounds_latfi(:,:)
    7568  REAL(rstd),ALLOCATABLE :: bounds_lonfi(:,:)
    76   REAL(rstd) :: pseudoalt(llm)
    77 
    78   INTEGER :: run_length 
    79   INTEGER :: annee_ref 
    80   INTEGER :: day_ref   
    81   INTEGER :: day_ini   
    82   REAL    :: start_time
    83   REAL    :: physics_timestep   
    84 
    85 
    86   INTEGER                       :: nqo, nbtr
    87   CHARACTER(len=4)              :: type_trac
    88   CHARACTER(len=20),ALLOCATABLE :: tname(:)    ! tracer short name for restart and diagnostics
    89   CHARACTER(len=23),ALLOCATABLE :: ttext(:)     ! tracer long name for diagnostics
    90   INTEGER,ALLOCATABLE           :: niadv(:)    ! equivalent dyn / physique
    91   INTEGER,ALLOCATABLE           :: conv_flg(:) ! conv_flg(it)=0 : convection desactivated for tracer number it
    92   INTEGER,ALLOCATABLE           :: pbl_flg(:)  ! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
    93   CHARACTER(len=8),ALLOCATABLE :: solsym(:)  ! tracer name from inca
    94 
    95   INTEGER :: iflag_phys   
     69!  REAL(rstd) :: pseudoalt(llm)
     70
    9671  INTEGER :: nbp_phys, nbp_phys_glo
    9772 
     
    190165  USE infotrac_phy, ONLY : init_infotrac_phy
    191166  USE inifis_mod, ONLY : inifis
    192   USE phyaqua_mod, ONLY : iniaqua
     167!  USE phyaqua_mod, ONLY : iniaqua
    193168   
    194169 
     
    197172
    198173
    199   INTEGER  :: ind,i,j,ij,pos
     174  INTEGER  :: ind,i,j,k,ij,pos
    200175  REAL(rstd),POINTER :: bounds_lon(:,:)
    201176  REAL(rstd),POINTER :: bounds_lat(:,:)
     
    214189
    215190  INTEGER :: run_length 
    216   INTEGER :: annee_ref 
    217   INTEGER :: day_ref   
     191  REAL,SAVE :: day_length ! length of a day (s) ! SAVEd to be OpenMP shared
     192  INTEGER,SAVE :: annee_ref 
     193  INTEGER,SAVE :: day_ref   
    218194  INTEGER :: day_ini   
    219195  REAL    :: start_time
    220196  REAL    :: physics_timestep   
    221197
    222 
    223   INTEGER                       :: nqo, nbtr
    224   CHARACTER(len=4)              :: type_trac
    225   CHARACTER(len=20),ALLOCATABLE :: tname(:)    ! tracer short name for restart and diagnostics
     198  ! Tracer stuff (SAVEd when needed to be OpenMP shared)
     199  INTEGER :: nq
     200  INTEGER,SAVE                  :: nqo, nbtr
     201  CHARACTER(len=4),SAVE         :: type_trac
     202  CHARACTER(len=20),ALLOCATABLE,SAVE :: tname(:)    ! tracer short name for restart and diagnostics
    226203  CHARACTER(len=23),ALLOCATABLE :: ttext(:)     ! tracer long name for diagnostics
    227204  INTEGER,ALLOCATABLE           :: niadv(:)    ! equivalent dyn / physique
     
    303280
    304281    ! Initialize tracer names, numbers, etc. for physics
    305 
     282!$OMP MASTER
    306283    !Config  Key  = type_trac
    307284    !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     
    313290     type_trac = 'lmdz'
    314291     CALL getin('type_trac',type_trac)
    315 
    316 ! init model for standard lmdz case
    317     nqo=2
    318     nbtr=2
     292!$OMP END MASTER
     293!$OMP BARRIER
     294
     295! allocate some of the tracer arrays
    319296    ALLOCATE(tname(nqtot))
    320297    ALLOCATE(ttext(nqtot))
    321298    ALLOCATE(niadv(nqtot))
     299
     300! read "traceur.def" file to know tracer names (and figure out nqo and nbtr)
     301!$OMP MASTER
     302    OPEN(unit=42,file="traceur.def",form="formatted",status="old",iostat=ierr)
     303    IF (ierr==0) THEN
     304      READ(42,*) nq ! should be the same as nqtot
     305      IF (nq /= nqtot) THEN
     306        WRITE(*,*) "Error: number of tracers in tracer.def should match nqtot!"
     307        WRITE(*,*) "       will just use nqtot=",nqtot," tracers"
     308      ENDIF
     309      DO i=1,nqtot
     310        READ(42,*) j,k,tname(i)
     311      ENDDO
     312      CLOSE(42)
     313    ENDIF
     314    ! figure out how many water tracers are present
     315    nqo=0
     316    DO i=1,nqtot
     317      IF (INDEX(tname(i),"H2O")==1) THEN
     318        nqo=nqo+1
     319      ENDIF
     320    ENDDO
     321    nbtr=nqtot-nqo
     322!$OMP END MASTER
     323!$OMP BARRIER
     324
    322325    ALLOCATE(conv_flg(nbtr))
    323326    ALLOCATE(pbl_flg(nbtr))
     
    326329    conv_flg(:) = 1 ! convection activated for all tracers
    327330    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
    328     tname(1)='H2Ov'   
    329     tname(2)='H2Ol'   
    330     tname(3)='RN'   
    331     tname(4)='PB'
    332     ttext(1)='H2OvVLH'   
    333     ttext(2)='H2OlVL1'   
    334     ttext(3)='RNVL1'   
    335     ttext(4)='PBVL1'
    336     solsym(1:2)=tname(3:4)
    337     niadv(1)=1
    338     niadv(2)=2
    339     niadv(3)=3
    340     niadv(4)=4
     331    ! tracer long names:
     332    ttext(1)=trim(tname(1))//"VLH" !'H2OvVLH'
     333    DO i=2,nqtot
     334      ttext(i)=trim(tname(1))//"VL1"
     335    ENDDO
     336    solsym(1:nbtr)=tname(nqo+1:nqtot)
     337    DO i=1,nqtot
     338      niadv(i)=i
     339    ENDDO
    341340    ! isotopes
    342341    ALLOCATE(nqfils(nqtot)) ; nqfils(:)=0
     
    375374
    376375   ! Initialize physical constant
     376!$OMP MASTER
    377377    day_length=86400
    378378    CALL getin('day_length',day_length)
     
    387387    day_ref=1
    388388    CALL getin("dayref",day_ref)
     389!$OMP END MASTER
     390!$OMP BARRIER
    389391   
    390392    physics_timestep=dt*itau_physics
Note: See TracChangeset for help on using the changeset viewer.