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

Annotation of /trunk/phylmd/test_ozonecm.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (hide annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 4768 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 guez 123 program test_ozonecm
2    
3 guez 278 ! This is a program in Fortran 2003.
4 guez 123
5     ! This program computes values of ozone abundance from Royer, on a
6     ! latitude-pressure grid, and writes the values to a NetCDF file.
7     ! The pressure grid is "presnivs" from "disvert".
8    
9 guez 278 use nr_util, only: arth, assert
10     use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, nf95_put_att, &
11     nf95_enddef, nf95_put_var, nf95_close
12     use netcdf, only: nf90_clobber, nf90_float, nf90_global
13    
14 guez 265 use dimensions, only: jjm, llm
15 guez 123 USE dimphy, ONLY : klon
16 guez 278 USE dimsoil, ONLY : nsoilmx
17 guez 313 use disvert_m, only: disvert, ap, bp, preff, presnivs
18     use dynetat0_chosen_m, only: read_serre
19 guez 278 USE indicesol, ONLY : nbsrf
20 guez 123 use ozonecm_m, only: ozonecm
21 guez 278 use phyetat0_m, only: rlat, phyetat0
22 guez 276 use unit_nml_m, only: unit_nml, set_unit_nml
23 guez 123
24     implicit none
25    
26     real p(llm + 1) ! pressure at LMDZ layer interface, in Pa
27     real wo(klon, llm, 360) ! column density of ozone in a cell, in kDU
28     real tro3(klon, llm, 360) ! mole fraction of ozone
29     integer julien, k
30     real, parameter:: RG = 9.80665 ! acceleration of gravity, in m s-2
31     real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
32    
33 guez 278 REAL pctsrf(klon, nbsrf)
34     REAL ftsol(klon, nbsrf)
35     REAL ftsoil(klon, nsoilmx, nbsrf)
36     REAL qsurf(klon, nbsrf)
37     REAL qsol(klon) ! column-density of water in soil, in kg m-2
38     REAL snow(klon, nbsrf)
39     REAL albe(klon, nbsrf)
40     REAL rain_fall(klon)
41     REAL snow_fall(klon)
42     real solsw(klon)
43     REAL sollw(klon)
44     real fder(klon)
45     REAL radsol(klon)
46     REAL frugs(klon, nbsrf)
47     REAL agesno(klon, nbsrf)
48     REAL zmea(klon)
49     REAL zstd(klon)
50     REAL zsig(klon)
51     REAL zgam(klon)
52     REAL zthe(klon)
53     REAL zpic(klon)
54     REAL zval(klon)
55     REAL t_ancien(klon, llm), q_ancien(klon, llm)
56     LOGICAL ancien_ok
57     real rnebcon(klon, llm), ratqs(klon, llm)
58     REAL clwcon(klon, llm), run_off_lic_0(klon)
59     real sig1(klon, llm) ! section adiabatic updraft
60    
61     real w01(klon, llm)
62     ! vertical velocity within adiabatic updraft
63    
64     integer ncid_startphy
65    
66 guez 123 ! For NetCDF:
67     integer ncid, dimid_time, dimid_plev, dimid_latitude
68     integer varid_time, varid_plev, varid_latitude, varid_tro3
69    
70     !---------------------
71    
72     call assert(klon == jjm + 1, "test_ozonecm: iim should be 1")
73    
74 guez 276 call set_unit_nml
75 guez 123 open(unit_nml, file="used_namelists.txt", status="replace", action="write")
76    
77 guez 313 call read_serre
78 guez 123 call disvert
79     p = ap + bp * preff
80 guez 304 call phyetat0(pctsrf, ftsol, ftsoil, qsurf, qsol, snow, albe, rain_fall, &
81     snow_fall, solsw, sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, &
82     zgam, zthe, zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, &
83     clwcon, run_off_lic_0, sig1, w01, ncid_startphy)
84 guez 123
85     do julien = 1, 360
86     wo(:, :, julien) = ozonecm(REAL(julien), spread(p, dim=1, ncopies=jjm+1))
87     end do
88    
89     close(unit_nml)
90    
91     forall (k=1: llm)
92     tro3(:, k, :) &
93     = wo(:, k, :) * 1e3 * dobson_u / (p(k)-p(k+1)) * rg / 48. * 29.
94     end forall
95    
96     call nf95_create("O3_Royer.nc", nf90_clobber, ncid)
97     call nf95_def_dim(ncid, "time", 360, dimid_time)
98     call nf95_def_dim(ncid, "plev", llm, dimid_plev)
99     call nf95_def_dim(ncid, "latitude", jjm + 1, dimid_latitude)
100     call nf95_def_var(ncid, "time", nf90_float, dimid_time, varid_time)
101     call nf95_def_var(ncid, "plev", nf90_float, dimid_plev, varid_plev)
102     call nf95_def_var(ncid, "latitude", nf90_float, dimid_latitude, &
103     varid_latitude)
104     call nf95_def_var(ncid, "tro3", nf90_float, &
105     (/dimid_latitude, dimid_plev, dimid_time/), varid_tro3)
106    
107     call nf95_put_att(ncid, varid_time, "units", "days since 1976-1-1")
108     call nf95_put_att(ncid, varid_time, "calendar", "360_day")
109     call nf95_put_att(ncid, varid_time, "standard_name", "time")
110    
111     call nf95_put_att(ncid, varid_plev, "units", "mbar")
112     call nf95_put_att(ncid, varid_plev, "long_name", "pressure")
113     call nf95_put_att(ncid, varid_plev, "standard_name", "air_pressure")
114    
115     call nf95_put_att(ncid, varid_latitude, "units", "degrees_north")
116     call nf95_put_att(ncid, varid_latitude, "standard_name", "latitude")
117    
118     call nf95_put_att(ncid, varid_tro3, "long_name", "O3 mole fraction")
119     call nf95_put_att(ncid, varid_tro3, "standard_name", &
120     "mole_fraction_of_ozone_in_air")
121    
122     call nf95_put_att(ncid, nf90_global, "title", &
123     "ozone climatology from J.-F. Royer")
124    
125     call nf95_enddef(ncid)
126    
127     call nf95_put_var(ncid, varid_time, (/(julien - 0.5, julien = 1, 360)/))
128    
129     call nf95_put_var(ncid, varid_plev, presnivs(llm:1:-1) / 100.)
130     ! sort in ascending order and convert to hPa
131    
132     call nf95_put_var(ncid, varid_latitude, rlat)
133    
134     call nf95_put_var(ncid, varid_tro3, tro3(:, llm:1:-1, :))
135     ! "plev" is in ascending order whereas "p" is descending
136    
137     call nf95_close(ncid)
138    
139     print *, 'The file "O3_Royer.nc" has been created.'
140    
141     end program test_ozonecm

  ViewVC Help
Powered by ViewVC 1.1.21