Ignore:
Timestamp:
Oct 30, 2016, 4:35:25 PM (8 years ago)
Author:
oboucher
Message:

Adding a module for stratospheric aerosols with a bin scheme.
The module gets activated with -strataer true compiling option.
May not quite work yet, more testing needed, but should not affect
the rest of LMDz as everything is under a CPP_StratAer key.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d_common/infotrac.F90

    r2567 r2690  
    4141  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
    4242   
    43     ! CRisi: cas particulier des isotopes
    44     LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
    45     INTEGER :: niso_possibles   
    46     PARAMETER ( niso_possibles=5)
    47     real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
    48     LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
    49     INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
    50     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
    51     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
    52     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
    53     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
    54     INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numéro d isotope entre 1 et niso_possibles
    55     INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
    56     INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
     43! CRisi: cas particulier des isotopes
     44  LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
     45  INTEGER :: niso_possibles   
     46  PARAMETER ( niso_possibles=5)
     47  REAL, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
     48  LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
     49  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
     50  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
     51  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
     52  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
     53  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
     54  INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numéro d isotope entre 1 et niso_possibles
     55  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
     56  INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
     57
     58#ifdef CPP_StratAer
     59!--CK/OB for stratospheric aerosols
     60  INTEGER, SAVE :: nbtr_bin
     61  INTEGER, SAVE :: nbtr_sulgas
     62  INTEGER, SAVE :: id_OCS_strat
     63  INTEGER, SAVE :: id_SO2_strat
     64  INTEGER, SAVE :: id_H2SO4_strat
     65  INTEGER, SAVE :: id_BIN01_strat
     66  INTEGER, SAVE :: id_TEST_strat
     67#endif
    5768 
    5869CONTAINS
     
    141152       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
    142153#endif
     154    ELSE IF (type_trac == 'coag') THEN
     155       WRITE(lunout,*) 'Tracers are treated for COAGULATION tests : type_trac=', type_trac
     156#ifndef CPP_StratAer
     157       WRITE(lunout,*) 'To run this option you must add cpp key StratAer and compile with StratAer code'
     158       CALL abort_gcm('infotrac_init','You must compile with cpp key StratAer',1)
     159#endif
    143160    ELSE IF (type_trac == 'lmdz') THEN
    144161       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     
    148165    END IF
    149166
    150 
    151167    ! Test if config_inca is other then none for run without INCA
    152168    IF (type_trac/='inca' .AND. config_inca/='none') THEN
     
    155171    END IF
    156172
    157 
    158173!-----------------------------------------------------------------------
    159174!
     
    162177!
    163178!-----------------------------------------------------------------------
    164     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     179    IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    165180       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    166181       IF(ierr.EQ.0) THEN
     
    171186          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
    172187          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
    173           if (planet_type=='earth') then
     188          IF (planet_type=='earth') THEN
    174189            nqtrue=4 ! Default value for Earth
    175           else
     190          ELSE
    176191            nqtrue=1 ! Default value for other planets
    177           endif
    178        END IF
     192          ENDIF
     193       ENDIF
    179194!jyg<
    180195!!       if ( planet_type=='earth') then
     
    211226       ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
    212227
    213     END IF   ! type_trac
     228    ENDIF   ! type_trac
    214229!>jyg
    215230
     
    266281!    Get choice of advection schema from file tracer.def or from INCA
    267282!---------------------------------------------------------------------
    268     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     283    IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    269284       IF(ierr.EQ.0) THEN
    270285          ! Continue to read tracer.def
     
    346361       END DO
    347362
    348        if ( planet_type=='earth') then
     363       IF ( planet_type=='earth') THEN
    349364         !CR: nombre de traceurs de l eau
    350          if (tnom_0(3) == 'H2Oi') then
     365         IF (tnom_0(3) == 'H2Oi') THEN
    351366            nqo=3
    352          else
     367         ELSE
    353368            nqo=2
    354          endif
     369         ENDIF
    355370         ! For Earth, water vapour & liquid tracers are not in the physics
    356371         nbtr=nqtrue-nqo
    357        else
     372       ELSE
    358373         ! Other planets (for now); we have the same number of tracers
    359374         ! in the dynamics than in the physics
    360375         nbtr=nqtrue
    361        endif
    362 
    363     ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr')
     376       ENDIF
     377
     378#ifdef CPP_StratAer
     379       IF (type_trac == 'coag') THEN
     380         nbtr_bin=0
     381         nbtr_sulgas=0
     382         DO iq=1,nqtrue
     383           IF (tnom_0(iq)(1:3)=='BIN') THEN !check if tracer name contains 'BIN'
     384             nbtr_bin=nbtr_bin+1
     385           ENDIF
     386           IF (tnom_0(iq)(1:3)=='GAS') THEN !check if tracer name contains 'GAS'
     387             nbtr_sulgas=nbtr_sulgas+1
     388           ENDIF
     389         ENDDO
     390         print*,'nbtr_bin=',nbtr_bin
     391         print*,'nbtr_sulgas=',nbtr_sulgas
     392         DO iq=1,nqtrue
     393           IF (tnom_0(iq)=='GASOCS') THEN
     394             id_OCS_strat=iq-nqo
     395           ENDIF
     396           IF (tnom_0(iq)=='GASSO2') THEN
     397             id_SO2_strat=iq-nqo
     398           ENDIF
     399           IF (tnom_0(iq)=='GASH2SO4') THEN
     400             id_H2SO4_strat=iq-nqo
     401           ENDIF
     402           IF (tnom_0(iq)=='BIN01') THEN
     403             id_BIN01_strat=iq-nqo
     404           ENDIF
     405           IF (tnom_0(iq)=='GASTEST') THEN
     406             id_TEST_strat=iq-nqo
     407           ENDIF
     408         ENDDO
     409         print*,'id_OCS_strat  =',id_OCS_strat
     410         print*,'id_SO2_strat  =',id_SO2_strat
     411         print*,'id_H2SO4_strat=',id_H2SO4_strat
     412         print*,'id_BIN01_strat=',id_BIN01_strat
     413       ENDIF
     414#endif
     415
     416    ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac = 'coag')
    364417!jyg<
    365418!
Note: See TracChangeset for help on using the changeset viewer.