/[lmdze]/trunk/libf/bibio/inithist.f90
ViewVC logotype

Diff of /trunk/libf/bibio/inithist.f90

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

revision 15 by guez, Fri Aug 1 15:24:12 2008 UTC revision 56 by guez, Tue Jan 10 19:02:02 2012 UTC
# Line 1  Line 1 
1  module inithist_m  module inithist_m
2    
   ! This module is clean: no C preprocessor directive, no include line  
   
3    implicit none    implicit none
4    
5  contains  contains
6    
7    subroutine inithist(day0, anne0, tstep, nq, fileid, filevid, infile, t_ops, &    subroutine inithist(day0, anne0, tstep, nq, t_ops, t_wrt)
        t_wrt)  
   
     ! From inithist.F,v 1.1.1.1 2004/05/19 12:53:05  
   
     !   Routine d'initialisation des ecritures des fichiers histoires LMDZ  
     !   au format IOIPSL  
8    
9      !   Appels succesifs des routines: histbeg      ! From inithist.F, version 1.1.1.1 2004/05/19 12:53:05
     !                                  histhori  
     !                                  histver  
     !                                  histdef  
     !                                  histend  
   
     !   Entree:  
     !      infile: nom du fichier histoire a creer  
     !      day0,anne0: date de reference  
     !      tstep: duree du pas de temps en seconde  
     !      t_ops: frequence de l'operation pour IOIPSL  
     !      t_wrt: frequence d'ecriture sur le fichier  
     !      nq: nombre de traceurs  
   
     !   Sortie:  
     !      fileid: ID du fichier netcdf cree  
     !      filevid:ID du fichier netcdf pour la grille v  
10    
11      !   L. Fairhead, LMD, 03/99      ! Routine d'initialisation des écritures des fichiers histoires LMDZ
12        ! au format IOIPSL
13      USE IOIPSL      ! Appels successifs des routines : histbeg, histhori, histver,
14        ! histdef, histend
15    
16        ! Entrées :
17        ! day0, anne0: date de référence
18        ! tstep : durée du pas de temps en secondes
19        ! t_ops : fréquence de l'opération pour IOIPSL
20        ! t_wrt : fréquence d'écriture sur le fichier
21        ! nq : nombre de traceurs
22    
23        ! L. Fairhead, LMD, 03/99
24    
25        USE calendar
26        use com_io_dyn, only: histid, histvid, histuid
27        use histcom
28      use dimens_m      use dimens_m
29      use paramet_m      use paramet_m
30      use comconst      use comconst
# Line 44  contains Line 34  contains
34      use serre      use serre
35      use temps      use temps
36      use ener      use ener
37      use advtrac_m      use iniadvtrac_m
38        use nr_util, only: pi
39    
40      !   Arguments      ! Arguments
     character(len=*) infile  
41      integer day0, anne0      integer day0, anne0
42      real, intent(in):: tstep, t_ops, t_wrt      real, intent(in):: tstep, t_ops, t_wrt
     integer fileid, filevid  
43      integer nq      integer nq
44    
45      !   Variables locales      ! Variables locales
   
     integer tau0  
46      real zjulian      real zjulian
47      integer iq      integer iq
48      real rlong(iip1,jjp1), rlat(iip1,jjp1)      real rlong(iip1, jjp1), rlat(iip1, jjp1)
49      integer uhoriid, vhoriid, thoriid, zvertiid      integer uhoriid, vhoriid, thoriid, zvertiid
50      integer ii,jj      integer ii, jj
51      integer zan, dayref      integer zan, dayref
52    
53      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
54    
55      !  Initialisations      ! Appel a histbeg: creation du fichier netcdf et initialisations diverses
   
     pi = 4. * atan (1.)  
   
     !  Appel a histbeg: creation du fichier netcdf et initialisations diverses  
56    
57      zan = anne0      zan = anne0
58      dayref = day0      dayref = day0
59      CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)      CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
     tau0 = itau_dyn  
60    
61      do jj = 1, jjp1      do jj = 1, jjp1
62         do ii = 1, iip1         do ii = 1, iip1
63            rlong(ii,jj) = rlonu(ii) * 180. / pi            rlong(ii, jj) = rlonu(ii) * 180. / pi
64            rlat(ii,jj) = rlatu(jj) * 180. / pi            rlat(ii, jj) = rlatu(jj) * 180. / pi
65         enddo         enddo
66      enddo      enddo
67    
68      call histbeg_totreg(infile, rlong(:,1), rlat(1,:), &      call histbeg_totreg("dyn_histu.nc", rlong(:,1), rlat(1,:), 1, iip1, 1, &
69           1, iip1, 1, jjp1, &           jjp1, itau_dyn, zjulian, tstep, uhoriid, histuid)
          tau0, zjulian, tstep, uhoriid, fileid)  
     !  
     !  Creation du fichier histoire pour la grille en V (oblige pour l'instant,  
     !  IOIPSL ne permet pas de grilles avec des nombres de point differents dans  
     !  un meme fichier)  
