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

Diff of /trunk/dyn3d/dynetat0.f

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

trunk/dyn3d/dynetat0.f revision 85 by guez, Thu Mar 6 17:35:22 2014 UTC trunk/Sources/dyn3d/dynetat0.f 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    INTEGER day_ini    private iim, jjm
8    
9      INTEGER day_ini
10      ! day number at the beginning of the run, based at value 1 on
11      ! January 1st of annee_ref
12    
13      integer:: day_ref = 1 ! jour de l'ann\'ee de l'\'etat initial
14      ! (= 350 si 20 d\'ecembre par exemple)
15    
16      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, time_0)    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
55    
56      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
57      ! Authors: P. Le Van, L. Fairhead      ! Authors: P. Le Van, L. Fairhead
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
61      use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d      use conf_gcm_m, only: raz_date
     use conf_gcm_m, only: fxyhypb, ysinus  
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
64      use ener, only: etot0, ang0, ptot0, stot0, ztot0      use ener, only: etot0, ang0, ptot0, stot0, ztot0
# Line 23  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
70      use serre, only: clon, clat, grossismy, grossismx      use temps, only: itau_dyn
71      use temps, only: day_ref, itau_dyn, annee_ref      use unit_nml_m, only: unit_nml
72    
73      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
74      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
# Line 33  contains Line 77  contains
77      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
78      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
79      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
     REAL, intent(out):: time_0  
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
87    
88      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
89    
90      print *, "Call sequence information: dynetat0"      print *, "Call sequence information: dynetat0"
# Line 53  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 63  contains Line 108  contains
108      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
109      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
110    
     day_ref = int(tab_cntrl(4))  
     annee_ref = int(tab_cntrl(5))  
   
111      IF (dtvr /= tab_cntrl(12)) THEN      IF (dtvr /= tab_cntrl(12)) THEN
112         print *, 'Warning: the time steps from day_step and "start.nc" ' // &         print *, 'Warning: the time steps from day_step and "start.nc" ' // &
113            'are different.'              'are different.'
114         print *, 'dtvr from day_step: ', dtvr         print *, 'dtvr from day_step: ', dtvr
115         print *, 'dtvr from "start.nc": ', tab_cntrl(12)         print *, 'dtvr from "start.nc": ', tab_cntrl(12)
116         print *, 'Using the value from day_step.'         print *, 'Using the value from day_step.'
# Line 80  contains Line 122  contains
122      stot0 = tab_cntrl(16)      stot0 = tab_cntrl(16)
123      ang0 = tab_cntrl(17)      ang0 = tab_cntrl(17)
124      pa = tab_cntrl(18)      pa = tab_cntrl(18)
125    
126      clon = tab_cntrl(20)      clon = tab_cntrl(20)
127      clat = tab_cntrl(21)      clat = tab_cntrl(21)
128      grossismx = tab_cntrl(22)      grossismx = tab_cntrl(22)
129      grossismy = tab_cntrl(23)      grossismy = tab_cntrl(23)
130      fxyhypb = tab_cntrl(24) == 1.      dzoomx = tab_cntrl(25)
131      if (.not. fxyhypb) ysinus = tab_cntrl(27) == 1.      dzoomy = tab_cntrl(26)
132      itau_dyn = tab_cntrl(31)      taux = tab_cntrl(28)
133        tauy = tab_cntrl(29)
134    
135        print *, "Enter namelist 'dynetat0_nml'."
136        read(unit=*, nml=dynetat0_nml)
137        write(unit_nml, nml=dynetat0_nml)
138    
139        if (raz_date) then
140           print *, 'Resetting the date, using the namelist.'
141           day_ini = day_ref
142           itau_dyn = 0
143        else
144           day_ref = tab_cntrl(4)
145           annee_ref = tab_cntrl(5)
146           itau_dyn = tab_cntrl(31)
147           day_ini = tab_cntrl(30)
148        end if
149    
150        print *, "day_ini = ", day_ini
151    
152        deallocate(tab_cntrl) ! pointer
153    
154      call NF95_INQ_VARID (ncid, "rlonu", varid)      call NF95_INQ_VARID (ncid, "rlonu", varid)
155      call NF95_GET_VAR(ncid, varid, rlonu)      call NF95_GET_VAR(ncid, varid, rlonu)
# Line 100  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, "cv", varid)      CALL nf95_inq_varid(ncid, 'xprimv', varid)
170      call NF95_GET_VAR(ncid, varid, cv_2d)      CALL nf95_get_var(ncid, varid, xprimv)
171    
172      call NF95_INQ_VARID (ncid, "aire", varid)      CALL nf95_inq_varid(ncid, 'xprimm025', varid)
173      call NF95_GET_VAR(ncid, varid, aire_2d)      CALL nf95_get_var(ncid, varid, xprimm025)
174    
175      call NF95_INQ_VARID (ncid, "phisinit", varid)      CALL nf95_inq_varid(ncid, 'xprimp025', varid)
176      call NF95_GET_VAR(ncid, varid, phis)      CALL nf95_get_var(ncid, varid, xprimp025)
177    
178      call NF95_INQ_VARID (ncid, "temps", varid)      call NF95_INQ_VARID (ncid, "rlatu1", varid)
179      call NF95_GET_VAR(ncid, varid, time_0)      call NF95_GET_VAR(ncid, varid, rlatu1)
180    
181      day_ini = tab_cntrl(30) + INT(time_0)      call NF95_INQ_VARID (ncid, "rlatu2", varid)
182      time_0 = time_0 - INT(time_0)      call NF95_GET_VAR(ncid, varid, rlatu2)
     ! {0 <= time0 < 1}  
183    
184      deallocate(tab_cntrl) ! pointer      CALL nf95_inq_varid(ncid, 'yprimu1', varid)
185        CALL nf95_get_var(ncid, varid, yprimu1)
186    
187        CALL nf95_inq_varid(ncid, 'yprimu2', varid)
188        CALL nf95_get_var(ncid, varid, yprimu2)
189    
190        call NF95_INQ_VARID (ncid, "phisinit", varid)
191        call NF95_GET_VAR(ncid, varid, phis)
192    
193      call NF95_INQ_VARID (ncid, "ucov", varid)      call NF95_INQ_VARID (ncid, "ucov", varid)
194      call NF95_GET_VAR(ncid, varid, ucov)      call NF95_GET_VAR(ncid, varid, ucov)

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

  ViewVC Help
Powered by ViewVC 1.1.21