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

Diff of /trunk/dyn3d/dynredem0.f

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

trunk/libf/dyn3d/dynredem0.f90 revision 39 by guez, Tue Jan 25 15:11:05 2011 UTC trunk/Sources/dyn3d/dynredem0.f revision 138 by guez, Fri May 22 23:13:19 2015 UTC
# Line 6  CONTAINS Line 6  CONTAINS
6    
7    SUBROUTINE dynredem0(fichnom, iday_end, phis)    SUBROUTINE dynredem0(fichnom, iday_end, phis)
8    
9      ! From dyn3d/dynredem.F, version 1.2 2004/06/22 11:45:30      ! From dyn3d/dynredem.F, version 1.2, 2004/06/22 11:45:30
10      ! Ecriture du fichier de redémarrage au format NetCDF (initialisation)      ! \'Ecriture du fichier de red\'emarrage au format NetCDF (initialisation)
11    
12      USE comconst, ONLY : cpp, daysec, dtvr, g, kappa, omeg, rad      USE comconst, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
13      USE comvert, ONLY : ap, bp, nivsig, nivsigs, pa, preff, presnivs      USE comgeom, ONLY: aire_2d, cu_2d, cv_2d, rlatu, rlatv, rlonu, rlonv
14      USE comgeom, ONLY : aire_2d, cu_2d, cv_2d, rlatu, rlatv, rlonu, rlonv      USE dimens_m, ONLY: iim, jjm, llm, nqmx
15      USE dimens_m, ONLY : iim, jjm, llm, nqmx      USE disvert_m, ONLY: ap, bp, pa, preff, presnivs
16      USE ener, ONLY : ang0, etot0, ptot0, stot0, ztot0      use dynetat0_m, only: day_ref, annee_ref
17      USE calendar, ONLY : ju2ymds, ymds2ju      USE ener, ONLY: ang0, etot0, ptot0, stot0, ztot0
18      USE iniadvtrac_m, ONLY : tname, ttext      USE iniadvtrac_m, ONLY: tname, ttext
19      USE logic, ONLY : fxyhypb, ysinus      USE ju2ymds_m, ONLY: ju2ymds
20      USE netcdf95, ONLY : nf95_close, nf95_create, nf95_def_dim, &      USE netcdf, ONLY: nf90_clobber, nf90_float, nf90_global, nf90_unlimited
21           nf95_def_var, nf95_enddef, nf95_inq_varid, nf95_put_att, &      USE netcdf95, ONLY: nf95_close, nf95_create, nf95_def_dim, nf95_def_var, &
22           nf95_put_var           nf95_enddef, nf95_inq_varid, nf95_put_att, nf95_put_var
23      USE netcdf, ONLY : nf90_clobber, nf90_float, nf90_global, &      USE paramet_m, ONLY: iip1, jjp1, llmp1
24           nf90_unlimited      USE serre, ONLY: clat, clon, dzoomx, dzoomy, grossismx, grossismy, taux, &
25      USE paramet_m, ONLY : iip1, jjp1, llmp1           tauy
26      USE serre, ONLY : clat, clon, dzoomx, dzoomy, grossismx, grossismy, &      use ymds2ju_m, only: ymds2ju
27           taux, tauy  
28      USE temps, ONLY : annee_ref, day_ref      CHARACTER(len=*), INTENT(IN):: fichnom
29        INTEGER, INTENT(IN):: iday_end
30      CHARACTER (len=*), INTENT (IN) :: fichnom      REAL, INTENT(IN):: phis(:, :)
     INTEGER, INTENT (IN) :: iday_end  
     REAL, INTENT (IN) :: phis(:, :)  
