/[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 3 by guez, Wed Feb 27 13:16:39 2008 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, infile, t_ops, &    subroutine inithist(t_ops, t_wrt)
        t_wrt)  
10    
11      ! From inithist.F,v 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 ecritures des fichiers histoires LMDZ      ! Routine d'initialisation des écritures des fichiers histoires au
15      !   au format IOIPSL      ! format IOIPSL.
16    
17      !   Appels succesifs des routines: histbeg      use comconst, only: dtvr
18      !                                  histhori      USE dimensions, ONLY: jjm, llm, nqmx
19      !                                  histver      USE disvert_m, ONLY: presnivs
20      !                                  histdef      use dynetat0_m, only: itau_dyn, rlatu, rlatv, rlonu, rlonv
21      !                                  histend      USE dynetat0_chosen_m, ONLY: day_ref, annee_ref
22        use histbeg_totreg_m, only: histbeg_totreg
23      !   Entree:      USE histdef_m, ONLY: histdef
24      !      infile: nom du fichier histoire a creer      USE histend_m, ONLY: histend
25      !      day0,anne0: date de reference      USE histvert_m, ONLY: histvert
26      !      tstep: duree du pas de temps en seconde      USE infotrac_init_m, ONLY: ttext
27      !      t_ops: frequence de l'operation pour IOIPSL      USE nr_util, ONLY: pi
28      !      t_wrt: frequence d'ecriture sur le fichier      USE paramet_m, ONLY: iip1, jjp1
29      !      nq: nombre de traceurs      use ymds2ju_m, ONLY: ymds2ju
   
     !   Sortie:  
     !      fileid: ID du fichier netcdf cree  
     !      filevid:ID du fichier netcdf pour la grille v  
   
     !   L. Fairhead, LMD, 03/99  
   
     USE IOIPSL  
     use dimens_m  
     use paramet_m  
     use comconst  
     use comvert  
     use logic  
     use comgeom  
     use serre  
     use temps  
     use ener  
     use advtrac_m  
   
     !   Arguments  
     character(len=*) infile  
     integer day0, anne0  
     real, intent(in):: tstep, t_ops, t_wrt  
     integer fileid, filevid  
     integer nq  
30    
31      !   Variables locales      real, intent(in):: t_ops ! fréquence de l'opération pour IOIPSL
32        real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier
33    
34      integer tau0      ! 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      !  Initialisations      print *, "Call sequence information: inithist"
42        CALL ymds2ju(annee_ref, 1, day_ref, 0., julian)
     pi = 4. * atan (1.)  
   
     !  Appel a histbeg: creation du fichier netcdf et initialisations diverses  
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)  
     tau0 = itau_dyn  
   
     do jj = 1, jjp1  
        do ii = 1, iip1  
           rlong(ii,jj) = rlonu(ii) * 180. / pi  
           rlat(ii,jj) = rlatu(jj) * 180. / pi  
        enddo  
     enddo  
   
     call histbeg_totreg(infile, iip1, rlong(:,1), jjp1, rlat(1,:), &  
          1, iip1, 1, jjp1, &  
          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)  
   
     do jj = 1, jjm  
        do ii = 1, iip1  
           rlong(ii,jj) = rlonv(ii) * 180. / pi  
           rlat(ii,jj) = rlatv(jj) * 180. / pi  
        enddo  
     enddo  
46    
47      call histbeg_totreg('dyn_histv.nc', iip1, rlong(:,1), jjm, rlat(1,:jjm), &      ! Creation du fichier histoire pour la grille en V (oblige pour l'instant,
48           1, iip1, 1, jjm, &      ! IOIPSL ne permet pas de grilles avec des nombres de point differents dans
49           tau0, zjulian, tstep, vhoriid, filevid)      ! un meme fichier)
50      !  
51      !  Appel a histhori pour rajouter les autres grilles horizontales      call histbeg_totreg('dyn_histv.nc', rlonv * 180. / pi, rlatv * 180. / pi, &
52      !           1, iip1, 1, jjm, itau_dyn, julian, dtvr, vhoriid, histvid)
53      do jj = 1, jjp1  
54         do ii = 1, iip1      call histbeg_totreg("dyn_hist.nc", rlonv * 180. / pi, rlatu * 180. / pi, &
55            rlong(ii,jj) = rlonv(ii) * 180. / pi           1, iip1, 1, jjp1, itau_dyn, julian, dtvr, thoriid, histid)
56            rlat(ii,jj) = rlatu(jj) * 180. / pi  
57         enddo      call histvert(histid, 'presnivs', 'Niveaux pression', 'mb', presnivs/100., &
58             zvertiid, 'down')
59        call histvert(histvid, 'presnivs', 'Niveaux pression', 'mb', &
60             presnivs/100., zvertiid, 'down')
61        call histvert(histuid, 'presnivs', 'Niveaux pression', 'mb', &
62             presnivs/100., zvertiid, 'down')
63    
64        call histdef(histuid, 'u', 'vent u', 'm/s', iip1, jjp1, uhoriid, llm, 1, &
65             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    
75        ! Traceurs
76        DO iq = 1, nqmx
77           call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &
78                llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
79      enddo      enddo
80    
81      call histhori(fileid, iip1, rlong, jjp1, rlat, 'scalar', &      call histdef(histid, 'masse', 'masse', 'kg', iip1, jjp1, thoriid, llm, 1, &
82           'Grille points scalaires', thoriid)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
83      !      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &
84      !  Appel a histvert pour la grille verticale           thoriid, 1, 1, 1, -99, 'inst(X)', t_ops, t_wrt)
85      !  
86      call histvert(fileid, 'sig_s', 'Niveaux sigma','-', &      call histend(histid)
87           llm, nivsigs, zvertiid)      call histend(histuid)
88      ! Pour le fichier V      call histend(histvid)
     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, &  
          32, 'inst(X)', t_ops, t_wrt)  
     !  
     !  Vents V  
     !  
     call histdef(filevid, 'vcov', 'vents v covariants', 'm/s', &  
          iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &  
          32, 'inst(X)', t_ops, t_wrt)  
   
     !  
     !  Temperature potentielle  
     !  
     call histdef(fileid, 'teta', 'temperature potentielle', '-', &  
          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
          32, 'inst(X)', t_ops, t_wrt)  
     !  
     !  Geopotentiel  
     !  
     call histdef(fileid, 'phi', 'geopotentiel instantane', '-', &  
          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
          32, 'inst(X)', t_ops, t_wrt)  
     !  
     !  Traceurs  
     !  
     DO iq=1,nq  
        call histdef(fileid, ttext(iq),  ttext(iq), '-', &  
             iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &  
             32, 'inst(X)', t_ops, t_wrt)  
     enddo  
     !  
     !  Masse  
     !  
     call histdef(fileid, 'masse', 'masse', 'kg', &  
          iip1, jjp1, thoriid, 1, 1, 1, -99, &  
          32, 'inst(X)', t_ops, t_wrt)  
     !  
     !  Pression au sol  
     !  
     call histdef(fileid, 'ps', 'pression naturelle au sol', 'Pa', &  
          iip1, jjp1, thoriid, 1, 1, 1, -99, &  
          32, 'inst(X)', t_ops, t_wrt)  
     !  
     !  Pression au sol  
     !  
     call histdef(fileid, 'phis', 'geopotentiel au sol', '-', &  
          iip1, jjp1, thoriid, 1, 1, 1, -99, &  
          32, '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.3  
changed lines
  Added in v.335

  ViewVC Help
Powered by ViewVC 1.1.21