Ignore:
Timestamp:
Jul 18, 2018, 4:48:34 PM (6 years ago)
Author:
mvals
Message:

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

Location:
trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars
Files:
2 added
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/datareadnc.F

    r1918 r1974  
    11c=======================================================================
    22      SUBROUTINE datareadnc(relief,phisinit,alb,ith,z0,
    3      &                    zmea,zstd,zsig,zgam,zthe)
     3     &                    zmea,zstd,zsig,zgam,zthe,
     4     &                    hmons,summit,zavg)
    45c=======================================================================
    56c
     
    4243c=======================================================================
    4344
    44       use ioipsl_getincom, only: getin
    45       USE comconst_mod, ONLY: g,pi
     45! to use  'getin'
     46      use ioipsl_getincom, only: getin
     47      use comconst_mod, only: g,pi
    4648      use datafile_mod, only: datadir
     49      use avg_horiz_mod, only: avg_horiz
     50      use mvc_horiz_mod, only: mvc_horiz
    4751
    4852      implicit none
     
    7478      REAL,intent(out) :: zgam(imdp1*jmdp1)
    7579      REAL,intent(out) :: zthe(imdp1*jmdp1)
    76 
     80      REAL,intent(out) :: hmons(imdp1*jmdp1) !CW17,361*180 hmons
     81      REAL,intent(out) :: summit(imdp1*jmdp1) !CW17,361*180 hmons
     82      REAL,intent(out) :: zavg(imdp1*jmdp1) !CW17,361*180 hmons
     83     
    7784! Local variables:
    7885      REAL        zdata(imd*jmdp1)
     
    95102
    96103      CHARACTER*20 string
    97       DIMENSION string(0:4)
     104      DIMENSION string(0:6)
    98105
    99106
     
    233240          call grid_noro1(360, 180, longitude, latitude, zdata,
    234241     .         iim, jjp1, rlonv, rlatu, zmea,zstd,zsig,zgam,zthe)
     242     
     243          !CW17
     244          call avg_horiz(imd,jmdp1,iim,jjm,longitude,
     245     .                latitude,rlonv,rlatu,zdata,pfield)
     246
     247          do j=1,jjp1 !CW17 49, iimp1=65, the last column = first column
     248             pfield(iimp1*j) =  pfield(1+iimp1*(j-1))
     249          enddo
     250          do i=1,iimp1*jjp1
     251c             if (pfield(i) .ne. -999999.) then
     252                zavg(i) = pfield(i)
     253c             else
     254c               zavg(i)=-999999.
     255c             endif
     256          enddo
    235257
    236258      endif
     
    297319c    FIN
    298320c-----------------------------------------------------------------------
    299 
     321 
     322c=======================================================================
     323c<<<<<<<<<<<<<<<<<<<<<<<add new dataset>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
     324      ! name of dataset
     325      string(5) = 'hmons' !subgrid hmons
     326c     the following data could be useful in future, but currently,
     327c     we don't need to put them into restartfi.nc
     328      string(6) = 'summit' !subgrid summit
     329c     string(7) = 'base'   !base of summit (not subgrid)
     330c     string(8) = 'bottom' !subgrid base
     331      do k=5,6
     332          write(*,*) 'string',k,string(k) 
     333c-----------------------------------------------------------------------
     334c    Lecture NetCDF 
     335c-----------------------------------------------------------------------
     336
     337          ierr = NF_INQ_VARID (unit, string(k), nvarid)
     338          if (ierr.ne.nf_noerr) then
     339            write(*,*) 'datareadnc error, cannot find ',trim(string(k))
     340            write(*,*) ' in file ',trim(datadir),'/surface.nc'
     341            stop
     342          endif
     343
     344c-----------------------------------------------------------------------
     345c    initialisation
     346c-----------------------------------------------------------------------
     347          call initial0(iimp1*jjp1,pfield)
     348          call initial0(imd*jmdp1,zdata)
     349          call initial0(imdp1*jmdp1,zdataS)
     350
     351#ifdef NC_DOUBLE
     352          ierr = NF_GET_VAR_DOUBLE(unit, nvarid, zdata)
     353#else
     354          ierr = NF_GET_VAR_REAL(unit, nvarid, zdata)
     355#endif
     356          if (ierr.ne.nf_noerr) then
     357            write(*,*) 'datareadnc: error failed loading ',
     358     .                  trim(string(k))
     359            stop
     360          endif
     361
     362c-----------------------------------------------------------------------
     363c   Passage de zdata en grille (imdp1 jmdp1)
     364c-----------------------------------------------------------------------
     365          do j=1,jmdp1     !  180
     366              do i=1,imd   !  360
     367                  !copy zdata to zdataS, line by line
     368                  !      i+ 361 *(j-1)          i+  360*(j-1)
     369                  zdataS(i+imdp1*(j-1)) = zdata(i+ngridmxgdat*(j-1))
     370              enddo
     371              ! the last column = the first column of zdata
     372              zdataS(imdp1+imdp1*(j-1)) = zdata(1+ngridmxgdat*(j-1))
     373          enddo
     374
     375          if (k .eq. 5 .or. k .eq. 6) then
     376              ! hmons, summit, keep the maximum of subgrids
     377              call mvc_horiz(imd,jmdp1,iim,jjm,longitude,
     378     .                latitude,rlonv,rlatu,zdata,pfield)
     379          endif
     380
     381
     382c-----------------------------------------------------------------------
     383c    Periodicite   
     384c-----------------------------------------------------------------------
     385
     386          do j=1,jjp1 ! 49, iimp1=65, the last column = first column
     387             pfield(iimp1*j) =  pfield(1+iimp1*(j-1))
     388          enddo
     389 
     390c-----------------------------------------------------------------------
     391c    Sauvegarde des champs   
     392c-----------------------------------------------------------------------
     393
     394          if (k.eq.5) then ! hmons
     395             do i=1,iimp1*jjp1
     396                  if (pfield(i) .ne. -999999.) then
     397                    hmons(i) = pfield(i)
     398                  else
     399                    hmons(i)=0.
     400                  endif
     401             enddo
     402          endif
     403         
     404          if (k.eq.6) then  ! summit
     405             do i=1,iimp1*jjp1
     406                    summit(i) = pfield(i)
     407             enddo
     408          endif
     409
     410      enddo
     411c<<<<<<<<<<<<<<<<<<<<<<<<<done add new dataset>>>>>>>>>>>>>>>>>>>>>>>>>>
     412c=======================================================================
    300413      END
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/newstart.F

    r1944 r1974  
    2727      use surfdat_h, only: phisfi, z0, zmea, zstd, zsig, zgam, zthe,
    2828     &                     albedodat, z0_default, qsurf, tsurf,
    29      &                     co2ice, emis
     29     &                     co2ice, emis, hmons
    3030      use comsoil_h, only: inertiedat, layer, mlayer, nsoilmx, tsoil
    3131      use control_mod, only: day_step, iphysiq, anneeref, planet_type
     
    9797      real zmeaS(iip1,jjp1),zstdS(iip1,jjp1)
    9898      real zsigS(iip1,jjp1),zgamS(iip1,jjp1),ztheS(iip1,jjp1)
     99      real hmonsS(iip1,jjp1)
     100      real summitS(iip1,jjp1)
     101      real zavgS(iip1,jjp1)
    99102      real z0S(iip1,jjp1)
    100103
     
    380383
    381384      CALL datareadnc(relief,phis,alb,surfith,z0S,
    382      &          zmeaS,zstdS,zsigS,zgamS,ztheS)
     385     &          zmeaS,zstdS,zsigS,zgamS,ztheS,
     386     &          hmonsS,summitS,zavgS)
    383387
    384388      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,phis,phisfi)
     
    392396      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,zgamS,zgam)
    393397      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,ztheS,zthe)
     398      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,hmonsS,hmons)
     399!      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,summitS,summit)
     400!      CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,zavgS,zavg)
    394401
    395402      endif ! of if (choix_1.ne.1)
     
    16421649      call physdem0("restartfi.nc",lonfi,latfi,nsoilmx,ngridmx,llm,
    16431650     .              nqtot,dtphys,real(day_ini),0.0,
    1644      .              airefi,albfi,ithfi,zmea,zstd,zsig,zgam,zthe)
     1651     .              airefi,albfi,ithfi,zmea,zstd,zsig,zgam,zthe,
     1652     .              hmons)
    16451653      call physdem1("restartfi.nc",nsoilmx,ngridmx,llm,nqtot,
    16461654     &              dtphys,hour_ini,
Note: See TracChangeset for help on using the changeset viewer.