Ignore:
Timestamp:
Aug 31, 2012, 3:22:47 PM (12 years ago)
Author:
acolaitis
Message:

LES. Added mars mode 3 (active dust with dust_mass and dust_number) and rectified pd_scalar default state.

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/LES/modif_mars/Registry.EM

    r674 r766  
    14001400rconfig   logical     pd_moist_dfi        namelist,dynamics     max_domains    .false.  rh    "pd_moist_dfi"    "positive-definite RK3 transport switch"      ""
    14011401rconfig   logical     pd_chem             namelist,dynamics     max_domains    .false. rh    "pd_chem"          "positive-definite RK3 transport switch"      ""
    1402 rconfig   logical     pd_scalar           namelist,dynamics     max_domains    .false. rh    "pd_scalar"        "positive-definite RK3 transport switch"      ""
     1402rconfig   logical     pd_scalar           namelist,dynamics     max_domains    .true. rh    "pd_scalar"        "positive-definite RK3 transport switch"      ""
    14031403rconfig   logical     pd_tke              namelist,dynamics     max_domains    .false. rh    "pd_tke"           "positive-definite RK3 transport switch"      ""
    14041404rconfig   logical top_radiation           namelist,dynamics     max_domains    .false. rh    "top_radiation"         ""      ""
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r700 r766  
    6969   USE module_model_constants
    7070   USE module_wrf_error
     71   USE module_init_utilities
    7172! add new modules here, if needed ...
    7273
     
    188189   INTEGER :: lctindex,ziindex
    189190   LOGICAL :: end_of_file
     191   ! *** ----------------------- ***
     192
     193   ! *** for Mars Mode 3         ***
     194   INTEGER nm3
     195   PARAMETER(nm3=1000)
     196   REAL, DIMENSION(nm3) :: qdust,qndust,dust_p_level
    190197   ! *** ----------------------- ***
    191198
     
    878885   ENDIF
    879886  ENDIF
     887  !!! DUST AND DUSTN
     888  IF (MARS_MODE .EQ. 3 .and. firstcall .EQV. .true. .and. (.not. restart)) THEN
     889      call read_dust(qdust,qndust,dust_p_level,nm3)
     890      if (dust_p_level(1) .lt. p_prof(1)) then !input profile needs rescaling to avoid a plateau. This happens when you use different sources to initialize the pressure of the LES and the input_dust. Typicaly: you use the MCD for input_therm and different runs for input_dust, that dont have the same surface pressure ! This trick is ok because we dont want to initialize with a very precise profile of dust, just a realistic one.
     891         dust_p_level = dust_p_level * p_prof(1)/dust_p_level(1)         
     892      endif
     893      DO k=1, nlayer
     894        q_prof(k,1) = interp_0(qdust, dust_p_level, p_prof(k), nm3)
     895        q_prof(k,2) = interp_0(qndust, dust_p_level, p_prof(k), nm3)
     896      ENDDO
     897      SCALAR(i,kps:kpe,j,2:3)=q_prof(:,:)  ! because we need to initialize the value of scalar!
     898  ENDIF
    880899#else
    881900SELECT CASE (MARS_MODE)
     
    10571076#ifdef NEWPHYS
    10581077    CASE(3)
    1059     qsurf_val(:)=0.                !!! temporaire, a definir           
     1078    qsurf_val(1)=q_prof(1,1)                !!! temporaire, a definir       
     1079    qsurf_val(2)=q_prof(1,2)     
    10601080    CASE(11)
    10611081    qsurf_val(1)=0.
     
    16971717!!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    16981718
     1719
     1720!!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     1721      subroutine read_dust(qdust,qndust,dust_p_level,n)
     1722      implicit none
     1723      integer n
     1724      real qdust(n),qndust(n),dust_p_level(n)
     1725      logical end_of_file
     1726
     1727      integer k
     1728
     1729! first element is the surface
     1730
     1731      open(unit=11,file='input_dust',form='formatted',status='old')
     1732      rewind(11)
     1733      end_of_file = .false.
     1734      k = 0
     1735      do while (.not. end_of_file)
     1736
     1737        read(11,*,end=102) qdust(k+1), qndust(k+1), dust_p_level(k+1)
     1738        write(*,*) k, qdust(k+1), qndust(k+1), dust_p_level(k+1)
     1739        k = k+1
     1740        go to 113
     1741 102    end_of_file = .true.
     1742 113    continue
     1743      enddo
     1744
     1745      close(unit=11,status = 'keep')
     1746
     1747      end subroutine read_dust
     1748!!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     1749
    16991750END MODULE module_lmd_driver
Note: See TracChangeset for help on using the changeset viewer.