70    
71      do jj = 1, jjm      do jj = 1, jjm
72         do ii = 1, iip1         do ii = 1, iip1
73            rlong(ii,jj) = rlonv(ii) * 180. / pi            rlong(ii, jj) = rlonv(ii) * 180. / pi
74            rlat(ii,jj) = rlatv(jj) * 180. / pi            rlat(ii, jj) = rlatv(jj) * 180. / pi
75         enddo         enddo
76      enddo      enddo
77    
78      call histbeg_totreg('dyn_histv.nc', rlong(:,1), rlat(1,:jjm), &      ! Creation du fichier histoire pour la grille en V (oblige pour l'instant,
79        ! IOIPSL ne permet pas de grilles avec des nombres de point differents dans
80        ! un meme fichier)
81    
82        call histbeg_totreg('dyn_histv.nc', rlong(:, 1), rlat(1, :jjm), &
83           1, iip1, 1, jjm, &           1, iip1, 1, jjm, &
84           tau0, zjulian, tstep, vhoriid, filevid)           itau_dyn, zjulian, tstep, vhoriid, histvid)
85      !      !
86      !  Appel a histhori pour rajouter les autres grilles horizontales      ! Appel a histhori pour rajouter les autres grilles horizontales
87      !      !
88      do jj = 1, jjp1      do jj = 1, jjp1
89         do ii = 1, iip1         do ii = 1, iip1
90            rlong(ii,jj) = rlonv(ii) * 180. / pi            rlong(ii, jj) = rlonv(ii) * 180. / pi
91            rlat(ii,jj) = rlatu(jj) * 180. / pi            rlat(ii, jj) = rlatu(jj) * 180. / pi
92         enddo         enddo
93      enddo      enddo
94    
95      call histhori_regular(fileid, iip1, rlong, jjp1, rlat, 'scalar', &      call histbeg_totreg("dyn_hist.nc", rlong(:, 1), rlat(1, :), 1, iip1, 1, &
96           'Grille points scalaires', thoriid)           jjp1, itau_dyn, zjulian, tstep, thoriid, histid)
97      !      !
98      !  Appel a histvert pour la grille verticale      ! Appel a histvert pour la grille verticale
99      !      !
100      call histvert(fileid, 'sig_s', 'Niveaux sigma','-', &        call histvert(histid, 'presnivs', 'Niveaux pression','mb', llm, &
101           llm, nivsigs, zvertiid)             presnivs/100., zvertiid,'down')
102      ! Pour le fichier V        call histvert(histvid, 'presnivs', 'Niveaux pression','mb', llm, &
103      call histvert(filevid, 'sig_s', 'Niveaux sigma','-', &             presnivs/100., zvertiid,'down')
104           llm, nivsigs, zvertiid)        call histvert(histuid, 'presnivs', 'Niveaux pression','mb', llm, &
105               presnivs/100., zvertiid,'down')
106      !      !
107      !  Appels a histdef pour la definition des variables a sauvegarder      ! Appels a histdef pour la definition des variables a sauvegarder
108      !      !
109      !  Vents U      ! Vents U
110      !      !
111      call histdef(fileid, 'ucov', 'vents u covariants', 'm/s', &      call histdef(histuid, 'u', 'vent u', 'm/s', &
112           iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &           iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
113           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
114      !      !
115      !  Vents V      ! Vents V
116      !      !
117      call histdef(filevid, 'vcov', 'vents v covariants', 'm/s', &      call histdef(histvid, 'v', 'vent v', 'm/s', &
118           iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &           iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
119           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
120    
121      !      !
122      !  Temperature potentielle      ! Temperature potentielle
123      !      !
124      call histdef(fileid, 'teta', 'temperature potentielle', '-', &      call histdef(histid, 'teta', 'temperature potentielle', '-', &
125           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
126           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
127      !      !
128      !  Geopotentiel      ! Geopotentiel
129      !      !
130      call histdef(fileid, 'phi', 'geopotentiel instantane', '-', &      call histdef(histid, 'phi', 'geopotentiel', '-', &
131           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
132           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
133      !      !
134      !  Traceurs      ! Traceurs
135      !      !
136      DO iq=1,nq      DO iq=1, nq
137         call histdef(fileid, ttext(iq),  ttext(iq), '-', &         call histdef(histid, ttext(iq), ttext(iq), '-', &
138              iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &              iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
139              'inst(X)', t_ops, t_wrt)              'inst(X)', t_ops, t_wrt)
140      enddo      enddo
141      !      !
142      !  Masse      ! Masse
143      !      !
144      call histdef(fileid, 'masse', 'masse', 'kg', &      call histdef(histid, 'masse', 'masse', 'kg', &
145           iip1, jjp1, thoriid, 1, 1, 1, -99, &           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
146           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
147      !      !
148      !  Pression au sol      ! Pression au sol
149      !      !
150      call histdef(fileid, 'ps', 'pression naturelle au sol', 'Pa', &      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', &
151           iip1, jjp1, thoriid, 1, 1, 1, -99, &           iip1, jjp1, thoriid, 1, 1, 1, -99, &
152           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
153      !      !
154      !  Pression au sol      ! Geopotentiel au sol
155      !      !
156      call histdef(fileid, 'phis', 'geopotentiel au sol', '-', &      call histdef(histid, 'phis', 'geopotentiel au sol', '-', &
157           iip1, jjp1, thoriid, 1, 1, 1, -99, &           iip1, jjp1, thoriid, 1, 1, 1, -99, &
158           'inst(X)', t_ops, t_wrt)           'inst(X)', t_ops, t_wrt)
159      !      !
160      !  Fin      ! Fin
161      !      !
162      call histend(fileid)      call histend(histid)
163      call histend(filevid)      call histend(histuid)
164        call histend(histvid)
165    
166    end subroutine inithist    end subroutine inithist
167    

Legend:
Removed from v.15  
changed lines
  Added in v.56

  ViewVC Help
Powered by ViewVC 1.1.21