/[lmdze]/trunk/dyn3d/dynetat0.f
ViewVC logotype

Contents of /trunk/dyn3d/dynetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 134 - (show annotations)
Wed Apr 29 15:47:56 2015 UTC (9 years ago) by guez
Original Path: trunk/Sources/dyn3d/dynetat0.f
File size: 5756 byte(s)
Sources inside, compilation outside.
1 module dynetat0_m
2
3 IMPLICIT NONE
4
5 INTEGER day_ini
6 ! day number at the beginning of the run, based at value 1 on
7 ! January 1st of annee_ref
8
9 integer:: day_ref = 1 ! jour de l'année de l'état initial
10 ! (= 350 si 20 décembre par exemple)
11
12 integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)
13
14 contains
15
16 SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
17
18 ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
19 ! Authors: P. Le Van, L. Fairhead
20 ! This procedure reads the initial state of the atmosphere.
21
22 use comconst, only: dtvr
23 use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d
24 use conf_gcm_m, only: raz_date
25 use dimens_m, only: iim, jjm, llm, nqmx
26 use disvert_m, only: pa
27 use ener, only: etot0, ang0, ptot0, stot0, ztot0
28 use iniadvtrac_m, only: tname
29 use netcdf, only: NF90_NOWRITE, NF90_NOERR
30 use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
31 NF95_Gw_VAR
32 use nr_util, only: assert
33 use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &
34 tauy
35 use temps, only: itau_dyn
36 use unit_nml_m, only: unit_nml
37
38 REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
39 REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
40 REAL, intent(out):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
41 REAL, intent(out):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
42 REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
43 REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
44 REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
45
46 ! Local variables:
47 INTEGER iq
48 REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run
49 INTEGER ierr, ncid, varid
50
51 namelist /dynetat0_nml/ day_ref, annee_ref
52
53 !-----------------------------------------------------------------------
54
55 print *, "Call sequence information: dynetat0"
56
57 call assert((/size(ucov, 1), size(vcov, 1), size(masse, 1), size(ps, 1), &
58 size(phis, 1), size(q, 1), size(teta, 1)/) == iim + 1, "dynetat0 iim")
59 call assert((/size(ucov, 2), size(vcov, 2) + 1, size(masse, 2), &
60 size(ps, 2), size(phis, 2), size(q, 2), size(teta, 2)/) == jjm + 1, &
61 "dynetat0 jjm")
62 call assert((/size(vcov, 3), size(ucov, 3), size(teta, 3), size(q, 3), &
63 size(masse, 3)/) == llm, "dynetat0 llm")
64 call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
65
66 ! Fichier état initial :
67 call nf95_open("start.nc", NF90_NOWRITE, ncid)
68
69 call nf95_inq_varid(ncid, "controle", varid)
70 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
71
72 call assert(int(tab_cntrl(1)) == iim, "dynetat0 tab_cntrl iim")
73 call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
74 call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
75
76 IF (dtvr /= tab_cntrl(12)) THEN
77 print *, 'Warning: the time steps from day_step and "start.nc" ' // &
78 'are different.'
79 print *, 'dtvr from day_step: ', dtvr
80 print *, 'dtvr from "start.nc": ', tab_cntrl(12)
81 print *, 'Using the value from day_step.'
82 ENDIF
83
84 etot0 = tab_cntrl(13)
85 ptot0 = tab_cntrl(14)
86 ztot0 = tab_cntrl(15)
87 stot0 = tab_cntrl(16)
88 ang0 = tab_cntrl(17)
89 pa = tab_cntrl(18)
90
91 clon = tab_cntrl(20)
92 clat = tab_cntrl(21)
93 grossismx = tab_cntrl(22)
94 grossismy = tab_cntrl(23)
95 dzoomx = tab_cntrl(25)
96 dzoomy = tab_cntrl(26)
97 taux = tab_cntrl(28)
98 tauy = tab_cntrl(29)
99
100 print *, "Enter namelist 'dynetat0_nml'."
101 read(unit=*, nml=dynetat0_nml)
102 write(unit_nml, nml=dynetat0_nml)
103
104 if (raz_date) then
105 print *, 'On réinitialise à la date lue dans la namelist.'
106 day_ini = day_ref
107 itau_dyn = 0
108 else
109 day_ref = tab_cntrl(4)
110 annee_ref = tab_cntrl(5)
111 itau_dyn = tab_cntrl(31)
112 day_ini = tab_cntrl(30)
113 end if
114
115 print *, "day_ini = ", day_ini
116
117 deallocate(tab_cntrl) ! pointer
118
119 call NF95_INQ_VARID (ncid, "rlonu", varid)
120 call NF95_GET_VAR(ncid, varid, rlonu)
121
122 call NF95_INQ_VARID (ncid, "rlatu", varid)
123 call NF95_GET_VAR(ncid, varid, rlatu)
124
125 call NF95_INQ_VARID (ncid, "rlonv", varid)
126 call NF95_GET_VAR(ncid, varid, rlonv)
127
128 call NF95_INQ_VARID (ncid, "rlatv", varid)
129 call NF95_GET_VAR(ncid, varid, rlatv)
130
131 call NF95_INQ_VARID (ncid, "cu", varid)
132 call NF95_GET_VAR(ncid, varid, cu_2d)
133
134 call NF95_INQ_VARID (ncid, "cv", varid)
135 call NF95_GET_VAR(ncid, varid, cv_2d)
136
137 call NF95_INQ_VARID (ncid, "aire", varid)
138 call NF95_GET_VAR(ncid, varid, aire_2d)
139
140 call NF95_INQ_VARID (ncid, "phisinit", varid)
141 call NF95_GET_VAR(ncid, varid, phis)
142
143 call NF95_INQ_VARID (ncid, "ucov", varid)
144 call NF95_GET_VAR(ncid, varid, ucov)
145
146 call NF95_INQ_VARID (ncid, "vcov", varid)
147 call NF95_GET_VAR(ncid, varid, vcov)
148
149 call NF95_INQ_VARID (ncid, "teta", varid)
150 call NF95_GET_VAR(ncid, varid, teta)
151
152 DO iq = 1, nqmx
153 call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)
154 IF (ierr /= NF90_NOERR) THEN
155 PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &
156 "setting it to zero..."
157 q(:, :, :, iq) = 0.
158 ELSE
159 call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
160 ENDIF
161 ENDDO
162
163 call NF95_INQ_VARID (ncid, "masse", varid)
164 call NF95_GET_VAR(ncid, varid, masse)
165
166 call NF95_INQ_VARID (ncid, "ps", varid)
167 call NF95_GET_VAR(ncid, varid, ps)
168 ! Check that there is a single value at each pole:
169 call assert(ps(1, 1) == ps(2:, 1), "dynetat0 ps north pole")
170 call assert(ps(1, jjm + 1) == ps(2:, jjm + 1), "dynetat0 ps south pole")
171
172 call NF95_CLOSE(ncid)
173
174 END SUBROUTINE dynetat0
175
176 end module dynetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21