/[lmdze]/trunk/libf/phylmd/ini_histhf.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/ini_histhf.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 30 by guez, Thu Apr 1 09:07:28 2010 UTC
# Line 6  module ini_hist Line 6  module ini_hist
6    
7  contains  contains
8    
9    subroutine ini_histhf(dtime, presnivs, nid_hf, nid_hf3d)    subroutine ini_histhf(dtime, nid_hf, nid_hf3d)
10    
11      ! From phylmd/ini_histhf.h, version 1.3 2005/05/25 13:10:09      ! From phylmd/ini_histhf.h, version 1.3 2005/05/25 13:10:09
12    
13      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
14      use temps, only: day_ref, annee_ref, itau_phy      use temps, only: day_ref, annee_ref, itau_phy
15      use dimphy, only: klon      use dimphy, only: klon
16      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend      USE calendar, only: ymds2ju
17        use histcom, only: histbeg_totreg, histvert, histend
18      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
19        use comvert, only: presnivs
20    
21      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
     real, intent(in):: presnivs(:)  
22      integer, intent(out):: nid_hf, nid_hf3d      integer, intent(out):: nid_hf, nid_hf3d
23    
24      REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)      REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
# Line 43  contains Line 44  contains
44      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &
45           llm, presnivs/100., nvert)           llm, presnivs/100., nvert)
46    
47      call ini_histhf3d(dtime, presnivs, nid_hf3d)      call ini_histhf3d(dtime, nid_hf3d)
48      CALL histend(nid_hf)      CALL histend(nid_hf)
49    
50    end subroutine ini_histhf    end subroutine ini_histhf
51    
52    !******************************************************************    !******************************************************************
53    
54    subroutine ini_histhf3d(dtime, presnivs, nid_hf3d)    subroutine ini_histhf3d(dtime, nid_hf3d)
55    
56      ! From phylmd/ini_histhf3d.h, v 1.2 2005/05/25 13:10:09      ! From phylmd/ini_histhf3d.h, v 1.2 2005/05/25 13:10:09
57    
# Line 61  contains Line 62  contains
62      use temps, only: itau_phy, day_ref, annee_ref      use temps, only: itau_phy, day_ref, annee_ref
63      use clesphys, only: ecrit_hf      use clesphys, only: ecrit_hf
64      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
65      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef      USE calendar, only: ymds2ju
66        use histcom, only: histbeg_totreg, histvert, histend, histdef
67        use comvert, only: presnivs
68    
69      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
     real, intent(in):: presnivs(:)  
70      integer, intent(out):: nid_hf3d      integer, intent(out):: nid_hf3d
71    
72      real zstohf, zout      real zstohf, zout
# Line 123  contains Line 125  contains
125    
126    !******************************************************************    !******************************************************************
127    
128    subroutine ini_histday(dtime, presnivs, ok_journe, nid_day)    subroutine ini_histday(dtime, ok_journe, nid_day, nq)
129    
130      ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09      ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09
131    
132      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
     use dimphy, only: klon  
133      use temps, only: itau_phy, day_ref, annee_ref      use temps, only: itau_phy, day_ref, annee_ref
134      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef      USE calendar, only: ymds2ju
135        use histcom, only: histbeg_totreg, histvert, histend, histdef
136      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
137      use clesphys, only: ecrit_day      use clesphys, only: ecrit_day
138        use grid_change, only: gr_phy_write_2d
139        use comvert, only: presnivs
140    
141      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
     real, intent(in):: presnivs(:)  
142      logical, intent(in):: ok_journe      logical, intent(in):: ok_journe
143      integer, intent(out):: nid_day      integer, intent(out):: nid_day
144        INTEGER, intent(in):: nq ! nombre de traceurs (y compris vapeur d'eau)
145    
146      REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)      ! Variables local to the procedure:
147      integer i, nhori, nvert, idayref      REAL zx_lat(iim, jjm + 1)
148        integer nhori, nvert
149      real zjulian      real zjulian
150    
151      !--------------------------------      !--------------------------------
152    
153      IF (ok_journe) THEN      IF (ok_journe) THEN
154         idayref = day_ref         CALL ymds2ju(annee_ref, 1, day_ref, 0., zjulian)
155         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)         zx_lat = gr_phy_write_2d(rlat)
156           CALL histbeg_totreg("histday", rlon(2: iim+1), zx_lat(1, :), 1, iim, &
157         CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlon, zx_lon)              1, jjm + 1, itau_phy, zjulian, dtime, nhori, nid_day)
        DO i = 1, iim  
           zx_lon(i, 1) = rlon(i+1)  
           zx_lon(i, jjm + 1) = rlon(i+1)  
        ENDDO  
        CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlat, zx_lat)  
        CALL histbeg_totreg("histday", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &  
             jjm + 1, itau_phy, zjulian, dtime, nhori, nid_day)  
