Ignore:
Timestamp:
Jun 18, 2009, 5:50:11 PM (16 years ago)
Author:
lguez
Message:

Translated calls using NetCDF 2.4 interface to calls using NetCDF 3.6
Fortran 90 interface.
Corrected a few comments in "output.def".

Location:
LMDZ4/branches/LMDZ4-dev/libf/phylmd
Files:
1 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/ozonecm_m.F90

    r1182 r1188  
    1 !
    21! $Header$
    3 !
    4       SUBROUTINE ozonecm(rjour, rlat, paprs, o3)
    5       USE dimphy
    6       IMPLICIT none
    7 C
    8 C The ozone climatology is based on an analytic formula which fits the
    9 C Krueger and Mintzner (1976) profile, as well as the variations with
    10 C altitude and latitude of the maximum ozone concentrations and the total
    11 C column ozone concentration of Keating and Young (1986). The analytic
    12 C formula have been established by J-F Royer (CRNM, Meteo France), who
    13 C also provided us the code.
    14 C
    15 C A. J. Krueger and R. A. Minzner, A Mid-Latitude Ozone Model for the
    16 C 1976 U.S. Standard Atmosphere, J. Geophys. Res., 81, 4477, (1976).
    17 C
    18 C Keating, G. M. and D. F. Young, 1985: Interim reference models for the
    19 C middle atmosphere, Handbook for MAP, vol. 16, 205-229.
    20 C
     2module ozonecm_m
    213
    22 cym#include "dimensions.h"
    23 cym#include "dimphy.h"
    24 #include "clesphys.h"
    25 #include "YOMCST.h"
    26       REAL rlat(klon), paprs(klon,klev+1)
    27       REAL o3(klon,klev)   ! ozone concentration in kg/kg
    28       REAL tozon, rjour, pi, pl
    29       INTEGER i, k
    30 C----------------------------------------------------------
    31       REAL field(klon,klev+1)
    32       REAL ps
    33       PARAMETER (ps=101325.0)
    34       REAL an, unit, zo3q3
    35       SAVE an, unit, zo3q3
    36 c$OMP THREADPRIVATE(an, unit, zo3q3)
    37       REAL mu,gms, zslat, zsint, zcost, z, ppm, qpm, a
    38       REAL asec, bsec, aprim, zo3a3
    39 C----------------------------------------------------------
    40 c         data an /365.25/   (meteo)
    41       DATA an /360.00/
    42       DATA unit /2.1415e-05/
    43       DATA zo3q3 /4.0e-08/
     4  IMPLICIT NONE
    445
    45       pi = 4.0 * ATAN(1.0)
    46       DO k = 1, klev
    47       DO i = 1, klon
    48       zslat = SIN(pi/180.*rlat(i))
    49       zsint = SIN(2.*pi*(rjour+15.)/an)
    50       zcost = COS(2.*pi*(rjour+15.)/an)
    51       z = 0.0531+zsint*(-0.001595+0.009443*zslat) +
    52      .  zcost*(-0.001344-0.00346*zslat) +
    53      .  zslat**2*(.056222+zslat**2*(-.037609
    54      . +.012248*zsint+.00521*zcost+.008890*zslat))
    55       zo3a3 = zo3q3/ps/2.
    56       z = z-zo3q3*ps
    57       gms = z
    58       mu = ABS(sin(pi/180.*rlat(i)))
    59       ppm = 800.-(500.*zslat+150.*zcost)*zslat
    60       qpm = 1.74e-5-(7.5e-6*zslat+1.7e-6*zcost)*zslat
    61       bsec = 2650.+5000.*zslat**2
    62       a = 4.0*(bsec)**(3./2.)*(ppm)**(3./2.)*(1.0+(bsec/ps)**(3./2.))
    63       a = a/(bsec**(3./2.)+ppm**(3./2.))**2
    64       aprim = (2.666666*qpm*ppm-a*gms)/(1.0-a)
    65       aprim = amax1(0.,aprim)
    66       asec = (gms-aprim)*(1.0+(bsec/ps)**(3./2.))
    67       asec = AMAX1(0.0,asec)
    68       aprim = gms-asec/(1.+(bsec/ps)**(3./2.))
    69       pl = paprs(i,k)
    70       tozon = aprim/(1.+3.*(ppm/pl)**2)+asec/(1.+(bsec/pl)**(3./2.))
    71      .  + zo3a3*pl*pl
    72       tozon = tozon / 9.81  ! en kg/m**2
    73       tozon = tozon / unit  ! en kg/m**2  > u dobson (10e-5 m)
    74       tozon = tozon / 1000. ! en cm
    75       field(i,k) = tozon
    76       ENDDO
    77       ENDDO
    78 c
    79       DO i = 1, klon
    80          field(i,klev+1) = 0.0
    81       ENDDO
    82       DO k = 1, klev
    83         DO i = 1, klon
    84           o3(i,k) = field(i,k) - field(i,k+1)
    85         ENDDO
    86       ENDDO
    87 c
    88       RETURN
    89       END
     6contains
     7
     8  SUBROUTINE ozonecm(rjour,rlat,paprs,o3)
     9
     10    ! The ozone climatology is based on an analytic formula which fits the
     11    ! Krueger and Mintzner (1976) profile, as well as the variations with
     12    ! altitude and latitude of the maximum ozone concentrations and the total
     13    ! column ozone concentration of Keating and Young (1986). The analytic
     14    ! formula have been established by J.-F. Royer (CRNM, Meteo France), who
     15    ! also provided us the code.
     16
     17    ! A. J. Krueger and R. A. Minzner, A Mid-Latitude Ozone Model for the
     18    ! 1976 U.S. Standard Atmosphere, J. Geophys. Res., 81, 4477, (1976).
     19
     20    ! Keating, G. M. and D. F. Young, 1985: Interim reference models for the
     21    ! middle atmosphere, Handbook for MAP, vol. 16, 205-229.
     22
     23    USE dimphy, only: klon, klev
     24
     25    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
     29    ! between interface "k" and interface "k + 1", in kDU.
     30
     31    ! Variables local to the procedure:
     32
     33    REAL tozon ! equivalent pressure of ozone above interface "k", in Pa
     34    real pi, pl
     35    INTEGER i, k
     36
     37    REAL field(klon,klev+1)
     38    ! "field(:, k)" is the column-density of ozone between interface
     39    ! "k" and the top of the atmosphere (interface "llm + 1"), in kDU.
     40
     41    real, PARAMETER:: ps=101325.
     42    REAL, parameter:: an = 360., zo3q3 = 4E-8
     43    REAL, parameter:: dobson_unit = 2.1415E-5 ! in kg m-2
     44    REAL gms, zslat, zsint, zcost, z, ppm, qpm, a
     45    REAL asec, bsec, aprim, zo3a3
     46
     47    !----------------------------------------------------------
     48
     49    pi = 4. * atan(1.)
     50    DO k = 1, klev
     51       DO i = 1, klon
     52          zslat = sin(pi / 180. * rlat(i))
     53          zsint = sin(2.*pi*(rjour+15.)/an)
     54          zcost = cos(2.*pi*(rjour+15.)/an)
     55          z = 0.0531 + zsint * (-0.001595+0.009443*zslat) &
     56               + zcost * (-0.001344-0.00346*zslat) &
     57               + zslat**2 * (.056222 + zslat**2 &
     58               * (-.037609+.012248*zsint+.00521*zcost+.008890*zslat))
     59          zo3a3 = zo3q3/ps/2.
     60          z = z - zo3q3*ps
     61          gms = z
     62          ppm = 800. - (500.*zslat+150.*zcost)*zslat
     63          qpm = 1.74E-5 - (7.5E-6*zslat+1.7E-6*zcost)*zslat
     64          bsec = 2650. + 5000.*zslat**2
     65          a = 4.0*(bsec)**(3./2.)*(ppm)**(3./2.)*(1.0+(bsec/ps)**(3./2.))
     66          a = a/(bsec**(3./2.)+ppm**(3./2.))**2
     67          aprim = (2.666666*qpm*ppm-a*gms)/(1.0-a)
     68          aprim = amax1(0., aprim)
     69          asec = (gms-aprim)*(1.0+(bsec/ps)**(3./2.))
     70          asec = amax1(0.0, asec)
     71          aprim = gms - asec/(1.+(bsec/ps)**(3./2.))
     72          pl = paprs(i, k)
     73          tozon = aprim / (1. + 3. * (ppm / pl)**2) &
     74               + asec / (1. + (bsec / pl)**(3./2.)) + zo3a3 * pl * pl
     75          ! Convert from Pa to kDU:
     76          field(i, k) = tozon / 9.81 / dobson_unit / 1e3
     77       END DO
     78    END DO
     79
     80    field(:,klev+1) = 0.
     81    forall (k = 1: klev) o3(:,k) = field(:,k) - field(:,k+1)
     82
     83  END SUBROUTINE ozonecm
     84
     85end module ozonecm_m
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/physiq.F

    r1183 r1188  
    3434      use mod_phys_lmdz_mpi_data, only: is_mpi_root
    3535      USE aero_mod
     36      use ozonecm_m, only: ozonecm ! ozone of J.-F. Royer
    3637
    3738      IMPLICIT none
     
    735736      EXTERNAL o3cm      ! initialiser l'ozone
    736737      EXTERNAL orbite    ! calculer l'orbite terrestre
    737       EXTERNAL ozonecm   ! prescrire l'ozone
    738738      EXTERNAL phyetat0  ! lire l'etat initial de la physique
    739739      EXTERNAL phyredem  ! ecrire l'etat de redemarrage de la physique
Note: See TracChangeset for help on using the changeset viewer.