Ignore:
Timestamp:
Feb 20, 2011, 12:20:51 PM (14 years ago)
Author:
aslmd
Message:

LMD_MM_MARS: corrections cycle de l'eau propagees a la nouvelle physique. + corrections readmeteo.F90 [version synchronisee precedemment n etait pas la plus a jour] + corrections api.F90 pour avoir cp, R comme GCM

Location:
trunk/mesoscale/LMD_MM_MARS/SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/mesoscale/LMD_MM_MARS/SRC/POSTPROC/api.F90

    r19 r73  
    4848      ! MARS CONSTANTS
    4949      !
    50       REAL, PARAMETER :: Rd  = 192.     ! gas constant m2 s-2 K-1
    51       REAL, PARAMETER :: Cp  = 844.6    ! r= 8.314511E+0*1000.E+0/mugaz
    52 !REAL, PARAMETER :: Rd  = 191.0
    53 !REAL, PARAMETER :: Cp  = 744.5
     50      !REAL, PARAMETER :: Rd  = 192.     ! gas constant m2 s-2 K-1
     51      !REAL, PARAMETER :: Cp  = 844.6    ! r= 8.314511E+0*1000.E+0/mugaz
     52      REAL, PARAMETER :: Rd  = 191.0
     53      REAL, PARAMETER :: Cp  = 744.5
    5454      REAL, PARAMETER :: RCP = Rd/Cp
    5555      REAL, PARAMETER :: p0  = 610.
  • trunk/mesoscale/LMD_MM_MARS/SRC/PREP_MARS/readmeteo.F90

    r72 r73  
    7474!! Intermediate data arrays
    7575integer :: k,l,m,n,p
    76 real, dimension(:), allocatable :: lat,lon,time,alt,aps,bps,levels,dsoilvert
     76real, dimension(:), allocatable :: lat,lon,time,alt,aps,bps,levels,vertdsoil
    7777real, dimension(:,:), allocatable :: vide,ones,ghtsfile
    7878real, dimension(:,:), allocatable :: interm
     
    207207allocate(dsoilfile(lonlen,latlen,altlen,timelen))
    208208allocate(isoilfile(lonlen,latlen,altlen,timelen))
    209 allocate(dsoilvert(altlen))
     209allocate(vertdsoil(altlen))
    210210!allocate(tfileorig(lonlen,latlen,altlen,timelen))
    211211allocate(ufile(lonlen,latlen,altlen,timelen))
     
    240240isoilfile(:,:,:,:)=0
    241241dsoilfile(:,:,:,:)=0
    242 dsoilvert(:)=0.
     242vertdsoil(:)=0.
    243243!tfileorig(:,:,:,:)=0
    244244!ufileorig(:,:,:,:)=0
     
    591591
    592592    print *,'Surface Water ice'
    593     ierr=NF_INQ_VARID(nid,"qsurf01",nvarid)
     593!!!!!! ATTENTION ATTENTION
     594!!!!!! water ice a la surface est qsurf(ig,nqmx)
     595    ierr=NF_INQ_VARID(nid,"qsurf02",nvarid)
    594596    if (ierr.ne.NF_NOERR) then
    595       write(*,*) "...No qsurf01 - surface Water ice set to 0"
     597      write(*,*) "...No qsurf02 - surface Water ice set to 0"
    596598      swatericefile(:,:,:)=0.
    597599    else
     
    648650        write(*,*) "...No soildepth - Set to -999"  !!! see soil_settings in LMD physics
    649651        DO l=1,altlen
    650                 dsoilvert(l)=-999.
     652                vertdsoil(l)=-999.
    651653        ENDDO
    652654    else
    653         ierr=NF_GET_VAR_REAL(nid,nvarid,dsoilvert)
     655        ierr=NF_GET_VAR_REAL(nid,nvarid,vertdsoil)
    654656    endif
    655657    print *, 'wait a minute' !! AS: I know this could be better
     
    657659     DO n=1,latlen
    658660      DO p=1,timelen
    659        dsoilfile(m,n,:,p) = dsoilvert(:)
     661       dsoilfile(m,n,:,p) = vertdsoil(:)
    660662      ENDDO
    661663     ENDDO
     
    10501052!------------------------!
    10511053FIELD='SM100200'
    1052 UNITS='kg/kg'
     1054UNITS='kg/m2'
    10531055DESC='Surf water ice'
    10541056XLVL=200100.
     
    14701472deallocate(isoilfile)
    14711473deallocate(dsoilfile)
    1472 !deallocate(dsoilvert)
    14731474!deallocate(tfileorig)
    14741475deallocate(ufile)
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/mars_lmd/libf/phymars/meso_physiq.F

    r72 r73  
    13211321       
    13221322      IF (tracer.AND.water.AND.ngridmx.NE.1) THEN
    1323          if (caps.and.(obliquit.lt.27.)) then
    1324            tsurf(ngrid)=1/(1/136.27-r/5.9e+5*alog(0.0095*ps(ngrid)))
    1325          endif
     1323         !if (caps.and.(obliquit.lt.27.)) then
     1324         !  tsurf(ngrid)=1/(1/136.27-r/5.9e+5*alog(0.0095*ps(ngrid)))
     1325         !endif
     1326!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1327!!!!! note WRF MESOSCALE AYMERIC -- mot cle "caps"
     1328!!!!! watercaptag n'est plus utilise que dans vdifc
     1329!!!!! ... pour que la sublimation ne soit pas stoppee
     1330!!!!! ... dans la calotte permanente nord si qsurf=0
     1331!!!!! on desire garder cet effet regle par caps=T
     1332!!!!! on a donc commente "if (caps.and.(obliquit.lt.27.))" ci-dessus
     1333!!!!! --- remplacer ces lignes par qqch de plus approprie
     1334!!!!!      si on s attaque a la calotte polaire sud
     1335!!!!! pas d'autre occurrence majeure du mot-cle "caps"
     1336!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1337
    13261338c       -------------------------------------------------------------
    13271339c       Change of surface albedo (set to 0.4) in case of ground frost
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r72 r73  
    154154!-------------------------------------------
    155155   INTEGER ::    i,j,k,its,ite,jts,jte,ij
    156    INTEGER ::    subs
     156   INTEGER ::    subs,iii
    157157
    158158   ! *** for LMD physics
     
    623623    CASE(0)  !! NO TRACERS (mars=0)
    624624      wtnom(nq) = 'co2'
     625    CASE(1)
     626      wtnom(1) = 'h2o_vap' 
     627      wtnom(2) = 'h2o_ice'
     628    CASE(2)
     629      wtnom(1) = 'dust'     
    625630    CASE(11) !! newwater mars==11 scalar:qh2o,qh2o_ice,qdust,qdust_number,qco2
    626631      wtnom(nq) = 'co2'
     
    665670#ifdef NEWPHYS
    666671q_prof(:,1:nq) = SCALAR(i,kps:kpe,j,2:nq+1)  !! the names were set above !! one dummy tracer in WRF
    667 q_prof(:,nq) = 0.95 !! cas du CO2 !! TEMPORAIRE
     672  !!! CAS DU CO2
     673  DO iii=1,nq
     674   IF ( wtnom(iii) .eq. 'co2' ) q_prof(:,iii) = 0.95
     675  ENDDO
    668676#else
    669677SELECT CASE (MARS_MODE)
     
    790798! Tracer at surface !
    791799!-------------------!
    792 #ifdef NEWPHYS
    793   !!! a faire !!!
    794   PRINT *, 'WARNING WARNING no tracer at surface'
    795   qsurf_val(:)=0.
    796 #else
    797800SELECT CASE (MARS_MODE)
    798801    CASE(0)  !! NO TRACERS (mars=0)
    799802    qsurf_val(:)=0.
    800803    CASE(1)  !! WATER CYCLE (mars=1)
     804#ifdef NEWPHYS   
     805    qsurf_val(2)=MARS_WICE(i,j)    !! logique avec wtnom(2) = 'h2o_ice' defini ci-dessus
     806    qsurf_val(1)=0.
     807#else
    801808    qsurf_val(2)=MARS_WICE(i,j)    !! attention... H2O ice is tracer nqmx in qsurf in LMD physics
    802     qsurf_val(1)=0.               
     809    qsurf_val(1)=0.
     810#endif   
    803811    CASE(2)  !! DUST CYCLE (mars=2)
    804812    qsurf_val(:)=0.
     813#ifdef NEWPHYS
     814    CASE(11)
     815    qsurf_val(:)=0. !! provisoire       
     816#endif
    805817END SELECT
    806 #endif
    807818
    808819!-------------------!
Note: See TracChangeset for help on using the changeset viewer.