/[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/Sources/dyn3d/inithist.f revision 212 by guez, Thu Jan 12 12:31:31 2017 UTC trunk/dyn3d/inithist.f90 revision 335 by guez, Thu Sep 12 21:22:46 2019 UTC
# Line 6  module inithist_m Line 6  module inithist_m
6    
7  contains  contains
8    
9    subroutine inithist(tstep, nq, 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      ! 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    
17      USE dimens_m, ONLY: jjm, llm      use comconst, only: dtvr
18        USE dimensions, ONLY: jjm, llm, nqmx
19      USE disvert_m, ONLY: presnivs      USE disvert_m, ONLY: presnivs
20      use dynetat0_m, only: day_ref, annee_ref, rlatu, rlatv, rlonu, rlonv      use dynetat0_m, only: itau_dyn, rlatu, rlatv, rlonu, rlonv
21      USE histbeg_totreg_m, ONLY : histbeg_totreg      USE dynetat0_chosen_m, ONLY: day_ref, annee_ref
22      USE histdef_m, ONLY : histdef      use histbeg_totreg_m, only: histbeg_totreg
23      USE histend_m, ONLY : histend      USE histdef_m, ONLY: histdef
24      USE histvert_m, ONLY : histvert      USE histend_m, ONLY: histend
25      USE iniadvtrac_m, ONLY: ttext      USE histvert_m, ONLY: histvert
26        USE infotrac_init_m, ONLY: ttext
27      USE nr_util, ONLY: pi      USE nr_util, ONLY: pi
28      USE paramet_m, ONLY: iip1, jjp1      USE paramet_m, ONLY: iip1, jjp1
29      USE temps, ONLY: itau_dyn      use ymds2ju_m, ONLY: ymds2ju
     USE ymds2ju_m, ONLY: ymds2ju  
30    
     real, intent(in):: tstep ! durée du pas de temps en secondes  
     integer, intent(in):: nq ! nombre de traceurs  
31      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
32      real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier      real, intent(in):: t_wrt ! fréquence d'écriture sur le fichier
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  
38    
39      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
40    
41      CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)      print *, "Call sequence information: inithist"
42        CALL ymds2ju(annee_ref, 1, day_ref, 0., julian)
43    
44      do jj = 1, jjp1      call histbeg_totreg("dyn_histu.nc", rlonu * 180. / pi, rlatu * 180. / pi, &
45         do ii = 1, iip1           1, iip1, 1, jjp1, itau_dyn, julian, dtvr, uhoriid, histuid)
           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)  
   
     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      ! 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      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, &
52           1, jjm, itau_dyn, zjulian, tstep, vhoriid, histvid)           1, iip1, 1, jjm, itau_dyn, julian, dtvr, 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)  
   
     ! Appel a histvert pour la grille verticale  
53    
54      call histvert(histid, 'presnivs', 'Niveaux pression','mb', presnivs/100., &      call histbeg_totreg("dyn_hist.nc", rlonv * 180. / pi, rlatu * 180. / pi, &
55           zvertiid,'down')           1, iip1, 1, jjp1, itau_dyn, julian, dtvr, thoriid, histid)
     call histvert(histvid, 'presnivs', 'Niveaux pression','mb', &  
          presnivs/100., zvertiid,'down')  
     call histvert(histuid, 'presnivs', 'Niveaux pression','mb', &  
          presnivs/100., zvertiid,'down')  
56    
57      ! Appels a histdef pour la definition des variables a sauvegarder      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, &      call histdef(histuid, 'u', 'vent u', 'm/s', iip1, jjp1, uhoriid, llm, 1, &
65           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
66      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, &
67           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
68      call histdef(histid, 'teta', 'temperature potentielle', '-', iip1, jjp1, &      call histdef(histid, 'temp', 'temperature', 'K', iip1, jjp1, &
69           thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)           thoriid, llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
70      call histdef(histid, 'phi', 'geopotentiel', '-', iip1, jjp1, thoriid, &      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)           llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
74    
75      ! Traceurs      ! Traceurs
76      DO iq=1, nq      DO iq = 1, nqmx
77         call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &         call histdef(histid, ttext(iq), ttext(iq), '-', iip1, jjp1, thoriid, &
78              llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)              llm, 1, llm, zvertiid, 'inst(X)', t_ops, t_wrt)
79      enddo      enddo
# Line 107  contains Line 82  contains
82           llm, zvertiid, 'inst(X)', t_ops, t_wrt)           llm, zvertiid, 'inst(X)', t_ops, t_wrt)
83      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', iip1, jjp1, &
84           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)  
85    
86      call histend(histid)      call histend(histid)
87      call histend(histuid)      call histend(histuid)

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

  ViewVC Help
Powered by ViewVC 1.1.21