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

Diff of /trunk/dyn3d/dynredem0.f90

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

revision 137 by guez, Wed Apr 29 15:47:56 2015 UTC 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 comgeom, ONLY: aire_2d, cu_2d, cv_2d, rlatu, rlatv, rlonu, rlonv      USE comgeom, ONLY: aire_2d, cu_2d, cv_2d, rlatu, rlatv, rlonu, rlonv
# Line 33  CONTAINS Line 33  CONTAINS
33    
34      INTEGER iq, l      INTEGER iq, l
35      INTEGER, PARAMETER:: length = 100      INTEGER, PARAMETER:: length = 100
36      REAL tab_cntrl(length) ! tableau des paramètres du run      REAL tab_cntrl(length) ! tableau des param\`etres du run
37    
38      ! Pour NetCDF :      ! Pour NetCDF :
39      INTEGER idim_index      INTEGER idim_index
# Line 53  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    
     DO l = 1, length  
        tab_cntrl(l) = 0.  
     END DO  
56      tab_cntrl(1) = iim      tab_cntrl(1) = iim
57      tab_cntrl(2) = jjm      tab_cntrl(2) = jjm
58      tab_cntrl(3) = llm      tab_cntrl(3) = llm
# Line 76  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
# Line 89  CONTAINS Line 86  CONTAINS
86      tab_cntrl(29) = tauy      tab_cntrl(29) = tauy
87    
88      tab_cntrl(30) = iday_end      tab_cntrl(30) = iday_end
89        tab_cntrl(31:) = 0.
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    

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

  ViewVC Help
Powered by ViewVC 1.1.21