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/ozonecm_m.F90

    r1188 r1215  
    66contains
    77
    8   SUBROUTINE ozonecm(rjour,rlat,paprs,o3)
     8  function ozonecm(rjour,rlat,paprs)
    99
    1010    ! The ozone climatology is based on an analytic formula which fits the
     
    2222
    2323    USE dimphy, only: klon, klev
     24    use assert_m, only: assert
    2425
    2526    REAL, INTENT (IN) :: rjour
    26     REAL, INTENT (IN) :: rlat(klon), paprs(klon,klev+1)
    27     REAL o3(klon,klev)
    28     ! "o3(j, k)" is the column-density of ozone in cell "(j, k)", that is
     27    REAL, INTENT (IN) :: rlat(:) ! (klon)
     28    REAL, INTENT (IN) :: paprs(:, :) ! (klon,klev+1)
     29
     30    REAL ozonecm(klon,klev)
     31    ! "ozonecm(j, k)" is the column-density of ozone in cell "(j, k)", that is
    2932    ! between interface "k" and interface "k + 1", in kDU.
    3033
     
    4750    !----------------------------------------------------------
    4851
     52    call assert((/size(rlat), size(paprs, 1)/) == klon, "ozonecm klon")
     53    call assert(size(paprs, 2) == klev + 1, "ozonecm klev")
     54
    4955    pi = 4. * atan(1.)
    5056    DO k = 1, klev
    5157       DO i = 1, klon
    5258          zslat = sin(pi / 180. * rlat(i))
    53           zsint = sin(2.*pi*(rjour+15.)/an)
    54           zcost = cos(2.*pi*(rjour+15.)/an)
     59          zsint = sin(2 * pi * (rjour + 15.) / an)
     60          zcost = cos(2 * pi * (rjour + 15.) / an)
    5561          z = 0.0531 + zsint * (-0.001595+0.009443*zslat) &
    5662               + zcost * (-0.001344-0.00346*zslat) &
     
    7985
    8086    field(:,klev+1) = 0.
    81     forall (k = 1: klev) o3(:,k) = field(:,k) - field(:,k+1)
     87    forall (k = 1: klev) ozonecm(:,k) = field(:,k) - field(:,k+1)
    8288
    83   END SUBROUTINE ozonecm
     89  END function ozonecm
    8490
    8591end module ozonecm_m
Note: See TracChangeset for help on using the changeset viewer.