158         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &
159              llm, presnivs/100., nvert)              llm, presnivs/100., nvert)
160         call histdef(nid_day, "Sigma_O3_Royer", &         if (nq <= 4) then
161              "column-density of ozone, in a cell, from Royer", "DU", &            call histdef(nid_day, "Sigma_O3_Royer", &
162              pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, par_oriz=1, &                 "column-density of ozone, in a cell, from Royer", "DU", &
163              par_szz=llm, pzid=nvert, popp="ave(X)", pfreq_opp=dtime, &                 pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, &
164              pfreq_wrt=real(ecrit_day))                 par_oriz=1, par_szz=llm, pzid=nvert, popp="ave(X)", &
165                   pfreq_opp=dtime, pfreq_wrt=real(ecrit_day))
166           end if
167         CALL histend(nid_day)         CALL histend(nid_day)
168      ENDIF      ENDIF
169    
# Line 171  contains Line 171  contains
171    
172    !****************************************************    !****************************************************
173    
174    subroutine ini_histins(dtime, presnivs, ok_instan, nid_ins)    subroutine ini_histins(dtime, ok_instan, nid_ins)
175    
176      ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09      ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09
177    
# Line 180  contains Line 180  contains
180      use temps, only: itau_phy, day_ref, annee_ref      use temps, only: itau_phy, day_ref, annee_ref
181      use clesphys, only: ecrit_ins      use clesphys, only: ecrit_ins
182      use indicesol, only: nbsrf, clnsurf      use indicesol, only: nbsrf, clnsurf
183      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef      USE calendar, only: ymds2ju
184        use histcom, only: histbeg_totreg, histvert, histend, histdef
185      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
186        use comvert, only: presnivs
187    
188      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
     real, intent(in):: presnivs(:)  
189      logical, intent(in):: ok_instan      logical, intent(in):: ok_instan
190      integer, intent(out):: nid_ins      integer, intent(out):: nid_ins
191    
# Line 464  contains Line 465  contains
465    
466    end subroutine ini_histins    end subroutine ini_histins
467    
468      !*************************************************
469    
470      subroutine ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
471    
472        ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30
473    
474        use dimens_m, only: iim, jjm, llm
475        USE calendar, only: ymds2ju
476        use histcom, only: histbeg_totreg, histvert, histend, histdef
477        use temps, only: annee_ref, day_ref, itau_phy
478        use iniadvtrac_m, only: niadv, tnom, ttext
479        use dimphy, only: klon
480        use clesphys, only: ecrit_tra
481        use grid_change, only: gr_phy_write_2d
482        use phyetat0_m, only: rlon, rlat
483        use comvert, only: presnivs
484    
485        INTEGER, intent(out):: nid_tra
486        real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
487    
488        integer, intent(in):: nq_phys
489        ! (nombre de traceurs auxquels on applique la physique)
490    
491        logical, intent(in):: lessivage
492    
493        ! Variables local to the procedure:
494    
495        REAL zjulian
496        REAL zx_lat(iim, jjm+1)
497        INTEGER nhori, nvert
498        REAL zsto, zout
499        integer it, iq, iiq
500    
501        !---------------------------------------------------------
502    
503        CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)
504        zx_lat(:, :) = gr_phy_write_2d(rlat)
505        CALL histbeg_totreg("histrac", rlon(2:iim+1), zx_lat(1, :), &
506             1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)
507        CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &
508             presnivs, nvert)
509    
510        zsto = pdtphys
511        zout = pdtphys * REAL(ecrit_tra)
512    
513        CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &
514             iim, jjm+1, nhori, 1, 1, 1, -99, &
515             "once",  zsto, zout)
516        CALL histdef(nid_tra, "aire", "Grid area", "-", &
517             iim, jjm+1, nhori, 1, 1, 1, -99, &
518             "once",  zsto, zout)
519        CALL histdef(nid_tra, "zmasse", "column density of air in cell", &
520             "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "ave(X)", &
521             zsto, zout)
522    
523        DO it = 1, nq_phys
524           ! champ 2D
525           iq=it+2
526           iiq=niadv(iq)
527           CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &
528                nhori, llm, 1, llm, nvert, "ave(X)", zsto, zout)
529           if (lessivage) THEN
530              CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &
531                   "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
532                   "ave(X)", zsto, zout)
533           endif
534    
535           !---Ajout Olivia
536           CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &
537                "tendance thermique"// ttext(iiq), "?", &
538                iim, jjm+1, nhori, llm, 1, llm, nvert, &
539                "ave(X)", zsto, zout)
540           CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &
541                "tendance convection"// ttext(iiq), "?", &
542                iim, jjm+1, nhori, llm, 1, llm, nvert, &
543                "ave(X)", zsto, zout)
544           CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &
545                "tendance couche limite"// ttext(iiq), "?", &
546                iim, jjm+1, nhori, llm, 1, llm, nvert, &
547                "ave(X)", zsto, zout)
548           !---fin Olivia    
549    
550        ENDDO
551    
552        CALL histdef(nid_tra, "pplay", "", "-", &
553             iim, jjm+1, nhori, llm, 1, llm, nvert, &
554             "inst(X)", zout, zout)
555        CALL histdef(nid_tra, "T", "temperature", "K", iim, jjm+1, nhori, llm, &
556             1, llm, nvert, "inst(X)", zout, zout)
557    
558        CALL histend(nid_tra)
559    
560      end subroutine ini_histrac
561    
562  end module ini_hist  end module ini_hist

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

  ViewVC Help
Powered by ViewVC 1.1.21