/[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 61 by guez, Fri Apr 20 14:58:43 2012 UTC trunk/dyn3d/inithist.f revision 261 by guez, Wed Mar 7 13:33:15 2018 UTC
# Line 2  module inithist_m Line 2  module inithist_m
2    
3    implicit none    implicit none
4    
5      integer histid, histvid, histuid
6    
7  contains  contains
8    
9    subroutine inithist(day0, anne0, tstep, nq, t_ops, t_wrt)    subroutine inithist(tstep, nq, 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      ! L. Fairhead, LMD, 03/99
13    
14      ! Routine d'initialisation des écritures des fichiers histoires      ! Routine d'initialisation des écritures des fichiers histoires au
15      ! LMDZ au format IOIPSL.      ! format IOIPSL.
16    
     USE calendar, ONLY: ymds2ju  
     USE com_io_dyn, ONLY: histid, histuid, histvid  
     USE histbeg_totreg_m, ONLY : histbeg_totreg  
     USE histdef_m, ONLY : histdef  
     USE histend_m, ONLY : histend  
     USE histvert_m, ONLY : histvert  
17      USE dimens_m, ONLY: jjm, llm      USE dimens_m, ONLY: jjm, llm
18      USE paramet_m, ONLY: iip1, jjp1      USE disvert_m, ONLY: presnivs
19      USE comvert, ONLY: presnivs      use dynetat0_m, only: day_ref, annee_ref, rlatu, rlatv, rlonu, rlonv
20      USE comgeom, ONLY: rlatu, rlatv, rlonu, rlonv      use histbeg_totreg_m, only: histbeg_totreg
21      USE temps, ONLY: itau_dyn      USE histdef_m, ONLY: histdef
22        USE histend_m, ONLY: histend
23        USE histvert_m, ONLY: histvert
24      USE iniadvtrac_m, ONLY: ttext      USE iniadvtrac_m, ONLY: ttext
25      USE nr_util, ONLY: pi      USE nr_util, ONLY: pi
26        USE paramet_m, ONLY: iip1, jjp1
27        USE temps, ONLY: itau_dyn
28        use ymds2ju_m, ONLY: ymds2ju
29    
     integer, intent(in):: day0, anne0 ! date de référence  
30      real, intent(in):: tstep ! durée du pas de temps en secondes      real, intent(in):: tstep ! durée du pas de temps en secondes
31      integer, intent(in):: nq ! nombre de traceurs      integer, intent(in):: nq ! nombre de traceurs
32      real, intent(in):: t_ops ! fréquence de l'opération pour IOIPSL      real, intent(in):: t_ops ! fréquence de l'opération pour IOIPSL
33      real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier      real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier
34    
35      ! Variables locales:      ! Local:
36      real zjulian      real julian
37      integer iq      integer iq
     real rlong(iip1, jjp1), rlat(iip1, jjp1)  
38      integer uhoriid, vhoriid, thoriid, zvertiid      integer uhoriid, vhoriid, thoriid, zvertiid
     integer ii, jj  
     integer zan, dayref  
39    
40      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
41    
42      zan = anne0      print *, "Call sequence information: inithist"
43      dayref = day0      CALL ymds2ju(annee_ref, 1, day_ref, 0., julian)
     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  
   
     call histbeg_totreg("dyn_histu.nc", rlong(:,1), rlat(1,:), 1, iip1, 1, &  
          jjp1, itau_dyn, zjulian, tstep, uhoriid, histuid)  
44    
45      do jj = 1, jjm      call histbeg_totreg("dyn_histu.nc", rlonu * 180. / pi, rlatu * 180. / pi, &
46         do ii = 1, iip1           1, iip1, 1, jjp1, itau_dyn, julian, tstep, uhoriid, histuid)
           rlong(ii, jj) = rlonv(ii) * 180. / pi  
           rlat(ii, jj) = rlatv(jj) * 180. / pi  
        enddo  
     enddo  
47    
48      ! 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,
49      ! 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
50      ! un meme fichier)      ! un meme fichier)
51    
52      call histbeg_totreg('dyn_histv.nc', rlong(:, 1), rlat(1, :jjm), 1, iip1, &      call histbeg_totreg('dyn_histv.nc', rlonv * 180. / pi, rlatv * 180. / pi, &
53           1, jjm, itau_dyn, zjulian, tstep, vhoriid, histvid)           1, iip1, 1, jjm, itau_dyn, julian, tstep, vhoriid, histvid)
   
     do jj = 1, jjp1  
        do ii = 1, iip1  
           rlong(ii, jj) = rlonv(ii) * 180. / pi  
           rlat(ii, jj) = rlatu(jj) * 180. / pi  
        enddo  
     enddo  
   
     call histbeg_totreg("dyn_hist.nc", rlong(:, 1), rlat(1, :), 1, iip1, 1, &  
          jjp1, itau_dyn, zjulian, tstep, thoriid, histid)  
