/[lmdze]/trunk/phylmd/test_ozonecm.f90
ViewVC logotype

Diff of /trunk/phylmd/test_ozonecm.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/test_ozonecm.f revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC trunk/phylmd/test_ozonecm.f revision 304 by guez, Thu Sep 6 15:51:09 2018 UTC
# Line 1  Line 1 
1  program test_ozonecm  program test_ozonecm
2    
3    ! This is a program in Fortran 95.    ! This is a program in Fortran 2003.
4    
5    ! This program computes values of ozone abundance from Royer, on a    ! This program computes values of ozone abundance from Royer, on a
6    ! latitude-pressure grid, and writes the values to a NetCDF file.    ! latitude-pressure grid, and writes the values to a NetCDF file.
7    ! The pressure grid is "presnivs" from "disvert".    ! The pressure grid is "presnivs" from "disvert".
8    
   use dimens_m, only: jjm, llm  
   USE dimphy, ONLY : klon  
   use disvert_m, only: pa, disvert, ap, bp, preff, presnivs  
   use jumble, only: new_unit  
   use ozonecm_m, only: ozonecm  
   use phyetat0_m, only: rlat  
9    use nr_util, only: arth, assert    use nr_util, only: arth, assert
10    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, nf95_put_att, &    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, nf95_put_att, &
11         nf95_enddef, nf95_put_var, nf95_close         nf95_enddef, nf95_put_var, nf95_close
12    use netcdf, only: nf90_clobber, nf90_float, nf90_global    use netcdf, only: nf90_clobber, nf90_float, nf90_global
13    use unit_nml_m, only: unit_nml  
14      use dimensions, only: jjm, llm
15      USE dimphy, ONLY : klon
16      USE dimsoil, ONLY : nsoilmx
17      use disvert_m, only: pa, disvert, ap, bp, preff, presnivs
18      USE indicesol, ONLY : nbsrf
19      use ozonecm_m, only: ozonecm
20      use phyetat0_m, only: rlat, phyetat0
21      use unit_nml_m, only: unit_nml, set_unit_nml
22    
23    implicit none    implicit none
24    
# Line 27  program test_ozonecm Line 29  program test_ozonecm
29    real, parameter:: RG = 9.80665 ! acceleration of gravity, in m s-2    real, parameter:: RG = 9.80665 ! acceleration of gravity, in m s-2
30    real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2    real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
31    
32      REAL pctsrf(klon, nbsrf)
33      REAL ftsol(klon, nbsrf)
34      REAL ftsoil(klon, nsoilmx, nbsrf)
35      REAL qsurf(klon, nbsrf)
36      REAL qsol(klon) ! column-density of water in soil, in kg m-2
37      REAL snow(klon, nbsrf)
38      REAL albe(klon, nbsrf)
39      REAL rain_fall(klon)
40      REAL snow_fall(klon)
41      real solsw(klon)
42      REAL sollw(klon)
43      real fder(klon)
44      REAL radsol(klon)
45      REAL frugs(klon, nbsrf)
46      REAL agesno(klon, nbsrf)
47      REAL zmea(klon)
48      REAL zstd(klon)
49      REAL zsig(klon)
50      REAL zgam(klon)
51      REAL zthe(klon)
52      REAL zpic(klon)
53      REAL zval(klon)
54      REAL t_ancien(klon, llm), q_ancien(klon, llm)
55      LOGICAL ancien_ok
56      real rnebcon(klon, llm), ratqs(klon, llm)
57      REAL clwcon(klon, llm), run_off_lic_0(klon)
58      real sig1(klon, llm) ! section adiabatic updraft
59    
60      real w01(klon, llm)
61      ! vertical velocity within adiabatic updraft
62    
63      integer ncid_startphy
64    
65    ! For NetCDF:    ! For NetCDF:
66    integer ncid, dimid_time, dimid_plev, dimid_latitude    integer ncid, dimid_time, dimid_plev, dimid_latitude
67    integer varid_time, varid_plev, varid_latitude, varid_tro3    integer varid_time, varid_plev, varid_latitude, varid_tro3
# Line 35  program test_ozonecm Line 70  program test_ozonecm
70    
71    call assert(klon == jjm + 1, "test_ozonecm: iim should be 1")    call assert(klon == jjm + 1, "test_ozonecm: iim should be 1")
72    
73    call new_unit(unit_nml)    call set_unit_nml
74    open(unit_nml, file="used_namelists.txt", status="replace", action="write")    open(unit_nml, file="used_namelists.txt", status="replace", action="write")
75    
76    pa = 5e4    pa = 5e4
77    call disvert    call disvert
78    p = ap + bp * preff    p = ap + bp * preff
79    rlat = arth(-90., 180. / jjm, jjm + 1)    call phyetat0(pctsrf, ftsol, ftsoil, qsurf, qsol, snow, albe, rain_fall, &
80           snow_fall, solsw, sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, &
81           zgam, zthe, zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, &
82           clwcon, run_off_lic_0, sig1, w01, ncid_startphy)
83    
84    do julien = 1, 360    do julien = 1, 360
85       wo(:, :, julien) = ozonecm(REAL(julien), spread(p, dim=1, ncopies=jjm+1))       wo(:, :, julien) = ozonecm(REAL(julien), spread(p, dim=1, ncopies=jjm+1))

Legend:
Removed from v.134  
changed lines
  Added in v.304

  ViewVC Help
Powered by ViewVC 1.1.21