/[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/Sources/dyn3d/dynetat0.f revision 139 by guez, Tue May 26 17:46:03 2015 UTC trunk/dyn3d/dynetat0.f 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 dimens_m, only: iim, jjm    use dimensions, only: iim, jjm
4    
5    IMPLICIT NONE    IMPLICIT NONE
6    
# Line 15  module dynetat0_m Line 15  module dynetat0_m
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    REAL, protected:: clon ! longitude of the center of the zoom, in rad
19    real clat ! latitude of the center of the zoom, in rad    real, protected:: clat ! latitude of the center of the zoom, in rad
20    
21    real grossismx, grossismy    real, protected:: grossismx, grossismy
22    ! facteurs de grossissement du zoom, selon la longitude et la latitude    ! facteurs de grossissement du zoom, selon la longitude et la latitude
23    ! = 2 si 2 fois, = 3 si 3 fois, etc.    ! = 2 si 2 fois, = 3 si 3 fois, etc.
24    
25    real dzoomx, dzoomy    real, protected:: dzoomx, dzoomy
26    ! extensions en longitude et latitude de la zone du zoom (fractions    ! extensions en longitude et latitude de la zone du zoom (fractions
27    ! de la zone totale)    ! de la zone totale)
28    
29    real taux, tauy    real, protected:: taux, tauy
30    ! raideur de la transition de l'int\'erieur à l'ext\'erieur du zoom    ! raideur de la transition de l'int\'erieur \`a l'ext\'erieur du zoom
31        
32    real rlatu(jjm + 1)    real rlatu(jjm + 1)
33    ! (latitudes of points of the "scalar" and "u" grid, in rad)    ! latitudes of points of the "scalar" and "u" grid, in rad
34    
35    real rlatv(jjm)    real rlatv(jjm)
36    ! (latitudes of points of the "v" grid, in rad, in decreasing order)    ! 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    real rlonu(iim + 1) ! longitudes of points of the "u" grid, in rad
39    
40    real rlonv(iim + 1)    real rlonv(iim + 1)
41    ! (longitudes of points of the "scalar" and "v" grid, in rad)    ! longitudes of points of the "scalar" and "v" grid, in rad
42    
43    real xprimu(iim + 1), xprimv(iim + 1)    real xprimu(iim + 1), xprimv(iim + 1)
44    ! xprimu et xprimv sont respectivement les valeurs de dx / dX aux    ! 2 pi / iim * (derivative of the longitudinal zoom function)(rlon[uv])
   ! points u et v.  
45    
46    REAL xprimm025(iim + 1), xprimp025(iim + 1)    REAL xprimm025(iim + 1), xprimp025(iim + 1)
47    REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)    REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
48      REAL ang0, etot0, ptot0, ztot0, stot0
49    
50    save    save
51    
# Line 59  contains Line 59  contains
59    
60      use comconst, only: dtvr      use comconst, only: dtvr
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, &
# Line 80  contains Line 79  contains
79    
80      ! Local variables:      ! Local variables:
81      INTEGER iq      INTEGER iq
82      REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres 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 149  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 187  contains Line 184  contains
184      CALL nf95_inq_varid(ncid, 'yprimu2', varid)      CALL nf95_inq_varid(ncid, 'yprimu2', varid)
185      CALL nf95_get_var(ncid, varid, yprimu2)      CALL nf95_get_var(ncid, varid, yprimu2)
186    
187      call NF95_INQ_VARID (ncid, "phisinit", varid)      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 201  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 223  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.139  
changed lines
  Added in v.276

  ViewVC Help
Powered by ViewVC 1.1.21