54    
55      ! Appel a histvert pour la grille verticale      call histbeg_totreg("dyn_hist.nc", rlonv * 180. / pi, rlatu * 180. / pi, &
56             1, iip1, 1, jjp1, itau_dyn, julian, tstep, thoriid, histid)
57    
58      call histvert(histid, 'presnivs', 'Niveaux pression','mb', llm, &      call histvert(histid, 'presnivs', 'Niveaux pression', 'mb', presnivs/100., &
59           presnivs/100., zvertiid,'down')           zvertiid, 'down')
60      call histvert(histvid, 'presnivs', 'Niveaux pression','mb', llm, &      call histvert(histvid, 'presnivs', 'Niveaux pression', 'mb', &
61           presnivs/100., zvertiid,'down')           presnivs/100., zvertiid, 'down')
62      call histvert(histuid, 'presnivs', 'Niveaux pression','mb', llm, &      call histvert(histuid, 'presnivs', 'Niveaux pression', 'mb', &
63           presnivs/100., zvertiid,'down')           presnivs/100., zvertiid, 'down')
   
     ! Appels a histdef pour la definition des variables a sauvegarder  
64    
65      call histdef(histuid, 'u', 'vent u', 'm/s', iip1, jjp1, uhoriid, llm, 1, &      call histdef(histuid, 'u', 'vent u', 'm/s', iip1, jjp1, uhoriid, llm, 1, &
66           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
67      call histdef(histvid, 'v', 'vent v', 'm/s', iip1, jjm, vhoriid, llm, 1, &      call histdef(histvid, 'v', 'vent v', 'm/s', iip1, jjm, vhoriid, llm, 1, &
68           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
69      call histdef(histid, 'teta', 'temperature potentielle', '-', iip1, jjp1, &      call histdef(histid, 'temp', 'temperature', 'K', iip1, jjp1, &
70             thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
71        call histdef(histid, 'theta', 'temperature potentielle', 'K', iip1, jjp1, &
72           thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)           thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
73      call histdef(histid, 'phi', 'geopotentiel', '-', iip1, jjp1, thoriid, &      call histdef(histid, 'phi', 'geopotentiel', '-', iip1, jjp1, thoriid, &
74           llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
75    
76      ! Traceurs      ! Traceurs
77      DO iq=1, nq      DO iq = 1, nq
78         call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &         call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &
79              llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)              llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
80      enddo      enddo
# Line 110  contains Line 83  contains
83           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
84      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &
85           thoriid, 1, 1, 1, -99, 'inst(X)', t_ops, t_wrt)           thoriid, 1, 1, 1, -99, 'inst(X)', t_ops, t_wrt)
     call histdef(histid, 'phis', 'geopotentiel au sol', '-', iip1, jjp1, &  
          thoriid, 1, 1, 1, -99, 'inst(X)', t_ops, t_wrt)  
86    
87      call histend(histid)      call histend(histid)
88      call histend(histuid)      call histend(histuid)

Legend:
Removed from v.61  
changed lines
  Added in v.261

  ViewVC Help
Powered by ViewVC 1.1.21