Changeset 1038 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Sep 13, 2013, 4:01:10 PM (12 years ago)
Author:
aslmd
Message:

MESOSCALE
LMDZ.MARS

--> Performed the necessary modifications for dynamic tracers

to work with the mesoscale model (new physics).

--> Added precompiling flag MESOSCALE around pressure modifications

done in revision 883. This makes the mesoscale model become crazy.

--> Added an option -e in makemeso to erase a configuration and start over.

NOTE
--> not sure recent versions (rev>1000) are compliant with nesting compilation.
--> use mesoscale model + new physics with caution. still not stabilized.

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
7 edited

Legend:

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

    r1036 r1038  
    33     $                  dqslift)
    44
     5#ifndef MESOSCALE
    56      use tracer_mod, only: alpha_lift, radius
     7#else
     8      use tracer_mod, only: alpha_lift, radius,
     9     &                      igcm_dust_mass, igcm_dust_number,
     10     &                      ref_r0,r3n_q
     11#endif
    612      IMPLICIT NONE
    713
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r1036 r1038  
    11      SUBROUTINE initracer(ngrid,nq,qsurf,co2ice)
    22
     3#ifndef MESOSCALE
    34       use infotrac, only: tnom
     5#endif
    46       use tracer_mod
    57       IMPLICIT NONE
     
    6163
    6264! Initialization: allocate arrays in tracer_mod
    63       allocate(noms(nq))
    6465      allocate(mmol(nq))
    6566      allocate(radius(nq))
     
    7071      allocate(igcm_dustbin(nq))
    7172
     73#ifndef MESOSCALE
     74      allocate(noms(nq))
    7275! Initialization: get tracer names from the dynamics and check if we are
    7376!                 using 'old' tracer convention ('q01',q02',...)
     
    9497        noms(iq)=tnom(iq)
    9598      enddo
     99#endif
    96100
    97101c------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_ini.F

    r315 r1038  
    3939
    4040            !!!!!!!!!!!!!!!!! DONE in soil_setting.F
    41       tnom(:)=wtnom(:)   !! est rempli dans advtrac.h
    42       PRINT*,'check: tracernames ', tnom
     41      PRINT*,'MESOSCALE. how many tracers: ',nq
     42      allocate(noms(nq)) !! est fait dans initracer normalement
     43      noms(:)=wtnom(:)   !! est rempli dans tracer_mod.F90
     44      PRINT*,'check: tracernames ', noms
    4345     !!!new physics
    4446     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    4850      PRINT*,'check: q2 ',q2(1,1),q2(ngridmx,nlayermx+1)
    4951      qsurf(:,:)=wqsurf(:,:)
    50       PRINT*,'check: qsurf ',qsurf(1,1),qsurf(ngridmx,nqmx)
     52      PRINT*,'check: qsurf ',qsurf(1,1),qsurf(ngridmx,nq)
    5153      co2ice(:)=wco2ice(:)
    5254      PRINT*,'check: co2 ',co2ice(1),co2ice(ngridmx)
     
    6264      iphysiq=ptimestep
    6365c
    64       !DO iq=1, nq
    65       !  PRINT*, tnom(iq), pq(:,:,iq)
    66       !ENDDO
    6766
    6867c
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_inifisinvar.F

    r315 r1038  
    1      $           ,nq,wdt
     1     $           ,wdt
    22     $           ,womeg,wmugaz
    33     $           ,wyear_day,wperiheli,waphelie,wperi_day,wobliquit
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_inifisvar.F

    r315 r1038  
    1       INTEGER nq
    21      REAL wdt
    32
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_var.F

    r708 r1038  
    66      REAL wco2ice(ngridmx)
    77      REAL wemis(ngridmx)
    8       REAL wqsurf(ngridmx,nqmx)
     8      REAL wqsurf(ngridmx,nq)
    99      REAL wq2(ngridmx,nlayermx+1)
    1010      REAL wwstar(ngridmx)
     
    1919      integer iloop
    2020      INTEGER tracerset    !!! this corresponds to config%mars
    21       CHARACTER (len=20) :: wtnom(nqmx) ! tracer name
     21      CHARACTER (len=20) :: wtnom(nq) ! tracer name
    2222
    2323      !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! JF
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1036 r1038  
    1818     &                      nuice_ref, rho_ice, rho_dust, ref_r0
    1919
    20 #ifdef MESOSCALE
    21       use infotrac !!! this is necessary for tracers
    22 #endif
    2320      IMPLICIT NONE
    2421c=======================================================================
     
    372369      REAL, ALLOCATABLE, DIMENSION(:,:) :: T_out
    373370      REAL, ALLOCATABLE, DIMENSION(:,:) :: u_out ! Interpolated teta and u at z_out
    374 !      REAL u_out1(ngridmx)
     371      REAL u_out1(ngridmx)
    375372      REAL T_out1(ngridmx)
    376373      REAL, ALLOCATABLE, DIMENSION(:) :: z_out     ! height of interpolation between z0 and z1 [meters]
     
    10361033         ENDIF ! of IF (tracer)
    10371034
     1035#ifndef MESOSCALE
    10381036        ! update surface pressure
    10391037        DO ig=1,ngrid
     
    10581056          ENDDO
    10591057        ENDDO
     1058#endif
    10601059     
    10611060      ENDIF  ! of IF (callcond)
Note: See TracChangeset for help on using the changeset viewer.