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

Diff of /trunk/dyn3d/inithist.f90

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

trunk/libf/bibio/inithist.f90 revision 39 by guez, Tue Jan 25 15:11:05 2011 UTC trunk/dyn3d/inithist.f90 revision 335 by guez, Thu Sep 12 21:22:46 2019 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      integer histid, histvid, histuid
6    
7  contains  contains
8    
9    subroutine inithist(day0, anne0, tstep, nq, fileid, filevid, t_ops, t_wrt)    subroutine inithist(t_ops, t_wrt)
10    
11      ! From inithist.F, version 1.1.1.1 2004/05/19 12:53:05      ! From inithist.F, version 1.1.1.1, 2004/05/19 12:53:05
12        ! L. Fairhead, LMD, 03/99
13    
14      ! Routine d'initialisation des écritures des fichiers histoires LMDZ      ! Routine d'initialisation des écritures des fichiers histoires au
15      ! au format IOIPSL      ! format IOIPSL.
     ! Appels successifs des routines : histbeg, histhori, histver,  
     ! histdef, histend  
   
     ! Entrées :  
     ! day0, anne0: date de référence  
     ! tstep : durée du pas de temps en secondes  
     ! t_ops : fréquence de l'opération pour IOIPSL  
     ! t_wrt : fréquence d'écriture sur le fichier  
     ! nq : nombre de traceurs  
   
     ! Sorties :  
     ! fileid : ID du fichier Netcdf créé  
     ! filevid : ID du fichier Netcdf pour la grille v  
16    
17      ! L. Fairhead, LMD, 03/99      use comconst, only: dtvr
18        USE dimensions, ONLY: jjm, llm, nqmx
19        USE disvert_m, ONLY: presnivs
20        use dynetat0_m, only: itau_dyn, rlatu, rlatv, rlonu, rlonv
21        USE dynetat0_chosen_m, ONLY: day_ref, annee_ref
22        use histbeg_totreg_m, only: histbeg_totreg
23        USE histdef_m, ONLY: histdef
24        USE histend_m, ONLY: histend
25        USE histvert_m, ONLY: histvert
26        USE infotrac_init_m, ONLY: ttext
27        USE nr_util, ONLY: pi
28        USE paramet_m, ONLY: iip1, jjp1
29        use ymds2ju_m, ONLY: ymds2ju
30    
31      USE calendar      real, intent(in):: t_ops ! fréquence de l'opération pour IOIPSL
32      use histcom      real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier
     use dimens_m  
     use paramet_m  
     use comconst  
     use comvert  
     use logic  
     use comgeom  
     use serre  
     use temps  
     use ener  
     use iniadvtrac_m  
     use nr_util, only: pi  
   
     ! Arguments  
     integer day0, anne0  
     real, intent(in):: tstep, t_ops, t_wrt  
     integer fileid, filevid  
     integer nq  
33    
34      ! Variables locales      ! Local:
35      real zjulian      double precision julian
36      integer iq      integer iq
     real rlong(iip1, jjp1), rlat(iip1, jjp1)  
37      integer uhoriid, vhoriid, thoriid, zvertiid      integer uhoriid, vhoriid, thoriid, zvertiid
     integer ii, jj  
     integer zan, dayref  
38    
39      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
40    
41      ! Appel a histbeg: creation du fichier netcdf et initialisations diverses      print *, "Call sequence information: inithist"
42        CALL ymds2ju(annee_ref, 1, day_ref, 0., julian)
43    
44      zan = anne0      call histbeg_totreg("dyn_histu.nc", rlonu * 180. / pi, rlatu * 180. / pi, &
45      dayref = day0           1, iip1, 1, jjp1, itau_dyn, julian, dtvr, uhoriid, histuid)
     CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)  
   
     do jj = 1, jjp1  
        do ii = 1, iip1  
           rlong(ii, jj) = rlonu(ii) * 180. / pi  
           rlat(ii, jj) = rlatu(jj) * 180. / pi  
        enddo  
     enddo  
46    
     call histbeg_totreg("dyn_hist.nc", rlong(:, 1), rlat(1, :), &  
          1, iip1, 1, jjp1, &  
          itau_dyn, zjulian, tstep, uhoriid, fileid)  
     !  
47      ! Creation du fichier histoire pour la grille en V (oblige pour l'instant,      ! Creation du fichier histoire pour la grille en V (oblige pour l'instant,
48      ! IOIPSL ne permet pas de grilles avec des nombres de point differents dans      ! IOIPSL ne permet pas de grilles avec des nombres de point differents dans
49      ! un meme fichier)      ! un meme fichier)
50    
51      do jj = 1, jjm      call histbeg_totreg('dyn_histv.nc', rlonv * 180. / pi, rlatv * 180. / pi, &
52         do ii = 1, iip1           1, iip1, 1, jjm, itau_dyn, julian, dtvr, vhoriid, histvid)
           rlong(ii, jj) = rlonv(ii) * 180. / pi  
           rlat(ii, jj) = rlatv(jj) * 180. / pi  
        enddo  
     enddo  
