Changeset 1038 for trunk


Ignore:
Timestamp:
Sep 13, 2013, 4:01:10 PM (11 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
Files:
22 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1036 r1038  
    19151915- Checked that changes are clean and that GCM yields identical results (in
    19161916  debug mode) to previous svn version.
     1917
     1918== 13/09/2013 == AS
     1919- Performed the necessary modifications for dynamic tracers
     1920  to work with the mesoscale model
     1921- Added precompiling flag MESOSCALE around pressure modifications
     1922  done in revision 883. This makes the mesoscale model become crazy.
  • 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)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_inifis1.inc

    r315 r1038  
    66
    77       CALL inifis(ngridmx,nlayer,         &
     8#ifdef NEWPHYS
     9               nq,  &
     10#endif
    811               wday_ini,wdaysec,                &
    912               wappel_phys,                     &
    1013               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    11                nqmx,dt,                                                &
     14#ifdef NEWPHYS
     15               dt,                                                     &
     16#else
     17               nq,dt,                                                &
     18#endif
    1219               womeg,wmugaz,                                           &
    1320               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_inifis2.inc

    r315 r1038  
    99       CASE(1)
    1010       CALL inifis(ngridmx,nlayer, &
     11#ifdef NEWPHYS
     12               nq,  &
     13#endif
    1114               wday_ini,wdaysec,                &
    1215               wappel_phys,                     &
    1316               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    14                nqmx,dt,                                                &
     17#ifdef NEWPHYS
     18               dt,                                                     &
     19#else
     20               nq,dt,                                                &
     21#endif
    1522               womeg,wmugaz,                                           &
    1623               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    2936       CASE(2)
    3037       CALL d2_inifis(ngridmx,nlayer, &
     38#ifdef NEWPHYS
     39               nq,  &
     40#endif
    3141               wday_ini,wdaysec,                   &
    3242               wappel_phys,                        &
    3343               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    34                nqmx,dt,                                                &
     44#ifdef NEWPHYS
     45               dt,                                                     &
     46#else
     47               nq,dt,                                                &
     48#endif
    3549               womeg,wmugaz,                                           &
    3650               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_inifis3.inc

    r315 r1038  
    99       CASE(1)
    1010       CALL inifis(ngridmx,nlayer, &
     11#ifdef NEWPHYS
     12               nq,  &
     13#endif
    1114               wday_ini,wdaysec,                &
    1215               wappel_phys,                     &
    1316               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    14                nqmx,dt,                                                &
     17#ifdef NEWPHYS
     18               dt,                                                     &
     19#else
     20               nq,dt,                                                &
     21#endif
    1522               womeg,wmugaz,                                           &
    1623               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    2835       CASE(2)
    2936       CALL d2_inifis(ngridmx,nlayer, &
     37#ifdef NEWPHYS
     38               nq,  &
     39#endif
    3040               wday_ini,wdaysec,                   &
    3141               wappel_phys,                        &
    3242               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    33                nqmx,dt,                                                &
     43#ifdef NEWPHYS
     44               dt,                                                     &
     45#else
     46               nq,dt,                                                &
     47#endif
    3448               womeg,wmugaz,                                           &
    3549               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    4761       CASE(3)
    4862       CALL d3_inifis(ngridmx,nlayer, &
     63#ifdef NEWPHYS
     64               nq,  &
     65#endif
    4966               wday_ini,wdaysec,                   &
    5067               wappel_phys,                        &
    5168               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    52                nqmx,dt,                                                &
     69#ifdef NEWPHYS
     70               dt,                                                     &
     71#else
     72               nq,dt,                                                &
     73#endif
    5374               womeg,wmugaz,                                           &
    5475               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_inifis4.inc

    r426 r1038  
    99       CASE(1)
    1010       CALL inifis(ngridmx,nlayer, &
     11#ifdef NEWPHYS
     12               nq,  &
     13#endif
    1114               wday_ini,wdaysec,                &
    1215               wappel_phys,                     &
    1316               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    14                nqmx,dt,                                                &
     17#ifdef NEWPHYS
     18               dt,                                                     &
     19#else
     20               nq,dt,                                                &
     21#endif
    1522               womeg,wmugaz,                                           &
    1623               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    2835       CASE(2)
    2936       CALL d2_inifis(ngridmx,nlayer, &
     37#ifdef NEWPHYS
     38               nq,  &
     39#endif
    3040               wday_ini,wdaysec,                   &
    3141               wappel_phys,                        &
    3242               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    33                nqmx,dt,                                                &
     43#ifdef NEWPHYS
     44               dt,                                                     &
     45#else
     46               nq,dt,                                                &
     47#endif
    3448               womeg,wmugaz,                                           &
    3549               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    4761       CASE(3)
    4862       CALL d3_inifis(ngridmx,nlayer, &
     63#ifdef NEWPHYS
     64               nq,  &
     65#endif
    4966               wday_ini,wdaysec,                   &
    5067               wappel_phys,                        &
    5168               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    52                nqmx,dt,                                                &
     69#ifdef NEWPHYS
     70               dt,                                                     &
     71#else
     72               nq,dt,                                                &
     73#endif
    5374               womeg,wmugaz,                                           &
    5475               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
     
    6687       CASE(4)
    6788       CALL d4_inifis(ngridmx,nlayer, &
     89#ifdef NEWPHYS
     90               nq,  &
     91#endif
    6892               wday_ini,wdaysec,                   &
    6993               wappel_phys,                        &
    7094               lat_vec,lon_vec,aire_vec,1/reradius,g,r_d,cp,           &
    71                nqmx,dt,                                                &
     95#ifdef NEWPHYS
     96               dt,                                                     &
     97#else
     98               nq,dt,                                                &
     99#endif
    72100               womeg,wmugaz,                                           &
    73101               wyear_day,wperiheli,waphelie,wperi_day,wobliquit,       &
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm

    r69 r1038  
    514514# Build the appropriate 'dimensions.h' file
    515515cd dimension
    516 makdim $ntrac $dim
     516makdim $dim
    517517# echo contents of dimensions.h to standard output
    518518cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm.last

    r69 r1038  
    518518# Build the appropriate 'dimensions.h' file
    519519cd dimension
    520 makdim $ntrac $dim
     520makdim $dim
    521521# echo contents of dimensions.h to standard output
    522522cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_g95

    r330 r1038  
    531531# Build the appropriate 'dimensions.h' file
    532532cd dimension
    533 ./makdim $ntrac $dim
     533./makdim $dim
    534534# echo contents of dimensions.h to standard output
    535535cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_g95.last

    r69 r1038  
    517517# Build the appropriate 'dimensions.h' file
    518518cd dimension
    519 makdim $ntrac $dim
     519makdim $dim
    520520# echo contents of dimensions.h to standard output
    521521cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_ifort

    r86 r1038  
    519519# Build the appropriate 'dimensions.h' file
    520520cd dimension
    521 ./makdim $ntrac $dim
     521./makdim $dim
    522522# echo contents of dimensions.h to standard output
    523523cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_mpi

    r86 r1038  
    531531# Build the appropriate 'dimensions.h' file
    532532cd dimension
    533 makdim $ntrac $dim
     533makdim $dim
    534534# echo contents of dimensions.h to standard output
    535535cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_mpifort

    r772 r1038  
    519519# Build the appropriate 'dimensions.h' file
    520520cd dimension
    521 ./makdim $ntrac $dim
     521./makdim $dim
    522522# echo contents of dimensions.h to standard output
    523523cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/mars_lmd_new/makegcm_pgf

    r335 r1038  
    523523# Build the appropriate 'dimensions.h' file
    524524cd dimension
    525 makdim $ntrac $dim
     525makdim $dim
    526526# echo contents of dimensions.h to standard output
    527527cat $libf/grid/dimensions.h
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r802 r1038  
    192192   ! *** for LMD physics
    193193   ! ------> inputs:
    194    INTEGER :: ngrid,nlayer,nq,nsoil,nqmx
     194   INTEGER :: ngrid,nlayer,nq,nsoil
    195195   REAL :: pday,ptime,MY 
    196196   REAL :: aire_val,lat_val,lon_val
     
    391391nlayer = kpe-kps+1                    ! number of vertical layers: nlayermx
    392392nsoil = NUM_SOIL_LAYERS               ! number of soil layers: nsoilmx
    393 if (num_3d_s > 1) then                ! number of advected fields: nqmx
     393if (num_3d_s > 1) then                ! number of advected fields
    394394        nq = num_3d_s-1               
    395         nqmx = num_3d_s-1
    396395else
    397396        nq = 1
    398         nqmx = 1
    399397endif
    400398! **** needed but hardcoded
     
    10521050    qsurf_val(2)=MARS_WICE(i,j)    !! logique avec wtnom(2) = 'h2o_ice' defini ci-dessus
    10531051                                   !! ----- retrocompatible ancienne physique
    1054                                    !! ----- [H2O ice is tracer nqmx in qsurf in LMD physics]
     1052                                   !! ----- [H2O ice is last tracer in qsurf in LMD physics]
    10551053    CASE(2) 
    10561054    qsurf_val(1)=0.                !! not coupled with lifting for the moment [non remobilise]
  • trunk/MESOSCALE/LMD_MM_MARS/makemeso

    r856 r1038  
    3535phys=""
    3636scenario=""
    37 while getopts "drc:njhgpfs:x" options; do
     37from_scratch=0
     38while getopts "drc:njhgpfs:xe" options; do
    3839  case $options in
    3940   d ) donotcompile=1;;       ## just to check the compile folder
     
    4546   p ) phys="newphys_";;      ## with new physics
    4647   f ) fresh_start=1;;        ## a fresh start
     48   e ) from_scratch=1;;       ## a fresh start with a completely new folder
    4749   s ) scenario="${OPTARG}";; ## a specific scenario, you need a corresponding "mars_lmd_..."
    4850   x ) donotcompile=1;phys="nophys_";donotcompilephys=1;; ## a case with no LMD physics included
     
    7274#
    7375# makemeso -f                ## fresh start [clean -a]
     76#
     77# makemeso -e                ## a completely new recompile with erasing ALL compiling folder
    7478#
    7579# makemeso -s storm          ## a specific scenario, you need a corresponding mars_lmd_... (only for newphys)
     
    169173            fi
    170174         else
    171             echo Number of tracers ? ; read tra
    172             if [ ${tra} -eq 0 ]
    173             then
    174               tra=1     
     175            echo Number of tracers ? ; read tra
     176            # tracers: no dynamically set in newphys 09/2013
     177            if [[ "${phys}" == "newphys_" ]]
     178            then
     179              tra=999
     180            else
     181              if [ ${tra} -eq 0 ]
     182              then
     183                tra=1   
     184              fi
    175185            fi
     186            # scatterers: a specific stuff for newphys
    176187            if [[ "${phys}" == "newphys_" ]]
    177188            then
     
    181192            fi
    182193         fi
     194  # 'from scratch' case
     195  if [ ${from_scratch} -eq 1 ]
     196  then
     197      echo "***** I ERASE THE FOLDER "${conf_wrf}
     198      \rm -rf ${conf_wrf}
     199  fi
    183200  # folder
    184201  mkdir ${conf_wrf} 2> /dev/null
     
    684701  mkdir temp
    685702  #cp -f LINUXfastI._${physz}_t${tra}_reg/*.a temp
    686   cp -f LINUX*/*.a temp
     703  cp -f LINUX*/*.a temp/
    687704  cd temp
    688705  ar x libbibio.a
Note: See TracChangeset for help on using the changeset viewer.