Ignore:
Timestamp:
May 6, 2010, 2:19:18 PM (14 years ago)
Author:
lguez
Message:

Added optional ozone tracer with chemistry parameterized by Daniel
Cariolle. This tracer is passive: it has no influence on the rest of
the simulation.

Added variable "zmasse" in file "histrac.nc". Corrected long name of
variable "pplay" in "histrac.nc". Changed name of variable "t" to "T"
in "histrac.nc", corrected long name and unit.

In "phytrac", moved definition of "zmasse" toward the beginning of the
procedure, so that "zmasse" can be given as argument to
"traclmdz". Also added arguments "julien", "gmtime" and "xlon" to
"traclmdz". The four additional arguments are required for the ozone
tracer.

In module "traclmdz_mod", factorized declaration "implicit none" that
was in each procedure. There is now an equivalent single declaration
at the module level.

In procedure "traclmdz", removed variable "delp". Use "zmasse * rg"
instead since we now have "zmasse" as an argument.

Tests. Compilations on Brodie only, with optimization options "-debug"
and "-dev", parallelization options "none", "mpi", "omp" and
"mpi_omp", this revision and revision 1373. Run cases with and without
ozone tracer, 1 and 2 MPI processes, 1 and 2 OpenMP
threads. Comparisons of all cases are ok, except for strange
variations in variables "d_tr_cl_RN" and "d_tr_cl_PB" of file
"histrac.nc", variables "RN" and "PB" of "restart.nc", variables
"trs_RN" and "trs_PB" of "restartphy.nc". Relative variations of these
variables between cases are of order 1e-7 or less, after one day of
simulation.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/traclmdz_mod.F90

    r1376 r1379  
    66! only if running without any other chemestry model as INCA or REPROBUS. 
    77!
     8
     9  IMPLICIT NONE
    810
    911  REAL,DIMENSION(:,:),ALLOCATABLE,SAVE :: masktr   ! Masque reservoir de sol traceur
     
    4446!$OMP THREADPRIVATE(id_pcs0, id_pcos0, id_pcq0)
    4547
     48  INTEGER, SAVE:: id_o3
     49  !$OMP THREADPRIVATE(id_o3)
     50  ! index of ozone tracer with Cariolle parameterization
     51  ! 0 means no ozone tracer
     52
    4653  LOGICAL,SAVE :: rnpb=.TRUE. ! Presence du couple Rn222, Pb210
    4754!$OMP THREADPRIVATE(rnpb)
     
    5663    USE dimphy
    5764    USE infotrac
    58     IMPLICIT NONE
    5965   
    6066    ! Input argument
     
    7884    USE dimphy
    7985    USE infotrac
     86    USE regr_pr_comb_coefoz_m, ONLY: alloc_coefoz
     87    USE press_coefoz_m, ONLY: press_coefoz
    8088    USE carbon_cycle_mod, ONLY : carbon_cycle_init, carbon_cycle_tr, carbon_cycle_cpl
    81 
    82     IMPLICIT NONE
    8389
    8490    INCLUDE "indicesol.h"
     
    135141   
    136142!
    137 ! Recherche des traceurs connus : Be7, CO2,...
     143! Recherche des traceurs connus : Be7, O3, CO2,...
    138144! --------------------------------------------
    139145    id_be=0
     146    id_o3=0
    140147    DO it=1,nbtr
    141148       iiq=niadv(it+2)
     
    149156          CALL init_be(pctsrf,masktr(:,id_be),tautr(id_be),vdeptr(id_be),scavtr(id_be),srcbe)
    150157          WRITE(*,*) 'Initialisation srcBe: OK'
     158       ELSE IF (tname(iiq)=="O3" .OR. tname(iiq)=="o3") THEN
     159          ! Recherche de l'ozone : parametrization de la chimie par Cariolle
     160          id_o3=it
     161          CALL alloc_coefoz   ! allocate ozone coefficients
     162          CALL press_coefoz   ! read input pressure levels
    151163       END IF   
    152164    END DO
     
    311323  END SUBROUTINE traclmdz_init
    312324
    313   SUBROUTINE traclmdz(                           &
    314        nstep,    pdtphys,      t_seri,           &
    315        paprs,    pplay,        cdragh,  coefh,   &
    316        yu1,      yv1,          ftsol,   pctsrf,  &
    317        xlat,     couchelimite, sh,               &
    318        tr_seri,  source,       solsym,  d_tr_cl)
     325  SUBROUTINE traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, &
     326       cdragh,  coefh, yu1, yv1, ftsol, pctsrf, xlat, xlon, couchelimite, sh, &
     327       tr_seri, source, solsym, d_tr_cl, zmasse)
    319328   
    320329    USE dimphy
    321330    USE infotrac
     331    USE regr_pr_comb_coefoz_m, ONLY: regr_pr_comb_coefoz
     332    USE o3_chem_m, ONLY: o3_chem
    322333    USE carbon_cycle_mod, ONLY : carbon_cycle, carbon_cycle_tr, carbon_cycle_cpl
    323    
    324     IMPLICIT NONE
    325    
    326334    INCLUDE "YOMCST.h"
    327335    INCLUDE "indicesol.h"
     
    335343!Configuration grille,temps:
    336344    INTEGER,INTENT(IN) :: nstep      ! nombre d'appels de la physiq
     345    INTEGER,INTENT(IN) :: julien     ! Jour julien
     346    REAL,INTENT(IN)    :: gmtime
    337347    REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde) 
    338348    REAL,DIMENSION(klon),INTENT(IN) :: xlat    ! latitudes pour chaque point
     349    REAL, INTENT(IN):: xlon(:) ! dim(klon) longitude
    339350
    340351!
     
    344355    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
    345356    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
     357    REAL,intent(in):: zmasse (:, :)   ! dim(klon,klev) density of air, in kg/m2
    346358
    347359
     
    375387
    376388    INTEGER :: i, k, it
     389    INTEGER lmt_pas ! number of time steps of "physics" per day
    377390
    378391    REAL,DIMENSION(klon)           :: d_trs    ! Td dans le reservoir
    379     REAL,DIMENSION(klon,klev)      :: delp     ! epaisseur de couche (Pa)
    380    
    381392    REAL,DIMENSION(klon,klev,nbtr) :: d_tr_dec ! Td radioactive
    382393    REAL                           :: zrho      ! Masse Volumique de l'air KgA/m3
     
    485496    END IF
    486497   
    487 
    488     DO k = 1, klev
    489        DO i = 1, klon
    490           delp(i,k) = paprs(i,k)-paprs(i,k+1)
    491        END DO
    492     END DO
    493    
    494498    DO it=1, nbtr
    495499       IF (couchelimite .AND. pbl_flg(it) == 0 ) THEN ! couche limite avec quantite dans le sol calculee
     
    497501               cdragh, coefh,t_seri,ftsol,pctsrf,  &
    498502               tr_seri(:,:,it),trs(:,it),          &
    499                paprs, pplay, delp,                &
     503               paprs, pplay, zmasse * rg, &
    500504               masktr(:,it),fshtr(:,it),hsoltr(it),&
    501505               tautr(it),vdeptr(it),               &
     
    592596
    593597!======================================================================
     598!   Parameterization of ozone chemistry
     599!======================================================================
     600
     601    IF (id_o3 /= 0) then
     602       lmt_pas = NINT(86400./pdtphys)
     603       IF (MOD(nstep - 1, lmt_pas) == 0) THEN
     604          ! Once per day, update the coefficients for ozone chemistry:
     605          CALL regr_pr_comb_coefoz(julien, xlat, paprs, pplay)
     606       END IF
     607       CALL o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, xlat, &
     608            xlon, tr_seri(:, :, id_o3))
     609    END IF
     610
     611!======================================================================
    594612!   Calcul de cycle de carbon
    595613!======================================================================
     
    607625    USE infotrac
    608626   
    609     IMPLICIT NONE
    610    
    611627    REAL,DIMENSION(klon,nbtr), INTENT(OUT) :: trs_out
    612628    INTEGER :: ierr
Note: See TracChangeset for help on using the changeset viewer.