Ignore:
Timestamp:
Jul 23, 2009, 5:52:59 PM (15 years ago)
Author:
lguez
Message:

-- Made "ozonecm" a function instead of a subroutine. Used assumed shape
arguments in "ozonecm".

-- Corrected long name and computation of NetCDF variable "ozone" in
the files "hist*".

-- Corrected comments for ozone variables.

-- In the case "read_climoz", used variables "rmd" and "rmo3" from
"YOMCST.h" instead of writing approximate values.

-- Replaced "real*..." declarations (not conforming to Fortran standard)
by "real(kind=...)" declarations.

-- Replaced value "1./46.6968" in ozone computations by the equivalent
(but clearer) "dobson_u * 1e3" (relative difference ~ 1e-5).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/radiation_AR4.F

    r1106 r1215  
    8989C* LOCAL VARIABLES:
    9090C
    91       REAL*8 ZOZ(KDLON,KFLEV)
     91      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
     92
     93      REAL(kind=8) ZOZ(KDLON,KFLEV)
     94!     column-density of ozone in layer, in kilo-Dobsons
     95
    9296      REAL*8 ZAKI(KDLON,2)     
    9397      REAL*8 ZCLD(KDLON,KFLEV)
     
    178182      DO JL = 1, KDLON
    179183         ZCLDSW0(JL,JK) = 0.0
    180          ZOZ(JL,JK) = POZON(JL,JK)*46.6968/RG
    181      .               *PDP(JL,JK)*(101325.0/PPSOL(JL))
     184         ZOZ(JL,JK) = POZON(JL,JK) / dobson_u / 1e3 / RG * PDP(JL,JK)
     185     $        * (101325. / PPSOL(JL))
    182186      ENDDO
    183187      ENDDO
     
    24772481      REAL*8 PPMB(KDLON,KFLEV+1)  ! HALF LEVEL PRESSURE (mb)
    24782482      REAL*8 PPSOL(KDLON)         ! SURFACE PRESSURE (Pa)
    2479       REAL*8 POZON(KDLON,KFLEV)   ! O3 CONCENTRATION (kg/kg)
     2483      REAL(kind=8) POZON(KDLON,KFLEV)   ! O3 mass fraction
    24802484      REAL*8 PTL(KDLON,KFLEV+1)   ! HALF LEVEL TEMPERATURE (K)
    24812485      REAL*8 PAER(KDLON,KFLEV,5)  ! OPTICAL THICKNESS OF THE AEROSOLS
     
    25032507C-------------------------------------------------------------------------
    25042508      REAL*8 ZABCU(KDLON,NUA,3*KFLEV+1)
    2505       REAL*8 ZOZ(KDLON,KFLEV)
    2506 c
     2509
     2510      REAL(kind=8) ZOZ(KDLON,KFLEV)
     2511!     equivalent pressure of ozone in a layer, in Pa
     2512
    25072513cym      REAL*8 ZFLUX(KDLON,2,KFLEV+1) ! RADIATIVE FLUXES (1:up; 2:down)
    25082514cym      REAL*8 ZFLUC(KDLON,2,KFLEV+1) ! CLEAR-SKY RADIATIVE FLUXES
     
    25502556C
    25512557      IF (MOD(itaplw0,lw0pas).EQ.0) THEN
    2552       DO k = 1, KFLEV  ! convertir ozone de kg/kg en pa/pa
    2553       DO i = 1, KDLON
    2554 c convertir ozone de kg/kg en pa (modif MPL 100505)
    2555          ZOZ(i,k) = POZON(i,k)*PDP(i,k) * RMD/RMO3
    2556 c        print *,'LW: ZOZ*10**6=',ZOZ(i,k)*1000000.
    2557       ENDDO
     2558c     Compute equivalent pressure of ozone from mass fraction:
     2559      DO k = 1, KFLEV
     2560         DO i = 1, KDLON
     2561            ZOZ(i,k) = POZON(i,k)*PDP(i,k) * RMD/RMO3
     2562         ENDDO
    25582563      ENDDO
    25592564cIM ctes ds clesphys.h   CALL LWU(RCO2,RCH4, RN2O, RCFC11, RCFC12,
Note: See TracChangeset for help on using the changeset viewer.