Ignore:
Timestamp:
Dec 15, 2021, 11:18:49 PM (2 years ago)
Author:
dcugnet
Message:

First commit for new tracers.

  • parser routines readTracFiles, strings_mod and tracer_types added in misc using revision 4 of https://svn.lmd.jussieu.fr/tracers-parser
  • tested in sequential and parallel mode using ioipsl.
  • for now, only two fields of "tracers(:)" derived type vector are used: "name" and "longName".
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/traclmdz_mod.F90

    r3581 r4046  
    9696    USE indice_sol_mod
    9797    USE print_control_mod, ONLY: lunout
     98    USE strings_mod, ONLY: strLower
    9899
    99100! Input variables
     
    175176!!       iiq=niadv(it+2)                                                            ! jyg
    176177       iiq=niadv(it+nqo)                                                            ! jyg
    177        IF ( tname(iiq) == "RN" ) THEN                                               
    178           id_rn=it ! radon
    179        ELSE IF ( tname(iiq) == "PB") THEN
    180           id_pb=it ! plomb
    181 ! RomP >>> profil initial de PB210
    182      open (ilesfil2,file='prof.pb210',status='old',iostat=irr2)
    183      IF (irr2 == 0) THEN
    184       read(ilesfil2,*) kradio2
    185       print*,'number of levels for pb210 profile ',kradio2
    186       do k=kradio2,1,-1
    187        read (ilesfil2,*) plomb(:,k)
    188       enddo
    189       close(ilesfil2)
    190       do k=1,klev
    191        do i=1,klon
    192          tr_seri(i,k,id_pb)=plomb(i,k)
    193 !!        print*, 'tr_seri',i,k,tr_seri(i,k,id_pb)
    194         enddo
    195       enddo
    196      ELSE
    197        print *, 'Prof.pb210 does not exist: use restart values'
    198      ENDIF
    199 ! RomP <<<
    200        ELSE IF ( tname(iiq) == "Aga" .OR. tname(iiq) == "AGA" ) THEN
    201           ! Age of stratospheric air
    202           id_aga=it
    203           radio(id_aga) = .FALSE.
    204           aerosol(id_aga) = .FALSE.
    205           pbl_flg(id_aga) = 0
    206          
    207           ! Find the first model layer above 1.5km from the surface
    208           IF (klev>=30) THEN
    209              lev_1p5km=6   ! NB! This value is for klev=39
    210           ELSE IF (klev>=10) THEN
    211              lev_1p5km=5   ! NB! This value is for klev=19
    212           ELSE
    213              lev_1p5km=klev/2
    214           END IF
    215        ELSE IF ( tname(iiq) == "BE" .OR. tname(iiq) == "Be" .OR.  &
    216             tname(iiq) == "BE7" .OR. tname(iiq) == "Be7" ) THEN 
    217           ! Recherche du Beryllium 7
    218           id_be=it
    219           ALLOCATE( srcbe(klon,klev) )
    220           radio(id_be) = .TRUE.
    221           aerosol(id_be) = .TRUE. ! le Be est un aerosol
    222 !jyg le 13/03/2013 ; ajout de pplay en argument de init_be
    223 !!!          CALL init_be(pctsrf,masktr(:,id_be),tautr(id_be),vdeptr(id_be),scavtr(id_be),srcbe)
    224           CALL init_be(pctsrf,pplay,masktr(:,id_be),tautr(id_be),vdeptr(id_be),scavtr(id_be),srcbe)
    225           WRITE(lunout,*) 'Initialisation srcBe: OK'
    226 ! RomP >>> profil initial de Be7
    227       open (ilesfil,file='prof.be7',status='old',iostat=irr)
    228       IF (irr == 0) THEN
    229        read(ilesfil,*) kradio
    230        print*,'number of levels for Be7 profile ',kradio
    231        do k=kradio,1,-1
    232         read (ilesfil,*) beryllium(:,k)
    233        enddo
    234        close(ilesfil)
    235        do k=1,klev
    236          do i=1,klon
    237           tr_seri(i,k,id_be)=beryllium(i,k)
    238 !!        print*, 'tr_seri',i,k,tr_seri(i,k,id_be)
    239          enddo
    240        enddo
    241      ELSE
    242        print *, 'Prof.Be7 does not exist: use restart values'
    243      ENDIF
    244 ! RomP <<<
    245        ELSE IF (tname(iiq)=="O3" .OR. tname(iiq)=="o3") THEN
    246           ! Recherche de l'ozone : parametrization de la chimie par Cariolle
    247           id_o3=it
    248           CALL alloc_coefoz   ! allocate ozone coefficients
    249           CALL press_coefoz   ! read input pressure levels
    250        ELSE IF ( tname(iiq) == "pcsat" .OR. tname(iiq) == "Pcsat" ) THEN
    251           id_pcsat=it
    252        ELSE IF ( tname(iiq) == "pcocsat" .OR. tname(iiq) == "Pcocsat" ) THEN
    253           id_pcocsat=it
    254        ELSE IF ( tname(iiq) == "pcq" .OR. tname(iiq) == "Pcq" ) THEN
    255           id_pcq=it
    256        ELSE IF ( tname(iiq) == "pcs0" .OR. tname(iiq) == "Pcs0" ) THEN
    257           id_pcs0=it
    258           conv_flg(it)=0 ! No transport by convection for this tracer
    259        ELSE IF ( tname(iiq) == "pcos0" .OR. tname(iiq) == "Pcos0" ) THEN
    260           id_pcos0=it
    261           conv_flg(it)=0 ! No transport by convection for this tracer
    262        ELSE IF ( tname(iiq) == "pcq0" .OR. tname(iiq) == "Pcq0" ) THEN
    263           id_pcq0=it
    264           conv_flg(it)=0 ! No transport by convection for this tracer
    265        ELSE
    266           WRITE(lunout,*) 'This is an unknown tracer in LMDZ : ', trim(tname(iiq))
    267        END IF
     178print*,'###'//TRIM(tracers(iiq)%name)//'###'
     179print*,'###'//TRIM(strLower(tracers(iiq)%name))//'###'
     180       SELECT CASE(strLower(tracers(iiq)%name))
     181         CASE("rn");      id_rn     = it ! radon
     182         CASE("pb");      id_pb     = it ! plomb
     183         CASE("aga");     id_aga    = it ! Age of stratospheric air
     184         CASE("be","be7");id_be     = it ! Recherche du Beryllium 7
     185         CASE("o3");      id_o3     = it ! Recherche de l'ozone
     186         CASE("pcsat");   id_pcsat  = it
     187         CASE("pcocsat"); id_pcocsat= it
     188         CASE("pcq");     id_pcq    = it
     189         CASE("pcs0");    id_pcs0   = it
     190         CASE("pcos0");   id_pcos0  = it
     191         CASE("pcq0");    id_pcq0   = it
     192         CASE DEFAULT
     193           WRITE(lunout,*) 'This is an unknown tracer in LMDZ : ', trim(tracers(iiq)%name)
     194       END SELECT
     195
     196       SELECT CASE(strLower(tracers(iiq)%name))
     197         CASE("pb")                        !--- RomP >>> profil initial de PB210
     198           OPEN(ilesfil2,file='prof.pb210',status='old',iostat=irr2)
     199           IF(irr2 == 0) THEN
     200             READ(ilesfil2,*) kradio2
     201             WRITE(lunout,*)'number of levels for pb210 profile ',kradio2
     202             DO k=kradio2,1,-1; READ (ilesfil2,*) plomb(:,k); END DO
     203             CLOSE(ilesfil2)
     204             tr_seri(:,:,id_pb) = plomb(:,:)
     205           ELSE
     206             WRITE(lunout,*)'Prof. Pb210 does not exist: use restart values'
     207           END IF
     208         CASE("aga")
     209           radio(id_aga) = .FALSE.
     210           aerosol(id_aga) = .FALSE.
     211           pbl_flg(id_aga) = 0
     212           ! Find the first model layer above 1.5km from the surface
     213           IF (klev>=30) THEN
     214              lev_1p5km=6                  !--- NB: This value is for klev=39
     215           ELSE IF (klev>=10) THEN
     216              lev_1p5km=5                  !--- NB: This value is for klev=19
     217           ELSE
     218              lev_1p5km=klev/2
     219           END IF
     220         CASE("be","be7")
     221           ALLOCATE( srcbe(klon,klev) )
     222           radio(id_be) = .TRUE.
     223           aerosol(id_be) = .TRUE.         !--- Le Be est un aerosol
     224           CALL init_be(pctsrf,pplay,masktr(:,id_be),tautr(id_be),vdeptr(id_be),scavtr(id_be),srcbe)
     225           WRITE(lunout,*) 'Initialisation srcBe: OK'
     226                                           !--- RomP >>> profil initial de Be7
     227           OPEN(ilesfil,file='prof.be7',status='old',iostat=irr)
     228           IF(irr == 0) THEN
     229             READ(ilesfil,*) kradio
     230             WRITE(lunout,*)'number of levels for Be7 profile ',kradio
     231             DO k=kradio,1,-1; READ(ilesfil,*) beryllium(:,k); END DO
     232             CLOSE(ilesfil)
     233             tr_seri(:,:,id_be)=beryllium(:,:)
     234           ELSE
     235             WRITE(lunout,*)'Prof. Be7 does not exist: use restart values'
     236           END IF
     237         CASE("o3")                         !--- Parametrisation par la chimie de Cariolle
     238           CALL alloc_coefoz                !--- Allocate ozone coefficients
     239           CALL press_coefoz                !--- Read input pressure levels
     240         CASE("pcs0","pcos0","pcq0")
     241           conv_flg(it)=0                   !--- No transport by convection for this tracer
     242       END SELECT
    268243    END DO
    269244
     
    309284       IF (zero) THEN
    310285          ! The tracer was not found in restart file or it was equal zero everywhere.
    311           WRITE(lunout,*) "The tracer ",trim(tname(iiq))," will be initialized"
     286          WRITE(lunout,*) "The tracer ",trim(tracers(iiq)%name)," will be initialized"
    312287          IF (it==id_pcsat .OR. it==id_pcq .OR. &
    313288               it==id_pcs0 .OR. it==id_pcq0) THEN
Note: See TracChangeset for help on using the changeset viewer.