53    
54      call histbeg_totreg('dyn_histv.nc', rlong(:, 1), rlat(1, :jjm), &      call histbeg_totreg("dyn_hist.nc", rlonv * 180. / pi, rlatu * 180. / pi, &
55           1, iip1, 1, jjm, &           1, iip1, 1, jjp1, itau_dyn, julian, dtvr, thoriid, histid)
56           itau_dyn, zjulian, tstep, vhoriid, filevid)  
57      !      call histvert(histid, 'presnivs', 'Niveaux pression', 'mb', presnivs/100., &
58      ! Appel a histhori pour rajouter les autres grilles horizontales           zvertiid, 'down')
59      !      call histvert(histvid, 'presnivs', 'Niveaux pression', 'mb', &
60      do jj = 1, jjp1           presnivs/100., zvertiid, 'down')
61         do ii = 1, iip1      call histvert(histuid, 'presnivs', 'Niveaux pression', 'mb', &
62            rlong(ii, jj) = rlonv(ii) * 180. / pi           presnivs/100., zvertiid, 'down')
63            rlat(ii, jj) = rlatu(jj) * 180. / pi  
64         enddo      call histdef(histuid, 'u', 'vent u', 'm/s', iip1, jjp1, uhoriid, llm, 1, &
65      enddo           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
66        call histdef(histvid, 'v', 'vent v', 'm/s', iip1, jjm, vhoriid, llm, 1, &
67             llm, zvertiid, 'inst(X)', t_ops, t_wrt)
68        call histdef(histid, 'temp', 'temperature', 'K', iip1, jjp1, &
69             thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
70        call histdef(histid, 'theta', 'temperature potentielle', 'K', iip1, jjp1, &
71             thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
72        call histdef(histid, 'phi', 'geopotential', 'm2 s-2', iip1, jjp1, thoriid, &
73             llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
74    
     call histhori_regular(fileid, iip1, rlong, jjp1, rlat, 'scalar', &  
          'Grille points scalaires', thoriid)  
     !  
     ! Appel a histvert pour la grille verticale  
     !  
     call histvert(fileid, 'sig_s', 'Niveaux sigma', '-', &  
          llm, nivsigs, zvertiid)  
     ! Pour le fichier V  
     call histvert(filevid, 'sig_s', 'Niveaux sigma', '-', &  
          llm, nivsigs, zvertiid)  
     !  
     ! Appels a histdef pour la definition des variables a sauvegarder  
     !  
     ! Vents U  
     !  
     call histdef(fileid, 'ucov', 'vents u covariants', 'm/s', &  
          iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &  
          'inst(X)', t_ops, t_wrt)  
     !  
     ! Vents V  
     !  
     call histdef(filevid, 'vcov', 'vents v covariants', 'm/s', &  
          iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &  
          'inst(X)', t_ops, t_wrt)  
   
     !  
     ! Temperature potentielle  
     !  
     call histdef(fileid, 'teta', 'temperature potentielle', '-', &  
          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
          'inst(X)', t_ops, t_wrt)  
     !  
     ! Geopotentiel  
     !  
     call histdef(fileid, 'phi', 'geopotentiel instantane', '-', &  
          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
          'inst(X)', t_ops, t_wrt)  
     !  
75      ! Traceurs      ! Traceurs
76      !      DO iq = 1, nqmx
77      DO iq=1, nq         call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &
78         call histdef(fileid, ttext(iq), ttext(iq), '-', &              llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
             iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
             'inst(X)', t_ops, t_wrt)  
79      enddo      enddo
80      !  
81      ! Masse      call histdef(histid, 'masse', 'masse', 'kg', iip1, jjp1, thoriid, llm, 1, &
82      !           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
83      call histdef(fileid, 'masse', 'masse', 'kg', &      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &
84           iip1, jjp1, thoriid, 1, 1, 1, -99, &           thoriid, 1, 1, 1, -99, 'inst(X)', t_ops, t_wrt)
85           'inst(X)', t_ops, t_wrt)  
86      !      call histend(histid)
87      ! Pression au sol      call histend(histuid)
88      !      call histend(histvid)
     call histdef(fileid, 'ps', 'pression naturelle au sol', 'Pa', &  
          iip1, jjp1, thoriid, 1, 1, 1, -99, &  
          'inst(X)', t_ops, t_wrt)  
     !  
     ! Pression au sol  
     !  
     call histdef(fileid, 'phis', 'geopotentiel au sol', '-', &  
          iip1, jjp1, thoriid, 1, 1, 1, -99, &  
          'inst(X)', t_ops, t_wrt)  
     !  
     ! Fin  
     !  
     call histend(fileid)  
     call histend(filevid)  
89    
90    end subroutine inithist    end subroutine inithist
91    

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

  ViewVC Help
Powered by ViewVC 1.1.21