/[lmdze]/trunk/dyn3d/dynetat0_chosen.f90
ViewVC logotype

Contents of /trunk/dyn3d/dynetat0_chosen.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 4167 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 module dynetat0_chosen_m
2
3 IMPLICIT NONE
4
5 integer, protected, save:: day_ref ! jour de l'ann\'ee de l'\'etat initial
6 ! (= 350 si 20 d\'ecembre par exemple)
7
8 integer, protected, save:: annee_ref
9 ! Annee de l'etat initial (avec 4 chiffres)
10
11 REAL, protected, save:: clon ! longitude of the center of the zoom, in rad
12 real, protected, save:: clat ! latitude of the center of the zoom, in rad
13
14 real, protected, save:: grossismx, grossismy
15 ! facteurs de grossissement du zoom, selon la longitude et la latitude
16 ! = 2 si 2 fois, = 3 si 3 fois, etc.
17
18 real, protected, save:: dzoomx, dzoomy
19 ! extensions en longitude et latitude de la zone du zoom (fractions
20 ! de la zone totale)
21
22 real, protected, save:: taux, tauy
23 ! raideur de la transition de l'int\'erieur \`a l'ext\'erieur du zoom
24
25 real, protected, save:: pa ! in Pa
26
27 contains
28
29 SUBROUTINE dynetat0_chosen
30
31 ! This procedure reads the initial state of the atmosphere. Values
32 ! that were chosen in ce0l.
33
34 ! Libraries:
35 use netcdf, only: NF90_NOWRITE
36 use netcdf95, only: nf95_open, nf95_inq_varid, NF95_CLOSE, NF95_Gw_VAR
37 use nr_util, only: assert
38
39 use comconst, only: dtvr
40 use conf_gcm_m, only: raz_date
41 use dimensions, only: iim, jjm, llm
42 use unit_nml_m, only: unit_nml
43
44 ! Local:
45 REAL, allocatable:: tab_cntrl(:) ! tableau des param\`etres du run
46 INTEGER ncid, varid
47
48 namelist /dynetat0_nml/ day_ref, annee_ref
49
50 !-----------------------------------------------------------------------
51
52 print *, "Call sequence information: dynetat0_chosen"
53
54 ! Fichier \'etat initial :
55 call nf95_open("start.nc", NF90_NOWRITE, ncid)
56
57 call nf95_inq_varid(ncid, "controle", varid)
58 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
59
60 call assert(int(tab_cntrl(1)) == iim, "dynetat0_chosen tab_cntrl iim")
61 call assert(int(tab_cntrl(2)) == jjm, "dynetat0_chosen tab_cntrl jjm")
62 call assert(int(tab_cntrl(3)) == llm, "dynetat0_chosen tab_cntrl llm")
63
64 IF (dtvr /= tab_cntrl(12)) THEN
65 print *, 'Warning: the time steps from day_step and "start.nc" ' // &
66 'are different.'
67 print *, 'dtvr from day_step: ', dtvr
68 print *, 'dtvr from "start.nc": ', tab_cntrl(12)
69 print *, 'Using the value from day_step.'
70 ENDIF
71
72 pa = tab_cntrl(18)
73
74 clon = tab_cntrl(20)
75 clat = tab_cntrl(21)
76 grossismx = tab_cntrl(22)
77 grossismy = tab_cntrl(23)
78 dzoomx = tab_cntrl(25)
79 dzoomy = tab_cntrl(26)
80 taux = tab_cntrl(28)
81 tauy = tab_cntrl(29)
82
83 if (raz_date) then
84 ! Default values:
85 day_ref = 1
86 annee_ref = 1998
87
88 print *, "Enter namelist 'dynetat0_nml'."
89 read(unit = *, nml = dynetat0_nml)
90 write(unit_nml, nml = dynetat0_nml)
91 else
92 day_ref = tab_cntrl(4)
93 annee_ref = tab_cntrl(5)
94 end if
95
96 call NF95_CLOSE(ncid)
97
98 END SUBROUTINE dynetat0_chosen
99
100 !********************************************************************
101
102 subroutine read_serre
103
104 use unit_nml_m, only: unit_nml
105 use nr_util, only: assert, pi
106
107 REAL:: clon_deg = 0. ! longitude of the center of the zoom, in degrees
108 real:: clat_deg = 0. ! latitude of the center of the zoom, in degrees
109
110 namelist /serre_nml/ clon_deg, clat_deg, grossismx, grossismy, dzoomx, &
111 dzoomy, taux, tauy
112 namelist /dynetat0_nml/ day_ref, annee_ref
113
114 !-------------------------------------------------
115
116 ! Default values:
117 grossismx = 1.
118 grossismy = 1.
119 dzoomx = 0.2
120 dzoomy = 0.2
121 taux = 3.
122 tauy = 3.
123
124 print *, "Enter namelist 'serre_nml'."
125 read(unit=*, nml=serre_nml)
126 write(unit_nml, nml=serre_nml)
127
128 call assert(grossismx >= 1. .and. grossismy >= 1., "read_serre grossism")
129 call assert(dzoomx > 0., dzoomx < 1., dzoomy < 1., &
130 "read_serre dzoomx dzoomy")
131 clon = clon_deg / 180. * pi
132 clat = clat_deg / 180. * pi
133
134 ! Default values:
135 day_ref = 1
136 annee_ref = 1998
137
138 print *, "Enter namelist 'dynetat0_nml'."
139 read(unit = *, nml = dynetat0_nml)
140 write(unit_nml, nml = dynetat0_nml)
141
142 pa = 5e4
143
144 end subroutine read_serre
145
146 end module dynetat0_chosen_m

  ViewVC Help
Powered by ViewVC 1.1.21