Ignore:
Timestamp:
Sep 5, 2012, 5:12:50 PM (12 years ago)
Author:
acolaitis
Message:

LES. Reorganized mode 3. dust_profile is now read by ideal.exe and stored in mars_qdust and mars_qndust. Added -mcmodel for large executable in the debug options of makegcm.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r766 r772  
    4141        MARS_Z0, &
    4242        CST_Z0, &
     43        MARS_QDUST, &
     44        MARS_QNDUST, &
    4345#endif
    4446        MARS_GW, &
     
    6971   USE module_model_constants
    7072   USE module_wrf_error
    71    USE module_init_utilities
    7273! add new modules here, if needed ...
    7374
     
    145146REAL, DIMENSION( ims:ime, jms:jme ), INTENT(INOUT   )  :: &
    146147     MARS_FLUXRAD,MARS_WSTAR
     148REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(IN   )  :: &
     149     MARS_QDUST, MARS_QNDUST
    147150#endif
    148151REAL, DIMENSION( ims:ime, 5, jms:jme ), INTENT(IN   )  :: &
     
    189192   INTEGER :: lctindex,ziindex
    190193   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
    197194   ! *** ----------------------- ***
    198195
     
    871868!--------------------------------!
    872869#ifdef NEWPHYS
     870!!! Initialize SCALAR for MODE 3.
     871IF ((MARS_MODE .EQ. 3) .and. (firstcall .EQV. .true.) .and. (.not. restart)) THEN
     872     SCALAR(i,kps:kpe,j,2)=MARS_QDUST(i,kps:kpe,j)
     873     SCALAR(i,kps:kpe,j,3)=MARS_QNDUST(i,kps:kpe,j)
     874ENDIF
    873875IF (MARS_MODE .EQ. 0) THEN
    874876    q_prof(:,1)=0.95
     
    884886      q_prof(:,:) = 0.95
    885887   ENDIF
    886   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!
    898888  ENDIF
    899889#else
     
    17171707!!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    17181708
    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 
    17501709END MODULE module_lmd_driver
Note: See TracChangeset for help on using the changeset viewer.