/[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 85 by guez, Thu Mar 6 17:35:22 2014 UTC revision 130 by guez, Tue Feb 24 15:43:51 2015 UTC
# Line 2  module dynetat0_m Line 2  module dynetat0_m
2    
3    IMPLICIT NONE    IMPLICIT NONE
4    
5    INTEGER day_ini    INTEGER day_ini
6      ! day number at the beginning of the run, based at value 1 on
7      ! January 1st of annee_ref
8    
9      integer:: day_ref = 1 ! jour de l'année de l'état initial
10      ! (= 350 si 20 décembre par exemple)
11    
12      integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)
13    
14  contains  contains
15    
16    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0)    SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
17    
18      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30      ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
19      ! Authors: P. Le Van, L. Fairhead      ! Authors: P. Le Van, L. Fairhead
# Line 14  contains Line 21  contains
21    
22      use comconst, only: dtvr      use comconst, only: dtvr
23      use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d      use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d
24      use conf_gcm_m, only: fxyhypb, ysinus      use conf_gcm_m, only: raz_date
25      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
26      use disvert_m, only: pa      use disvert_m, only: pa
27      use ener, only: etot0, ang0, ptot0, stot0, ztot0      use ener, only: etot0, ang0, ptot0, stot0, ztot0
# Line 23  contains Line 30  contains
30      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, &
31           NF95_Gw_VAR           NF95_Gw_VAR
32      use nr_util, only: assert      use nr_util, only: assert
33      use serre, only: clon, clat, grossismy, grossismx      use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &
34      use temps, only: day_ref, itau_dyn, annee_ref           tauy
35        use temps, only: itau_dyn
36        use unit_nml_m, only: unit_nml
37    
38      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)      REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
39      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
# Line 33  contains Line 42  contains
42      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)      REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
43      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa      REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
44      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
     REAL, intent(out):: time_0  
45    
46      ! Local variables:      ! Local variables:
47      INTEGER iq      INTEGER iq
48      REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run      REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run
49      INTEGER ierr, ncid, varid      INTEGER ierr, ncid, varid
50    
51        namelist /dynetat0_nml/ day_ref, annee_ref
52    
53      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
54    
55      print *, "Call sequence information: dynetat0"      print *, "Call sequence information: dynetat0"
# Line 63  contains Line 73  contains
73      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")      call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
74      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")      call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
75    
     day_ref = int(tab_cntrl(4))  
     annee_ref = int(tab_cntrl(5))  
   
76      IF (dtvr /= tab_cntrl(12)) THEN      IF (dtvr /= tab_cntrl(12)) THEN
77         print *, 'Warning: the time steps from day_step and "start.nc" ' // &         print *, 'Warning: the time steps from day_step and "start.nc" ' // &
78            'are different.'              'are different.'
79         print *, 'dtvr from day_step: ', dtvr         print *, 'dtvr from day_step: ', dtvr
80         print *, 'dtvr from "start.nc": ', tab_cntrl(12)         print *, 'dtvr from "start.nc": ', tab_cntrl(12)
81         print *, 'Using the value from day_step.'         print *, 'Using the value from day_step.'
# Line 80  contains Line 87  contains
87      stot0 = tab_cntrl(16)      stot0 = tab_cntrl(16)
88      ang0 = tab_cntrl(17)      ang0 = tab_cntrl(17)
89      pa = tab_cntrl(18)      pa = tab_cntrl(18)
90    
91      clon = tab_cntrl(20)      clon = tab_cntrl(20)
92      clat = tab_cntrl(21)      clat = tab_cntrl(21)
93      grossismx = tab_cntrl(22)      grossismx = tab_cntrl(22)
94      grossismy = tab_cntrl(23)      grossismy = tab_cntrl(23)
95      fxyhypb = tab_cntrl(24) == 1.      dzoomx = tab_cntrl(25)
96      if (.not. fxyhypb) ysinus = tab_cntrl(27) == 1.      dzoomy = tab_cntrl(26)
97      itau_dyn = tab_cntrl(31)      taux = tab_cntrl(28)
98        tauy = tab_cntrl(29)
99    
100        print *, "Enter namelist 'dynetat0_nml'."
101        read(unit=*, nml=dynetat0_nml)
102        write(unit_nml, nml=dynetat0_nml)
103    
104        if (raz_date) then
105           print *, 'On réinitialise à la date lue dans la namelist.'
106           day_ini = day_ref
107           itau_dyn = 0
108        else
109           day_ref = tab_cntrl(4)
110           annee_ref = tab_cntrl(5)
111           itau_dyn = tab_cntrl(31)
112           day_ini = tab_cntrl(30)
113        end if
114    
115        print *, "day_ini = ", day_ini
116    
117        deallocate(tab_cntrl) ! pointer
118    
119      call NF95_INQ_VARID (ncid, "rlonu", varid)      call NF95_INQ_VARID (ncid, "rlonu", varid)
120      call NF95_GET_VAR(ncid, varid, rlonu)      call NF95_GET_VAR(ncid, varid, rlonu)
# Line 112  contains Line 140  contains
140      call NF95_INQ_VARID (ncid, "phisinit", varid)      call NF95_INQ_VARID (ncid, "phisinit", varid)
141      call NF95_GET_VAR(ncid, varid, phis)      call NF95_GET_VAR(ncid, varid, phis)
142    
     call NF95_INQ_VARID (ncid, "temps", varid)  
     call NF95_GET_VAR(ncid, varid, time_0)  
   
     day_ini = tab_cntrl(30) + INT(time_0)  
     time_0 = time_0 - INT(time_0)  
     ! {0 <= time0 < 1}  
   
     deallocate(tab_cntrl) ! pointer  
   
143      call NF95_INQ_VARID (ncid, "ucov", varid)      call NF95_INQ_VARID (ncid, "ucov", varid)
144      call NF95_GET_VAR(ncid, varid, ucov)      call NF95_GET_VAR(ncid, varid, ucov)
145    

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

  ViewVC Help
Powered by ViewVC 1.1.21