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

Diff of /trunk/Sources/dyn3d/dynetat0.f

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

revision 138 by guez, Wed Apr 29 15:47:56 2015 UTC revision 139 by guez, Tue May 26 17:46:03 2015 UTC
# Line 1  Line 1 
1  module dynetat0_m  module dynetat0_m
2    
3      use dimens_m, only: iim, jjm
4    
5    IMPLICIT NONE    IMPLICIT NONE
6    
7      private iim, jjm
8    
9    INTEGER day_ini    INTEGER day_ini
10    ! day number at the beginning of the run, based at value 1 on    ! day number at the beginning of the run, based at value 1 on
11    ! January 1st of annee_ref    ! January 1st of annee_ref
12    
13    integer:: day_ref = 1 ! jour de l'année de l'état initial    integer:: day_ref = 1 ! jour de l'ann\'ee de l'\'etat initial
14    ! (= 350 si 20 décembre par exemple)    ! (= 350 si 20 d\'ecembre par exemple)
15    
16    integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)    integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)
17    
18      REAL clon ! longitude of the center of the zoom, in rad
19      real clat ! latitude of the center of the zoom, in rad
20    
21      real grossismx, grossismy
22      ! facteurs de grossissement du zoom, selon la longitude et la latitude
23      ! = 2 si 2 fois, = 3 si 3 fois, etc.
24    
25      real dzoomx, dzoomy
26      ! extensions en longitude et latitude de la zone du zoom (fractions
27      ! de la zone totale)
28    
29      real taux, tauy
30      ! raideur de la transition de l'int\'erieur à l'ext\'erieur du zoom
31      
32      real rlatu(jjm + 1)
33      ! (latitudes of points of the "scalar" and "u" grid, in rad)
34    
35      real rlatv(jjm)
36      ! (latitudes of points of the "v" grid, in rad, in decreasing order)
37    
38      real rlonu(iim + 1) ! longitudes of points of the "u" grid, in rad
39    
40      real rlonv(iim + 1)
41      ! (longitudes of points of the "scalar" and "v" grid, in rad)
42    
43      real xprimu(iim + 1), xprimv(iim + 1)
44      ! xprimu et xprimv sont respectivement les valeurs de dx / dX aux
45      ! points u et v.
46    
47      REAL xprimm025(iim + 1), xprimp025(iim + 1)
48      REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
49    
50      save
51    
52  contains  contains
53    
54    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
# Line 20  contains Line 58  contains
58      ! This procedure reads the initial state of the atmosphere.      ! This procedure reads the initial state of the atmosphere.
59    
60      use comconst, only: dtvr      use comconst, only: dtvr
     use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d  
61      use conf_gcm_m, only: raz_date      use conf_gcm_m, only: raz_date
62      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
63      use disvert_m, only: pa      use disvert_m, only: pa
# Line 30  contains Line 67  contains
67      use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &      use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
68           NF95_Gw_VAR           NF95_Gw_VAR
69      use nr_util, only: assert      use nr_util, only: assert
     use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &  
          tauy  
70      use temps, only: itau_dyn      use temps, only: itau_dyn
71      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
72    
# Line 45  contains Line 80  contains
80    
81      ! Local variables:      ! Local variables:
82      INTEGER iq      INTEGER iq
83      REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run      REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres du run
84      INTEGER ierr, ncid, varid      INTEGER ierr, ncid, varid
85    
86      namelist /dynetat0_nml/ day_ref, annee_ref      namelist /dynetat0_nml/ day_ref, annee_ref
# Line 63  contains Line 98  contains
98           size(masse, 3)/) == llm, "dynetat0 llm")           size(masse, 3)/) == llm, "dynetat0 llm")
99      call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")      call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
100    
101      ! Fichier état initial :      ! Fichier \'etat initial :
102      call nf95_open("start.nc", NF90_NOWRITE, ncid)      call nf95_open("start.nc", NF90_NOWRITE, ncid)
103    
104      call nf95_inq_varid(ncid, "controle", varid)      call nf95_inq_varid(ncid, "controle", varid)
# Line 102  contains Line 137  contains
137      write(unit_nml, nml=dynetat0_nml)      write(unit_nml, nml=dynetat0_nml)
138    
139      if (raz_date) then      if (raz_date) then
140         print *, 'On réinitialise à la date lue dans la namelist.'         print *, 'Resetting the date, using the namelist.'
141         day_ini = day_ref         day_ini = day_ref
142         itau_dyn = 0         itau_dyn = 0
143      else      else
# Line 128  contains Line 163  contains
163      call NF95_INQ_VARID (ncid, "rlatv", varid)      call NF95_INQ_VARID (ncid, "rlatv", varid)
164      call NF95_GET_VAR(ncid, varid, rlatv)      call NF95_GET_VAR(ncid, varid, rlatv)
165    
166      call NF95_INQ_VARID (ncid, "cu", varid)      CALL nf95_inq_varid(ncid, 'xprimu', varid)
167      call NF95_GET_VAR(ncid, varid, cu_2d)      CALL nf95_get_var(ncid, varid, xprimu)
168    
169        CALL nf95_inq_varid(ncid, 'xprimv', varid)
170        CALL nf95_get_var(ncid, varid, xprimv)
171    
172        CALL nf95_inq_varid(ncid, 'xprimm025', varid)
173        CALL nf95_get_var(ncid, varid, xprimm025)
174    
175        CALL nf95_inq_varid(ncid, 'xprimp025', varid)
176        CALL nf95_get_var(ncid, varid, xprimp025)
177    
178        call NF95_INQ_VARID (ncid, "rlatu1", varid)
179        call NF95_GET_VAR(ncid, varid, rlatu1)
180    
181        call NF95_INQ_VARID (ncid, "rlatu2", varid)
182        call NF95_GET_VAR(ncid, varid, rlatu2)
183    
184      call NF95_INQ_VARID (ncid, "cv", varid)      CALL nf95_inq_varid(ncid, 'yprimu1', varid)
185      call NF95_GET_VAR(ncid, varid, cv_2d)      CALL nf95_get_var(ncid, varid, yprimu1)
186    
187      call NF95_INQ_VARID (ncid, "aire", varid)      CALL nf95_inq_varid(ncid, 'yprimu2', varid)
188      call NF95_GET_VAR(ncid, varid, aire_2d)      CALL nf95_get_var(ncid, varid, yprimu2)
189    
190      call NF95_INQ_VARID (ncid, "phisinit", varid)      call NF95_INQ_VARID (ncid, "phisinit", varid)
191      call NF95_GET_VAR(ncid, varid, phis)      call NF95_GET_VAR(ncid, varid, phis)

Legend:
Removed from v.138  
changed lines
  Added in v.139

  ViewVC Help
Powered by ViewVC 1.1.21