/[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

trunk/libf/phylmd/ini_hist.f90 revision 15 by guez, Fri Aug 1 15:24:12 2008 UTC trunk/libf/phylmd/ini_histhf.f90 revision 34 by guez, Wed Jun 2 11:01:12 2010 UTC
# Line 1  Line 1 
1  module ini_hist  module ini_histhf_m
2    
3    ! This module is clean: no C preprocessor directive, no include line.    implicit none
   
   IMPLICIT none  
4    
5  contains  contains
6    
7    subroutine ini_histhf(dtime, presnivs, nid_hf, nid_hf3d)    subroutine ini_histhf(dtime, nid_hf, nid_hf3d)
8    
9      ! 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
10    
11      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
12      use temps, only: day_ref, annee_ref, itau_phy      use temps, only: day_ref, annee_ref, itau_phy
13      use dimphy, only: klon      use dimphy, only: klon
14      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend      USE calendar, only: ymds2ju
15        use histcom, only: histbeg_totreg, histvert, histend
16      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
17        use comvert, only: presnivs
18        use ini_histhf3d_m, only: ini_histhf3d
19    
20      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
     real, intent(in):: presnivs(:)  
21      integer, intent(out):: nid_hf, nid_hf3d      integer, intent(out):: nid_hf, nid_hf3d
22    
23      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 43  contains
43      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &
44           llm, presnivs/100., nvert)           llm, presnivs/100., nvert)
45    
46      call ini_histhf3d(dtime, presnivs, nid_hf3d)      call ini_histhf3d(dtime, nid_hf3d)
47      CALL histend(nid_hf)      CALL histend(nid_hf)
48    
49    end subroutine ini_histhf    end subroutine ini_histhf
50    
51    !******************************************************************  end module ini_histhf_m
   
   subroutine ini_histhf3d(dtime, presnivs, nid_hf3d)  
   
     ! From phylmd/ini_histhf3d.h, v 1.2 2005/05/25 13:10:09  
   
     ! sorties hf 3d  
   
     use dimens_m, only: iim, jjm, llm  
     use dimphy, only: klon, nbtr  
     use temps, only: itau_phy, day_ref, annee_ref  
     use clesphys, only: ecrit_hf  
     use phyetat0_m, only: rlon, rlat  
     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef  
   
     REAL, intent(in):: dtime ! pas temporel de la physique (s)  
     real, intent(in):: presnivs(:)  
     integer, intent(out):: nid_hf3d  
   
     real zstohf, zout  
     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)  
     real zjulian  
     integer i, nhori, nvert, idayref  
   
     !------------------------------------------  
   
     zstohf = dtime * REAL(ecrit_hf)  
     zout = dtime * REAL(ecrit_hf)  
   
     idayref = day_ref  
     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)  
   
     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)  
     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("histhf3d", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &  
          (jjm + 1), itau_phy, zjulian, dtime, nhori, nid_hf3d)  
   
     CALL histvert(nid_hf3d, "presnivs", "Vertical levels", "mb", &  
          llm, presnivs/100., nvert)  
   
     ! Champs 3D:  
   
     CALL histdef(nid_hf3d, "temp", "Air temperature", "K", &  
          iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
          "ave(X)", zstohf, zout)  
   
     CALL histdef(nid_hf3d, "ovap", "Specific humidity", "kg/kg", &  
          iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
          "ave(X)", zstohf, zout)  
   
     CALL histdef(nid_hf3d, "vitu", "Zonal wind", "m/s", &  
          iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
          "ave(X)", zstohf, zout)  
   
     CALL histdef(nid_hf3d, "vitv", "Meridional wind", "m/s", &  
          iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
          "ave(X)", zstohf, zout)  
   
     if (nbtr >= 3) then  
        CALL histdef(nid_hf3d, "O3", "Ozone mass fraction", "?", iim, &  
             (jjm + 1), nhori, llm, 1, llm, nvert, "ave(X)", zstohf, &  
             zout)  
     end if  
   
     CALL histend(nid_hf3d)  
   
   end subroutine ini_histhf3d  
   
   !******************************************************************  
   
   subroutine ini_histday(dtime, presnivs, ok_journe, nid_day)  
   
     ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09  
   
     use dimens_m, only: iim, jjm, llm  
     use dimphy, only: klon  
     use temps, only: itau_phy, day_ref, annee_ref  
     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef  
     use phyetat0_m, only: rlon, rlat  
     use clesphys, only: ecrit_day  
   
     REAL, intent(in):: dtime ! pas temporel de la physique (s)  
     real, intent(in):: presnivs(:)  
     logical, intent(in):: ok_journe  
     integer, intent(out):: nid_day  
   
     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)  
     integer i, nhori, nvert, idayref  
     real zjulian  
   
     !--------------------------------  
   
     IF (ok_journe) THEN  
        idayref = day_ref  
        CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)  
   
        CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlon, zx_lon)  
        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)  
        CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &  
             llm, presnivs/100., nvert)  
        call histdef(nid_day, "Sigma_O3_Royer", &  
             "column-density of ozone, in a cell, from Royer", "DU", &  
             pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, par_oriz=1, &  
             par_szz=llm, pzid=nvert, popp="ave(X)", pfreq_opp=dtime, &  
             pfreq_wrt=real(ecrit_day))  
        CALL histend(nid_day)  
     ENDIF  
   
   end subroutine ini_histday  
   
   !****************************************************  
   
   subroutine ini_histins(dtime, presnivs, ok_instan, nid_ins)  
   
     ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09  
   
     use dimens_m, only: iim, jjm, llm  
     use dimphy, only: klon  
     use temps, only: itau_phy, day_ref, annee_ref  
     use clesphys, only: ecrit_ins  
     use indicesol, only: nbsrf, clnsurf  
     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef  
     use phyetat0_m, only: rlon, rlat  
   
     REAL, intent(in):: dtime ! pas temporel de la physique (s)  
     real, intent(in):: presnivs(:)  
     logical, intent(in):: ok_instan  
     integer, intent(out):: nid_ins  
   
     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)  
     real zjulian, zsto, zout  
     integer i, nhori, nvert, idayref, nsrf  
   
     !-------------------------------------------------------------------  
   
     IF (ok_instan) THEN  
   
        zsto = dtime * ecrit_ins  
        zout = dtime * ecrit_ins  
   
        idayref = day_ref  
        CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)  
   
        CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)  
        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("histins", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &  
             jjm + 1, itau_phy, zjulian, dtime, nhori, nid_ins)  
        write(*, *)'Inst ', itau_phy, zjulian  
        CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &  
             llm, presnivs/100., nvert)  
   
        CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "once", zsto, zout)  
   
        CALL histdef(nid_ins, "aire", "Grid area", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "once", zsto, zout)  
   
        ! Champs 2D:  
   
        CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol",  &  
             "kg/(s*m2)", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        !        CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",  
        !    .                iim, (jjm + 1), nhori, 1, 1, 1, -99,  
        !    .                "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "topl", "OLR", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface",  &  
             "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        DO nsrf = 1, nbsrf  
   
           call histdef(nid_ins, "pourc_"//clnsurf(nsrf),  &  
                "% "//clnsurf(nsrf), "%",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "fract_"//clnsurf(nsrf),  &  
                "Fraction "//clnsurf(nsrf), "1",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "sens_"//clnsurf(nsrf),  &  
                "Sensible heat flux "//clnsurf(nsrf), "W/m2",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "tsol_"//clnsurf(nsrf),  &  
                "Surface Temperature"//clnsurf(nsrf), "W/m2",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "lat_"//clnsurf(nsrf),  &  
                "Latent heat flux "//clnsurf(nsrf), "W/m2",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "taux_"//clnsurf(nsrf),  &  
                "Zonal wind stress"//clnsurf(nsrf), "Pa", &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "tauy_"//clnsurf(nsrf),  &  
                "Meridional xind stress "//clnsurf(nsrf), "Pa",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "albe_"//clnsurf(nsrf),  &  
                "Albedo "//clnsurf(nsrf), "-",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
   
           call histdef(nid_ins, "rugs_"//clnsurf(nsrf),  &  
                "rugosite "//clnsurf(nsrf), "-",   &  
                iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
                "inst(X)", zsto, zout)  
           !XXX  
        END DO  
        CALL histdef(nid_ins, "rugs", "rugosity", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "albs", "Surface albedo", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
        CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99,  &  
             "inst(X)", zsto, zout)  
   
        !IM cf. AM 081204 BEG  
        ! HBTM2  
        CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height",  &  
             "K", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &  
             iim, (jjm + 1), nhori, 1, 1, 1, -99, &  
             "inst(X)", zsto, zout)  
   
        !IM cf. AM 081204 END  
   
        ! Champs 3D:  
   
        CALL histdef(nid_ins, "temp", "Temperature", "K", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "geop", "Geopotential height", "m", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &  
             iim, (jjm + 1), nhori, llm, 1, llm, nvert, &  
             "inst(X)", zsto, zout)  
   
        CALL histend(nid_ins)  
     ENDIF  
   
   end subroutine ini_histins  
   
 end module ini_hist  

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

  ViewVC Help
Powered by ViewVC 1.1.21