Changeset 1405 for LMDZ4


Ignore:
Timestamp:
Jul 1, 2010, 3:16:29 PM (14 years ago)
Author:
jghattas
Message:
  • Added tracer "Age of stratospheric air", activated by putting Aga in tracer.def.
  • The logical rnpb is now controled during execution. rnpb is true only if both tracers RN and PB existe in tracer.def. RN and PB can now be removed from tracer.def
  • Modification in output. It is now possible to have 3 tracers. But still only tracer number 3 and tracer number 4(if existing) will be written.

F Lott, JG

Location:
LMDZ4/branches/LMDZ4_AR5/libf/phylmd
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_output_mod.F90

    r1400 r1405  
    12241224     ENDIF
    12251225
    1226       if (nqtot>=3) THEN
    1227 !Attention    DO iq=3,nqtot
    1228     DO iq=3,4 
    1229        iiq=niadv(iq)
    1230 ! CALL histdef3d (iff, o_trac%flag,'o_'//tnom(iq)%name,ttext(iiq), "-" )
    1231   CALL histdef3d (iff, o_trac(iq-2)%flag,o_trac(iq-2)%name,ttext(iiq), "-" )
    1232     ENDDO
    1233       endif
     1226
     1227!Attention : sorties uniquement pour traceurs 3 et 4
     1228     IF (nqtot>=3) THEN
     1229        IF (tname(3) == "Aga" .OR. tname(3)=="AGA") THEN
     1230           o_trac(1)%name= "Aga"
     1231           ttext(3)= "Age stratospheric air"
     1232        END IF
     1233        CALL histdef3d (iff, o_trac(1)%flag,o_trac(1)%name,ttext(3), "-" )
     1234     END IF
     1235     
     1236     IF (nqtot>=4) CALL histdef3d (iff, o_trac(2)%flag,o_trac(2)%name,ttext(4), "-" )
     1237
    12341238
    12351239        CALL histend(nid_files(iff))
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_output_write.h

    r1398 r1405  
    15091509        ENDIF
    15101510
    1511 !       IF (o_trac%flag(iff)<=lev_files(iff)) THEN
    1512          if (nqtot.GE.3) THEN
    1513 !           DO iq=3,nqtot
    1514            DO iq=3,4
    1515        IF (o_trac(iq-2)%flag(iff)<=lev_files(iff)) THEN
    1516          CALL histwrite_phy(nid_files(iff),
    1517      s                  o_trac(iq-2)%name,itau_w,qx(:,:,iq))
    1518        ENDIF
    1519            ENDDO
    1520          endif
     1511
     1512        IF (nqtot.GE.3 .AND. o_trac(1)%flag(iff)<=lev_files(iff)) THEN
     1513           CALL histwrite_phy(nid_files(iff),
     1514     s          o_trac(1)%name,itau_w,qx(:,:,3))
     1515        ENDIF
     1516
     1517        IF (nqtot.GE.4 .AND. o_trac(2)%flag(iff)<=lev_files(iff)) THEN
     1518           CALL histwrite_phy(nid_files(iff),
     1519     s          o_trac(2)%name,itau_w,qx(:,:,4))
     1520        ENDIF
     1521
     1522
    15211523
    15221524      if (ok_sync) then
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/traclmdz_mod.F90

    r1279 r1405  
    3535!$OMP THREADPRIVATE(id_be)
    3636
    37   LOGICAL,SAVE :: rnpb=.TRUE. ! Presence du couple Rn222, Pb210
     37  INTEGER,SAVE :: id_aga      ! Identification number for tracer : Age of stratospheric air
     38!$OMP THREADPRIVATE(id_aga)
     39  INTEGER,SAVE :: lev_1p5km   ! Approximative vertical layer number at 1.5km above surface, used for calculation of the age of air. The result shouldn't be that sensible to the exactness of this value as long as it is in the lower troposphere.
     40!$OMP THREADPRIVATE(lev_1p5km)
     41
     42  INTEGER,SAVE :: id_rn, id_pb ! Identification number for tracer : radon (Rn222), lead (Pb210)
     43  !$OMP THREADPRIVATE(id_rn, id_pb)
     44  LOGICAL,SAVE :: rnpb=.FALSE. ! Presence du couple Rn222, Pb210
    3845!$OMP THREADPRIVATE(rnpb)
    3946
     47 
    4048
    4149CONTAINS
     
    123131! Recherche des traceurs connus : Be7, CO2,...
    124132! --------------------------------------------
    125     id_be=0
     133    id_rn=0; id_pb=0; id_aga=0; id_be=0
    126134    DO it=1,nbtr
    127135       iiq=niadv(it+2)
    128        IF ( tname(iiq) == "BE" .OR. tname(iiq) == "Be" .OR.  &
     136       IF ( tname(iiq) == "RN" ) THEN
     137          id_rn=it ! radon
     138       ELSE IF ( tname(iiq) == "PB") THEN
     139          id_pb=it ! plomb
     140       ELSE IF ( tname(iiq) == "Aga" .OR. tname(iiq) == "AGA" ) THEN
     141          ! Age of stratospheric air
     142          id_aga=it
     143          radio(id_aga) = .FALSE.
     144          aerosol(id_aga) = .FALSE.
     145          pbl_flg(id_aga) = 0
     146
     147          ! Find the first model layer above 1.5km from the surface
     148          IF (klev>=30) THEN
     149             lev_1p5km=6   ! NB! This value is for klev=39
     150          ELSE IF (klev>=10) THEN
     151             lev_1p5km=5   ! NB! This value is for klev=19
     152          ELSE
     153             lev_1p5km=klev/2
     154          END IF
     155       ELSE IF ( tname(iiq) == "BE" .OR. tname(iiq) == "Be" .OR.  &
    129156            tname(iiq) == "BE7" .OR. tname(iiq) == "Be7" ) THEN 
    130157          ! Recherche du Beryllium 7
     
    135162          CALL init_be(pctsrf,masktr(:,id_be),tautr(id_be),vdeptr(id_be),scavtr(id_be),srcbe)
    136163          WRITE(*,*) 'Initialisation srcBe: OK'
    137        END IF   
     164       END IF
     165       
    138166    END DO
    139167!
    140168! Valeurs specifiques pour les traceurs Rn222 et Pb210
    141169! ----------------------------------------------
    142     IF (rnpb) THEN
    143         
     170    IF ( id_rn/=0 .AND. id_pb/=0 ) THEN
     171       rnpb = .TRUE.
    144172       radio(1)= .TRUE.
    145173       radio(2)= .TRUE.
     
    249277       WRITE(solsym(it),'(i2)') it
    250278    END DO
     279
     280!
     281! Update tracer : Age of stratospheric air
     282!
     283    IF (id_aga/=0) THEN
     284       
     285       ! Bottom layers
     286       DO k = 1, lev_1p5km
     287          tr_seri(:,k,id_aga) = 0.0
     288       END DO
     289       
     290       ! Layers above 1.5km
     291       DO k = lev_1p5km+1,klev-1
     292          tr_seri(:,k,id_aga) = tr_seri(:,k,id_aga) + pdtphys
     293       END DO
     294       
     295       ! Top layer
     296       tr_seri(:,klev,id_aga) = tr_seri(:,klev-1,id_aga)
     297       
     298    END IF
     299
    251300!======================================================================
    252301!     -- Calcul de l'effet de la couche limite --
     
    273322   
    274323    DO it=1, nbtr
    275        IF (couchelimite .AND. pbl_flg(it) == 0 ) THEN ! couche limite avec quantite dans le sol calculee
     324       IF (couchelimite .AND. pbl_flg(it) == 0 .AND. rnpb) THEN ! couche limite avec quantite dans le sol calculee
    276325          CALL cltracrn(it, pdtphys, yu1, yv1,     &
    277326               cdragh, coefh,t_seri,ftsol,pctsrf,  &
Note: See TracChangeset for help on using the changeset viewer.