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

Diff of /trunk/dyn3d/dynetat0.f

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

revision 130 by guez, Tue Feb 24 15:43:51 2015 UTC revision 276 by guez, Thu Jul 12 14:49:20 2018 UTC
# Line 1  Line 1 
1  module dynetat0_m  module dynetat0_m
2    
3      use dimensions, 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, protected:: clon ! longitude of the center of the zoom, in rad
19      real, protected:: clat ! latitude of the center of the zoom, in rad
20    
21      real, protected:: 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, protected:: dzoomx, dzoomy
26      ! extensions en longitude et latitude de la zone du zoom (fractions
27      ! de la zone totale)
28    
29      real, protected:: 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      REAL ang0, etot0, ptot0, ztot0, stot0
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 dimensions, only: iim, jjm, llm, nqmx
63      use disvert_m, only: pa      use disvert_m, only: pa
     use ener, only: etot0, ang0, ptot0, stot0, ztot0  
64      use iniadvtrac_m, only: tname      use iniadvtrac_m, only: tname
65      use netcdf, only: NF90_NOWRITE, NF90_NOERR      use netcdf, only: NF90_NOWRITE, NF90_NOERR
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
     use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &  
          tauy  
69      use temps, only: itau_dyn      use temps, only: itau_dyn
70      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
71    
# Line 45  contains Line 79  contains
79    
80      ! Local variables:      ! Local variables:
81      INTEGER iq      INTEGER iq
82      REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run      REAL, allocatable:: 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      namelist /dynetat0_nml/ day_ref, annee_ref
# Line 63  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 102  contains Line 136  contains
136      write(unit_nml, nml=dynetat0_nml)      write(unit_nml, nml=dynetat0_nml)
137    
138      if (raz_date) then      if (raz_date) then
139         print *, 'On réinitialise à la date lue dans la namelist.'         print *, 'Resetting the date, using the namelist.'
140         day_ini = day_ref         day_ini = day_ref
141         itau_dyn = 0         itau_dyn = 0
142      else      else
# Line 114  contains Line 148  contains
148    
149      print *, "day_ini = ", day_ini      print *, "day_ini = ", day_ini
150    
     deallocate(tab_cntrl) ! pointer  
   
151      call NF95_INQ_VARID (ncid, "rlonu", varid)      call NF95_INQ_VARID (ncid, "rlonu", varid)
152      call NF95_GET_VAR(ncid, varid, rlonu)      call NF95_GET_VAR(ncid, varid, rlonu)
153    
# Line 128  contains Line 160  contains
160      call NF95_INQ_VARID (ncid, "rlatv", varid)      call NF95_INQ_VARID (ncid, "rlatv", varid)
161      call NF95_GET_VAR(ncid, varid, rlatv)      call NF95_GET_VAR(ncid, varid, rlatv)
162    
163      call NF95_INQ_VARID (ncid, "cu", varid)      CALL nf95_inq_varid(ncid, 'xprimu', varid)
164      call NF95_GET_VAR(ncid, varid, cu_2d)      CALL nf95_get_var(ncid, varid, xprimu)
165    
166        CALL nf95_inq_varid(ncid, 'xprimv', varid)
167        CALL nf95_get_var(ncid, varid, xprimv)
168    
169        CALL nf95_inq_varid(ncid, 'xprimm025', varid)
170        CALL nf95_get_var(ncid, varid, xprimm025)
171    
172      call NF95_INQ_VARID (ncid, "cv", varid)      CALL nf95_inq_varid(ncid, 'xprimp025', varid)
173      call NF95_GET_VAR(ncid, varid, cv_2d)      CALL nf95_get_var(ncid, varid, xprimp025)
174    
175      call NF95_INQ_VARID (ncid, "aire", varid)      call NF95_INQ_VARID (ncid, "rlatu1", varid)
176      call NF95_GET_VAR(ncid, varid, aire_2d)      call NF95_GET_VAR(ncid, varid, rlatu1)
177    
178      call NF95_INQ_VARID (ncid, "phisinit", varid)      call NF95_INQ_VARID (ncid, "rlatu2", varid)
179        call NF95_GET_VAR(ncid, varid, rlatu2)
180    
181        CALL nf95_inq_varid(ncid, 'yprimu1', varid)
182        CALL nf95_get_var(ncid, varid, yprimu1)
183    
184        CALL nf95_inq_varid(ncid, 'yprimu2', varid)
185        CALL nf95_get_var(ncid, varid, yprimu2)
186    
187        call NF95_INQ_VARID (ncid, "phis", varid)
188      call NF95_GET_VAR(ncid, varid, phis)      call NF95_GET_VAR(ncid, varid, phis)
189    
190      call NF95_INQ_VARID (ncid, "ucov", varid)      call NF95_INQ_VARID (ncid, "ucov", varid)
# Line 151  contains Line 198  contains
198    
199      DO iq = 1, nqmx      DO iq = 1, nqmx
200         call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)         call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)
201         IF (ierr /= NF90_NOERR) THEN         IF (ierr == NF90_NOERR) THEN
202              call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
203           ELSE
204            PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &            PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &
205                 "setting it to zero..."                 "setting it to zero..."
206            q(:, :, :, iq) = 0.            q(:, :, :, iq) = 0.
        ELSE  
           call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))  
207         ENDIF         ENDIF
208      ENDDO      ENDDO
209    
# Line 173  contains Line 220  contains
220    
221    END SUBROUTINE dynetat0    END SUBROUTINE dynetat0
222    
223      !********************************************************************
224    
225      subroutine read_serre
226    
227        use unit_nml_m, only: unit_nml
228        use nr_util, only: assert, pi
229    
230        REAL:: clon_deg = 0. ! longitude of the center of the zoom, in degrees
231        real:: clat_deg = 0. ! latitude of the center of the zoom, in degrees
232    
233        namelist /serre_nml/ clon_deg, clat_deg, grossismx, grossismy, dzoomx, &
234             dzoomy, taux, tauy
235    
236        !-------------------------------------------------
237    
238        ! Default values:
239        grossismx = 1.
240        grossismy = 1.
241        dzoomx = 0.2
242        dzoomy = 0.2
243        taux = 3.
244        tauy = 3.
245    
246        print *, "Enter namelist 'serre_nml'."
247        read(unit=*, nml=serre_nml)
248        write(unit_nml, nml=serre_nml)
249    
250        call assert(grossismx >= 1. .and. grossismy >= 1., "read_serre grossism")
251        call assert(dzoomx > 0., dzoomx < 1., dzoomy < 1., &
252             "read_serre dzoomx dzoomy")
253        clon = clon_deg / 180. * pi
254        clat = clat_deg / 180. * pi
255    
256      end subroutine read_serre
257    
258  end module dynetat0_m  end module dynetat0_m

Legend:
Removed from v.130  
changed lines
  Added in v.276

  ViewVC Help
Powered by ViewVC 1.1.21