/[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

trunk/dyn3d/dynetat0.f revision 113 by guez, Thu Sep 18 19:56:46 2014 UTC trunk/Sources/dyn3d/dynetat0.f revision 156 by guez, Thu Jul 16 17:39:10 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 \`a 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      ! 2 pi / iim * (derivative of the longitudinal zoom function)(rlon[uv])
45    
46      REAL xprimm025(iim + 1), xprimp025(iim + 1)
47      REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
48    
49      save
50    
51  contains  contains
52    
53    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0)    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
54    
55      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
56      ! Authors: P. Le Van, L. Fairhead      ! Authors: P. Le Van, L. Fairhead
57      ! This procedure reads the initial state of the atmosphere.      ! This procedure reads the initial state of the atmosphere.
58    
59      use comconst, only: dtvr      use comconst, only: dtvr
60      use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d      use conf_gcm_m, only: raz_date
61      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
62      use disvert_m, only: pa      use disvert_m, only: pa
63      use ener, only: etot0, ang0, ptot0, stot0, ztot0      use ener, only: etot0, ang0, ptot0, stot0, ztot0
# Line 22  contains Line 66  contains
66      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, &
67           NF95_Gw_VAR           NF95_Gw_VAR
68      use nr_util, only: assert      use nr_util, only: assert
69      use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &      use temps, only: itau_dyn
70           tauy      use unit_nml_m, only: unit_nml
     use temps, only: day_ref, itau_dyn, annee_ref  
71    
72      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
73      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
# Line 33  contains Line 76  contains
76      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
77      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
78      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
     REAL, intent(out):: time_0  
79    
80      ! Local variables:      ! Local variables:
81      INTEGER iq      INTEGER iq
82      REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run      REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres du run
83      INTEGER ierr, ncid, varid      INTEGER ierr, ncid, varid
84    
85        namelist /dynetat0_nml/ day_ref, annee_ref
86    
87      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
88    
89      print *, "Call sequence information: dynetat0"      print *, "Call sequence information: dynetat0"
# Line 53  contains Line 97  contains
97           size(masse, 3)/) == llm, "dynetat0 llm")           size(masse, 3)/) == llm, "dynetat0 llm")
98      call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")      call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
99    
100      ! Fichier état initial :      ! Fichier \'etat initial :
101      call nf95_open("start.nc", NF90_NOWRITE, ncid)      call nf95_open("start.nc", NF90_NOWRITE, ncid)
102    
103      call nf95_inq_varid(ncid, "controle", varid)      call nf95_inq_varid(ncid, "controle", varid)
# Line 63  contains Line 107  contains
107      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
108      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
109    
     day_ref = int(tab_cntrl(4))  
     annee_ref = int(tab_cntrl(5))  
   
110      IF (dtvr /= tab_cntrl(12)) THEN      IF (dtvr /= tab_cntrl(12)) THEN
111         print *, 'Warning: the time steps from day_step and "start.nc" ' // &         print *, 'Warning: the time steps from day_step and "start.nc" ' // &
112            'are different.'              'are different.'
113         print *, 'dtvr from day_step: ', dtvr         print *, 'dtvr from day_step: ', dtvr
114         print *, 'dtvr from "start.nc": ', tab_cntrl(12)         print *, 'dtvr from "start.nc": ', tab_cntrl(12)
115         print *, 'Using the value from day_step.'         print *, 'Using the value from day_step.'
# Line 90  contains Line 131  contains
131      taux = tab_cntrl(28)      taux = tab_cntrl(28)
132      tauy = tab_cntrl(29)      tauy = tab_cntrl(29)
133    
134      itau_dyn = tab_cntrl(31)      print *, "Enter namelist 'dynetat0_nml'."
135        read(unit=*, nml=dynetat0_nml)
136        write(unit_nml, nml=dynetat0_nml)
137    
138        if (raz_date) then
139           print *, 'Resetting the date, using the namelist.'
140           day_ini = day_ref
141           itau_dyn = 0
142        else
143           day_ref = tab_cntrl(4)
144           annee_ref = tab_cntrl(5)
145           itau_dyn = tab_cntrl(31)
146           day_ini = tab_cntrl(30)
147        end if
148    
149        print *, "day_ini = ", day_ini
150    
151        deallocate(tab_cntrl) ! pointer
152    
153      call NF95_INQ_VARID (ncid, "rlonu", varid)      call NF95_INQ_VARID (ncid, "rlonu", varid)
154      call NF95_GET_VAR(ncid, varid, rlonu)      call NF95_GET_VAR(ncid, varid, rlonu)
# Line 104  contains Line 162  contains
162      call NF95_INQ_VARID (ncid, "rlatv", varid)      call NF95_INQ_VARID (ncid, "rlatv", varid)
163      call NF95_GET_VAR(ncid, varid, rlatv)      call NF95_GET_VAR(ncid, varid, rlatv)
164    
165      call NF95_INQ_VARID (ncid, "cu", varid)      CALL nf95_inq_varid(ncid, 'xprimu', varid)
166      call NF95_GET_VAR(ncid, varid, cu_2d)      CALL nf95_get_var(ncid, varid, xprimu)
167    
168      call NF95_INQ_VARID (ncid, "cv", varid)      CALL nf95_inq_varid(ncid, 'xprimv', varid)
169      call NF95_GET_VAR(ncid, varid, cv_2d)      CALL nf95_get_var(ncid, varid, xprimv)
170    
171      call NF95_INQ_VARID (ncid, "aire", varid)      CALL nf95_inq_varid(ncid, 'xprimm025', varid)
172      call NF95_GET_VAR(ncid, varid, aire_2d)      CALL nf95_get_var(ncid, varid, xprimm025)
173    
174      call NF95_INQ_VARID (ncid, "phisinit", varid)      CALL nf95_inq_varid(ncid, 'xprimp025', varid)
175      call NF95_GET_VAR(ncid, varid, phis)      CALL nf95_get_var(ncid, varid, xprimp025)
176    
177      call NF95_INQ_VARID (ncid, "temps", varid)      call NF95_INQ_VARID (ncid, "rlatu1", varid)
178      call NF95_GET_VAR(ncid, varid, time_0)      call NF95_GET_VAR(ncid, varid, rlatu1)
179    
180      day_ini = tab_cntrl(30) + INT(time_0)      call NF95_INQ_VARID (ncid, "rlatu2", varid)
181      time_0 = time_0 - INT(time_0)      call NF95_GET_VAR(ncid, varid, rlatu2)
     ! {0 <= time0 < 1}  
182    
183      deallocate(tab_cntrl) ! pointer      CALL nf95_inq_varid(ncid, 'yprimu1', varid)
184        CALL nf95_get_var(ncid, varid, yprimu1)
185    
186        CALL nf95_inq_varid(ncid, 'yprimu2', varid)
187        CALL nf95_get_var(ncid, varid, yprimu2)
188    
189        call NF95_INQ_VARID (ncid, "phisinit", varid)
190        call NF95_GET_VAR(ncid, varid, phis)
191    
192      call NF95_INQ_VARID (ncid, "ucov", varid)      call NF95_INQ_VARID (ncid, "ucov", varid)
193      call NF95_GET_VAR(ncid, varid, ucov)      call NF95_GET_VAR(ncid, varid, ucov)

Legend:
Removed from v.113  
changed lines
  Added in v.156

  ViewVC Help
Powered by ViewVC 1.1.21