/[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 17 by guez, Tue Aug 5 13:31:32 2008 UTC
# Line 123  contains Line 123  contains
123    
124    !******************************************************************    !******************************************************************
125    
126    subroutine ini_histday(dtime, presnivs, ok_journe, nid_day)    subroutine ini_histday(dtime, presnivs, ok_journe, nid_day, nq)
127    
128      ! 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
129    
130      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
     use dimphy, only: klon  
131      use temps, only: itau_phy, day_ref, annee_ref      use temps, only: itau_phy, day_ref, annee_ref
132      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
133      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
134      use clesphys, only: ecrit_day      use clesphys, only: ecrit_day
135        use grid_change, only: gr_phy_write_2d
136    
137      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
138      real, intent(in):: presnivs(:)      real, intent(in):: presnivs(:)
139      logical, intent(in):: ok_journe      logical, intent(in):: ok_journe
140      integer, intent(out):: nid_day      integer, intent(out):: nid_day
141        INTEGER, intent(in):: nq ! nombre de traceurs (y compris vapeur d'eau)
142    
143      REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)      ! Variables local to the procedure:
144      integer i, nhori, nvert, idayref      REAL zx_lat(iim, jjm + 1)
145        integer nhori, nvert
146      real zjulian      real zjulian
147    
148      !--------------------------------      !--------------------------------
149    
150      IF (ok_journe) THEN      IF (ok_journe) THEN
151         idayref = day_ref         CALL ymds2ju(annee_ref, 1, day_ref, 0., zjulian)
152         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)         zx_lat = gr_phy_write_2d(rlat)
153           CALL histbeg_totreg("histday", rlon(2: iim+1), zx_lat(1, :), 1, iim, &
154         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)  
155         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &
156              llm, presnivs/100., nvert)              llm, presnivs/100., nvert)
157         call histdef(nid_day, "Sigma_O3_Royer", &         if (nq <= 4) then
158              "column-density of ozone, in a cell, from Royer", "DU", &            call histdef(nid_day, "Sigma_O3_Royer", &
159              pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, par_oriz=1, &                 "column-density of ozone, in a cell, from Royer", "DU", &
160              par_szz=llm, pzid=nvert, popp="ave(X)", pfreq_opp=dtime, &                 pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, &
161              pfreq_wrt=real(ecrit_day))                 par_oriz=1, par_szz=llm, pzid=nvert, popp="ave(X)", &
162                   pfreq_opp=dtime, pfreq_wrt=real(ecrit_day))
163           end if
164         CALL histend(nid_day)         CALL histend(nid_day)
165      ENDIF      ENDIF
166    
# Line 464  contains Line 461  contains
461    
462    end subroutine ini_histins    end subroutine ini_histins
463    
464      !*************************************************
465    
466      subroutine ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)
467    
468        ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30
469    
470        use dimens_m, only: iim, jjm, llm
471        use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend
472        use temps, only: annee_ref, day_ref, itau_phy
473        use advtrac_m, only: niadv, tnom, ttext
474        use dimphy, only: klon
475        use clesphys, only: ecrit_tra
476        use grid_change, only: gr_phy_write_2d
477        use phyetat0_m, only: rlon, rlat
478    
479        INTEGER, intent(out):: nid_tra
480        real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
481        REAL, intent(in):: presnivs(:)
482    
483        integer, intent(in):: nqmax
484        ! (nombre de traceurs auxquels on applique la physique)
485    
486        logical, intent(in):: lessivage
487    
488        ! Variables local to the procedure:
489    
490        REAL zjulian
491        REAL zx_lat(iim, jjm+1)
492        INTEGER nhori, nvert
493        REAL zsto, zout
494        integer it, iq, iiq
495    
496        !---------------------------------------------------------
497    
498        CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)
499        zx_lat(:, :) = gr_phy_write_2d(rlat)
500        CALL histbeg_totreg("histrac", rlon(2:iim+1), zx_lat(1, :), &
501             1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)
502        CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &
503             presnivs, nvert)
504    
505        zsto = pdtphys
506        zout = pdtphys * REAL(ecrit_tra)
507    
508        CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &
509             iim, jjm+1, nhori, 1, 1, 1, -99, &
510             "once",  zsto, zout)
511        CALL histdef(nid_tra, "aire", "Grid area", "-", &
512             iim, jjm+1, nhori, 1, 1, 1, -99, &
513             "once",  zsto, zout)
514        CALL histdef(nid_tra, "zmasse", "column density of air in cell", &
515             "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "ave(X)", &
516             zsto, zout)
517    
518        DO it = 1, nqmax
519           ! champ 2D
520           iq=it+2
521           iiq=niadv(iq)
522           CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &
523                nhori, llm, 1, llm, nvert, "ave(X)", zsto, zout)
524           if (lessivage) THEN
525              CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &
526                   "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
527                   "ave(X)", zsto, zout)
528           endif
529    
530           !---Ajout Olivia
531           CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &
532                "tendance thermique"// ttext(iiq), "?", &
533                iim, jjm+1, nhori, llm, 1, llm, nvert, &
534                "ave(X)", zsto, zout)
535           CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &
536                "tendance convection"// ttext(iiq), "?", &
537                iim, jjm+1, nhori, llm, 1, llm, nvert, &
538                "ave(X)", zsto, zout)
539           CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &
540                "tendance couche limite"// ttext(iiq), "?", &
541                iim, jjm+1, nhori, llm, 1, llm, nvert, &
542                "ave(X)", zsto, zout)
543           !---fin Olivia    
544    
545        ENDDO
546    
547        CALL histdef(nid_tra, "pplay", "", "-", &
548             iim, jjm+1, nhori, llm, 1, llm, nvert, &
549             "inst(X)", zout, zout)
550        CALL histdef(nid_tra, "t", "", "-", &
551             iim, jjm+1, nhori, llm, 1, llm, nvert, &
552             "inst(X)", zout, zout)
553    
554        CALL histend(nid_tra)
555    
556      end subroutine ini_histrac
557    
558  end module ini_hist  end module ini_hist

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

  ViewVC Help
Powered by ViewVC 1.1.21