Changeset 888


Ignore:
Timestamp:
Feb 18, 2013, 2:56:41 PM (12 years ago)
Author:
slebonnois
Message:

SL: small modifications to the tools, to Venus default .def files and to outputs (including forgotten modifications linked to the 1D); + bug corrections in phytitan

Location:
trunk
Files:
18 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/Tools/fft.F90

    r816 r888  
    208208! 2.1.1 Atmospheric temperature
    209209!===============================================================================
     210if (ok_out(4)) then
    210211allocate(temp(lonlength,latlength,altlength,timelength))
    211212
     
    216217  text="t"
    217218  call get_var4d(infid,lonlength,latlength,altlength,timelength,text,temp,ierr1,ierr2)
    218   if (ierr1.ne.NF_NOERR) stop "Error: Failed to get temperature ID"
    219 endif
    220 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading temperature"
     219  if (ierr1.ne.NF_NOERR) then
     220    print*,"Error: Failed to get temperature ID"
     221    ok_out(4)=.false.
     222  endif
     223endif
     224if (ierr2.ne.NF_NOERR) then
     225  print*,"Error: Failed reading temperature"
     226  ok_out(4)=.false.
     227endif
     228endif !ok_out(4)
    221229
    222230!===============================================================================
    223231! 2.1.2 Winds
    224232!===============================================================================
     233! zonal wind vitu (in m/s)
     234if (ok_out(1)) then
    225235allocate(vitu(lonlength,latlength,altlength,timelength))
    226 allocate(vitv(lonlength,latlength,altlength,timelength))
    227 allocate(vitw(lonlength,latlength,altlength,timelength))
    228 
    229 ! zonal wind vitu (in m/s)
     236
    230237text="vitu"
    231238call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitu,ierr1,ierr2)
    232 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitu ID"
    233 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading zonal wind"
     239if (ierr1.ne.NF_NOERR) then
     240  print*,"Error: Failed to get vitu ID"
     241  ok_out(1)=.false.
     242endif
     243if (ierr2.ne.NF_NOERR) then
     244  print*,"Error: Failed reading zonal wind"
     245  ok_out(1)=.false.
     246endif
     247endif !ok_out(1)
    234248
    235249! meridional wind vitv (in m/s)
     250if (ok_out(2)) then
     251allocate(vitv(lonlength,latlength,altlength,timelength))
     252
    236253text="vitv"
    237254call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitv,ierr1,ierr2)
    238 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitv ID"
    239 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading meridional wind"
     255if (ierr1.ne.NF_NOERR) then
     256  print*,"Error: Failed to get vitv ID"
     257  ok_out(2)=.false.
     258endif
     259if (ierr2.ne.NF_NOERR) then
     260  print*,"Error: Failed reading meridional wind"
     261  ok_out(2)=.false.
     262endif
     263endif !ok_out(2)
    240264
    241265! vertical wind vitw (in Pa/s)
     266if (ok_out(3)) then
     267allocate(vitw(lonlength,latlength,altlength,timelength))
     268
    242269text="vitw"
    243270call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitw,ierr1,ierr2)
    244 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitw ID"
    245 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading vertical wind"
     271if (ierr1.ne.NF_NOERR) then
     272  print*,"Error: Failed to get vitw ID"
     273  ok_out(3)=.false.
     274endif
     275if (ierr2.ne.NF_NOERR) then
     276  print*,"Error: Failed reading vertical wind"
     277  ok_out(3)=.false.
     278endif
     279endif !ok_out(3)
    246280
    247281!===============================================================================
     
    256290! allocations
    257291!-------------
     292if (ok_out(1)) then
    258293allocate(fftau(lonlength,latlength,altlength,timelength))
     294allocate(uprim(lonlength,latlength,altlength,timelength))
     295allocate(ulf(lonlength,latlength,altlength,timelength))
     296allocate(ubf(lonlength,latlength,altlength,timelength))
     297allocate(uhf(lonlength,latlength,altlength,timelength))
     298endif !ok_out(1)
     299if (ok_out(2)) then
    259300allocate(fftav(lonlength,latlength,altlength,timelength))
     301allocate(vprim(lonlength,latlength,altlength,timelength))
     302allocate(vlf(lonlength,latlength,altlength,timelength))
     303allocate(vbf(lonlength,latlength,altlength,timelength))
     304allocate(vhf(lonlength,latlength,altlength,timelength))
     305endif !ok_out(2)
     306if (ok_out(3)) then
    260307allocate(fftaw(lonlength,latlength,altlength,timelength))
     308allocate(wprim(lonlength,latlength,altlength,timelength))
     309allocate(wlf(lonlength,latlength,altlength,timelength))
     310allocate(wbf(lonlength,latlength,altlength,timelength))
     311allocate(whf(lonlength,latlength,altlength,timelength))
     312endif !ok_out(3)
     313if (ok_out(4)) then
    261314allocate(fftaT(lonlength,latlength,altlength,timelength))
    262 allocate(uprim(lonlength,latlength,altlength,timelength))
    263 allocate(vprim(lonlength,latlength,altlength,timelength))
    264 allocate(wprim(lonlength,latlength,altlength,timelength))
    265315allocate(Tprim(lonlength,latlength,altlength,timelength))
    266 allocate(ulf(lonlength,latlength,altlength,timelength))
    267 allocate(vlf(lonlength,latlength,altlength,timelength))
    268 allocate(wlf(lonlength,latlength,altlength,timelength))
    269316allocate(Tlf(lonlength,latlength,altlength,timelength))
    270 allocate(ubf(lonlength,latlength,altlength,timelength))
    271 allocate(vbf(lonlength,latlength,altlength,timelength))
    272 allocate(wbf(lonlength,latlength,altlength,timelength))
    273317allocate(Tbf(lonlength,latlength,altlength,timelength))
    274 allocate(uhf(lonlength,latlength,altlength,timelength))
    275 allocate(vhf(lonlength,latlength,altlength,timelength))
    276 allocate(whf(lonlength,latlength,altlength,timelength))
    277318allocate(Thf(lonlength,latlength,altlength,timelength))
     319endif !ok_out(4)
    278320
    279321! lon,lat,alt
    280 allocate(umean(lonlength,latlength,altlength))
    281 allocate(vmean(lonlength,latlength,altlength))
    282 allocate(wmean(lonlength,latlength,altlength))
    283 allocate(Tmean(lonlength,latlength,altlength))
     322if (ok_out(1)) allocate(umean(lonlength,latlength,altlength))
     323if (ok_out(2)) allocate(vmean(lonlength,latlength,altlength))
     324if (ok_out(3)) allocate(wmean(lonlength,latlength,altlength))
     325if (ok_out(4)) allocate(Tmean(lonlength,latlength,altlength))
    284326
    285327! time / frequencies
     
    298340!-----------------
    299341
    300 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitu,umean)
    301 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitv,vmean)
    302 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitw,wmean)
    303 call moytim(lonlength,latlength,altlength,timelength,miss_val,temp,Tmean)
     342if (ok_out(1)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitu,umean)
     343if (ok_out(2)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitv,vmean)
     344if (ok_out(3)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitw,wmean)
     345if (ok_out(4)) call moytim(lonlength,latlength,altlength,timelength,miss_val,temp,Tmean)
    304346
    305347do ilon=1,lonlength
     
    307349  do ilev=1,altlength
    308350   do itim=1,timelength
     351if (ok_out(1)) then
    309352    if ((vitu(ilon,ilat,ilev,itim).ne.miss_val).and. &
    310353        (umean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    313356  uprim(ilon,ilat,ilev,itim) = miss_val
    314357    endif
     358endif !ok_out(1)
     359if (ok_out(2)) then
    315360    if ((vitv(ilon,ilat,ilev,itim).ne.miss_val).and. &
    316361        (vmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    319364  vprim(ilon,ilat,ilev,itim) = miss_val
    320365    endif
     366endif !ok_out(2)
     367if (ok_out(3)) then
    321368    if ((vitw(ilon,ilat,ilev,itim).ne.miss_val).and. &
    322369        (wmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    325372  wprim(ilon,ilat,ilev,itim) = miss_val
    326373    endif
     374endif !ok_out(3)
     375if (ok_out(4)) then
    327376    if ((temp(ilon,ilat,ilev,itim).ne.miss_val).and. &
    328377        (Tmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    331380  Tprim(ilon,ilat,ilev,itim) = miss_val
    332381    endif
     382endif !ok_out(4)
    333383   enddo
    334384  enddo
     
    743793datashape1d   =time_dimid2
    744794
     795call write_var1d(outfid2,datashape1d,timelength,&
     796                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     797                 freq )
     798
    745799call write_var4d(outfid2,datashape4d,lonlength,latlength,altlength,timelength,&
    746800                 "fftav     ", "FFT ampl of vitv    ","m s-1     ",miss_val,&
     
    768822datashape1d   =time_dimid3
    769823
     824call write_var1d(outfid3,datashape1d,timelength,&
     825                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     826                 freq )
     827
    770828call write_var4d(outfid3,datashape4d,lonlength,latlength,altlength,timelength,&
    771829                 "fftaw     ", "FFT ampl of vitw    ","Pa s-1    ",miss_val,&
     
    793851datashape1d   =time_dimid4
    794852
     853call write_var1d(outfid4,datashape1d,timelength,&
     854                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     855                 freq )
     856
    795857call write_var4d(outfid4,datashape4d,lonlength,latlength,altlength,timelength,&
    796858                 "fftaT     ", "FFT ampl of temp    ","K         ",miss_val,&
  • trunk/LMDZ.TITAN/Tools/filter.h

    r816 r888  
    1111
    1212! Choice of output files:
    13 !                                            (U,     V,      W,     T)
    14  logical,dimension(4),parameter :: ok_out=(/.true.,.true.,.false.,.true./)
     13!                                  (U,     V,      W,     T)
     14 logical,dimension(4) :: ok_out=(/.true.,.true.,.false.,.true./)
    1515
  • trunk/LMDZ.TITAN/libf/phytitan/cooling.F

    r808 r888  
    137137      save RHOP,UBARI,WNOI,DWNI
    138138
     139      REAL effg    ! effg est une fonction(z en m)
     140
    139141c-----------------------------------------------------------------------
    140142
     
    321323C TURN THE Q'S INTO TIMESCALES.....
    322324          DO 3300 ig=1,NG
    323              eff_g = RG*(RA/(RA+Z(ig,J)))**2 ! 10% DIFF AT 1 MBAR
    324              COLDEN = RHOP*(PRESS(ig,J+1)-PRESS(ig,J))/eff_g
     325          COLDEN = RHOP*(PRESS(ig,J+1)-PRESS(ig,J))/effg(Z(ig,J))
    325326c            Q0(J) = (COLDEN * CSUBP )/Q0(J)
    326327             Q0(ig,J) = Q0(ig,J) / (COLDEN*CSUBP)
  • trunk/LMDZ.TITAN/libf/phytitan/ini_histday.h

    r474 r888  
    1111         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1212         DO i = 1, iim
    13             zx_lon(i,1) = rlond(i+1)
    14             zx_lon(i,jjmp1) = rlond(i+1)
     13            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     14            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    1515         ENDDO
    1616         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
  • trunk/LMDZ.TITAN/libf/phytitan/ini_histins.h

    r175 r888  
    1010         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1111         DO i = 1, iim
    12             zx_lon(i,1) = rlond(i+1)
    13             zx_lon(i,jjmp1) = rlond(i+1)
     12            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     13            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    1414         ENDDO
    1515         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
  • trunk/LMDZ.TITAN/libf/phytitan/ini_histmth.h

    r474 r888  
    1111         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1212         DO i = 1, iim
    13             zx_lon(i,1) = rlond(i+1)
    14             zx_lon(i,jjmp1) = rlond(i+1)
     13            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     14            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    1515         ENDDO
    1616         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
  • trunk/LMDZ.TITAN/libf/phytitan/optci_1pt_3.F

    r808 r888  
    1616     &     pi, sigma, prod,reali,fhvis
    1717
    18       integer k, j,inq
     18      integer k, j,inq,kgas
    1919
    2020      real tbar, pbar, bmu, coef1, effg, taeros, taeroscat, cbar,
    2121     &     qext, qsct, qabs, qbar, xmono, xrule, deltaz, tnuext,
    2222     &     tnuscat, cnbar, qextc, qsctc, qabsc, qbarc, taugas, pnn,
    23      &     pcc, pcn, phn, kgas, u, ig, tau2, tlimit
     23     &     pcc, pcn, phn, u, ig, tau2, tlimit
    2424
    2525      PARAMETER(NLAYER=llm,NLEVEL=NLAYER+1)
  • trunk/LMDZ.TITAN/libf/phytitan/phytrac.F

    r808 r888  
    712712c    On a quand meme le droit de produire des traceurs dans la cellule.
    713713c    On considere donc que la valeur de sortie 3D correspond a la valeur de sortie 2D.
    714 c    Cela permet aussi entre autre d'eviter les NaN pour les traceurs des nuages !
     714c    Cela permet aussi entre autre d eviter les NaN pour les traceurs des nuages !
    715715c    (au dessus de la tropo pas de nuages donc qaer(nrad+1:ntype*nrad) = 0 !!!)
    716716                 IF (zqaer0(j,l,iq).lt.1e-100) THEN
     
    788788c----------------------
    789789c La microphysique avec nuages doit se faire obligatoirement en 3D.  (FAUX ACTUELLEMENT)
    790 c Rien n'empeche de faire la chimie en 2D. Cependant pour prendre en compte la
     790c Rien n empeche de faire la chimie en 2D. Cependant pour prendre en compte la
    791791c condensation due a la microfi (en 3D) on recalcule la tendance finale pour
    792792c les especes concernees (CH4, C2H6 pour le moment).
     
    852852
    853853c--------------------------------------------------
    854 c CALCUL DU FLUX DE CHALEUR LATENTE D'EVAPORATION
     854c CALCUL DU FLUX DE CHALEUR LATENTE D EVAPORATION
    855855c DU METHANE
    856856c--------------------------------------------------
     
    941941c      OCCCLD
    942942c      Calcul le nombre d'occurence d'un nuage
    943 c      d'opacité comprise en kmin et kmax
     943c      d opacité comprise en kmin et kmax
    944944c          k        kmin            kmax
    945945c          1   0.0000000      0.10000000   
  • trunk/LMDZ.VENUS/Tools/fft.F90

    r816 r888  
    208208! 2.1.1 Atmospheric temperature
    209209!===============================================================================
     210if (ok_out(4)) then
    210211allocate(temp(lonlength,latlength,altlength,timelength))
    211212
     
    216217  text="t"
    217218  call get_var4d(infid,lonlength,latlength,altlength,timelength,text,temp,ierr1,ierr2)
    218   if (ierr1.ne.NF_NOERR) stop "Error: Failed to get temperature ID"
    219 endif
    220 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading temperature"
     219  if (ierr1.ne.NF_NOERR) then
     220    print*,"Error: Failed to get temperature ID"
     221    ok_out(4)=.false.
     222  endif
     223endif
     224if (ierr2.ne.NF_NOERR) then
     225  print*,"Error: Failed reading temperature"
     226  ok_out(4)=.false.
     227endif
     228endif !ok_out(4)
    221229
    222230!===============================================================================
    223231! 2.1.2 Winds
    224232!===============================================================================
     233! zonal wind vitu (in m/s)
     234if (ok_out(1)) then
    225235allocate(vitu(lonlength,latlength,altlength,timelength))
    226 allocate(vitv(lonlength,latlength,altlength,timelength))
    227 allocate(vitw(lonlength,latlength,altlength,timelength))
    228 
    229 ! zonal wind vitu (in m/s)
     236
    230237text="vitu"
    231238call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitu,ierr1,ierr2)
    232 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitu ID"
    233 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading zonal wind"
     239if (ierr1.ne.NF_NOERR) then
     240  print*,"Error: Failed to get vitu ID"
     241  ok_out(1)=.false.
     242endif
     243if (ierr2.ne.NF_NOERR) then
     244  print*,"Error: Failed reading zonal wind"
     245  ok_out(1)=.false.
     246endif
     247endif !ok_out(1)
    234248
    235249! meridional wind vitv (in m/s)
     250if (ok_out(2)) then
     251allocate(vitv(lonlength,latlength,altlength,timelength))
     252
    236253text="vitv"
    237254call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitv,ierr1,ierr2)
    238 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitv ID"
    239 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading meridional wind"
     255if (ierr1.ne.NF_NOERR) then
     256  print*,"Error: Failed to get vitv ID"
     257  ok_out(2)=.false.
     258endif
     259if (ierr2.ne.NF_NOERR) then
     260  print*,"Error: Failed reading meridional wind"
     261  ok_out(2)=.false.
     262endif
     263endif !ok_out(2)
    240264
    241265! vertical wind vitw (in Pa/s)
     266if (ok_out(3)) then
     267allocate(vitw(lonlength,latlength,altlength,timelength))
     268
    242269text="vitw"
    243270call get_var4d(infid,lonlength,latlength,altlength,timelength,text,vitw,ierr1,ierr2)
    244 if (ierr1.ne.NF_NOERR) stop "Error: Failed to get vitw ID"
    245 if (ierr2.ne.NF_NOERR) stop "Error: Failed reading vertical wind"
     271if (ierr1.ne.NF_NOERR) then
     272  print*,"Error: Failed to get vitw ID"
     273  ok_out(3)=.false.
     274endif
     275if (ierr2.ne.NF_NOERR) then
     276  print*,"Error: Failed reading vertical wind"
     277  ok_out(3)=.false.
     278endif
     279endif !ok_out(3)
    246280
    247281!===============================================================================
     
    256290! allocations
    257291!-------------
     292if (ok_out(1)) then
    258293allocate(fftau(lonlength,latlength,altlength,timelength))
     294allocate(uprim(lonlength,latlength,altlength,timelength))
     295allocate(ulf(lonlength,latlength,altlength,timelength))
     296allocate(ubf(lonlength,latlength,altlength,timelength))
     297allocate(uhf(lonlength,latlength,altlength,timelength))
     298endif !ok_out(1)
     299if (ok_out(2)) then
    259300allocate(fftav(lonlength,latlength,altlength,timelength))
     301allocate(vprim(lonlength,latlength,altlength,timelength))
     302allocate(vlf(lonlength,latlength,altlength,timelength))
     303allocate(vbf(lonlength,latlength,altlength,timelength))
     304allocate(vhf(lonlength,latlength,altlength,timelength))
     305endif !ok_out(2)
     306if (ok_out(3)) then
    260307allocate(fftaw(lonlength,latlength,altlength,timelength))
     308allocate(wprim(lonlength,latlength,altlength,timelength))
     309allocate(wlf(lonlength,latlength,altlength,timelength))
     310allocate(wbf(lonlength,latlength,altlength,timelength))
     311allocate(whf(lonlength,latlength,altlength,timelength))
     312endif !ok_out(3)
     313if (ok_out(4)) then
    261314allocate(fftaT(lonlength,latlength,altlength,timelength))
    262 allocate(uprim(lonlength,latlength,altlength,timelength))
    263 allocate(vprim(lonlength,latlength,altlength,timelength))
    264 allocate(wprim(lonlength,latlength,altlength,timelength))
    265315allocate(Tprim(lonlength,latlength,altlength,timelength))
    266 allocate(ulf(lonlength,latlength,altlength,timelength))
    267 allocate(vlf(lonlength,latlength,altlength,timelength))
    268 allocate(wlf(lonlength,latlength,altlength,timelength))
    269316allocate(Tlf(lonlength,latlength,altlength,timelength))
    270 allocate(ubf(lonlength,latlength,altlength,timelength))
    271 allocate(vbf(lonlength,latlength,altlength,timelength))
    272 allocate(wbf(lonlength,latlength,altlength,timelength))
    273317allocate(Tbf(lonlength,latlength,altlength,timelength))
    274 allocate(uhf(lonlength,latlength,altlength,timelength))
    275 allocate(vhf(lonlength,latlength,altlength,timelength))
    276 allocate(whf(lonlength,latlength,altlength,timelength))
    277318allocate(Thf(lonlength,latlength,altlength,timelength))
     319endif !ok_out(4)
    278320
    279321! lon,lat,alt
    280 allocate(umean(lonlength,latlength,altlength))
    281 allocate(vmean(lonlength,latlength,altlength))
    282 allocate(wmean(lonlength,latlength,altlength))
    283 allocate(Tmean(lonlength,latlength,altlength))
     322if (ok_out(1)) allocate(umean(lonlength,latlength,altlength))
     323if (ok_out(2)) allocate(vmean(lonlength,latlength,altlength))
     324if (ok_out(3)) allocate(wmean(lonlength,latlength,altlength))
     325if (ok_out(4)) allocate(Tmean(lonlength,latlength,altlength))
    284326
    285327! time / frequencies
     
    298340!-----------------
    299341
    300 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitu,umean)
    301 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitv,vmean)
    302 call moytim(lonlength,latlength,altlength,timelength,miss_val,vitw,wmean)
    303 call moytim(lonlength,latlength,altlength,timelength,miss_val,temp,Tmean)
     342if (ok_out(1)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitu,umean)
     343if (ok_out(2)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitv,vmean)
     344if (ok_out(3)) call moytim(lonlength,latlength,altlength,timelength,miss_val,vitw,wmean)
     345if (ok_out(4)) call moytim(lonlength,latlength,altlength,timelength,miss_val,temp,Tmean)
    304346
    305347do ilon=1,lonlength
     
    307349  do ilev=1,altlength
    308350   do itim=1,timelength
     351if (ok_out(1)) then
    309352    if ((vitu(ilon,ilat,ilev,itim).ne.miss_val).and. &
    310353        (umean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    313356  uprim(ilon,ilat,ilev,itim) = miss_val
    314357    endif
     358endif !ok_out(1)
     359if (ok_out(2)) then
    315360    if ((vitv(ilon,ilat,ilev,itim).ne.miss_val).and. &
    316361        (vmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    319364  vprim(ilon,ilat,ilev,itim) = miss_val
    320365    endif
     366endif !ok_out(2)
     367if (ok_out(3)) then
    321368    if ((vitw(ilon,ilat,ilev,itim).ne.miss_val).and. &
    322369        (wmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    325372  wprim(ilon,ilat,ilev,itim) = miss_val
    326373    endif
     374endif !ok_out(3)
     375if (ok_out(4)) then
    327376    if ((temp(ilon,ilat,ilev,itim).ne.miss_val).and. &
    328377        (Tmean(ilon,ilat,ilev)    .ne.miss_val)) then
     
    331380  Tprim(ilon,ilat,ilev,itim) = miss_val
    332381    endif
     382endif !ok_out(4)
    333383   enddo
    334384  enddo
     
    743793datashape1d   =time_dimid2
    744794
     795call write_var1d(outfid2,datashape1d,timelength,&
     796                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     797                 freq )
     798
    745799call write_var4d(outfid2,datashape4d,lonlength,latlength,altlength,timelength,&
    746800                 "fftav     ", "FFT ampl of vitv    ","m s-1     ",miss_val,&
     
    768822datashape1d   =time_dimid3
    769823
     824call write_var1d(outfid3,datashape1d,timelength,&
     825                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     826                 freq )
     827
    770828call write_var4d(outfid3,datashape4d,lonlength,latlength,altlength,timelength,&
    771829                 "fftaw     ", "FFT ampl of vitw    ","Pa s-1    ",miss_val,&
     
    793851datashape1d   =time_dimid4
    794852
     853call write_var1d(outfid4,datashape1d,timelength,&
     854                "freq      ", "FFT frequencies     ","s-1       ",miss_val,&
     855                 freq )
     856
    795857call write_var4d(outfid4,datashape4d,lonlength,latlength,altlength,timelength,&
    796858                 "fftaT     ", "FFT ampl of temp    ","K         ",miss_val,&
  • trunk/LMDZ.VENUS/Tools/filter.h

    r816 r888  
    1111
    1212! Choice of output files:
    13 !                                            (U,     V,      W,     T)
    14  logical,dimension(4),parameter :: ok_out=(/.true.,.true.,.false.,.true./)
     13!                                  (U,     V,      W,     T)
     14 logical,dimension(4) :: ok_out=(/.true.,.true.,.false.,.true./)
    1515
  • trunk/LMDZ.VENUS/deftank/physiq.def

    r134 r888  
    2929OK_mensuel=y
    3030## frequence (en  jours ) de l'ecriture du fichier histmth pour Venus               
    31 # regle la frequence d'ecriture dans histmth (mensuel)
     31# regle la frequence d'ecriture dans histmth (mensuel) et/ou histins
    3232ecritphy=0.1
    33 ### OK_instan=y, ecrire sorties "instantanees" (chaque pas de temps de la  physique)
     33### OK_instan=y, ecrire sorties "instantanees" (meme freq que histmth)
    3434OK_instan=n
    3535#
  • trunk/LMDZ.VENUS/deftank/run.def

    r809 r888  
    1111anneeref=1111
    1212## Remise a zero de la date initiale
    13 raz_date=1
     13raz_date=0
    1414## Reinit des variables de controle
    1515resetvarc=n
  • trunk/LMDZ.VENUS/libf/phyvenus/ini_histday.h

    r808 r888  
    1313         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1414         DO i = 1, iim
    15             zx_lon(i,1) = rlond(i+1)
    16             zx_lon(i,jjmp1) = rlond(i+1)
     15            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     16            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    1717         ENDDO
    1818         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
  • trunk/LMDZ.VENUS/libf/phyvenus/ini_histins.h

    r97 r888  
    1313         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1414         DO i = 1, iim
    15             zx_lon(i,1) = rlond(i+1)
    16             zx_lon(i,jjmp1) = rlond(i+1)
     15            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     16            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    1717         ENDDO
    1818         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
     
    2929
    3030c-------------------------------------------------------
    31 
    32 c-------------------------------------------------------
    33 
     31      IF(lev_histday.GE.1) THEN
     32c
     33ccccccccccccc 2D fields, basics
     34c
     35         CALL histdef(nid_ins, "phis", "Surface geop. height", "-",
     36     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     37     .                "once",  zsto,zout)
     38c
     39         CALL histdef(nid_ins, "aire", "Grid area", "-",
     40     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     41     .                "once",  zsto,zout)
     42c
     43         CALL histdef(nid_ins, "tsol", "Surface Temperature", "K",
     44     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     45     .                "ins(X)", zsto,zout)
     46c
     47         CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa",
     48     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     49     .                "ins(X)", zsto,zout)
     50c
     51c        CALL histdef(nid_ins, "ue", "Zonal energy transport", "-",
     52c    .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     53c    .                "ins(X)", zsto,zout)
     54c
     55c        CALL histdef(nid_ins, "ve", "Merid energy transport", "-",
     56c    .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     57c    .                "ins(X)", zsto,zout)
     58c
     59         CALL histdef(nid_ins, "cdragh", "Drag coef on T", "-",
     60     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     61     .                "ins(X)", zsto,zout)
     62c
     63         CALL histdef(nid_ins, "cdragm", "Drag coef on U", "-",
     64     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     65     .                "ins(X)", zsto,zout)
     66c
     67      ENDIF !lev_histday.GE.1
     68c
     69c-------------------------------------------------------
     70      IF(lev_histday.GE.2) THEN
     71c
     72ccccccccccccc 3D fields, basics
     73c
     74         CALL histdef(nid_ins, "temp", "Air temperature", "K",
     75     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     76     .                "ins(X)", zsto,zout)
     77c
     78         CALL histdef(nid_ins, "pres", "Air pressure", "Pa",
     79     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     80     .                "ins(X)", zsto,zout)
     81c
     82         CALL histdef(nid_ins, "geop", "Geopotential height", "m",
     83     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     84     .                "ins(X)", zsto,zout)
     85c
     86         CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s",
     87     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     88     .                "ins(X)", zsto,zout)
     89c
     90         CALL histdef(nid_ins, "vitv", "Meridional wind", "m/s",
     91     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     92     .                "ins(X)", zsto,zout)
     93c
     94         CALL histdef(nid_ins, "vitw", "Vertical wind", "Pa/s",
     95     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     96     .                "ins(X)", zsto,zout)
     97c
     98         CALL histdef(nid_ins, "dudyn", "Dynamics dU", "m/s2",
     99     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     100     .                "ins(X)", zsto,zout)
     101c
     102         CALL histdef(nid_ins, "duvdf", "Boundary-layer dU", "m/s2",
     103     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     104     .                "ins(X)", zsto,zout)
     105c
     106c        CALL histdef(nid_ins, "mang", "Angular momentum", "kg m2/s",
     107c    .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     108c    .                "ins(X)", zsto,zout)
     109c
     110         CALL histdef(nid_ins, "Kz", "vertical diffusion coef", "m2/s",
     111     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     112     .                "ins(X)", zsto,zout)
     113c
     114c plusieurs traceurs
     115          if (iflag_trac.eq.1) THEN
     116            DO iq=1,nqmax
     117             IF (iq.LE.99) THEN
     118          WRITE(str2,'(i2.2)') iq
     119          CALL histdef(nid_ins, tname(iq), ttext(iq), "ppm",
     120     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     121     .                "ins(X)", zsto,zout)
     122             ELSE
     123          PRINT*, "Trop de traceurs"
     124          CALL abort
     125             ENDIF
     126            ENDDO
     127          endif
     128c
     129         CALL histdef(nid_ins, "tops", "Solar rad. at TOA", "W/m2",
     130     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     131     .                "ins(X)", zsto,zout)
     132c
     133      ENDIF !lev_histday.GE.2
     134c
     135c-------------------------------------------------------
     136      IF(lev_histday.GE.3) THEN
     137c
     138cccccccccccccccccc  Radiative transfer
     139c
     140c 2D
     141c
     142         CALL histdef(nid_ins, "topl", "IR rad. at TOA", "W/m2",
     143     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     144     .                "ins(X)", zsto,zout)
     145c
     146         CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2",
     147     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     148     .                "ins(X)", zsto,zout)
     149c
     150         CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2",
     151     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     152     .                "ins(X)", zsto,zout)
     153c
     154c 3D
     155c
     156         CALL histdef(nid_ins, "SWnet", "Net SW flux","W/m2",
     157     .                iim,jjmp1,nhori, klev,1,klev,nvert,
     158     .                32, "ins(X)", zsto,zout)
     159c
     160         CALL histdef(nid_ins, "LWnet", "Net LW flux","W/m2",
     161     .                iim,jjmp1,nhori, klev,1,klev,nvert,
     162     .                32, "ins(X)", zsto,zout)
     163c
     164         CALL histdef(nid_ins, "fluxvdf", "PBL net flux","W/m2",
     165     .                iim,jjmp1,nhori, klev,1,klev,nvert,
     166     .                32, "ins(X)", zsto,zout)
     167c
     168         CALL histdef(nid_ins, "fluxdyn", "Dyn. net flux","W/m2",
     169     .                iim,jjmp1,nhori, klev,1,klev,nvert,
     170     .                32, "ins(X)", zsto,zout)
     171c
     172         CALL histdef(nid_ins, "fluxajs", "Dry adj. net flux","W/m2",
     173     .                iim,jjmp1,nhori, klev,1,klev,nvert,
     174     .                32, "ins(X)", zsto,zout)
     175c
     176c        CALL histdef(nid_ins, "fluxec", "Cin. net flux","W/m2",
     177c    .                iim,jjmp1,nhori, klev,1,klev,nvert,
     178c    .                32, "ins(X)", zsto,zout)
     179c
     180      ENDIF !lev_histday.GE.3
     181c
     182c-------------------------------------------------------
     183      IF(lev_histday.GE.4) THEN
     184c
     185         CALL histdef(nid_ins, "dtdyn", "Dynamics dT", "K/s",
     186     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     187     .                "ins(X)", zsto,zout)
     188c
     189c        CALL histdef(nid_ins, "dtphy", "Physics dT", "K/s",
     190c    .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     191c    .                "ins(X)", zsto,zout)
     192c
     193         CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s",
     194     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     195     .                "ins(X)", zsto,zout)
     196c
     197         CALL histdef(nid_ins, "dtajs", "Dry adjust. dT", "K/s",
     198     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     199     .                "ins(X)", zsto,zout)
     200c
     201         CALL histdef(nid_ins, "dtswr", "SW radiation dT", "K/s",
     202     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     203     .                "ins(X)", zsto,zout)
     204c
     205         CALL histdef(nid_ins, "dtlwr", "LW radiation dT", "K/s",
     206     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     207     .                "ins(X)", zsto,zout)
     208c
     209c        CALL histdef(nid_ins, "dtec", "Cinetic dissip dT", "K/s",
     210c    .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     211c    .                "ins(X)", zsto,zout)
     212c
     213         CALL histdef(nid_ins, "duajs", "Dry convection dU", "m/s2",
     214     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     215     .                "ins(X)", zsto,zout)
     216c
     217         CALL histdef(nid_ins, "dugwo", "GW oro dU", "m/s2",
     218     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     219     .                "ins(X)", zsto,zout)
     220c
     221         CALL histdef(nid_ins, "dugwno", "GW non-oro dU", "m/s2",
     222     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     223     .                "ins(X)", zsto,zout)
     224c
     225c        CALL histdef(nid_ins, "dvvdf", "Boundary-layer dV", "m/s2",
     226c    .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     227c    .                "ins(X)", zsto,zout)
     228c
     229      ENDIF !lev_histday.GE.4
     230c
     231c-------------------------------------------------------
     232      IF(lev_histday.GE.5) THEN
     233c
     234c        call histdef(nid_ins, "taux",
     235c    $         "Zonal wind stress", "Pa", 
     236c    $         iim,jjmp1,nhori, 1,1,1, -99, 32,
     237c    $         "ins(X)", zsto,zout)
     238c
     239c        call histdef(nid_ins, "tauy",
     240c    $         "Meridional xind stress", "Pa", 
     241c    $         iim,jjmp1,nhori, 1,1,1, -99, 32,
     242c    $         "ins(X)", zsto,zout)
     243c
     244c        CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-",
     245c    .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     246c    .                "ins(X)", zsto,zout)
     247c
     248c        CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-",
     249c    .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     250c    .                "ins(X)", zsto,zout)
     251c
     252      ENDIF !lev_histday.GE.5
     253c-------------------------------------------------------
     254c
    34255         CALL histend(nid_ins)
    35256c
  • trunk/LMDZ.VENUS/libf/phyvenus/ini_histmth.h

    r101 r888  
    1818         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlond,zx_lon)
    1919         DO i = 1, iim
    20             zx_lon(i,1) = rlond(i+1)
    21             zx_lon(i,jjmp1) = rlond(i+1)
     20            zx_lon(i,1) = rlond(i+jjmp1-jjm)
     21            zx_lon(i,jjmp1) = rlond(i+jjmp1-jjm)
    2222         ENDDO
    2323         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlatd,zx_lat)
  • trunk/LMDZ.VENUS/libf/phyvenus/write_histins.h

    r97 r888  
    1717c
    1818c-------------------------------------------------------
    19 
     19      IF(lev_histday.GE.1) THEN
     20c
     21ccccccccccccc 2D fields, basics
     22c
     23      i = NINT(zout/zsto)
     24      CALL gr_fi_ecrit(1,klon,iim,jjmp1,pphis,zx_tmp_2d)
     25      CALL histwrite(nid_ins,"phis",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     26C
     27      i = NINT(zout/zsto)
     28      CALL gr_fi_ecrit(1,klon,iim,jjmp1,airephy,zx_tmp_2d)
     29      CALL histwrite(nid_ins,"aire",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     30c
     31      CALL gr_fi_ecrit(1, klon,iim,jjmp1, ftsol,zx_tmp_2d)
     32      CALL histwrite(nid_ins,"tsol",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     33c
     34      DO i = 1, klon
     35         zx_tmp_fi2d(i) = paprs(i,1)
     36      ENDDO
     37      CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     38      CALL histwrite(nid_ins,"psol",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     39c
     40c     CALL gr_fi_ecrit(1, klon,iim,jjmp1, ue,zx_tmp_2d)
     41c     CALL histwrite(nid_ins,"ue",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     42c
     43c     CALL gr_fi_ecrit(1, klon,iim,jjmp1, ve,zx_tmp_2d)
     44c VENUS: regardee a l'envers!!!!!!!!!!!!!!!
     45c     zx_tmp_2d=-1.*zx_tmp_2d
     46c     CALL histwrite(nid_ins,"ve",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     47c
     48      CALL gr_fi_ecrit(1, klon,iim,jjmp1, cdragh,zx_tmp_2d)
     49      CALL histwrite(nid_ins,"cdragh",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     50c
     51      CALL gr_fi_ecrit(1, klon,iim,jjmp1, cdragm,zx_tmp_2d)
     52      CALL histwrite(nid_ins,"cdragm",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     53c
     54      ENDIF !lev_histday.GE.1
     55c
     56c-------------------------------------------------------
     57      IF(lev_histday.GE.2) THEN
     58c
     59ccccccccccccc 3D fields, basics
     60c
     61      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, t_seri, zx_tmp_3d)
     62      CALL histwrite(nid_ins,"temp",itau_w,zx_tmp_3d,
     63     .                                   iim*jjmp1*klev,ndex3d)
     64c
     65      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, pplay, zx_tmp_3d)
     66      CALL histwrite(nid_ins,"pres",itau_w,zx_tmp_3d,
     67     .                                   iim*jjmp1*klev,ndex3d)
     68c
     69      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, zphi, zx_tmp_3d)
     70      CALL histwrite(nid_ins,"geop",itau_w,zx_tmp_3d,
     71     .                                   iim*jjmp1*klev,ndex3d)
     72c
     73      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, u_seri, zx_tmp_3d)
     74      CALL histwrite(nid_ins,"vitu",itau_w,zx_tmp_3d,
     75     .                                   iim*jjmp1*klev,ndex3d)
     76c
     77      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, v_seri, zx_tmp_3d)
     78c VENUS: regardee a l'envers!!!!!!!!!!!!!!!
     79      zx_tmp_3d=-1.*zx_tmp_3d
     80      CALL histwrite(nid_ins,"vitv",itau_w,zx_tmp_3d,
     81     .                                   iim*jjmp1*klev,ndex3d)
     82c
     83      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, omega, zx_tmp_3d)
     84      CALL histwrite(nid_ins,"vitw",itau_w,zx_tmp_3d,
     85     .                                   iim*jjmp1*klev,ndex3d)
     86c
     87c en (m/s)/s     
     88      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_dyn, zx_tmp_3d)
     89      CALL histwrite(nid_ins,"dudyn",itau_w,zx_tmp_3d,
     90     .                                   iim*jjmp1*klev,ndex3d)
     91c
     92c en (m/s)/s     
     93      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_vdf, zx_tmp_3d)
     94      CALL histwrite(nid_ins,"duvdf",itau_w,zx_tmp_3d,
     95     .                                   iim*jjmp1*klev,ndex3d)
     96c
     97c     CALL gr_fi_ecrit(klev,klon,iim,jjmp1, mang, zx_tmp_3d)
     98c     CALL histwrite(nid_ins,"mang",itau_w,zx_tmp_3d,
     99c    .                                   iim*jjmp1*klev,ndex3d)
     100c
     101      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, ycoefh, zx_tmp_3d)
     102      CALL histwrite(nid_ins,"Kz",itau_w,zx_tmp_3d,
     103     .                                   iim*jjmp1*klev,ndex3d)
     104c
     105c plusieurs traceurs
     106       IF (iflag_trac.eq.1) THEN
     107         DO iq=1,nqmax
     108          IF (iq.LE.99) THEN
     109       CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,iq), zx_tmp_3d)
     110       WRITE(str2,'(i2.2)') iq
     111       CALL histwrite(nid_ins,tname(iq),itau_w,zx_tmp_3d,
     112     .                                   iim*jjmp1*klev,ndex3d)
     113          ELSE
     114       PRINT*, "Trop de traceurs"
     115       CALL abort
     116          ENDIF
     117         ENDDO
     118       ENDIF
     119c
     120      CALL gr_fi_ecrit(1, klon,iim,jjmp1, topsw,zx_tmp_2d)
     121      CALL histwrite(nid_ins,"tops",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     122c
     123      ENDIF !lev_histday.GE.2
     124c
     125c-------------------------------------------------------
     126      IF(lev_histday.GE.3) THEN
     127c
     128cccccccccccccccccc  Radiative transfer
     129c
     130c 2D
     131c
     132      CALL gr_fi_ecrit(1, klon,iim,jjmp1, toplw,zx_tmp_2d)
     133      CALL histwrite(nid_ins,"topl",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     134c
     135      CALL gr_fi_ecrit(1, klon,iim,jjmp1, solsw,zx_tmp_2d)
     136      CALL histwrite(nid_ins,"sols",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     137c
     138      CALL gr_fi_ecrit(1, klon,iim,jjmp1, sollw,zx_tmp_2d)
     139      CALL histwrite(nid_ins,"soll",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     140c
     141c 3D
     142c
     143      zx_tmp_fi3d(1:klon,1:klev)=swnet(1:klon,1:klev)
     144      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     145      CALL histwrite(nid_ins,"SWnet",itau_w,zx_tmp_3d,
     146     .                                   iim*jjmp1*klev,ndex3d)
     147c
     148      zx_tmp_fi3d(1:klon,1:klev)=lwnet(1:klon,1:klev)
     149      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     150      CALL histwrite(nid_ins,"LWnet",itau_w,zx_tmp_3d,
     151     .                                   iim*jjmp1*klev,ndex3d)
     152c
     153      zx_tmp_fi3d(1:klon,1:klev)=fluxt(1:klon,1:klev)
     154      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     155      CALL histwrite(nid_ins,"fluxvdf",itau_w,zx_tmp_3d,
     156     .                                   iim*jjmp1*klev,ndex3d)
     157c
     158      zx_tmp_fi3d(1:klon,1:klev)=flux_dyn(1:klon,1:klev)
     159      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     160      CALL histwrite(nid_ins,"fluxdyn",itau_w,zx_tmp_3d,
     161     .                                   iim*jjmp1*klev,ndex3d)
     162c
     163      zx_tmp_fi3d(1:klon,1:klev)=flux_ajs(1:klon,1:klev)
     164      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     165      CALL histwrite(nid_ins,"fluxajs",itau_w,zx_tmp_3d,
     166     .                                   iim*jjmp1*klev,ndex3d)
     167c
     168c     zx_tmp_fi3d(1:klon,1:klev)=flux_ec(1:klon,1:klev)
     169c     CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     170c     CALL histwrite(nid_ins,"fluxec",itau_w,zx_tmp_3d,
     171c    .                                   iim*jjmp1*klev,ndex3d)
     172c
     173      ENDIF !lev_histday.GE.3
     174c
     175c-------------------------------------------------------
     176      IF(lev_histday.GE.4) THEN
     177c
     178c en K/s     
     179      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)
     180      CALL histwrite(nid_ins,"dtdyn",itau_w,zx_tmp_3d,
     181     .                                   iim*jjmp1*klev,ndex3d)
     182c
     183c en K/s     
     184c     CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t, zx_tmp_3d)
     185c     CALL histwrite(nid_ins,"dtphy",itau_w,zx_tmp_3d,
     186c    .                                   iim*jjmp1*klev,ndex3d)
     187c
     188c en K/s     
     189      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,d_t_vdf,zx_tmp_3d)
     190      CALL histwrite(nid_ins,"dtvdf",itau_w,zx_tmp_3d,
     191     .                                   iim*jjmp1*klev,ndex3d)
     192c
     193c en K/s     
     194      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,d_t_ajs,zx_tmp_3d)
     195      CALL histwrite(nid_ins,"dtajs",itau_w,zx_tmp_3d,
     196     .                                   iim*jjmp1*klev,ndex3d)
     197c
     198c K/day ==> K/s
     199      zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY
     200      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     201      CALL histwrite(nid_ins,"dtswr",itau_w,zx_tmp_3d,
     202     .                                   iim*jjmp1*klev,ndex3d)
     203c
     204c K/day ==> K/s     
     205      zx_tmp_fi3d(1:klon,1:klev)=-1.*cool(1:klon,1:klev)/RDAY
     206      CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     207      CALL histwrite(nid_ins,"dtlwr",itau_w,zx_tmp_3d,
     208     .                                   iim*jjmp1*klev,ndex3d)
     209c en K/s     
     210c     zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)
     211c     CALL gr_fi_ecrit(klev,klon,iim,jjmp1,zx_tmp_fi3d,zx_tmp_3d)
     212c     CALL histwrite(nid_ins,"dtec",itau_w,zx_tmp_3d,
     213c    .                                   iim*jjmp1*klev,ndex3d)
     214c
     215c en (m/s)/s     
     216      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_ajs, zx_tmp_3d)
     217      CALL histwrite(nid_ins,"duajs",itau_w,zx_tmp_3d,
     218     .                                   iim*jjmp1*klev,ndex3d)
     219c
     220c en (m/s)/s     
     221      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_oro, zx_tmp_3d)
     222      CALL histwrite(nid_ins,"dugwo",itau_w,zx_tmp_3d,
     223     .                                   iim*jjmp1*klev,ndex3d)
     224c
     225c en (m/s)/s     
     226      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_hin, zx_tmp_3d)
     227      CALL histwrite(nid_ins,"dugwno",itau_w,zx_tmp_3d,
     228     .                                   iim*jjmp1*klev,ndex3d)
     229c
     230c en (m/s)/s     
     231c     CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_vdf, zx_tmp_3d)
     232c VENUS: regardee a l'envers!!!!!!!!!!!!!!!
     233c     zx_tmp_3d=-1.*zx_tmp_3d
     234c     CALL histwrite(nid_ins,"dvvdf",itau_w,zx_tmp_3d,
     235c    .                                   iim*jjmp1*klev,ndex3d)
     236c
     237      ENDIF !lev_histday.GE.4
     238c
     239c-------------------------------------------------------
     240       IF(lev_histday.GE.5) THEN
     241c
     242c
     243c      CALL gr_fi_ecrit(1, klon,iim,jjmp1, fluxu , zx_tmp_2d)
     244c      CALL histwrite(nid_ins,"taux_",itau_w,
     245c    $      zx_tmp_2d,iim*jjmp1,ndex2d)
     246c     
     247c      CALL gr_fi_ecrit(1, klon,iim,jjmp1, fluxv , zx_tmp_2d)
     248c      CALL histwrite(nid_ins,"tauy_",itau_w,
     249c    $      zx_tmp_2d,iim*jjmp1,ndex2d)
     250c
     251c     CALL gr_fi_ecrit(1, klon,iim,jjmp1, cdragm,zx_tmp_2d)
     252c     CALL histwrite(nid_ins,"cdrm",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     253c
     254c     CALL gr_fi_ecrit(1, klon,iim,jjmp1, cdragh,zx_tmp_2d)
     255c     CALL histwrite(nid_ins,"cdrh",itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     256c
     257      ENDIF !lev_histday.GE.5
    20258c-------------------------------------------------------
    21259c
  • trunk/LMDZ.VENUS/libf/phyvenus/writeg1d.F

    r3 r888  
    2424c
    2525      INTEGER ngrid,nx,i
    26 c     REAL*4 xr4(1000)
    27       REAL xr4(1000)
     26      REAL*4 xr4(1000)
     27c      REAL xr4(1000)
    2828      REAL x(nx)
    2929      CHARACTER*(*) nom,titre
  • trunk/UTIL/NCL/planeto.ncl

    r808 r888  
    137137; A REVOIR !!!
    138138     ; !! stupid bug, due to precision when time axis in double in file...
    139      ;     if ((ntcutmin.eq.0).and.(ntcutmax.eq.0)) then
    140      ;       mindimval(index)=mindimval(index)*1.000001
    141      ;       maxdimval(index)=maxdimval(index)*1.000001
    142      ;     end if
     139           if ((ntcutmin.eq.0).and.(ntcutmax.eq.0)) then
     140             mindimval(index)=mindimval(index)*0
     141             maxdimval(index)=maxdimval(index)*1.1
     142           end if
    143143     ; !! stupid bug, due to precision when time axis in double in file...
    144144        else
Note: See TracChangeset for help on using the changeset viewer.