Changeset 1697 for LMDZ5


Ignore:
Timestamp:
Dec 19, 2012, 5:57:23 PM (12 years ago)
Author:
lguez
Message:

Created new variable vert_prof_dissip to choose the vertical profile
of horizontal dissipation. vert_prof_dissip is an integer, allowed
values are 0 and 1. Did not make it a logical variable because we
expect to have the choice between more than 2 profiles later, when we
converge with extra-terrestrial versions of LMDZ. Replaced test on
ok_strato and llm in inidissip by test on vert_prof_dissip.

Merged some lines of dyn3d/conf_gcm.F and dyn3dpar/conf_gcm.F (we want
as little difference as possible between dyn3d and dyn3dpar).

Checked that the sequential configuration does not change results for
the bench of "install.sh".

Location:
LMDZ5/trunk/libf
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/comdissnew.h

    r1319 r1697  
    1212
    1313      COMMON/comdissnew/ lstardis,nitergdiv,nitergrot,niterh,tetagdiv,  &
    14      &                   tetagrot,tetatemp,coefdis 
     14     &                   tetagrot,tetatemp,coefdis, vert_prof_dissip
    1515
    1616      LOGICAL lstardis
    1717      INTEGER nitergdiv, nitergrot, niterh
     18
     19      integer vert_prof_dissip ! vertical profile of horizontal dissipation
     20!     Allowed values:
     21!     0: fractional function of pressure
     22!     1: tanh of altitude
     23
    1824      REAL     tetagdiv, tetagrot,  tetatemp, coefdis
    1925
  • LMDZ5/trunk/libf/dyn3d/conf_gcm.F

    r1577 r1697  
    1414#endif
    1515      USE infotrac, ONLY : type_trac
     16      use assert_m, only: assert
     17
    1618      IMPLICIT NONE
    1719c-----------------------------------------------------------------------
     
    9395      CALL getin('lunout', lunout)
    9496      IF (lunout /= 5 .and. lunout /= 6) THEN
    95         OPEN(lunout,FILE='lmdz.out')
     97        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',
     98     &          STATUS='unknown',FORM='formatted')
    9699      ENDIF
    97100
     
    173176
    174177!Config  Key  = nsplit_phys
    175 !Config  Desc = nombre de pas par jour
    176 !Config  Def  = 1
    177 !Config  Help = nombre de pas par jour (multiple de iperiod) (
    178 !Config          ici pour  dt = 1 min )
    179178       nsplit_phys = 1
    180179       CALL getin('nsplit_phys',nsplit_phys)
     
    625624      CALL getin('ok_dyn_ave',ok_dyn_ave)
    626625
    627 
    628626      write(lunout,*)' #########################################'
    629627      write(lunout,*)' Configuration des parametres du gcm: '
     
    635633      write(lunout,*)' day_step = ', day_step
    636634      write(lunout,*)' iperiod = ', iperiod
     635      write(lunout,*)' nsplit_phys = ', nsplit_phys
    637636      write(lunout,*)' iconser = ', iconser
    638637      write(lunout,*)' iecri = ', iecri
     
    805804!Config  Desc = sortie des transports zonaux dans la dynamique
    806805!Config  Def  = n
    807 !Config  Help =
     806!Config  Help = Permet de mettre en route le calcul des transports
    808807!Config         
    809        ok_dynzon = .FALSE.
    810        CALL getin('ok_dynzon',ok_dynzon)
     808      ok_dynzon = .FALSE.
     809      CALL getin('ok_dynzon',ok_dynzon)
    811810
    812811!Config  Key  = ok_dyn_ins
     
    838837        write(lunout,*)'STOP !!!'
    839838        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
    840         STOP
     839        STOP 1
    841840      ENDIF
    842841     
     
    848847      ok_strato=.FALSE.
    849848      CALL getin('ok_strato',ok_strato)
     849
     850      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     851      CALL getin('vert_prof_dissip', vert_prof_dissip)
     852      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
     853     $     "bad value for vert_prof_dissip")
    850854
    851855!Config  Key  = ok_gradsfile
  • LMDZ5/trunk/libf/dyn3d/gcm.F

    r1671 r1697  
    405405
    406406      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
    407      *                tetagdiv, tetagrot , tetatemp              )
     407     *                tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
    408408
    409409c-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d/inidissip.F90

    r1611 r1697  
    33!
    44SUBROUTINE inidissip ( lstardis,nitergdiv,nitergrot,niterh  , &
    5      tetagdiv,tetagrot,tetatemp             )
     5     tetagdiv,tetagrot,tetatemp, vert_prof_dissip)
    66  !=======================================================================
    77  !   initialisation de la dissipation horizontale
     
    2525  INTEGER,INTENT(in) :: nitergdiv,nitergrot,niterh
    2626  REAL,INTENT(in) :: tetagdiv,tetagrot,tetatemp
     27
     28  integer, INTENT(in):: vert_prof_dissip
     29  ! Vertical profile of horizontal dissipation
     30  ! Allowed values:
     31  ! 0: fractional function of pressure
     32  ! 1: tanh of altitude
    2733
    2834! Local variables:
     
    167173  !   --------------------------------------------------
    168174
    169   if (ok_strato .and. llm==39) then
     175  if (vert_prof_dissip == 1) then
    170176     do l=1,llm
    171177        pseudoz=8.*log(preff/presnivs(l))
  • LMDZ5/trunk/libf/dyn3dpar/comdissnew.h

    r1319 r1697  
    1212
    1313      COMMON/comdissnew/ lstardis,nitergdiv,nitergrot,niterh,tetagdiv,  &
    14      &                   tetagrot,tetatemp,coefdis 
     14     &                   tetagrot,tetatemp,coefdis, vert_prof_dissip
    1515
    1616      LOGICAL lstardis
    1717      INTEGER nitergdiv, nitergrot, niterh
     18
     19      integer vert_prof_dissip ! vertical profile of horizontal dissipation
     20!     Allowed values:
     21!     0: fractional function of pressure
     22!     1: tanh of altitude
     23
    1824      REAL     tetagdiv, tetagrot,  tetatemp, coefdis
    1925
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F

    r1577 r1697  
    66      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
    77c
     8      USE control_mod
    89#ifdef CPP_IOIPSL
    910      use IOIPSL
     
    1617      use mod_hallo, ONLY : use_mpi_alloc
    1718      use parallel, ONLY : omp_chunk
    18       USE control_mod
    1919      USE infotrac, ONLY : type_trac
     20      use assert_m, only: assert
     21
    2022      IMPLICIT NONE
    2123c-----------------------------------------------------------------------
     
    4345#include "serre.h"
    4446#include "comdissnew.h"
    45 !#include "clesphys.h"
    46 #include "iniprint.h"
    4747#include "temps.h"
    4848#include "comconst.h"
    4949
    5050! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     51! #include "clesphys.h"
     52#include "iniprint.h"
    5153c
    5254c
     
    105107        OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
    106108     &          STATUS='unknown',FORM='formatted')
    107 
    108109      ENDIF
    109110
     
    185186
    186187!Config  Key  = nsplit_phys
    187 !Config  Desc = nombre d'iteration de la physique
    188 !Config  Def  = 240
    189 !Config  Help = nombre d'itration de la physique
    190 !
    191188       nsplit_phys = 1
    192189       CALL getin('nsplit_phys',nsplit_phys)
     
    325322       CALL getin('tau_top_bound',tau_top_bound)
    326323
    327 !
    328324!Config  Key  = coefdis
    329325!Config  Desc = coefficient pour gamdissip
     
    608604      type_trac = 'lmdz'
    609605      CALL getin('type_trac',type_trac)
    610 
    611606
    612607!Config  Key  = config_inca
     
    830825
    831826!Config  Key  = ok_dynzon
    832 !Config  Desc = calcul et sortie des transports
     827!Config  Desc = sortie des transports zonaux dans la dynamique
    833828!Config  Def  = n
    834829!Config  Help = Permet de mettre en route le calcul des transports
     
    865860        write(lunout,*)"Le zoom en longitude est incompatible",
    866861     &                 " avec l'utilisation du filtre FFT ",
    867      &                 "---> filtre FFT désactivé "
     862     &                 "---> FFT filter not active"
    868863       use_filtre_fft=.FALSE.
    869864      ENDIF
     
    898893      ok_strato=.FALSE.
    899894      CALL getin('ok_strato',ok_strato)
     895
     896      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     897      CALL getin('vert_prof_dissip', vert_prof_dissip)
     898      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
     899     $     "bad value for vert_prof_dissip")
    900900
    901901!Config  Key  = ok_gradsfile
     
    968968      write(lunout,*)' type_trac = ', type_trac
    969969      write(lunout,*)' config_inca = ', config_inca
    970       write(lunout,*)' ok_dynzon = ', ok_dynzon 
     970      write(lunout,*)' ok_dynzon = ', ok_dynzon
    971971      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    972972      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r1671 r1697  
    418418
    419419      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
    420      *                tetagdiv, tetagrot , tetatemp              )
     420     *                tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
    421421
    422422c-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3dpar/inidissip.F90

    r1611 r1697  
    33!
    44SUBROUTINE inidissip ( lstardis,nitergdiv,nitergrot,niterh  , &
    5      tetagdiv,tetagrot,tetatemp             )
     5     tetagdiv,tetagrot,tetatemp, vert_prof_dissip)
    66  !=======================================================================
    77  !   initialisation de la dissipation horizontale
     
    2525  INTEGER,INTENT(in) :: nitergdiv,nitergrot,niterh
    2626  REAL,INTENT(in) :: tetagdiv,tetagrot,tetatemp
     27
     28  integer, INTENT(in):: vert_prof_dissip
     29  ! Vertical profile of horizontal dissipation
     30  ! Allowed values:
     31  ! 0: fractional function of pressure
     32  ! 1: tanh of altitude
    2733
    2834! Local variables:
     
    167173  !   --------------------------------------------------
    168174
    169   if (ok_strato .and. llm==39) then
     175  if (vert_prof_dissip == 1) then
    170176     do l=1,llm
    171177        pseudoz=8.*log(preff/presnivs(l))
Note: See TracChangeset for help on using the changeset viewer.