31    
32      !   Local:      ! Local:
33    
34      INTEGER :: iq, l      INTEGER iq, l
35      INTEGER, PARAMETER:: length = 100      INTEGER, PARAMETER:: length = 100
36      REAL :: tab_cntrl(length) ! tableau des parametres du run      REAL tab_cntrl(length) ! tableau des param\`etres du run
37    
38      !   Variables locales pour NetCDF:      ! Pour NetCDF :
39        INTEGER idim_index
40      INTEGER :: dims2(2), dims3(3), dims4(4)      INTEGER idim_rlonu, idim_rlonv, idim_rlatu, idim_rlatv
41      INTEGER :: idim_index      INTEGER idim_s, idim_sig
42      INTEGER :: idim_rlonu, idim_rlonv, idim_rlatu, idim_rlatv      INTEGER dimid_temps
43      INTEGER :: idim_s, idim_sig      INTEGER ncid, varid
44      INTEGER :: idim_tim  
45      INTEGER :: ncid, varid      REAL zjulian, hours
46        INTEGER yyears0, jjour0, mmois0
47      REAL :: zjulian, hours      CHARACTER(len=30) unites
     INTEGER :: yyears0, jjour0, mmois0  
     CHARACTER (len=30) :: unites  
48    
49      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
50    
# Line 57  CONTAINS Line 53  CONTAINS
53      CALL ymds2ju(annee_ref, 1, iday_end, 0., zjulian)      CALL ymds2ju(annee_ref, 1, iday_end, 0., zjulian)
54      CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)      CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
55    
56      DO l = 1, length      tab_cntrl(1) = iim
57         tab_cntrl(l) = 0.      tab_cntrl(2) = jjm
58      END DO      tab_cntrl(3) = llm
59      tab_cntrl(1) = real(iim)      tab_cntrl(4) = day_ref
60      tab_cntrl(2) = real(jjm)      tab_cntrl(5) = annee_ref
     tab_cntrl(3) = real(llm)  
     tab_cntrl(4) = real(day_ref)  
     tab_cntrl(5) = real(annee_ref)  
61      tab_cntrl(6) = rad      tab_cntrl(6) = rad
62      tab_cntrl(7) = omeg      tab_cntrl(7) = omeg
63      tab_cntrl(8) = g      tab_cntrl(8) = g
# Line 80  CONTAINS Line 73  CONTAINS
73      tab_cntrl(18) = pa      tab_cntrl(18) = pa
74      tab_cntrl(19) = preff      tab_cntrl(19) = preff
75    
76      ! Paramètres  pour le zoom :      ! Param\`etres pour le zoom :
   
77      tab_cntrl(20) = clon      tab_cntrl(20) = clon
78      tab_cntrl(21) = clat      tab_cntrl(21) = clat
79      tab_cntrl(22) = grossismx      tab_cntrl(22) = grossismx
80      tab_cntrl(23) = grossismy      tab_cntrl(23) = grossismy
81        tab_cntrl(24) = 1.
82        tab_cntrl(25) = dzoomx
83        tab_cntrl(26) = dzoomy
84        tab_cntrl(27) = 0.
85        tab_cntrl(28) = taux
86        tab_cntrl(29) = tauy
87    
88      IF (fxyhypb) THEN      tab_cntrl(30) = iday_end
89         tab_cntrl(24) = 1.      tab_cntrl(31:) = 0.
        tab_cntrl(25) = dzoomx  
        tab_cntrl(26) = dzoomy  
        tab_cntrl(27) = 0.  
        tab_cntrl(28) = taux  
        tab_cntrl(29) = tauy  
     ELSE  
        tab_cntrl(24) = 0.  
        tab_cntrl(25) = dzoomx  
        tab_cntrl(26) = dzoomy  
        tab_cntrl(27) = 0.  
        tab_cntrl(28) = 0.  
        tab_cntrl(29) = 0.  
        IF (ysinus) tab_cntrl(27) = 1.  
     END IF  
   
     tab_cntrl(30) = real(iday_end)  
90    
91      CALL nf95_create(fichnom, nf90_clobber, ncid)      CALL nf95_create(fichnom, nf90_clobber, ncid)
92      CALL nf95_put_att(ncid, nf90_global, 'title', &      CALL nf95_put_att(ncid, nf90_global, 'title', &
93           'Fichier de démarrage dynamique')           'start file for the dynamics code')
94    
95      ! Definir les dimensions du fichiers:      ! Definir les dimensions du fichiers:
96    
# Line 119  CONTAINS Line 101  CONTAINS
101      CALL nf95_def_dim(ncid, 'rlatv', jjm, idim_rlatv)      CALL nf95_def_dim(ncid, 'rlatv', jjm, idim_rlatv)
102      CALL nf95_def_dim(ncid, 'sigs', llm, idim_s)      CALL nf95_def_dim(ncid, 'sigs', llm, idim_s)
103      CALL nf95_def_dim(ncid, 'sig', llmp1, idim_sig)      CALL nf95_def_dim(ncid, 'sig', llmp1, idim_sig)
104      CALL nf95_def_dim(ncid, 'temps', nf90_unlimited, idim_tim)      CALL nf95_def_dim(ncid, 'temps', nf90_unlimited, dimid_temps)
105    
106      ! Definir et enregistrer certains champs invariants:      ! Definir et enregistrer certains champs invariants:
107    
# Line 138  CONTAINS Line 120  CONTAINS
120      CALL nf95_def_var(ncid, 'rlatv', nf90_float, idim_rlatv, varid)      CALL nf95_def_var(ncid, 'rlatv', nf90_float, idim_rlatv, varid)
121      CALL nf95_put_att(ncid, varid, 'title', 'Latitudes des points V')      CALL nf95_put_att(ncid, varid, 'title', 'Latitudes des points V')
122    
     CALL nf95_def_var(ncid, 'nivsigs', nf90_float, idim_s, varid)  
     CALL nf95_put_att(ncid, varid, 'title', 'Numero naturel des couches s')  
   
     CALL nf95_def_var(ncid, 'nivsig', nf90_float, idim_sig, varid)  
     CALL nf95_put_att(ncid, varid, 'title', &  
          'Numero naturel des couches sigma')  
   
123      CALL nf95_def_var(ncid, 'ap', nf90_float, idim_sig, varid)      CALL nf95_def_var(ncid, 'ap', nf90_float, idim_sig, varid)
124      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient A pour hybride')      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient A pour hybride')
125    
# Line 155  CONTAINS Line 130  CONTAINS
130    
131      ! Coefficients de passage cov. <-> contra. <--> naturel      ! Coefficients de passage cov. <-> contra. <--> naturel
132    
133      dims2(1) = idim_rlonu      CALL nf95_def_var(ncid, 'cu', nf90_float, (/idim_rlonu, idim_rlatu/), varid)
     dims2(2) = idim_rlatu  
     CALL nf95_def_var(ncid, 'cu', nf90_float, dims2, varid)  
134      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient de passage pour U')      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient de passage pour U')
135    
136      dims2(1) = idim_rlonv      CALL nf95_def_var(ncid, 'cv', nf90_float, (/idim_rlonv, idim_rlatv/), varid)
     dims2(2) = idim_rlatv  
     CALL nf95_def_var(ncid, 'cv', nf90_float, dims2, varid)  
137      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient de passage pour V')      CALL nf95_put_att(ncid, varid, 'title', 'Coefficient de passage pour V')
138    
139      ! Aire de chaque maille:      ! Aire de chaque maille:
140    
141      dims2(1) = idim_rlonv      CALL nf95_def_var(ncid, 'aire', nf90_float, (/idim_rlonv, idim_rlatu/), &
142      dims2(2) = idim_rlatu           varid)
     CALL nf95_def_var(ncid, 'aire', nf90_float, dims2, varid)  
143      CALL nf95_put_att(ncid, varid, 'title', 'Aires de chaque maille')      CALL nf95_put_att(ncid, varid, 'title', 'Aires de chaque maille')
144    
145      ! Geopentiel au sol:      ! Geopentiel au sol:
146    
147      dims2(1) = idim_rlonv      CALL nf95_def_var(ncid, 'phisinit', nf90_float, &
148      dims2(2) = idim_rlatu           (/idim_rlonv, idim_rlatu/), varid)
     CALL nf95_def_var(ncid, 'phisinit', nf90_float, dims2, varid)  
149      CALL nf95_put_att(ncid, varid, 'title', 'Geopotentiel au sol')      CALL nf95_put_att(ncid, varid, 'title', 'Geopotentiel au sol')
150    
151      ! Definir les variables pour pouvoir les enregistrer plus tard:      ! Definir les variables pour pouvoir les enregistrer plus tard:
152    
153      CALL nf95_def_var(ncid, 'temps', nf90_float, idim_tim, varid)      CALL nf95_def_var(ncid, 'temps', nf90_float, dimid_temps, varid)
154      CALL nf95_put_att(ncid, varid, 'title', 'Temps de simulation')      CALL nf95_put_att(ncid, varid, 'title', 'Temps de simulation')
155      WRITE (unites, 200) yyears0, mmois0, jjour0      WRITE(unites, fmt = 200) yyears0, mmois0, jjour0
156  200 FORMAT ('days since ', I4, '-', I2.2, '-', I2.2, ' 00:00:00')  200 FORMAT ('days since ', I4, '-', I2.2, '-', I2.2, ' 00:00:00')
157      CALL nf95_put_att(ncid, varid, 'units', unites)      CALL nf95_put_att(ncid, varid, 'units', unites)
158    
159        CALL nf95_def_var(ncid, 'ucov', nf90_float, &
160      dims4(1) = idim_rlonu           (/idim_rlonu, idim_rlatu, idim_s, dimid_temps/), varid)
     dims4(2) = idim_rlatu  
     dims4(3) = idim_s  
     dims4(4) = idim_tim  
     CALL nf95_def_var(ncid, 'ucov', nf90_float, dims4, varid)  
161      CALL nf95_put_att(ncid, varid, 'title', 'Vitesse U')      CALL nf95_put_att(ncid, varid, 'title', 'Vitesse U')
162    
163      dims4(1) = idim_rlonv      CALL nf95_def_var(ncid, 'vcov', nf90_float, &
164      dims4(2) = idim_rlatv           (/idim_rlonv, idim_rlatv, idim_s, dimid_temps/), varid)
     dims4(3) = idim_s  
     dims4(4) = idim_tim  
     CALL nf95_def_var(ncid, 'vcov', nf90_float, dims4, varid)  
165      CALL nf95_put_att(ncid, varid, 'title', 'Vitesse V')      CALL nf95_put_att(ncid, varid, 'title', 'Vitesse V')
166    
167      dims4(1) = idim_rlonv      CALL nf95_def_var(ncid, 'teta', nf90_float, &
168      dims4(2) = idim_rlatu           (/idim_rlonv, idim_rlatu, idim_s, dimid_temps/), varid)
     dims4(3) = idim_s  
     dims4(4) = idim_tim  
     CALL nf95_def_var(ncid, 'teta', nf90_float, dims4, varid)  
169      CALL nf95_put_att(ncid, varid, 'title', 'Temperature')      CALL nf95_put_att(ncid, varid, 'title', 'Temperature')
170    
     dims4(1) = idim_rlonv  
     dims4(2) = idim_rlatu  
     dims4(3) = idim_s  
     dims4(4) = idim_tim  
171      DO iq = 1, nqmx      DO iq = 1, nqmx
172         CALL nf95_def_var(ncid, tname(iq), nf90_float, dims4, varid)         CALL nf95_def_var(ncid, tname(iq), nf90_float, &
173                (/idim_rlonv, idim_rlatu, idim_s, dimid_temps/), varid)
174         CALL nf95_put_att(ncid, varid, 'title', ttext(iq))         CALL nf95_put_att(ncid, varid, 'title', ttext(iq))
175      END DO      END DO
176    
177      dims4(1) = idim_rlonv      CALL nf95_def_var(ncid, 'masse', nf90_float, &
178      dims4(2) = idim_rlatu           (/idim_rlonv, idim_rlatu, idim_s, dimid_temps/), varid)
     dims4(3) = idim_s  
     dims4(4) = idim_tim  
     CALL nf95_def_var(ncid, 'masse', nf90_float, dims4, varid)  
179      CALL nf95_put_att(ncid, varid, 'title', 'C est quoi ?')      CALL nf95_put_att(ncid, varid, 'title', 'C est quoi ?')
180    
181      dims3(1) = idim_rlonv      CALL nf95_def_var(ncid, 'ps', nf90_float, &
182      dims3(2) = idim_rlatu           (/idim_rlonv, idim_rlatu, dimid_temps/), varid)
     dims3(3) = idim_tim  
     CALL nf95_def_var(ncid, 'ps', nf90_float, dims3, varid)  
183      CALL nf95_put_att(ncid, varid, 'title', 'Pression au sol')      CALL nf95_put_att(ncid, varid, 'title', 'Pression au sol')
184    
185      CALL nf95_enddef(ncid)      CALL nf95_enddef(ncid)
# Line 248  CONTAINS Line 199  CONTAINS
199      CALL nf95_inq_varid(ncid, 'rlatv', varid)      CALL nf95_inq_varid(ncid, 'rlatv', varid)
200      CALL nf95_put_var(ncid, varid, rlatv)      CALL nf95_put_var(ncid, varid, rlatv)
201    
     CALL nf95_inq_varid(ncid, 'nivsigs', varid)  
     CALL nf95_put_var(ncid, varid, nivsigs)  
   
     CALL nf95_inq_varid(ncid, 'nivsig', varid)  
     CALL nf95_put_var(ncid, varid, nivsig)  
   
202      CALL nf95_inq_varid(ncid, 'ap', varid)      CALL nf95_inq_varid(ncid, 'ap', varid)
203      CALL nf95_put_var(ncid, varid, ap)      CALL nf95_put_var(ncid, varid, ap)
204    

Legend:
Removed from v.39  
changed lines
  Added in v.138

  ViewVC Help
Powered by ViewVC 1.1.21