Changeset 665


Ignore:
Timestamp:
May 23, 2012, 10:33:16 AM (13 years ago)
Author:
aslmd
Message:

MESOSCALE : output more physical variables in Registry. update GCM for storm
simulations. bug fix in readmeteo with ccn. UTIL PYTHON : bug fix for
operation cat (time axis)

Location:
trunk
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/readmeteo.F90

    r549 r665  
    662662    if (ierr.ne.NF_NOERR) then
    663663      write(*,*) "...No ccn - CCN mass set to 0"
    664       dustfile(:,:,:,:)=0.
     664      ccnfile(:,:,:,:)=0.
    665665    else
    666666      ierr=NF_GET_VAR_REAL(nid,nvarid,ccnfile)
     
    671671    if (ierr.ne.NF_NOERR) then
    672672      write(*,*) "...No ccnN - CCN number set to 0"
    673       dustnfile(:,:,:,:)=0.
     673      ccnnfile(:,:,:,:)=0.
    674674    else
    675675      ierr=NF_GET_VAR_REAL(nid,nvarid,ccnnfile)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM

    r549 r665  
    8787state  real  THETA     ij   misc  1  -  rd   "THETA"     "SLOPE INCLINATION"               "deg"     #SAVEMARS2 theta_sl
    8888state  real  PSI       ij   misc  1  -  rd   "PSI"       "SLOPE ORIENTATION"               "deg"     #SAVEMARS2 psi_sl
    89 state  real  TAU_DUST  ij   misc  1  -  rd   "TAU_DUST"  "REFERENCE VISIBLE DUST OPACITY"  ""        #SAVEMARS2 tauref
     89state  real  TAU_DUST  ij   misc  1  -  rhd   "TAU_DUST"  "REFERENCE VISIBLE DUST OPACITY"  ""        #SAVEMARS2 tauref
    9090state  real  SWDOWNZ   ij   misc  1  -  rd   "SWDOWNZ"   "DOWNWARD SW FLUX AT SURFACE"     "W m-2"   #SAVEMARS2 fluxsurf_sw_tot     
    9191state  real  LWDOWNZ   ij   misc  1  -  rd   "LWDOWNZ"   "DOWNWARD LW FLUX AT SURFACE"     "W m-2"   #SAVEMARS2 fluxsurf_lw
    9292state  real  SWUP      ij   misc  1  -  rd   "SWUP"      "UPWARD SW FLUX AT TOP"           "W m-2"   #SAVEMARS2 fluxtop_sw_tot   
    9393state  real  LWUP      ij   misc  1  -  rd   "LWUP"      "UPWARD LW FLUX AT TOP"           "W m-2"   #SAVEMARS2 fluxtop_lw
    94 state  real  MTOT      ij   misc  1  -  rd   "MTOT"      "TOTAL MASS WATER VAPOR in pmic"  "pmic"    #SAVEMARS2 mtot
    95 state  real  ICETOT    ij   misc  1  -  rd   "ICETOT"    "TOTAL MASS WATER ICE"            "kg m-2"  #SAVEMARS2 icetot
    96 state  real  RAVE      ij   misc  1  -  rd   "RAVE"      "MEAN ICE RADIUS"                 "m"       #SAVEMARS2 rave
     94state  real  MTOT      ij   misc  1  -  rhd   "MTOT"      "TOTAL MASS WATER VAPOR in pmic"  "pmic"    #SAVEMARS2 mtot
     95state  real  ICETOT    ij   misc  1  -  rhd   "ICETOT"    "TOTAL MASS WATER ICE"            "kg m-2"  #SAVEMARS2 icetot
     96state  real  RAVE      ij   misc  1  -  rhd   "RAVE"      "MEAN ICE RADIUS"                 "m"       #SAVEMARS2 rave
    9797state  real  RICE      ikj  misc  1  -  rd   "RICE"      "ICE RADIUS"                      "m"       #SAVEMARS3 rice
    9898state  real  HR_SW     ikj  misc  1  -  rd   "HR_SW"     "HEATING RATE SW"                 "K/s"     #SAVEMARS3 zdtsw
    9999state  real  HR_LW     ikj  misc  1  -  rd   "HR_LW"     "HEATING RATE LW"                 "K/s"     #SAVEMARS3 zdtlw
    100100state  real  HR_SH     ikj  misc  1  -  rd   "HR_SH"     "HEATING RATE sens. heat"         "K/s"     #SAVEMARS3 zdtdif
    101 state  real  QSURFICE  ij   misc  1  -  rd   "QSURFICE"  "WATER ICE AT SURFACE"            "kg m-2"  #SAVEMARS2 qsurfice
    102 state  real  RDUST     ikj  misc  1  -  rd   "RDUST"     "DUST RADIUS"                     "m"       #SAVEMARS3 rdust
     101state  real  QSURFICE  ij   misc  1  -  rhd   "QSURFICE"  "WATER ICE AT SURFACE"            "kg m-2"  #SAVEMARS2 qsurfice
     102state  real  RDUST     ikj  misc  1  -  rhd   "RDUST"     "DUST RADIUS"                     "m"       #SAVEMARS3 rdust
    103103state  real  HR_NIR    ikj  misc  1  -  rd   "HR_NIR"    "HEATING RATE nirco2"             "K/s"     #SAVEMARS3 zdtnirco2
    104104state  real  HR_NLTE   ikj  misc  1  -  rd   "HR_NLTE"   "HEATING RATE nlte"               "K/s"     #SAVEMARS3 zdtnlte
    105 state  real  ALBBARE   ij   misc  1  -  rd   "ALBBARE"   "SOIL ALBEDO"                     ""        #SAVEMARS2 albedodat
    106 state  real  VMR_ICE   ikj  misc  1  -  rd   "VMR_ICE"   "VOL. MIXING RATIO ICE"           "ppm"     #SAVEMARS3 vmr
    107 state  real  TAU_ICE   ij   misc  1  -  rd   "TAU_ICE"   "CLOUD OD at 825 cm-1 TES"        ""        #SAVEMARS2 tauTES
     105state  real  ALBBARE   ij   misc  1  -  rhd   "ALBBARE"   "SOIL ALBEDO"                     ""        #SAVEMARS2 albedodat
     106state  real  VMR_ICE   ikj  misc  1  -  rhd   "VMR_ICE"   "VOL. MIXING RATIO ICE"           "ppm"     #SAVEMARS3 vmr
     107state  real  TAU_ICE   ij   misc  1  -  rhd   "TAU_ICE"   "CLOUD OD at 825 cm-1 TES"        ""        #SAVEMARS2 tauTES
    108108state  real  PDTZ      ikj  misc  1  -  rd   "PDT"       "TEMP TENDENCY"                   "K s-1"   #SAVEMARS3 pdt
    109 state  real  ZMAX_TH   ij   misc  1  -  rd   "ZMAX_TH"   "MAXIMUM LEVEL REACHED IN TH"     "m"       #SAVEMARS2 zmax_th
     109state  real  ZMAX_TH   ij   misc  1  -  rhd   "ZMAX_TH"   "MAXIMUM LEVEL REACHED IN TH"     "m"       #SAVEMARS2 zmax_th
    110110state  real  HFMAX_TH  ij   misc  1  -  rd   "HFMAX_TH"  "MAXIMUM TH HEAT FLUX"            "m.K/s"   #SAVEMARS2 hfmax_th
    111 state  real  WSTAR     ij   misc  1  -  rd   "WSTAR"     "FREE CONVECTION VELOCITY FROM TH" "m/s"    #SAVEMARS2 wstar
     111state  real  WSTAR     ij   misc  1  -  rhd   "WSTAR"     "FREE CONVECTION VELOCITY FROM TH" "m/s"    #SAVEMARS2 wstar
    112112state  real  Z0SET     ij   misc  1  -  rd   "Z0SET"     "SET SURFACE ROUGHNESS"           "m"       #SAVEMARS2 z0
    113113
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new_storm/libf/phymars/STORM_JULIEN_LAST/GCM_modif/aeropacity_use.F

    r308 r665  
    189189        msolsir(1:nlayer,1:naerkind)=0
    190190        mqextsqabs(1:nlayer,1:naerkind)=0
    191         WRITE(*,*) "Typical profiles of solsir and Qext/Qabs(IR):"
     191        WRITE(*,*) "Typical profiles of Qext(vis)/Qext(IR)"
     192        WRITE(*,*) "  and Qext(IR)/Qabs(IR):"
    192193        DO iaer = 1, naerkind ! Loop on aerosol kind
    193194          WRITE(*,*) "Aerosol # ",iaer
     
    210211!       otherwise default value read from starfi.nc file will be used)
    211212        call getin("tauvis",tauvis)
     213
     214!       Some information about the water cycle
     215        IF (water) THEN
     216          write(*,*) "water_param CCN reduc. fac. ", ccn_factor
     217        ENDIF
    212218
    213219        firstcall=.false.
     
    445451            taudusttmp(ig) = taudusttmp(ig) +
    446452     &                       aerosol(ig,l,iaerdust(iaer))
    447 
    448453          ENDDO
    449454        ENDDO
     
    590595!         ccn(ig,l) = ccn(ig,l) / 8.
    591596c -----------------------------------------------------------------
    592        write(*,*) "water_param CCN reduc. fac. ", ccn_factor
    593597       DO l=1,nlayer
    594598         DO ig=1,ngrid
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new_storm/libf/phymars/STORM_JULIEN_LAST/GCM_modif/callradite_use.F

    r308 r665  
    264264c        PLEASE MAKE SURE that you set up the right number of
    265265c          scatterers in dimradmars.h (naerkind);
    266 c          name_iaer(1) = "dust_conrath"   !! poussiere classique
    267           name_iaer(1) = "dust_doubleq"
    268 cc        name_iaer(2) = "dust_submicron" !! JB: experimental
    269 c          name_iaer(2) = "h2o_ice"
     266          name_iaer(1) = "dust_conrath"   !! default choice is good old Conrath profile
     267          IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme
     268          if (nqmx.gt.1) then
     269           ! trick to avoid problems compiling with 1 tracer
     270           ! and picky compilers who know name_iaer(2) is out of bounds
     271           j=2
     272          IF (water.AND.activice) name_iaer(j) = "h2o_ice"      !! radiatively-active clouds
     273          IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff
     274          endif ! of if (nqmx.gt.1)
    270275c        ----------------------------------------------------------
    271276
     
    389394c     Computing aerosol optical depth in each layer:
    390395      CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    391      &            pq,ccn,tauref,tau,aerosol,reffrad,nueffrad, QREFvis3d,
    392      &            QREFir3d,omegaREFvis3d,omegaREFir3d,zdqnorm)
     396     &      pq,ccn,tauref,tau,aerosol,reffrad,nueffrad, QREFvis3d,
     397     &      QREFir3d,omegaREFvis3d,omegaREFir3d,zdqnorm)
     398
    393399c     Starting loop on sub-domain
    394400c     ----------------------------
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new_storm/libf/phymars/STORM_JULIEN_LAST/GCM_modif/initracer_use.F

    r308 r665  
    4343#include "advtrac.h"
    4444#include "comgeomfi.h"
    45 #include "watercap.h"
    4645#include "chimiedata.h"
    4746
     
    111110              write(*,*) 'initracer: error expected dustbin=2'
    112111            else
    113               noms(1)='dust_mass'   ! dust mass mixing ratio
    114               noms(2)='dust_number' ! dust number mixing ratio
     112!              noms(1)='dust_mass'   ! dust mass mixing ratio
     113!              noms(2)='dust_number' ! dust number mixing ratio
     114! same as above, but avoid explict possible out-of-bounds on array
     115               noms(1)='dust_mass'   ! dust mass mixing ratio
     116               do iq=2,2
     117               noms(iq)='dust_number' ! dust number mixing ratio
     118               enddo
    115119            endif
    116120          endif
     
    120124          noms(nqmx)='h2o_vap'
    121125          mmol(nqmx)=18.
    122           noms(nqmx-1)='h2o_ice'
    123           mmol(nqmx-1)=18.
     126!            noms(nqmx-1)='h2o_ice'
     127!            mmol(nqmx-1)=18.
     128          !"loop" to avoid potential out-of-bounds in array
     129          do iq=nqmx-1,nqmx-1
     130            noms(iq)='h2o_ice'
     131            mmol(iq)=18.
     132          enddo
    124133        endif
    125134        ! 3. Chemistry
     
    157166      if (oldnames.and.water) then
    158167        write(*,*)'initracer: moving surface water ice to index ',nqmx-1
    159         qsurf(1:ngridmx,nqmx-1)=qsurf(1:ngridmx,nqmx)
     168        ! "loop" to avoid potential out-of-bounds on arrays
     169        do iq=nqmx-1,nqmx-1
     170          qsurf(1:ngridmx,iq)=qsurf(1:ngridmx,iq+1)
     171        enddo
    160172        qsurf(1:ngridmx,nqmx)=0
    161173      endif
     
    218230      igcm_ar=0
    219231      igcm_ar_n2=0
     232      igcm_n=0
     233      igcm_no=0
     234      igcm_no2=0
     235      igcm_n2d=0
     236      igcm_co2plus=0
     237      igcm_oplus=0
     238      igcm_o2plus=0
     239      igcm_coplus=0
     240      igcm_cplus=0
     241      igcm_nplus=0
     242      igcm_noplus=0
     243      igcm_n2plus=0
     244      igcm_hplus=0
     245      igcm_elec=0
     246
    220247
    221248      ! 1. find dust tracers
     
    320347          count=count+1
    321348        endif
     349        if (noms(iq).eq."n") then
     350          igcm_n=iq
     351          mmol(igcm_n)=14.
     352          count=count+1
     353        endif
     354        if (noms(iq).eq."no") then
     355          igcm_no=iq
     356          mmol(igcm_no)=30.
     357          count=count+1
     358        endif
     359        if (noms(iq).eq."no2") then
     360          igcm_no2=iq
     361          mmol(igcm_no2)=46.
     362          count=count+1
     363        endif
     364        if (noms(iq).eq."n2d") then
     365          igcm_n2d=iq
     366          mmol(igcm_n2d)=28.
     367          count=count+1
     368        endif
     369        if (noms(iq).eq."co2plus") then
     370          igcm_co2plus=iq
     371          mmol(igcm_co2plus)=44.
     372          count=count+1
     373        endif
     374        if (noms(iq).eq."oplus") then
     375          igcm_oplus=iq
     376          mmol(igcm_oplus)=16.
     377          count=count+1
     378        endif
     379        if (noms(iq).eq."o2plus") then
     380          igcm_o2plus=iq
     381          mmol(igcm_o2plus)=32.
     382          count=count+1
     383        endif
     384        if (noms(iq).eq."coplus") then
     385          igcm_coplus=iq
     386          mmol(igcm_coplus)=28.
     387          count=count+1
     388        endif
     389        if (noms(iq).eq."cplus") then
     390          igcm_cplus=iq
     391          mmol(igcm_cplus)=12.
     392          count=count+1
     393        endif
     394        if (noms(iq).eq."nplus") then
     395          igcm_nplus=iq
     396          mmol(igcm_nplus)=14.
     397          count=count+1
     398        endif
     399        if (noms(iq).eq."noplus") then
     400          igcm_noplus=iq
     401          mmol(igcm_noplus)=30.
     402          count=count+1
     403        endif
     404        if (noms(iq).eq."n2plus") then
     405          igcm_n2plus=iq
     406          mmol(igcm_n2plus)=28.
     407          count=count+1
     408        endif
     409        if (noms(iq).eq."hplus") then
     410          igcm_hplus=iq
     411          mmol(igcm_hplus)=1.
     412          count=count+1
     413        endif
     414        if (noms(iq).eq."elec") then
     415          igcm_elec=iq
     416          mmol(igcm_elec)=1./1822.89
     417          count=count+1
     418        endif
    322419        if (noms(iq).eq."h2o_vap") then
    323420          igcm_h2o_vap=iq
     
    336433          count=count+1
    337434        endif
     435 
     436
    338437      enddo ! of do iq=1,nqmx
    339438!      count=count+nbqchem
     
    486585         alpha_lift(igcm_h2o_vap) =0.
    487586         alpha_devil(igcm_h2o_vap)=0.
    488 
    489 c       "Dryness coefficient" controlling the evaporation and
    490 c        sublimation from the ground water ice (close to 1)
    491 c        HERE, the goal is to correct for the fact
    492 c        that the simulated permanent water ice polar caps
    493 c        is larger than the actual cap and the atmospheric
    494 c        opacity not always realistic.
    495 
    496          do ig=1,ngridmx
    497            if (ngridmx.ne.1) watercaptag(ig)=.false.
    498            dryness(ig) = 1.
    499          enddo
    500 
    501          IF (caps) THEN
    502 c Perennial H20 north cap defined by watercaptag=true (allows surface to be
    503 c hollowed by sublimation in vdifc).
    504          yeyey = 0
    505          do ig=1,ngridmx
    506 !          !!! TESTS TESTS outliers
    507 !          !!! TESTS TESTS outliers
    508 !          if ( ( lati(ig)*180./pi      .ge.  75 ) .and.
    509 !     .         ( lati(ig)*180./pi      .le.  77 ) .and.
    510 !     .         ( ( ( long(ig)*180./pi .ge. 000. ) .and.
    511 !     .              ( long(ig)*180./pi .le. 120. ) )
    512 !     .             .or.
    513 !     .             ( ( long(ig)*180./pi .ge. -130. ) .and.
    514 !     .             ( long(ig)*180./pi .le. -115. ) ) ) ) then
    515 !             if (yeyey .eq. 0) then  !!! 1/2 en 64x48 sinon trop large en lat
    516 !              write(*,*) "outliers ", lati(ig)*180./pi, long(ig)*180./pi
    517 !              if (ngridmx.ne.1) watercaptag(ig)=.true.
    518 !              dryness(ig) = 1.
    519 !              albedodat(ig) = 0.45 !! comme alb_surfice
    520 !              yeyey = 1
    521 !             else
    522 !              yeyey = 0
    523 !             endif
    524 !          endif
    525 !          !!! TESTS TESTS outliers
    526 !          !!! TESTS TESTS outliers
    527 !
    528 !          !!! TESTS TESTS addcap
    529 !          !!! TESTS TESTS addcap     
    530 !          if ( ( lati(ig)*180./pi      .ge.  82 ) .and.
    531 !     .         ( lati(ig)*180./pi      .le.  84 ) .and.
    532 !     .         ( ( long(ig)*180./pi .gt. -030. ) .and.
    533 !     .              ( long(ig)*180./pi .lt. 090. ) ) ) then
    534 !              write(*,*) "capadd ", lati(ig)*180./pi, long(ig)*180./pi
    535 !              if (ngridmx.ne.1) watercaptag(ig)=.true.
    536 !              albedodat(ig) = 0.45 !! comme alb_surfice
    537 !              dryness(ig) = 1.
    538 !          endif
    539 !          !!! TESTS TESTS addcap
    540 !          !!! TESTS TESTS addcap
    541    
    542            if (lati(ig)*180./pi.gt.84) then
    543              if (ngridmx.ne.1) watercaptag(ig)=.true.
    544              dryness(ig) = 1.
    545 c Use the following cap definition for high spatial resolution (latitudinal bin <= 5 deg)
    546 c             if (lati(ig)*180./pi.lt.85.and.long(ig).ge.0) then
    547 c               if (ngridmx.ne.1) watercaptag(ig)=.true.
    548 c               dryness(ig) = 1.
    549 c             endif
    550 c             if (lati(ig)*180./pi.ge.85) then
    551 c               if (ngridmx.ne.1) watercaptag(ig)=.true.
    552 c               dryness(ig) = 1.
    553 c             endif
    554            endif  ! (lati>80 deg)
    555          end do ! (ngridmx)
    556         ENDIF ! (caps)
    557 
    558587         if(water.and.(nqmx.ge.2)) then
    559588           radius(igcm_h2o_ice)=3.e-6
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new_storm/libf/phymars/STORM_JULIEN_LAST/GCM_modif/physiq_modif_use.F

    r308 r665  
    1       SUBROUTINE physiq(ngrid,nlayer,nq,
    2      $            firstcall,lastcall,
    3      $            pday,ptime,ptimestep,
    4      $            pplev,pplay,pphi,
    5      $            pu,pv,pt,pq,
    6      $            pw,
    7      $            pdu,pdv,pdt,pdq,pdpsrf,tracerdyn)
    8 
     1      SUBROUTINE physiq(
     2     $            ngrid,nlayer,nq
     3     $            ,firstcall,lastcall
     4     $            ,pday,ptime,ptimestep
     5     $            ,pplev,pplay,pphi
     6     $            ,pu,pv,pt,pq
     7     $            ,pw
     8     $            ,pdu,pdv,pdt,pdq,pdpsrf,tracerdyn
     9#ifdef MESOSCALE
     10#include "meso_inc/meso_inc_invar.F"
     11#endif
     12     $            )
    913
    1014      IMPLICIT NONE
     
    4246c      8. Contribution to tendencies due to thermosphere
    4347c      9. Surface and sub-surface temperature calculations
    44 c     10. Renormalisation
    45 c     11. Write outputs :
     48c     10. Write outputs :
    4649c           - "startfi", "histfi" (if it's time)
    4750c           - Saving statistics (if "callstats = .true.")
    4851c           - Dumping eof (if "calleofdump = .true.")
    4952c           - Output any needed variables in "diagfi"
    50 c     12. Diagnostic: mass conservation of tracers
     53c     11. Diagnostic: mass conservation of tracers
    5154c
    5255c   author:
     
    6164c           Radiatively active tracers: J.-B. Madeleine (10/2008-06/2009)
    6265c             Nb: See callradite.F for more information.
     66c           Mesoscale lines: Aymeric Spiga (2007 - 2011) -- check MESOSCALE flags
    6367c           
    6468c   arguments:
     
    124128
    125129#include "chimiedata.h"
    126 #include "watercap.h"
    127130#include "param.h"
    128131#include "param_v3.h"
     
    131134#include "netcdf.inc"
    132135
    133 
     136#include "slope.h"
     137
     138#ifdef MESOSCALE
     139#include "wrf_output_2d.h"
     140#include "wrf_output_3d.h"
     141#include "advtrac.h"   !!! this is necessary for tracers (in dyn3d)
     142#include "meso_inc/meso_inc_var.F"
     143#endif
    134144
    135145c Arguments :
     
    180190      REAL fluxgrd(ngridmx)          ! surface conduction flux (W.m-2)
    181191      REAL qsurf(ngridmx,nqmx)       ! tracer on surface (e.g. kg.m-2)
    182       REAL q2(ngridmx,nlayermx+1)    ! Turbulent Kinetic Energy
    183       INTEGER ig_vl1                 ! Grid Point near VL1   (for diagnostic)
     192      REAL q2(ngridmx,nlayermx+1)    ! Turbulent Kinetic Energy
     193     
     194      REAL watercapflag(ngridmx)     ! water cap flag
    184195
    185196c     Variables used by the water ice microphysical scheme:
     
    187198      REAL nuice(ngridmx,nlayermx)   ! Estimated effective variance
    188199                                     !   of the size distribution
    189 c     Albedo of deposited surface ice
    190       !!REAL, PARAMETER :: alb_surfice = 0.4 ! 0.45
    191       REAL, PARAMETER :: alb_surfice = 0.45 !!TESTS_JB
     200
     201c     Variables used by the slope model
     202      REAL sl_ls, sl_lct, sl_lat
     203      REAL sl_tau, sl_alb, sl_the, sl_psi
     204      REAL sl_fl0, sl_flu
     205      REAL sl_ra, sl_di0
     206      REAL sky
    192207
    193208      SAVE day_ini, icount
     
    195210      SAVE co2ice,albedo,emis, q2
    196211      SAVE capcal,fluxgrd,dtrad,fluxrad,fluxrad_sky,qsurf
    197       SAVE ig_vl1
    198212
    199213      REAL stephan   
     
    251265      REAL zdqchim(ngridmx,nlayermx,nqmx)
    252266      REAL zdqschim(ngridmx,nqmx)
    253       REAL zdqnorm(ngridmx,nlayermx,2)                     !quantity of dust which have to be added by the dynamical core
     267      REAL zdqnorm(ngridmx,nlayermx,2) !quantity of dust which have to be added
    254268
    255269
     
    304318      REAL time_phys
    305319
     320c Variables for PBL
     321
     322      REAL lmax_th_out(ngridmx),zmax_th(ngridmx)
     323      REAL, SAVE :: wmax_th(ngridmx)
     324      REAL hfmax_th(ngridmx)
     325      REAL pdu_th(ngridmx,nlayermx),pdv_th(ngridmx,nlayermx)
     326      REAL pdt_th(ngridmx,nlayermx),pdq_th(ngridmx,nlayermx,nqmx)
     327      INTEGER lmax_th(ngridmx)
     328      REAL dtke_th(ngridmx,nlayermx+1)
     329      REAL zcdv(ngridmx), zcdh(ngridmx)
     330      REAL Teta_out(ngridmx),u_out(ngridmx)  ! Interpolated teta and u at z_out
     331      REAL z_out                          ! height of interpolation between z0 and z1
     332      REAL ustar(ngridmx),tstar(ngridmx)  ! friction velocity and friction potential temp
     333      REAL zu2(ngridmx)
    306334c=======================================================================
    307335
     
    315343c        variables set to 0
    316344c        ~~~~~~~~~~~~~~~~~~
    317          call zerophys(ngrid*nlayer*naerkind,aerosol)
    318          call zerophys(ngrid*nlayer,dtrad)
    319          call zerophys(ngrid,fluxrad)
     345         aerosol(:,:,:)=0
     346         dtrad(:,:)=0
     347         fluxrad(:)=0
     348
     349         wmax_th(:)=0.
    320350
    321351c        read startfi
    322352c        ~~~~~~~~~~~~
    323 
     353#ifndef MESOSCALE
    324354! Read netcdf initial physical parameters.
    325355         CALL phyetat0 ("startfi.nc",0,0,
     
    327357     &         day_ini,time_phys,
    328358     &         tsurf,tsoil,emis,q2,qsurf,co2ice)
     359#else
     360#include "meso_inc/meso_inc_ini.F"
     361#endif
    329362
    330363         if (pday.ne.day_ini) then
     
    337370
    338371         write (*,*) 'In physiq day_ini =', day_ini
     372
     373c        initialize tracers
     374c        ~~~~~~~~~~~~~~~~~~
     375         tracerdyn=tracer
     376         IF (tracer) THEN
     377            CALL initracer(qsurf,co2ice)
     378         ENDIF  ! end tracer
    339379
    340380c        Initialize albedo and orbital calculation
     
    358398         icount=1
    359399
    360 
    361 c        initialize tracers
    362 c        ~~~~~~~~~~~~~~~~~~
    363          tracerdyn=tracer
    364          IF (tracer) THEN
    365             CALL initracer(qsurf,co2ice)
    366          ENDIF  ! end tracer
    367 
    368 c        Determining gridpoint near Viking Lander 1 (used for diagnostic only)
    369 c        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    370 
    371          if(ngrid.ne.1) then
    372            latvl1= 22.27
    373            lonvl1= -47.94
    374            ig_vl1= 1+ int( (1.5-(latvl1-90.)*jjm/180.)  -2 )*iim +
    375      &              int(1.5+(lonvl1+180)*iim/360.)
    376            write(*,*) 'Viking Lander 1 GCM point: lat,lon',
    377      &              lati(ig_vl1)*180/pi, long(ig_vl1)*180/pi
    378          end if
    379 
     400#ifndef MESOSCALE
    380401c        Initialize thermospheric parameters
    381402c        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    382403
    383404         if (callthermos) call param_read
    384 
     405#endif
    385406c        Initialize R and Cp as constant
    386407
     
    396417
    397418        IF (tracer.AND.water.AND.(ngridmx.NE.1)) THEN
    398           write(*,*)"physiq: water_param Surface ice alb:",alb_surfice
     419          write(*,*)"physiq: water_param Surface water ice albedo:",
     420     .                  albedo_h2o_ice
    399421        ENDIF
    400422                   
     
    415437c     Initialize various variables
    416438c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    417       call zerophys(ngrid*nlayer, pdv)
    418       call zerophys(ngrid*nlayer, pdu)
    419       call zerophys(ngrid*nlayer, pdt)
    420       call zerophys(ngrid*nlayer*nq, pdq)
    421       call zerophys(ngrid, pdpsrf)
    422       call zerophys(ngrid, zflubid)
    423       call zerophys(ngrid, zdtsurf)
    424       call zerophys(ngrid*nq, dqsurf)
     439      pdv(:,:)=0
     440      pdu(:,:)=0
     441      pdt(:,:)=0
     442      pdq(:,:,:)=0
     443      pdpsrf(:)=0
     444      zflubid(:)=0
     445      zdtsurf(:)=0
     446      dqsurf(:,:)=0
    425447      igout=ngrid/2+1
    426448
     
    469491      ENDDO
    470492
     493#ifndef MESOSCALE
    471494c-----------------------------------------------------------------------
    472495c    1.2.5 Compute mean mass, cp, and R
     
    476499         call concentrations(pplay,pt,pdt,pq,pdq,ptimestep)
    477500      endif
     501#endif
    478502c-----------------------------------------------------------------------
    479503c    2. Compute radiative tendencies :
     
    518542c          Radiative transfer
    519543c          ------------------
     544
    520545           CALL callradite(icount,ngrid,nlayer,nq,zday,zls,pq,albedo,
    521546     $     emis,mu0,pplev,pplay,pt,tsurf,fract,dist_sol,igout,
     
    523548     &     tauref,tau,aerosol,ccn,rdust,rice,nuice,zdqnorm)
    524549
     550c          Outputs for basic check (middle of domain)
     551c          ------------------------------------------
     552           print*, 'Ls =',zls*180./pi,
     553     &             'check lat lon', lati(igout)*180/pi,
     554     &                              long(igout)*180/pi
     555           print*, 'tauref(700 Pa) =',tauref(igout),
     556     &             ' tau(700 Pa) =',tau(igout,1)*700./pplev(igout,1)
     557
     558c          ---------------------------------------------------------
     559c          Call slope parameterization for direct and scattered flux
     560c          ---------------------------------------------------------
     561           IF(callslope) THEN
     562            print *, 'Slope scheme is on and computing...'
     563            DO ig=1,ngrid 
     564              sl_the = theta_sl(ig)
     565              IF (sl_the .ne. 0.) THEN
     566                ztim1=fluxsurf_sw(ig,1)+fluxsurf_sw(ig,2)
     567                DO l=1,2
     568                 sl_lct = ptime*24. + 180.*long(ig)/pi/15.
     569                 sl_ra  = pi*(1.0-sl_lct/12.)
     570                 sl_lat = 180.*lati(ig)/pi
     571                 sl_tau = tau(ig,1)
     572                 sl_alb = albedo(ig,l)
     573                 sl_psi = psi_sl(ig)
     574                 sl_fl0 = fluxsurf_sw(ig,l)
     575                 sl_di0 = 0.
     576                 if (mu0(ig) .gt. 0.) then
     577                  sl_di0 = mu0(ig)*(exp(-sl_tau/mu0(ig)))
     578                  sl_di0 = sl_di0*1370./dist_sol/dist_sol
     579                  sl_di0 = sl_di0/ztim1
     580                  sl_di0 = fluxsurf_sw(ig,l)*sl_di0
     581                 endif
     582                 ! you never know (roundup concern...)
     583                 if (sl_fl0 .lt. sl_di0) sl_di0=sl_fl0
     584                 !!!!!!!!!!!!!!!!!!!!!!!!!!
     585                 CALL param_slope( mu0(ig), declin, sl_ra, sl_lat,
     586     &                             sl_tau, sl_alb, sl_the, sl_psi,
     587     &                             sl_di0, sl_fl0, sl_flu )
     588                 !!!!!!!!!!!!!!!!!!!!!!!!!!
     589                 fluxsurf_sw(ig,l) = sl_flu
     590                ENDDO
     591              !!! compute correction on IR flux as well
     592              sky= (1.+cos(pi*theta_sl(ig)/180.))/2.
     593              fluxsurf_lw(ig)= fluxsurf_lw(ig)*sky
     594              ENDIF
     595            ENDDO
     596           ENDIF
     597
    525598c          CO2 near infrared absorption
    526599c          ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    527            call zerophys(ngrid*nlayer,zdtnirco2)
     600           zdtnirco2(:,:)=0
    528601           if (callnirco2) then
    529602              call nirco2abs (ngrid,nlayer,pplay,dist_sol,
     
    554627           ENDIF
    555628
    556 
    557 
    558629        ENDIF ! of if(mod(icount-1,iradia).eq.0)
    559630
     
    569640     $         stephan*zplanck(ig)*zplanck(ig)
    570641               fluxrad(ig)=fluxrad_sky(ig)-zplanck(ig)
     642               IF(callslope) THEN
     643                 sky= (1.+cos(pi*theta_sl(ig)/180.))/2.
     644                 fluxrad(ig)=fluxrad(ig)+(1.-sky)*zplanck(ig)
     645               ENDIF
    571646           ENDDO
    572 
    573647
    574648         DO l=1,nlayer
     
    602676c    4. Vertical diffusion (turbulent mixing):
    603677c    -----------------------------------------
    604 c
     678
    605679      IF (calldifv) THEN
    606 
    607680
    608681         DO ig=1,ngrid
     
    610683         ENDDO
    611684
    612          CALL zerophys(ngrid*nlayer,zdum1)
    613          CALL zerophys(ngrid*nlayer,zdum2)
     685         zdum1(:,:)=0
     686         zdum2(:,:)=0
    614687         do l=1,nlayer
    615688            do ig=1,ngrid
     
    617690            enddo
    618691         enddo
    619          
     692
     693
     694#ifdef MESOSCALE
     695      IF (.not.flag_LES) THEN
     696#endif
     697c ----------------------
     698c Treatment of a special case : using new surface layer (Richardson based)
     699c without using the thermals in gcm and mesoscale can yield problems in
     700c weakly unstable situations when winds are near to 0. For those cases, we add
     701c a unit subgrid gustiness. Remember that thermals should be used we using the
     702c Richardson based surface layer model.
     703        IF ( .not.calltherm .and. callrichsl ) THEN
     704          DO ig=1, ngridmx
     705             IF (zh(ig,1) .lt. tsurf(ig)) THEN
     706               wmax_th(ig)=1.
     707             ENDIF       
     708          ENDDO
     709        ENDIF
     710c ----------------------
     711#ifdef MESOSCALE
     712      ENDIF
     713#endif
     714
     715
    620716c        Calling vdif (Martian version WITH CO2 condensation)
    621717         CALL vdifc(ngrid,nlayer,nq,co2ice,zpopsk,
     
    625721     $        zdum1,zdum2,zdh,pdq,zflubid,
    626722     $        zdudif,zdvdif,zdhdif,zdtsdif,q2,
    627      &        zdqdif,zdqsdif)
    628 
     723     &        zdqdif,zdqsdif,wmax_th,zcdv,zcdh)
     724
     725#ifdef MESOSCALE
     726#include "meso_inc/meso_inc_les.F"
     727#endif
    629728         DO l=1,nlayer
    630729            DO ig=1,ngrid
     
    638737         ENDDO
    639738
    640          DO ig=1,ngrid
    641             zdtsurf(ig)=zdtsurf(ig)+zdtsdif(ig)
    642          ENDDO
     739          DO ig=1,ngrid
     740             zdtsurf(ig)=zdtsurf(ig)+zdtsdif(ig)
     741          ENDDO
    643742
    644743         if (tracer) then
     
    662761     s      (fluxrad(ig)+fluxgrd(ig))/capcal(ig)
    663762         ENDDO
     763#ifdef MESOSCALE
     764         IF (flag_LES) THEN
     765            write(*,*) 'LES mode !'
     766            write(*,*) 'Please set calldifv to T in callphys.def'
     767            STOP
     768         ENDIF
     769#endif
    664770      ENDIF ! of IF (calldifv)
    665771
     772c-----------------------------------------------------------------------
     773c   TEST. Thermals :
     774c HIGHLY EXPERIMENTAL, BEWARE !!
     775c   -----------------------------
     776 
     777      if(calltherm) then
     778 
     779        call calltherm_interface(firstcall,
     780     $ long,lati,zzlev,zzlay,
     781     $ ptimestep,pu,pv,pt,pq,pdu,pdv,pdt,pdq,q2,
     782     $ pplay,pplev,pphi,zpopsk,
     783     $ pdu_th,pdv_th,pdt_th,pdq_th,lmax_th,zmax_th,
     784     $ dtke_th,hfmax_th,wmax_th)
     785 
     786         DO l=1,nlayer
     787           DO ig=1,ngrid
     788              pdu(ig,l)=pdu(ig,l)+pdu_th(ig,l)
     789              pdv(ig,l)=pdv(ig,l)+pdv_th(ig,l)
     790              pdt(ig,l)=pdt(ig,l)+pdt_th(ig,l)
     791              q2(ig,l)=q2(ig,l)+dtke_th(ig,l)*ptimestep
     792           ENDDO
     793        ENDDO
     794 
     795        DO ig=1,ngrid
     796          q2(ig,nlayer+1)=q2(ig,nlayer+1)+dtke_th(ig,nlayer+1)*ptimestep
     797        ENDDO     
     798   
     799        if (tracer) then
     800        DO iq=1,nq
     801         DO l=1,nlayer
     802           DO ig=1,ngrid
     803             pdq(ig,l,iq)=pdq(ig,l,iq)+pdq_th(ig,l,iq)
     804           ENDDO
     805         ENDDO
     806        ENDDO
     807        endif
     808
     809        lmax_th_out(:)=real(lmax_th(:))
     810
     811        else   !of if calltherm
     812        lmax_th(:)=0
     813        wmax_th(:)=0.
     814        lmax_th_out(:)=0.
     815        end if
    666816
    667817c-----------------------------------------------------------------------
     
    676826            ENDDO
    677827         ENDDO
    678          CALL zerophys(ngrid*nlayer,zduadj)
    679          CALL zerophys(ngrid*nlayer,zdvadj)
    680          CALL zerophys(ngrid*nlayer,zdhadj)
     828         zduadj(:,:)=0
     829         zdvadj(:,:)=0
     830         zdhadj(:,:)=0
    681831
    682832         CALL convadj(ngrid,nlayer,nq,ptimestep,
    683      $                pplay,pplev,zpopsk,
     833     $                pplay,pplev,zpopsk,lmax_th,
    684834     $                pu,pv,zh,pq,
    685835     $                pdu,pdv,zdh,pdq,
    686836     $                zduadj,zdvadj,zdhadj,
    687837     $                zdqadj)
     838
    688839
    689840         DO l=1,nlayer
     
    718869     $              co2ice,albedo,emis,
    719870     $              zdtc,zdtsurfc,pdpsrf,zduc,zdvc,zdqc,
    720      $              fluxsurf_sw,zls)
     871     $              fluxsurf_sw,zls)
    721872
    722873         DO l=1,nlayer
     
    793944c     ------------------
    794945
     946#ifndef MESOSCALE
    795947c        --------------
    796948c        photochemistry :
     
    837989
    838990         END IF  ! of IF (photochem.or.thermochem)
     991#endif
    839992
    840993c   7c. Aerosol particles
     
    9081061      endif !  of if (tracer)
    9091062
    910 
     1063#ifndef MESOSCALE
    9111064c-----------------------------------------------------------------------
    9121065c   8. THERMOSPHERE CALCULATION
     
    9331086
    9341087      endif ! of if (callthermos)
     1088#endif
    9351089
    9361090c-----------------------------------------------------------------------
     
    9511105
    9521106      IF (tracer.AND.water.AND.(ngridmx.NE.1)) THEN
     1107#ifndef MESOSCALE
    9531108         if (caps.and.(obliquit.lt.27.)) then
    9541109           ! NB: Updated surface pressure, at grid point 'ngrid', is
     
    9571112     &                     (pplev(ngrid,1)+pdpsrf(ngrid)*ptimestep)))
    9581113         endif
     1114#endif
    9591115c       -------------------------------------------------------------
    960 c       Change of surface albedo (set to 0.4) in case of ground frost
     1116c       Change of surface albedo in case of ground frost
    9611117c       everywhere except on the north permanent cap and in regions
    9621118c       covered by dry ice.
     
    9651121         do ig=1,ngrid
    9661122           if ((co2ice(ig).eq.0).and.
    967      &        (qsurf(ig,igcm_h2o_ice).gt.0.005)) then
    968               albedo(ig,1) = alb_surfice
    969               albedo(ig,2) = alb_surfice
     1123     &        (qsurf(ig,igcm_h2o_ice).gt.frost_albedo_threshold)) then
     1124              albedo(ig,1) = albedo_h2o_ice
     1125              albedo(ig,2) = albedo_h2o_ice
     1126c              write(*,*) "frost thickness", qsurf(ig,igcm_h2o_ice)
     1127c              write(*,*) "physiq.F frost :"
     1128c     &        ,lati(ig)*180./pi, long(ig)*180./pi
    9701129           endif
    9711130         enddo  ! of do ig=1,ngrid
     
    9941153
    9951154c-----------------------------------------------------------------------
    996 c  11. Write output files
     1155c  10. Write output files
    9971156c  ----------------------
    9981157
     
    10391198      ENDDO
    10401199
    1041 c    Compute surface stress : (NB: z0 is a common in planete.h)
     1200      ! Potential Temperature
     1201
     1202       DO ig=1,ngridmx
     1203          DO l=1,nlayermx
     1204              zh(ig,l) = zt(ig,l)*(zplay(ig,l)/zplev(ig,1))**rcp
     1205          ENDDO
     1206       ENDDO
     1207
     1208
     1209c    Compute surface stress : (NB: z0 is a common in surfdat.h)
    10421210c     DO ig=1,ngrid
    1043 c        cd = (0.4/log(zzlay(ig,1)/z0))**2
     1211c        cd = (0.4/log(zzlay(ig,1)/z0(ig)))**2
    10441212c        zstress(ig) = rho(ig,1)*cd*(zu(ig,1)**2 + zv(ig,1)**2)
    10451213c     ENDDO
     
    10471215c     Sum of fluxes in solar spectral bands (for output only)
    10481216      DO ig=1,ngrid
    1049              fluxtop_sw_tot(ig)=fluxtop_sw(ig,1) + fluxtop_sw(ig,2)
    1050              fluxsurf_sw_tot(ig)=fluxsurf_sw(ig,1) + fluxsurf_sw(ig,2)
     1217             fluxtop_sw_tot(ig)=fluxtop_sw(ig,1) + fluxtop_sw(ig,2)
     1218             fluxsurf_sw_tot(ig)=fluxsurf_sw(ig,1) + fluxsurf_sw(ig,2)
    10511219      ENDDO
    10521220c ******* TEST ******************************************************
     
    10611229        ENDDO
    10621230      ENDDO
    1063       if(min(pt(igmin,lmin),zt(igmin,lmin)).lt.70.) then       
     1231      if(min(pt(igmin,lmin),zt(igmin,lmin)).lt.70.) then
    10641232        write(*,*) 'PHYSIQ: stability WARNING :'
    10651233        write(*,*) 'pt, zt Tmin = ', pt(igmin,lmin), zt(igmin,lmin),
     
    10881256
    10891257      IF (ngrid.NE.1) THEN
    1090          print*,'Ls =',zls*180./pi,
    1091      &   ' tauref(700 Pa,lat=0) =',tauref(ngrid/2),
    1092      &   ' tau(Viking1) =',tau(ig_vl1,1)
    1093 
    1094 
     1258
     1259#ifndef MESOSCALE
    10951260c        -------------------------------------------------------------------
    10961261c        Writing NetCDF file  "RESTARTFI" at the end of the run
     
    11111276     .              zgam,zthe)
    11121277         ENDIF
     1278#endif
    11131279
    11141280c        -------------------------------------------------------------------
     
    11201286           if (water) then
    11211287
    1122              call zerophys(ngrid,mtot)
    1123              call zerophys(ngrid,icetot)
    1124              call zerophys(ngrid,rave)
    1125              call zerophys(ngrid,tauTES)
     1288             mtot(:)=0
     1289             icetot(:)=0
     1290             rave(:)=0
     1291             tauTES(:)=0
    11261292             do ig=1,ngrid
    11271293               do l=1,nlayermx
     
    11601326c        which can later be used to make the statistic files of the run:
    11611327c        "stats")          only possible in 3D runs !
    1162 
    11631328         
    11641329         IF (callstats) THEN
     
    12681433         ENDIF
    12691434
     1435
     1436#ifdef MESOSCALE
     1437      !!!
     1438      !!! OUTPUT FIELDS
     1439      !!!
     1440      wtsurf(1:ngrid) = tsurf(1:ngrid)    !! surface temperature
     1441      wco2ice(1:ngrid) = co2ice(1:ngrid)  !! co2 ice
     1442      mtot(1:ngrid) = mtot(1:ngrid) * 1.e6 / rho_ice
     1443      !! JF
     1444      TAU_lay(:)=tau(:,1)!!true opacity (not a reference like tauref)
     1445      IF (igcm_dust_mass .ne. 0) THEN
     1446        qsurfice_dust(1:ngrid) = qsurf(1:ngrid,igcm_dust_mass)
     1447      ENDIF
     1448      IF (igcm_h2o_ice .ne. 0) THEN     
     1449        qsurfice(1:ngrid) = qsurf(1:ngrid,igcm_h2o_ice)
     1450        vmr=1.e6 * zq(1:ngrid,1:nlayer,igcm_h2o_ice)
     1451     .           * mugaz / mmol(igcm_h2o_ice)
     1452      ENDIF
     1453      !! Dust quantity integration along the vertical axe
     1454      dustot(:)=0
     1455      do ig=1,ngrid
     1456       do l=1,nlayermx
     1457        dustot(ig) = dustot(ig) +
     1458     &               zq(ig,l,igcm_dust_mass)
     1459     &               *  (pplev(ig,l) - pplev(ig,l+1)) / g
     1460       enddo
     1461      enddo
     1462c AUTOMATICALLY GENERATED FROM REGISTRY
     1463#include "fill_save.inc"
     1464#else
     1465
    12701466c        ==========================================================
    12711467c        WRITEDIAGFI: Outputs in netcdf file "DIAGFI", containing
     
    12751471c        WRITEDIAGFI can ALSO be called from any other subroutines
    12761472c        for any variables !!
    1277         call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2,
    1278      &                  emis)
     1473c        call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2,
     1474c    &                  emis)
     1475!         call WRITEDIAGFI(ngrid,"pplay","Pressure","Pa",3,zplay)
     1476!         call WRITEDIAGFI(ngrid,"pplev","Pressure","Pa",3,zplev)
    12791477         call WRITEDIAGFI(ngrid,"tsurf","Surface temperature","K",2,
    12801478     &                  tsurf)
     
    12821480        call WRITEDIAGFI(ngrid,"co2ice","co2 ice thickness","kg.m-2",2,
    12831481     &                  co2ice)
     1482
     1483c         call WRITEDIAGFI(ngrid,"temp7","temperature in layer 7",
     1484c     &                  "K",2,zt(1,7))
    12841485c         call WRITEDIAGFI(ngrid,"fluxsurf_lw","fluxsurf_lw","W.m-2",2,
    12851486c     &                  fluxsurf_lw)
     
    12911492c     &                  fluxtop_sw_tot)
    12921493         call WRITEDIAGFI(ngrid,"temp","temperature","K",3,zt)
    1293 c        call WRITEDIAGFI(ngrid,"tau","tau"," ",2,tau)
    12941494        call WRITEDIAGFI(ngrid,"u","Zonal wind","m.s-1",3,zu)
    12951495        call WRITEDIAGFI(ngrid,"v","Meridional wind","m.s-1",3,zv)
    12961496        call WRITEDIAGFI(ngrid,"w","Vertical wind","m.s-1",3,pw)
    1297 c         call WRITEDIAGFI(ngrid,"rho","density","none",3,rho)
     1497         call WRITEDIAGFI(ngrid,"rho","density","none",3,rho)
    12981498c        call WRITEDIAGFI(ngrid,"q2","q2","kg.m-3",3,q2)
    1299 c        call WRITEDIAGFI(ngrid,'Teta','T potentielle','K',3,zh)
     1499!        call WRITEDIAGFI(ngrid,'Teta','T potentielle','K',3,zh)
    13001500c        call WRITEDIAGFI(ngrid,"pressure","Pressure","Pa",3,pplay)
    13011501c        call WRITEDIAGFI(ngrid,"ssurf","Surface stress","N.m-2",2,
     
    13051505c        call WRITEDIAGFI(ngridmx,'lw_htrt','lw heat. rate',
    13061506c    &                   'w.m-2',3,zdtlw)
    1307 
    1308 !!!!!!!!!!!!!!!!!!!!!!!!SOIL SOIL SOIL
     1507c        CALL WRITEDIAGFI(ngridmx,'tauTESap',
     1508c     &                         'tau abs 825 cm-1',
     1509c     &                         '',2,tauTES)
     1510
     1511#ifdef MESOINI
     1512        call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2,
     1513     &                  emis)
     1514        call WRITEDIAGFI(ngrid,"rho","density","none",3,rho)
    13091515        call WRITEDIAGFI(ngrid,"tsoil","Soil temperature",
    13101516     &                       "K",3,tsoil)
    13111517        call WRITEDIAGFI(ngrid,"inertiedat","Soil inertia",
    13121518     &                       "K",3,inertiedat)
    1313 !!!!!!!!!!!!!!!!!!!!!!!!SOIL SOIL SOIL
     1519#endif
     1520
    13141521
    13151522c        ----------------------------------------------------------
     
    13241531       
    13251532         ! Compute co2 column
    1326          call zerophys(ngrid,co2col)
     1533         co2col(:)=0
    13271534         do l=1,nlayermx
    13281535           do ig=1,ngrid
     
    13311538           enddo
    13321539         enddo
    1333 c         call WRITEDIAGFI(ngrid,"co2col","CO2 column","kg.m-2",2,
    1334 c     &                  co2col)
     1540         call WRITEDIAGFI(ngrid,"co2col","CO2 column","kg.m-2",2,
     1541     &                  co2col)
    13351542         endif ! of if (tracer.and.(igcm_co2.ne.0))
    13361543
     
    13411548           if (water) then
    13421549
     1550#ifdef MESOINI
    13431551            !!!! waterice = q01, voir readmeteo.F90
    13441552            call WRITEDIAGFI(ngridmx,'q01',noms(igcm_h2o_ice),
     
    13531561     &                      'kg.m-2',2,
    13541562     &                       qsurf(1:ngridmx,igcm_h2o_ice))
     1563#endif
    13551564
    13561565             CALL WRITEDIAGFI(ngridmx,'mtot',
     
    13601569     &                       'total mass of water ice',
    13611570     &                       'kg/m2',2,icetot)
    1362 cc            vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_ice)
    1363 cc    &                *mugaz/mmol(igcm_h2o_ice)
    1364 cc            call WRITEDIAGFI(ngridmx,'vmr_h2oice','h2o ice vmr',
    1365 cc    &                       'mol/mol',3,vmr)
    1366 c             CALL WRITEDIAGFI(ngridmx,'reffice',
    1367 c     &                       'Mean reff',
    1368 c     &                       'm',2,rave)
    1369 cc            call WRITEDIAGFI(ngridmx,'rice','Ice particle size',
    1370 cc    &                       'm',3,rice)
    1371 cc            If activice is true, tauTES is computed in aeropacity.F;
    1372 c             if (.not.activice) then
    1373 c               CALL WRITEDIAGFI(ngridmx,'tauTESap',
    1374 c     &                         'tau abs 825 cm-1',
    1375 c     &                         '',2,tauTES)
    1376 c             endif
    1377 c             call WRITEDIAGFI(ngridmx,'h2o_ice_s',
    1378 c     &                       'surface h2o_ice',
    1379 c     &                       'kg.m-2',2,qsurf(1,igcm_h2o_ice))
     1571c            vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_ice)
     1572c    &                *mugaz/mmol(igcm_h2o_ice)
     1573c            call WRITEDIAGFI(ngridmx,'vmr_h2oice','h2o ice vmr',
     1574c    &                       'mol/mol',3,vmr)
     1575             CALL WRITEDIAGFI(ngridmx,'reffice',
     1576     &                       'Mean reff',
     1577     &                       'm',2,rave)
     1578c            call WRITEDIAGFI(ngridmx,'rice','Ice particle size',
     1579c    &                       'm',3,rice)
     1580c            If activice is true, tauTES is computed in aeropacity.F;
     1581             if (.not.activice) then
     1582               CALL WRITEDIAGFI(ngridmx,'tauTESap',
     1583     &                         'tau abs 825 cm-1',
     1584     &                         '',2,tauTES)
     1585             endif
     1586             call WRITEDIAGFI(ngridmx,'h2o_ice_s',
     1587     &                       'surface h2o_ice',
     1588     &                       'kg.m-2',2,qsurf(1,igcm_h2o_ice))
     1589
     1590            if (caps) then
     1591             do ig=1,ngridmx
     1592                if (watercaptag(ig)) watercapflag(ig) = 1
     1593             enddo
     1594             CALL WRITEDIAGFI(ngridmx,'watercaptag',
     1595     &                         'Ice water caps',
     1596     &                         '',2,watercapflag)
     1597            endif
     1598            CALL WRITEDIAGFI(ngridmx,'albedo',
     1599     &                         'albedo',
     1600     &                         '',2,albedo(1:ngridmx,1))
    13801601           endif !(water)
    13811602
     
    14071628c          call WRITEDIAGFI(ngridmx,'tau','taudust','SI',2,tau(1,1))
    14081629           if (doubleq) then
    1409 cc            call WRITEDIAGFI(ngridmx,'qsurf','qsurf',
    1410 cc    &                       'kg.m-2',2,qsurf(1,1))
    1411 cc            call WRITEDIAGFI(ngridmx,'Nsurf','N particles',
    1412 cc    &                       'N.m-2',2,qsurf(1,2))
    1413 cc            call WRITEDIAGFI(ngridmx,'dqsdev','ddevil lift',
    1414 cc    &                       'kg.m-2.s-1',2,zdqsdev(1,1))
    1415 cc            call WRITEDIAGFI(ngridmx,'dqssed','sedimentation',
    1416 cc    &                       'kg.m-2.s-1',2,zdqssed(1,1))
    1417 c             call WRITEDIAGFI(ngridmx,'reffdust','reffdust',
    1418 c     &                        'm',3,rdust*ref_r0)
     1630c            call WRITEDIAGFI(ngridmx,'qsurf','qsurf',
     1631c    &                       'kg.m-2',2,qsurf(1,1))
     1632c            call WRITEDIAGFI(ngridmx,'Nsurf','N particles',
     1633c    &                       'N.m-2',2,qsurf(1,2))
     1634c            call WRITEDIAGFI(ngridmx,'dqsdev','ddevil lift',
     1635c    &                       'kg.m-2.s-1',2,zdqsdev(1,1))
     1636c            call WRITEDIAGFI(ngridmx,'dqssed','sedimentation',
     1637c    &                       'kg.m-2.s-1',2,zdqssed(1,1))
     1638             call WRITEDIAGFI(ngridmx,'reffdust','reffdust',
     1639     &                        'm',3,rdust*ref_r0)
    14191640             call WRITEDIAGFI(ngridmx,'dustq','Dust mass mr',
    14201641     &                        'kg/kg',3,pq(1,1,igcm_dust_mass))
    1421             call WRITEDIAGFI(ngridmx,'dustN','Dust number',
     1642c            call WRITEDIAGFI(ngridmx,'dustN','Dust number',
     1643c    &                        'part/kg',3,pq(1,1,igcm_dust_number))
     1644#ifdef MESOINI
     1645             call WRITEDIAGFI(ngridmx,'dustN','Dust number',
    14221646     &                        'part/kg',3,pq(1,1,igcm_dust_number))
     1647#endif
    14231648           else
    14241649             do iq=1,dustbin
     
    14371662
    14381663c        ----------------------------------------------------------
     1664c        ----------------------------------------------------------
     1665c        PBL OUTPUS
     1666c        ----------------------------------------------------------
     1667c        ----------------------------------------------------------
     1668
     1669
     1670c        ----------------------------------------------------------
     1671c        Outputs of surface layer
     1672c        ----------------------------------------------------------
     1673
     1674
     1675         z_out=0.
     1676         if (calltherm .and. (z_out .gt. 0.)) then
     1677         call surflayer_interpol(ngrid,nlayer,z0,g,zzlay,zu,zv,wmax_th
     1678     &              ,tsurf,zh,z_out,Teta_out,u_out,ustar,tstar)
     1679
     1680         zu2(:)=sqrt(zu(:,1)*zu(:,1)+zv(:,1)*zv(:,1))
     1681         call WRITEDIAGFI(ngridmx,'sqrt(zu2)',
     1682     &              'horizontal velocity norm','m/s',
     1683     &                         2,zu2)
     1684
     1685         call WRITEDIAGFI(ngridmx,'Teta_out',
     1686     &              'potential temperature at z_out','K',
     1687     &                         2,Teta_out)
     1688         call WRITEDIAGFI(ngridmx,'u_out',
     1689     &              'horizontal velocity norm at z_out','m/s',
     1690     &                         2,u_out)
     1691         call WRITEDIAGFI(ngridmx,'u*',
     1692     &              'friction velocity','m/s',
     1693     &                         2,ustar)
     1694         call WRITEDIAGFI(ngridmx,'teta*',
     1695     &              'friction potential temperature','K',
     1696     &                         2,tstar)
     1697         else
     1698           if((.not. calltherm).and.(z_out .gt. 0.)) then
     1699            print*, 'WARNING : no interpolation in surface-layer :'
     1700            print*, 'Outputing surface-layer quantities without thermals
     1701     & does not make sense'
     1702           endif
     1703         endif
     1704
     1705c        ----------------------------------------------------------
     1706c        Outputs of thermals
     1707c        ----------------------------------------------------------
     1708         if (calltherm) then
     1709
     1710!        call WRITEDIAGFI(ngrid,'dtke',
     1711!     &              'tendance tke thermiques','m**2/s**2',
     1712!     &                         3,dtke_th)
     1713!        call WRITEDIAGFI(ngrid,'d_u_ajs',
     1714!     &              'tendance u thermiques','m/s',
     1715!     &                         3,pdu_th*ptimestep)
     1716!        call WRITEDIAGFI(ngrid,'d_v_ajs',
     1717!     &              'tendance v thermiques','m/s',
     1718!     &                         3,pdv_th*ptimestep)
     1719!        if (tracer) then
     1720!        if (nq .eq. 2) then
     1721!        call WRITEDIAGFI(ngrid,'deltaq_th',
     1722!     &              'delta q thermiques','kg/kg',
     1723!     &                         3,ptimestep*pdq_th(:,:,2))
     1724!        endif
     1725!        endif
     1726
     1727        call WRITEDIAGFI(ngridmx,'lmax_th',
     1728     &              'hauteur du thermique','K',
     1729     &                         2,lmax_th_out)
     1730        call WRITEDIAGFI(ngridmx,'hfmax_th',
     1731     &              'maximum TH heat flux','K.m/s',
     1732     &                         2,hfmax_th)
     1733        call WRITEDIAGFI(ngridmx,'wmax_th',
     1734     &              'maximum TH vertical velocity','m/s',
     1735     &                         2,wmax_th)
     1736
     1737         endif
     1738
     1739c        ----------------------------------------------------------
     1740c        ----------------------------------------------------------
     1741c        END OF PBL OUTPUS
     1742c        ----------------------------------------------------------
     1743c        ----------------------------------------------------------
     1744
     1745
     1746c        ----------------------------------------------------------
    14391747c        Output in netcdf file "diagsoil.nc" for subterranean
    14401748c          variables (output every "ecritphy", as for writediagfi)
     
    14511759c        END OF WRITEDIAGFI
    14521760c        ==========================================================
     1761#endif
    14531762
    14541763      ELSE     ! if(ngrid.eq.1)
     
    14701779c        CALL writeg1d(ngrid,nlayer,pw,'w','m.s-1')
    14711780
     1781! THERMALS STUFF 1D
     1782
     1783         z_out=0.
     1784         if (calltherm .and. (z_out .gt. 0.)) then
     1785         call surflayer_interpol(ngrid,nlayer,z0,g,zzlay,zu,zv,wmax_th
     1786     &              ,tsurf,zh,z_out,Teta_out,u_out,ustar,tstar)
     1787
     1788         zu2(:)=sqrt(zu(:,1)*zu(:,1)+zv(:,1)*zv(:,1))
     1789         call WRITEDIAGFI(ngridmx,'sqrt(zu2)',
     1790     &              'horizontal velocity norm','m/s',
     1791     &                         0,zu2)
     1792
     1793         call WRITEDIAGFI(ngridmx,'Teta_out',
     1794     &              'potential temperature at z_out','K',
     1795     &                         0,Teta_out)
     1796         call WRITEDIAGFI(ngridmx,'u_out',
     1797     &              'horizontal velocity norm at z_out','m/s',
     1798     &                         0,u_out)
     1799         call WRITEDIAGFI(ngridmx,'u*',
     1800     &              'friction velocity','m/s',
     1801     &                         0,ustar)
     1802         call WRITEDIAGFI(ngridmx,'teta*',
     1803     &              'friction potential temperature','K',
     1804     &                         0,tstar)
     1805         else
     1806           if((.not. calltherm).and.(z_out .gt. 0.)) then
     1807            print*, 'WARNING : no interpolation in surface-layer :'
     1808            print*, 'Outputing surface-layer quantities without thermals
     1809     & does not make sense'
     1810           endif
     1811         endif
     1812
     1813         if(calltherm) then
     1814
     1815        call WRITEDIAGFI(ngridmx,'lmax_th',
     1816     &              'hauteur du thermique','point',
     1817     &                         0,lmax_th_out)
     1818        call WRITEDIAGFI(ngridmx,'hfmax_th',
     1819     &              'maximum TH heat flux','K.m/s',
     1820     &                         0,hfmax_th)
     1821        call WRITEDIAGFI(ngridmx,'wmax_th',
     1822     &              'maximum TH vertical velocity','m/s',
     1823     &                         0,wmax_th)
     1824
     1825         co2col(:)=0.
     1826         if (tracer) then
     1827         do l=1,nlayermx
     1828           do ig=1,ngrid
     1829             co2col(ig)=co2col(ig)+
     1830     &                  zq(ig,l,1)*(pplev(ig,l)-pplev(ig,l+1))/g
     1831         enddo
     1832         enddo
     1833
     1834         end if
     1835         call WRITEDIAGFI(ngrid,'co2col','integrated co2 mass'          &
     1836     &                                      ,'kg/m-2',0,co2col)
     1837         endif
     1838         call WRITEDIAGFI(ngrid,'w','vertical velocity'                 &
     1839     &                              ,'m/s',1,pw)
     1840         call WRITEDIAGFI(ngrid,"q2","q2","kg.m-3",1,q2)
     1841         call WRITEDIAGFI(ngrid,"tsurf","Surface temperature","K",0,
     1842     &                  tsurf)
     1843         call WRITEDIAGFI(ngrid,"u","u wind","m/s",1,zu)
     1844         call WRITEDIAGFI(ngrid,"v","v wind","m/s",1,zv)
     1845
     1846         call WRITEDIAGFI(ngrid,"pplay","Pressure","Pa",1,zplay)
     1847         call WRITEDIAGFI(ngrid,"pplev","Pressure","Pa",1,zplev)
    14721848! or output in diagfi.nc (for testphys1d)
    14731849         call WRITEDIAGFI(ngridmx,'ps','Surface pressure','Pa',0,ps)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new_storm/libf/phymars/STORM_JULIEN_LAST/aeropacity_tachemobile_z.F

    r609 r665  
    472472c--------------------------------------------------------------------
    473473
    474       justbackground=.false.
     474      justbackground=.false. !! default value
     475      write(*,*) "justbackground"
     476      call getin("justbackground",justbackground)
     477      write(*,*) "justbackground = ",justbackground
     478
    475479
    476480      IF (justbackground .eq. .true.)  THEN
     
    775779        DO l=1,nlayer
    776780          DO ig=1,ngrid
    777             dsodust(ig,l) = dsodust(ig,l) +
    778      &                      aerosol(ig,l,iaerdust(iaer)) * g /
    779      &                      (pplev(ig,l) - pplev(ig,l+1))
     781c            dsodust(ig,l) = dsodust(ig,l) +
     782c     &                      aerosol(ig,l,iaerdust(iaer)) * g /
     783c     &                      (pplev(ig,l) - pplev(ig,l+1))
     784            dsodust(ig,l) =
     785     &          (  0.75 * QREFvis3d(ig,l,iaer) /
     786     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
     787     &          pq(ig,l,igcm_dust_mass)
    780788          ENDDO
    781789        ENDDO
  • trunk/MESOSCALE_DEV/MANUAL/SRC/faq.tex

    r493 r665  
    195195%%% WPS PREP_MARS peuvent être liés entre e.g. pgf et mpi, ou ifort et mpifort
    196196
     197%%% BIG FILES declare -x WRFIO_NCD_LARGE_FILE_SUPPORT=1
     198
    197199\clearemptydoublepage
  • trunk/UTIL/PYTHON/planetoplot.py

    r647 r665  
    254254              elif axtime == "sol":   time = soltab
    255255          else:
     256              if ope in ["cat"] and nnn > 0:    count = time[-1] + 1  ## so that a cat is possible with simple subscripts
     257              else:                             count = 0
    256258              if "Times" in nc.dimensions:   time = count + np.arange(0,len(nc.dimensions["Times"]),1)
    257259              elif "Time" in nc.dimensions:  time = count + np.arange(0,len(nc.dimensions["Time"]),1)
    258260              else:                          time = count + np.arange(0,1,1)
    259               if ope in ["cat"]:
    260                  if nnn > 0:  count = time[-1] + 1  ## so that a cat is possible with simple subscripts
    261                  else:        count = 0
    262               else: count = 0
    263261          if axtime in ["lt"]:
    264262              ftime = np.zeros(len(time))
Note: See TracChangeset for help on using the changeset viewer.