Ignore:
Timestamp:
Mar 5, 2014, 2:19:12 PM (10 years ago)
Author:
lguez
Message:

Converted to free source form files in libf/phylmd which were still in
fixed source form. The conversion was done using the polish mode of
the NAG Fortran Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

-- replaced #include by include.

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/o3cm.F90

    r1988 r1992  
    1 !
     1
    22! $Id$
    3 !
    4       SUBROUTINE o3cm (amb, bmb, sortie, ntab)
    5       IMPLICIT none
    6 c======================================================================
    7 c Auteur(s): Z.X. Li (LMD/CNRS) date: 19930818
    8 c Objet: Ce programme calcule le contenu en ozone "sortie"
    9 c        (unite: cm.atm) entre deux niveaux "amb" et "bmb" (unite: mb)
    10 c        "ntab" est le nombre d'intervalles pour l'integration, sa
    11 c        valeur depend bien sur de l'epaisseur de la couche et de
    12 c        la precision qu'on souhaite a obtenir
    13 c======================================================================
    14       REAL amb, bmb, sortie
    15       INTEGER ntab
    16 c======================================================================
    17       INTEGER n
    18       REAL xtab(500), xa, xb, ya, yb, xincr
    19 c======================================================================
    20       external mbtozm
    21       CHARACTER (LEN=20) :: modname=''
    22       CHARACTER (LEN=80) :: abort_message
    23 c======================================================================
    24 c la fonction en ligne w(x) donne le profil de l'ozone en fonction
    25 c de l'altitude (unite: cm.atm / km)
    26 c (Green 1964, Appl. Opt. 3: 203-208)
    27       REAL wp, xp, h, x, w, con
    28       PARAMETER (wp=0.218, xp=23.25, h=4.63, con=1.0)
    29       w(x) = wp/h * EXP((x-xp)/h)/ (con+EXP((x-xp)/h))**2
    30 c======================================================================
    31       IF (ntab .GT. 499) THEN
    32         abort_message = 'BIG ntab'
    33         CALL abort_gcm (modname,abort_message,1)
    34       ENDIF
    35       xincr = (bmb-amb) / REAL(ntab)
    36       xtab(1) = amb
    37       DO n = 2, ntab
    38          xtab(n) = xtab(n-1) + xincr
    39       ENDDO
    40       xtab(ntab+1) = bmb
    41       sortie = 0.0
    42       DO n = 1, ntab
    43          CALL mbtozm(xtab(n), xa)
    44          CALL mbtozm(xtab(n+1), xb)
    45          xa = xa / 1000.
    46          xb = xb / 1000.
    47          ya = w(xa)
    48          yb = w(xb)
    49          sortie = sortie + (ya+yb)/2.0 * ABS(xb-xa)
    50       ENDDO
    51       RETURN
    52       END
    53       SUBROUTINE mbtozm(rmb,zm)
    54       IMPLICIT none
    55 c======================================================================
    56 c Auteur(s): Z.X. Li (LMD/CNRS)
    57 c Objet: transformer une hauteur de mb (rmb) en metre (zm)
    58 c======================================================================
    59       REAL rmb, zm
    60 c======================================================================
    61       REAL gama, tzero, pzero, g, r
    62       PARAMETER (gama=6.5e-3, tzero=288., pzero=1013.25)
    63       PARAMETER (g=9.81, r=287.0)
    64       zm = tzero/gama * ( 1.-(rmb/pzero)**(r*gama/g) )
    65       RETURN
    66       END
     3
     4SUBROUTINE o3cm(amb, bmb, sortie, ntab)
     5  IMPLICIT NONE
     6  ! ======================================================================
     7  ! Auteur(s): Z.X. Li (LMD/CNRS) date: 19930818
     8  ! Objet: Ce programme calcule le contenu en ozone "sortie"
     9  ! (unite: cm.atm) entre deux niveaux "amb" et "bmb" (unite: mb)
     10  ! "ntab" est le nombre d'intervalles pour l'integration, sa
     11  ! valeur depend bien sur de l'epaisseur de la couche et de
     12  ! la precision qu'on souhaite a obtenir
     13  ! ======================================================================
     14  REAL amb, bmb, sortie
     15  INTEGER ntab
     16  ! ======================================================================
     17  INTEGER n
     18  REAL xtab(500), xa, xb, ya, yb, xincr
     19  ! ======================================================================
     20  EXTERNAL mbtozm
     21  CHARACTER (LEN=20) :: modname = ''
     22  CHARACTER (LEN=80) :: abort_message
     23  ! ======================================================================
     24  ! la fonction en ligne w(x) donne le profil de l'ozone en fonction
     25  ! de l'altitude (unite: cm.atm / km)
     26  ! (Green 1964, Appl. Opt. 3: 203-208)
     27  REAL wp, xp, h, x, w, con
     28  PARAMETER (wp=0.218, xp=23.25, h=4.63, con=1.0)
     29
     30  w(x) = wp/h*exp((x-xp)/h)/(con+exp((x-xp)/h))**2
     31  ! ======================================================================
     32  IF (ntab>499) THEN
     33    abort_message = 'BIG ntab'
     34    CALL abort_gcm(modname, abort_message, 1)
     35  END IF
     36  xincr = (bmb-amb)/real(ntab)
     37  xtab(1) = amb
     38  DO n = 2, ntab
     39    xtab(n) = xtab(n-1) + xincr
     40  END DO
     41  xtab(ntab+1) = bmb
     42  sortie = 0.0
     43  DO n = 1, ntab
     44    CALL mbtozm(xtab(n), xa)
     45    CALL mbtozm(xtab(n+1), xb)
     46    xa = xa/1000.
     47    xb = xb/1000.
     48    ya = w(xa)
     49    yb = w(xb)
     50    sortie = sortie + (ya+yb)/2.0*abs(xb-xa)
     51  END DO
     52  RETURN
     53END SUBROUTINE o3cm
     54SUBROUTINE mbtozm(rmb, zm)
     55  IMPLICIT NONE
     56  ! ======================================================================
     57  ! Auteur(s): Z.X. Li (LMD/CNRS)
     58  ! Objet: transformer une hauteur de mb (rmb) en metre (zm)
     59  ! ======================================================================
     60  REAL rmb, zm
     61  ! ======================================================================
     62  REAL gama, tzero, pzero, g, r
     63  PARAMETER (gama=6.5E-3, tzero=288., pzero=1013.25)
     64  PARAMETER (g=9.81, r=287.0)
     65
     66  zm = tzero/gama*(1.-(rmb/pzero)**(r*gama/g))
     67  RETURN
     68END SUBROUTINE mbtozm
Note: See TracChangeset for help on using the changeset viewer.