Changeset 1391 for trunk/LMDZ.COMMON


Ignore:
Timestamp:
Mar 6, 2015, 3:12:12 PM (10 years ago)
Author:
emillour
Message:

Common dynamical core:
Updates in the dynamics to keeup up with updates in LMDZ5
(up to LMDZ5 trunk rev 2200):

  • compilation:
  • create_make_gcm : added processing of .f & .f90 files (not just .F and .F90)
  • makelmdz: add "mix" option for -io (ouptut with both IOIPSL and XIOS)
  • makelmdz_fcm: add "mix" option for -io
  • filtrez:
  • acc.F and eigen.F : add "implicit none" and variable declarations
  • bibio:
  • handle_err_m.F90: replace "stop" with call to abort_gcm()
  • i1mach.F, j4save.F: add "implicit none" and variable declarations
  • xercnt.F, xermsg.F, xerprn.F, xersve.F, xgetua.F: add "implicit none" and variable declarations
  • dyn3d_common:
  • disvert.F90 : added comments on meaning of "pa" variable
  • grid_atob.F : better control on level of default ouputs
  • infotrac.F90: update Earth-specific stuff (nqo water tracers)
  • interpre.F: correction on the size of input array w
  • juldate.F, massbar.F, ppm3d.F, ran1.F: add "implicit none" and variable declarations
  • sortvarc.F: code cleanup
  • iniacademic.F90: cleanup and extra sanity check.
  • dyn3d:
  • abort_gcm.F: additions for XIOS
  • conf_gcm.F90: transformed to free form from conf_gcm.F
  • gcm.F: added test to check that iphysiq is a multiple of iperiod
  • getparam.F90, guidz_mod.F: update from LMDZ5
  • integrd.F: replace stop with call_abort()
  • dyn3dpar:
  • abort_gcm.F: minor cleanup
  • gcm.F: added test to check that iphysiq is a multiple of iperiod
  • getparam.F90, guide_p_mod.F90: update from LMDZ5
  • integrd_p.F: abort with call_abort when there is negative surface pressure
  • leapfrog_p.F: add INCA specific stuff to keep up with current LMDZ5
  • conf_gcm.F90: transformed to free form from conf_gcm.F

EM

Location:
trunk/LMDZ.COMMON
Files:
35 edited
2 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/create_make_gcm

    r1302 r1391  
    136136
    137137   if [ -d $diri ] ; then
    138    if [ "`ls $diri/*.F $diri/*/*.F`" != "" ] || [ "`ls $diri/*.F90 $diri/*/*.F90`" != "" ]  ; then
     138   if [ "`ls $diri/*.F $diri/*/*.F`" != "" ] || [ "`ls $diri/*.[fF]90 $diri/*/*.[fF]90`" != "" ]  ; then
    139139#      cd $diri >/dev/null 2>&1
    140140      echo
    141141      listlib=""
    142142# Liste des fichiers .F et .F90 n'etant pas des programmes principaux
    143       for fili in `ls $diri/*.F $diri/*/*.F` ; do
     143      for fili in `ls $diri/*.[fF] $diri/*/*.[fF]` ; do
    144144         # Check if file is a routine or main program
    145145         # i.e: look for the "program" keword preceeded by leading spaces
     
    150150         fi
    151151      done
    152       for fili in `ls $diri/*.F90 $diri/*/*.F90` ; do
     152      for fili in `ls $diri/*.[fF]90 $diri/*/*.[fF]90` ; do
    153153         # Check if file is a routine or main program
    154154         # i.e. look for "program" keyword (with possibly some leading spaces)
     
    214214               elif [ -f $dirinc/$strj ] ; then
    215215                  str2='$(LIBF)/'$dirstr/$stri
    216                elif [ -f $dirinc/$strj.F90 ]  || [ -f $dirinc/$strj.F ]  ; then
     216               elif [ -f $dirinc/$strj.[fF]90 ]  || [ -f $dirinc/$strj.[fF] ]  ; then
    217217                  strlib=`echo $libstr | awk -F/ ' { print $1 } '`
    218218                  str2='$(LIBO)/lib'$strlib'.a('$strj'.o)'
    219                elif [ -f $dirinc/$stri.F90 ]  || [ -f $dirinc/$stri.F ]  ; then
     219               elif [ -f $dirinc/$stri.[fF]90 ]  || [ -f $dirinc/$stri.[fF] ]  ; then
    220220                  strlib=`echo $libstr | awk -F/ ' { print $1 } '`
    221221                  str2='$(LIBO)/lib'$strlib'.a('$stri'.o)'
  • trunk/LMDZ.COMMON/libf/bibio/handle_err_m.F90

    r1 r1391  
    3939          end if
    4040       end if
    41        stop 1
     41       call abort_gcm("NetCDF95 handle_err", "", 1)
    4242    end if
    4343
  • trunk/LMDZ.COMMON/libf/bibio/i1mach.F

    r1 r1391  
    11*DECK I1MACH
    22      INTEGER FUNCTION I1MACH (I)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  I1MACH
    45C***PURPOSE  Return integer machine dependent constants.
     
    9596      SAVE IMACH
    9697      EQUIVALENCE (IMACH(4),OUTPUT)
     98      INTEGER I
    9799C***FIRST EXECUTABLE STATEMENT  I1MACH
    98100      IMACH( 1) =         5
  • trunk/LMDZ.COMMON/libf/bibio/j4save.F

    r1 r1391  
    11*DECK J4SAVE
    22      FUNCTION J4SAVE (IWHICH, IVALUE, ISET)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  J4SAVE
    45C***SUBSIDIARY
     
    5960      DATA IPARAM(5)/1/
    6061      DATA IPARAM(6),IPARAM(7),IPARAM(8),IPARAM(9)/0,0,0,0/
     62      INTEGER J4SAVE,IWHICH,IVALUE
    6163C***FIRST EXECUTABLE STATEMENT  J4SAVE
    6264      J4SAVE = IPARAM(IWHICH)
  • trunk/LMDZ.COMMON/libf/bibio/xercnt.F

    r1 r1391  
    11*DECK XERCNT
    22      SUBROUTINE XERCNT (LIBRAR, SUBROU, MESSG, NERR, LEVEL, KONTRL)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  XERCNT
    45C***SUBSIDIARY
     
    5657C***END PROLOGUE  XERCNT
    5758      CHARACTER*(*) LIBRAR, SUBROU, MESSG
     59      INTEGER NERR, LEVEL, KONTRL
    5860C***FIRST EXECUTABLE STATEMENT  XERCNT
    5961      RETURN
  • trunk/LMDZ.COMMON/libf/bibio/xermsg.F

    r1 r1391  
    11*DECK XERMSG
    22      SUBROUTINE XERMSG (LIBRAR, SUBROU, MESSG, NERR, LEVEL)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  XERMSG
    45C***PURPOSE  Process error messages for SLATEC and other libraries.
     
    189190      CHARACTER*72  TEMP
    190191      CHARACTER*20  LFIRST
     192      INTEGER NERR, LEVEL, LKNTRL
     193      INTEGER J4SAVE, MAXMES, KDUMMY, I, KOUNT, LERR, LLEVEL
     194      INTEGER MKNTRL, LTEMP
    191195C***FIRST EXECUTABLE STATEMENT  XERMSG
    192196      LKNTRL = J4SAVE (2, 0, .FALSE.)
  • trunk/LMDZ.COMMON/libf/bibio/xerprn.F

    r1 r1391  
    11*DECK XERPRN
    22      SUBROUTINE XERPRN (PREFIX, NPREF, MESSG, NWRAP)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  XERPRN
    45C***SUBSIDIARY
     
    8182      CHARACTER*2 NEWLIN
    8283      PARAMETER (NEWLIN = '$$')
     84      INTEGER N, I1MACH, I, LPREF, LWRAP, LENMSG, NEXTC
     85      INTEGER LPIECE, IDELTA
    8386C***FIRST EXECUTABLE STATEMENT  XERPRN
    8487      CALL XGETUA(IU,NUNIT)
  • trunk/LMDZ.COMMON/libf/bibio/xersve.F

    r1 r1391  
    22      SUBROUTINE XERSVE (LIBRAR, SUBROU, MESSG, KFLAG, NERR, LEVEL,
    33     +   ICOUNT)
     4      IMPLICIT NONE
    45C***BEGIN PROLOGUE  XERSVE
    56C***SUBSIDIARY
     
    5859C   920501  Reformatted the REFERENCES section.  (WRB)
    5960C***END PROLOGUE  XERSVE
    60       PARAMETER (LENTAB=10)
     61      INTEGER,PARAMETER :: LENTAB=10
    6162      INTEGER LUN(5)
    6263      CHARACTER*(*) LIBRAR, SUBROU, MESSG
     
    6667      SAVE LIBTAB, SUBTAB, MESTAB, NERTAB, LEVTAB, KOUNT, KOUNTX, NMSG
    6768      DATA KOUNTX/0/, NMSG/0/
     69      INTEGER NERR,LEVEL,KONTRL
     70      INTEGER NERTAB, LEVTAB, KOUNT, KOUNTX, NMSG
     71      INTEGER KFLAG, ICOUNT, NUNIT, KUNIT, IUNIT, I1MACH, I
    6872C***FIRST EXECUTABLE STATEMENT  XERSVE
    6973C
  • trunk/LMDZ.COMMON/libf/bibio/xgetua.F

    r1 r1391  
    11*DECK XGETUA
    22      SUBROUTINE XGETUA (IUNITA, N)
     3      IMPLICIT NONE
    34C***BEGIN PROLOGUE  XGETUA
    45C***PURPOSE  Return unit number(s) to which error messages are being
     
    4142C***END PROLOGUE  XGETUA
    4243      DIMENSION IUNITA(5)
     44      INTEGER IUNITA, N, J4SAVE, INDEX, I
    4345C***FIRST EXECUTABLE STATEMENT  XGETUA
    4446      N = J4SAVE(5,0,.FALSE.)
  • trunk/LMDZ.COMMON/libf/dyn3d/abort_gcm.F

    r1 r1391  
    1212      USE ioipsl_getincom
    1313#endif
     14
     15#ifdef CPP_XIOS
     16    ! ug Pour les sorties XIOS
     17      USE wxios
     18#endif
     19
    1420#include "iniprint.h"
    1521 
     
    2228C         ierr    = severity of situation ( = 0 normal )
    2329
    24       character(len=*) modname
    25       integer ierr
    26       character(len=*) message
     30      character(len=*), intent(in):: modname
     31      integer, intent(in):: ierr
     32      character(len=*), intent(in):: message
    2733
    2834      write(lunout,*) 'in abort_gcm'
     35
     36#ifdef CPP_XIOS
     37    !Fermeture propre de XIOS
     38      CALL wxios_close()
     39#endif
     40
    2941#ifdef CPP_IOIPSL
    3042      call histclo
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1390 r1391  
    11!
    22! $Id: conf_gcm.F 1418 2010-07-19 15:11:24Z jghattas $
    3 !
    4 !
    5 !
    6       SUBROUTINE conf_gcm( tapedef, etatinit )
    7 !
    8       USE control_mod
     3
     4SUBROUTINE conf_gcm( tapedef, etatinit )
     5
     6USE control_mod
    97#ifdef CPP_IOIPSL
    10       use IOIPSL
     8  use IOIPSL
    119#else
    12 ! if not using IOIPSL, we still need to use (a local version of) getin
    13       use ioipsl_getincom
     10  ! if not using IOIPSL, we still need to use (a local version of) getin
     11  use ioipsl_getincom
    1412#endif
    15       USE infotrac, ONLY : type_trac
    16       use assert_m, only: assert
    17       use sponge_mod, only: callsponge,mode_sponge,nsponge,tetasponge
    18 
    19       IMPLICIT NONE
     13  USE infotrac, ONLY : type_trac
     14  use assert_m, only: assert
     15  use sponge_mod, only: callsponge,mode_sponge,nsponge,tetasponge
     16
     17  IMPLICIT NONE
    2018!-----------------------------------------------------------------------
    2119!     Auteurs :   L. Fairhead , P. Le Van  .
     
    2725!     -metres  du zoom  avec  celles lues sur le fichier start .
    2826!
    29        LOGICAL etatinit
    30        INTEGER tapedef
     27  LOGICAL etatinit
     28  INTEGER tapedef
    3129
    3230!   Declarations :
    3331!   --------------
    34 #include "dimensions.h"
    35 #include "paramet.h"
    36 #include "logic.h"
    37 #include "serre.h"
    38 #include "comdissnew.h"
    39 #include "iniprint.h"
    40 #include "temps.h"
    41 #include "comconst.h"
     32  include "dimensions.h"
     33  include "paramet.h"
     34  include "logic.h"
     35  include "serre.h"
     36  include "comdissnew.h"
     37  include "iniprint.h"
     38  include "temps.h"
     39  include "comconst.h"
    4240
    4341! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     
    4846!   ------
    4947
    50       CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
    51       REAL clonn,clatt,grossismxx,grossismyy
    52       REAL dzoomxx,dzoomyy, tauxx,tauyy
    53       LOGICAL  fxyhypbb, ysinuss
    54       INTEGER i
    55       LOGICAL use_filtre_fft
     48  CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
     49  REAL clonn,clatt,grossismxx,grossismyy
     50  REAL dzoomxx,dzoomyy, tauxx,tauyy
     51  LOGICAL  fxyhypbb, ysinuss
     52  INTEGER i
     53  LOGICAL use_filtre_fft
    5654!
    5755!  -------------------------------------------------------------------
     
    8886!Config  Help = unite de fichier pour les impressions
    8987!Config         (defaut sortie standard = 6)
    90       lunout=6
    91       CALL getin('lunout', lunout)
    92       IF (lunout /= 5 .and. lunout /= 6) THEN
    93         OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                     &
    94      &          STATUS='unknown',FORM='formatted')
    95       ENDIF
     88  lunout=6
     89  CALL getin('lunout', lunout)
     90  IF (lunout /= 5 .and. lunout /= 6) THEN
     91    OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                      &
     92          STATUS='unknown',FORM='formatted')
     93  ENDIF
    9694
    9795!Config  Key  = prt_level
     
    10098!Config  Help = Niveau d'impression pour le débogage
    10199!Config         (0 = minimum d'impression)
    102       prt_level = 0
    103       CALL getin('prt_level',prt_level)
     100  prt_level = 0
     101  CALL getin('prt_level',prt_level)
    104102
    105103!-----------------------------------------------------------------------
     
    110108!Config  Def  = earth
    111109!Config  Help = this flag sets the type of atymosphere that is considered
    112       planet_type="earth"
    113       CALL getin('planet_type',planet_type)
     110  planet_type="earth"
     111  CALL getin('planet_type',planet_type)
    114112
    115113!Config  Key  = calend
     
    118116!Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
    119117!Config         
    120       calend = 'earth_360d'
    121       CALL getin('calend', calend)
     118  calend = 'earth_360d'
     119  CALL getin('calend', calend)
    122120
    123121!Config  Key  = dayref
     
    126124!Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
    127125!Config         par expl. ,comme ici ) ... A completer
    128       dayref=1
    129       CALL getin('dayref', dayref)
     126  dayref=1
     127  CALL getin('dayref', dayref)
    130128
    131129!Config  Key  = anneeref
     
    134132!Config  Help = Annee de l'etat  initial
    135133!Config         (   avec  4  chiffres   ) ... A completer
    136       anneeref = 1998
    137       CALL getin('anneeref',anneeref)
     134  anneeref = 1998
     135  CALL getin('anneeref',anneeref)
    138136
    139137!Config  Key  = raz_date
     
    144142!Config         1 prise en compte de la date de gcm.def avec remise a zero
    145143!Config         des compteurs de pas de temps
    146       raz_date = 0
    147       CALL getin('raz_date', raz_date)
     144  raz_date = 0
     145  CALL getin('raz_date', raz_date)
    148146
    149147!Config  Key  = resetvarc
     
    151149!Config  Def  = n
    152150!Config  Help = Reinit des variables de controle
    153       resetvarc = .false.
    154       CALL getin('resetvarc',resetvarc)
     151  resetvarc = .false.
     152  CALL getin('resetvarc',resetvarc)
    155153
    156154!Config  Key  = nday
     
    159157!Config  Help = Nombre de jours d'integration
    160158!Config         ... On pourait aussi permettre des mois ou des annees !
    161       nday = 10
    162       CALL getin('nday',nday)
    163 
    164       ! alternative to specifying nday (see also 'less1day' and 'fractday'
    165       ! options below: sopecify numbre of dynamic steps to run:
    166       ndynstep = -9999 ! default value ; if ndynstep <0 then option not used.
    167       call getin('ndynstep',ndynstep)
     159  nday = 10
     160  CALL getin('nday',nday)
     161
     162  ! alternative to specifying nday (see also 'less1day' and 'fractday'
     163  ! options below: sopecify numbre of dynamic steps to run:
     164  ndynstep = -9999 ! default value ; if ndynstep <0 then option not used.
     165  call getin('ndynstep',ndynstep)
    168166     
    169167!Config  Key  = starttime
     
    172170!Config  Help = Heure de depart de la simulation
    173171!Config         en jour
    174       starttime = 0
    175       CALL getin('starttime',starttime)
     172  starttime = 0
     173  CALL getin('starttime',starttime)
    176174     
    177       ! Mars: time of start for run in "start.nc" (when there are multiple time
    178       !       steps stored in the file)
    179       timestart=-9999 ! default value; if <0, use last stored time
    180       call getin("timestart",timestart)
     175  ! Mars: time of start for run in "start.nc" (when there are multiple time
     176  !       steps stored in the file)
     177  timestart=-9999 ! default value; if <0, use last stored time
     178  call getin("timestart",timestart)
    181179     
    182180!Config  Key  = less1day
     
    184182!Config  Def  = n
    185183!Config  Help = Possibilite d'integrer moins d'un jour
    186       less1day = .false.
    187       CALL getin('less1day',less1day)
     184  less1day = .false.
     185  CALL getin('less1day',less1day)
    188186
    189187!Config  Key  = fractday
     
    191189!Config  Def  = 0.01
    192190!Config  Help = integration sur une fraction de jour
    193       fractday = 0.01
    194       CALL getin('fractday',fractday)
     191  fractday = 0.01
     192  CALL getin('fractday',fractday)
    195193
    196194!Config  Key  = day_step
     
    199197!Config  Help = nombre de pas par jour (multiple de iperiod) (
    200198!Config          ici pour  dt = 1 min )
    201        day_step = 240
    202        CALL getin('day_step',day_step)
     199  day_step = 240
     200  CALL getin('day_step',day_step)
    203201
    204202!Config  Key  = nsplit_phys
     
    206204!Config  Def  = 1
    207205!Config  Help = nombre de subdivisions par pas physique
    208        nsplit_phys = 1
    209        CALL getin('nsplit_phys',nsplit_phys)
     206  nsplit_phys = 1
     207  CALL getin('nsplit_phys',nsplit_phys)
    210208
    211209!Config  Key  = iperiod
     
    213211!Config  Def  = 5
    214212!Config  Help = periode pour le pas Matsuno (en pas de temps)
    215        iperiod = 5
    216        CALL getin('iperiod',iperiod)
     213  iperiod = 5
     214  CALL getin('iperiod',iperiod)
    217215
    218216!Config  Key  = iapp_tracvl
     
    220218!Config  Def  = iperiod
    221219!Config  Help = frequence du groupement des flux (en pas de temps)
    222        iapp_tracvl = iperiod
    223        CALL getin('iapp_tracvl',iapp_tracvl)
     220  iapp_tracvl = iperiod
     221  CALL getin('iapp_tracvl',iapp_tracvl)
    224222
    225223!Config  Key  = iconser
     
    228226!Config  Help = periode de sortie des variables de controle
    229227!Config         (En pas de temps)
    230        iconser = 240 
    231        CALL getin('iconser', iconser)
     228  iconser = 240 
     229  CALL getin('iconser', iconser)
    232230
    233231!Config  Key  = iecri
     
    235233!Config  Def  = 1
    236234!Config  Help = periode d'ecriture du fichier histoire (en jour)
    237        iecri = 1
    238        CALL getin('iecri',iecri)
     235  iecri = 1
     236  CALL getin('iecri',iecri)
    239237
    240238
     
    243241!Config  Def  = 1
    244242!Config  Help = periode de stockage fichier histmoy (en jour)
    245        periodav = 1.
    246        CALL getin('periodav',periodav)
     243  periodav = 1.
     244  CALL getin('periodav',periodav)
    247245
    248246!Config  Key  = output_grads_dyn
     
    250248!Config  Def  = n
    251249!Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
    252        output_grads_dyn=.false.
    253        CALL getin('output_grads_dyn',output_grads_dyn)
     250  output_grads_dyn=.false.
     251  CALL getin('output_grads_dyn',output_grads_dyn)
    254252
    255253!Config  Key  = dissip_period
     
    259257!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
    260258!Config  dissip_period>0 => on prend cette valeur
    261        dissip_period = 0
    262        call getin('idissip',dissip_period) ! old Mars/Genreic model parameter
    263        ! if there is a "dissip_period" in run.def, it overrides "idissip"
    264        CALL getin('dissip_period',dissip_period)
     259  dissip_period = 0
     260  call getin('idissip',dissip_period) ! old Mars/Genreic model parameter
     261  ! if there is a "dissip_period" in run.def, it overrides "idissip"
     262  CALL getin('dissip_period',dissip_period)
    265263
    266264!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     
    273271!Config         'y' si on veut star et 'n' si on veut non-start !
    274272!Config         Moi y en a pas comprendre !
    275        lstardis = .TRUE.
    276        CALL getin('lstardis',lstardis)
     273  lstardis = .TRUE.
     274  CALL getin('lstardis',lstardis)
    277275
    278276
     
    282280!Config  Help = nombre d'iterations de l'operateur de dissipation
    283281!Config         gradiv
    284        nitergdiv = 1
    285        CALL getin('nitergdiv',nitergdiv)
     282  nitergdiv = 1
     283  CALL getin('nitergdiv',nitergdiv)
    286284
    287285!Config  Key  = nitergrot
     
    290288!Config  Help = nombre d'iterations de l'operateur de dissipation 
    291289!Config         nxgradrot
    292        nitergrot = 2
    293        CALL getin('nitergrot',nitergrot)
     290  nitergrot = 2
     291  CALL getin('nitergrot',nitergrot)
    294292
    295293
     
    299297!Config  Help = nombre d'iterations de l'operateur de dissipation
    300298!Config         divgrad
    301        niterh = 2
    302        CALL getin('niterh',niterh)
     299  niterh = 2
     300  CALL getin('niterh',niterh)
    303301
    304302
     
    308306!Config  Help = temps de dissipation des plus petites longeur
    309307!Config         d'ondes pour u,v (gradiv)
    310        tetagdiv = 7200.
    311        CALL getin('tetagdiv',tetagdiv)
     308  tetagdiv = 7200.
     309  CALL getin('tetagdiv',tetagdiv)
    312310
    313311!Config  Key  = tetagrot
     
    316314!Config  Help = temps de dissipation des plus petites longeur
    317315!Config         d'ondes pour u,v (nxgradrot)
    318        tetagrot = 7200.
    319        CALL getin('tetagrot',tetagrot)
     316  tetagrot = 7200.
     317  CALL getin('tetagrot',tetagrot)
    320318
    321319!Config  Key  = tetatemp
     
    324322!Config  Help =  temps de dissipation des plus petites longeur
    325323!Config         d'ondes pour h (divgrad)   
    326        tetatemp  = 7200.
    327        CALL getin('tetatemp',tetatemp )
     324  tetatemp  = 7200.
     325  CALL getin('tetatemp',tetatemp )
    328326
    329327! For Earth model only:
     
    333331! avec ok_strato=y
    334332
    335        dissip_factz=4.
    336        dissip_deltaz=10.
    337        dissip_zref=30.
    338        CALL getin('dissip_factz',dissip_factz )
    339        CALL getin('dissip_deltaz',dissip_deltaz )
    340        CALL getin('dissip_zref',dissip_zref )
     333  dissip_factz=4.
     334  dissip_deltaz=10.
     335  dissip_zref=30.
     336  CALL getin('dissip_factz',dissip_factz )
     337  CALL getin('dissip_deltaz',dissip_deltaz )
     338  CALL getin('dissip_zref',dissip_zref )
    341339
    342340! For other planets:
     
    345343! Actifs uniquement avec ok_strato=y
    346344
    347        dissip_fac_mid=2.
    348        dissip_fac_up=10.
    349        dissip_deltaz=10.! Intervalle (km) pour le changement mid / up
    350        dissip_hdelta=5. ! scale height (km) dans la zone de la transition(m)
    351        dissip_pupstart=1.e3  ! pression (Pa) au bas la transition mid / up
    352        CALL getin('dissip_fac_mid',dissip_fac_mid )
    353        CALL getin('dissip_fac_up',dissip_fac_up )
    354        CALL getin('dissip_deltaz',dissip_deltaz )
    355        CALL getin('dissip_hdelta',dissip_hdelta )
    356        CALL getin('dissip_pupstart',dissip_pupstart )
     345  dissip_fac_mid=2.
     346  dissip_fac_up=10.
     347  dissip_deltaz=10.! Intervalle (km) pour le changement mid / up
     348  dissip_hdelta=5. ! scale height (km) dans la zone de la transition(m)
     349  dissip_pupstart=1.e3  ! pression (Pa) au bas la transition mid / up
     350  CALL getin('dissip_fac_mid',dissip_fac_mid )
     351  CALL getin('dissip_fac_up',dissip_fac_up )
     352  CALL getin('dissip_deltaz',dissip_deltaz )
     353  CALL getin('dissip_hdelta',dissip_hdelta )
     354  CALL getin('dissip_pupstart',dissip_pupstart )
    357355
    358356! top_bound sponge: only active if iflag_top_bound!=0
     
    360358!                   iflag_top_bound=1 for sponge over 4 topmost layers
    361359!                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
    362        iflag_top_bound=0
    363        CALL getin('iflag_top_bound',iflag_top_bound)
     360  iflag_top_bound=0
     361  CALL getin('iflag_top_bound',iflag_top_bound)
    364362
    365363! mode_top_bound : fields towards which sponge relaxation will be done:
     
    368366!                  mode_top_bound=2: u and v relax towards their zonal mean
    369367!                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
    370        mode_top_bound=3
    371        CALL getin('mode_top_bound',mode_top_bound)
     368  mode_top_bound=3
     369  CALL getin('mode_top_bound',mode_top_bound)
    372370
    373371! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
    374        tau_top_bound=1.e-5
    375        CALL getin('tau_top_bound',tau_top_bound)
     372  tau_top_bound=1.e-5
     373  CALL getin('tau_top_bound',tau_top_bound)
    376374
    377375! the other possible sponge layer (sponge_mod)
    378        callsponge=.false. ! default value; don't use the sponge
    379        call getin("callsponge",callsponge)
    380        ! check that user is not trying to use both sponge models
    381        if ((iflag_top_bound.ge.1).and.callsponge) then
    382          write(lunout,*)'Bad choice of options:'
    383          write(lunout,*)' iflag_top_bound=',iflag_top_bound
    384          write(lunout,*)' and callsponge=.true.'
    385          write(lunout,*)'But both sponge models should not be',
    386      &                  ' used simultaneously!'
    387          stop
    388        endif
     376  callsponge=.false. ! default value; don't use the sponge
     377  call getin("callsponge",callsponge)
     378  ! check that user is not trying to use both sponge models
     379  if ((iflag_top_bound.ge.1).and.callsponge) then
     380    write(lunout,*)'Bad choice of options:'
     381    write(lunout,*)' iflag_top_bound=',iflag_top_bound
     382    write(lunout,*)' and callsponge=.true.'
     383    write(lunout,*)'But both sponge models should not be', &
     384                   ' used simultaneously!'
     385    stop
     386  endif
    389387       
    390388! nsponge: number of atmospheric layers over which the sponge extends
    391        nsponge=3 ! default value
    392        call getin("nsponge",nsponge)
     389  nsponge=3 ! default value
     390  call getin("nsponge",nsponge)
    393391
    394392! mode_sponge: (quenching is towards ... over the upper nsponge layers)
     
    396394!      1: (h=hmean,u=umean,v=0)
    397395!      2: (h=hmean,u=umean,v=vmean)"
    398        mode_sponge=2 ! default value
    399        call getin("mode_sponge",mode_sponge)
     396  mode_sponge=2 ! default value
     397  call getin("mode_sponge",mode_sponge)
    400398
    401399! tetasponge: characteristic time scale (seconds) at topmost layer
    402400!            (time scale then doubles with decreasing layer index)."
    403        tetasponge=50000.0
    404        call getin("tetasponge",tetasponge)
     401  tetasponge=50000.0
     402  call getin("tetasponge",tetasponge)
    405403
    406404! FOR TITAN: tidal forces
    407        tidal=.TRUE.
    408        CALL getin('tidal',tidal)
     405  if (planet_type=="titan") then
     406    tidal=.TRUE.
     407    CALL getin('tidal',tidal)
     408  else
     409    tidal=.false.
     410  endif
    409411
    410412!Config  Key  = coefdis
     
    412414!Config  Def  = 0
    413415!Config  Help = coefficient pour gamdissip 
    414        coefdis = 0.
    415        CALL getin('coefdis',coefdis)
     416  coefdis = 0.
     417  CALL getin('coefdis',coefdis)
    416418
    417419!Config  Key  = purmats
     
    420422!Config  Help = Choix du schema d'integration temporel.
    421423!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
    422        purmats = .FALSE.
    423        CALL getin('purmats',purmats)
     424  purmats = .FALSE.
     425  CALL getin('purmats',purmats)
    424426
    425427!Config  Key  = ok_guide
     
    427429!Config  Def  = n
    428430!Config  Help = Guidage
    429        ok_guide = .FALSE.
    430        CALL getin('ok_guide',ok_guide)
    431 
    432 !    ...............................................................
     431  ok_guide = .FALSE.
     432  CALL getin('ok_guide',ok_guide)
    433433
    434434!Config  Key  =  read_start
     
    437437!Config  Help = y: intialize dynamical fields using a 'start.nc' file
    438438!               n: fields are initialized by 'iniacademic' routine
    439        read_start= .true.
    440        CALL getin('read_start',read_start)
     439  read_start= .true.
     440  CALL getin('read_start',read_start)
    441441
    442442!Config  Key  = iflag_phys
     
    445445!Config  Help = Permet de faire tourner le modele sans
    446446!Config         physique.
    447        iflag_phys = 1
    448        CALL getin('iflag_phys',iflag_phys)
    449 
     447  iflag_phys = 1
     448  CALL getin('iflag_phys',iflag_phys)
    450449
    451450!Config  Key  =  iphysiq
     
    453452!Config  Def  = 5
    454453!Config  Help = Periode de la physique en pas de temps de la dynamique.
    455        iphysiq = 5
    456        CALL getin('iphysiq', iphysiq)
     454  iphysiq = 5
     455  CALL getin('iphysiq', iphysiq)
    457456
    458457!Config  Key  = iflag_trac
     
    461460!Config  Help = Permet de faire tourner le modele sans traceurs
    462461!Config         
    463        iflag_trac = 1
    464        CALL getin('iflag_trac',iflag_trac)
     462  iflag_trac = 1
     463  CALL getin('iflag_trac',iflag_trac)
    465464
    466465!Config  Key  = ip_ebil_dyn
     
    472471!Config         1 pas de print
    473472!Config         2 print,
    474        ip_ebil_dyn = 0
    475        CALL getin('ip_ebil_dyn',ip_ebil_dyn)
     473  ip_ebil_dyn = 0
     474  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
    476475
    477476!Config  Key  = offline
     
    480479!Config  Help = Permet de mettre en route la
    481480!Config         nouvelle parametrisation de l'eau liquide !
    482        offline = .FALSE.
    483        CALL getin('offline',offline)
     481  offline = .FALSE.
     482  CALL getin('offline',offline)
    484483
    485484!Config  Key  = type_trac
     
    490489!Config         'inca' = model de chime INCA
    491490!Config         'repr' = model de chime REPROBUS
    492       type_trac = 'lmdz'
    493       CALL getin('type_trac',type_trac)
     491  type_trac = 'lmdz'
     492  CALL getin('type_trac',type_trac)
    494493
    495494!Config  Key  = config_inca
     
    500499!Config         'chem' = INCA avec calcul de chemie
    501500!Config         'aero' = INCA avec calcul des aerosols
    502       config_inca = 'none'
    503       CALL getin('config_inca',config_inca)
     501  config_inca = 'none'
     502  CALL getin('config_inca',config_inca)
    504503
    505504!Config  Key  = ok_dynzon
     
    508507!Config  Help = Permet de mettre en route le calcul des transports
    509508!Config         
    510       ok_dynzon = .FALSE.
    511       CALL getin('ok_dynzon',ok_dynzon)
     509  ok_dynzon = .FALSE.
     510  CALL getin('ok_dynzon',ok_dynzon)
    512511
    513512!Config  Key  = ok_dyn_ins
     
    516515!Config  Help =
    517516!Config         
    518       ok_dyn_ins = .FALSE.
    519       CALL getin('ok_dyn_ins',ok_dyn_ins)
     517  ok_dyn_ins = .FALSE.
     518  CALL getin('ok_dyn_ins',ok_dyn_ins)
    520519
    521520!Config  Key  = ok_dyn_ave
     
    524523!Config  Help =
    525524!Config         
    526       ok_dyn_ave = .FALSE.
    527       CALL getin('ok_dyn_ave',ok_dyn_ave)
     525  ok_dyn_ave = .FALSE.
     526  CALL getin('ok_dyn_ave',ok_dyn_ave)
    528527
    529528!Config  Key  = use_filtre_fft
     
    533532!Config         le filtrage aux poles.
    534533! Le filtre fft n'est pas implemente dans dyn3d
    535       use_filtre_fft=.FALSE.
    536       CALL getin('use_filtre_fft',use_filtre_fft)
    537 
    538       IF (use_filtre_fft) THEN
    539         write(lunout,*)'STOP !!!'
    540         write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
    541         STOP 1
    542       ENDIF
     534  use_filtre_fft=.FALSE.
     535  CALL getin('use_filtre_fft',use_filtre_fft)
     536
     537  IF (use_filtre_fft) THEN
     538    write(lunout,*)'STOP !!!'
     539    write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
     540    STOP 1
     541  ENDIF
    543542     
    544543!Config key = ok_strato
     
    547546!Config  Help = active la version stratosphérique de LMDZ de F. Lott
    548547
    549       ok_strato=.TRUE.
    550       CALL getin('ok_strato',ok_strato)
     548  ok_strato=.TRUE.
     549  CALL getin('ok_strato',ok_strato)
    551550
    552551! NB: vert_prof_dissip is Earth-specific; should not impact other models
    553       if (planet_type=="earth") then
    554        vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
    555        CALL getin('vert_prof_dissip', vert_prof_dissip)
    556        call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
    557      $     "bad value for vert_prof_dissip")
    558       else
    559        vert_prof_dissip=0 ! default for planets !
    560        if (planet_type=="mars") then
    561          vert_prof_dissip=1 ! use fac_mid & fac_up & startalt & delta
    562        endif
    563       endif
     552  if (planet_type=="earth") then
     553    vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     554    CALL getin('vert_prof_dissip', vert_prof_dissip)
     555    call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
     556         "bad value for vert_prof_dissip")
     557  else
     558    vert_prof_dissip=0 ! default for planets !
     559    if (planet_type=="mars") then
     560      vert_prof_dissip=1 ! use fac_mid & fac_up & startalt & delta
     561    endif
     562  endif
    564563
    565564!Config  Key  = ok_gradsfile
     
    568567!Config  Help = active les sorties grads du guidage
    569568
    570        ok_gradsfile = .FALSE.
    571        CALL getin('ok_gradsfile',ok_gradsfile)
     569  ok_gradsfile = .FALSE.
     570  CALL getin('ok_gradsfile',ok_gradsfile)
    572571
    573572!Config  Key  = ok_limit
     
    576575!Config  Help = production du fichier limit.nc requise
    577576
    578        ok_limit = .TRUE.
    579        CALL getin('ok_limit',ok_limit)
     577  ok_limit = .TRUE.
     578  CALL getin('ok_limit',ok_limit)
    580579
    581580!Config  Key  = ok_etat0
     
    584583!Config  Help = production des fichiers start.nc, startphy.nc requise
    585584
    586       ok_etat0 = .TRUE.
    587       CALL getin('ok_etat0',ok_etat0)
     585  ok_etat0 = .TRUE.
     586  CALL getin('ok_etat0',ok_etat0)
    588587
    589588!----------------------------------------
    590589! Parameters for zonal averages in the case of Titan
    591       moyzon_mu = .false.
    592       moyzon_ch = .false.
    593       if (planet_type=="titan") then
    594        CALL getin('moyzon_mu', moyzon_mu)
    595        CALL getin('moyzon_ch', moyzon_ch)
    596       endif
     590  moyzon_mu = .false.
     591  moyzon_ch = .false.
     592  if (planet_type=="titan") then
     593    CALL getin('moyzon_mu', moyzon_mu)
     594    CALL getin('moyzon_ch', moyzon_ch)
     595  endif
    597596!----------------------------------------
    598597
     
    604603!
    605604!----------------------------------------
    606       IF( etatinit ) then
    607 
    608 !Config  Key  = clon
    609 !Config  Desc = centre du zoom, longitude
    610 !Config  Def  = 0
    611 !Config  Help = longitude en degres du centre
    612 !Config         du zoom
    613        clon = 0.
    614        CALL getin('clon',clon)
    615 
    616 !Config  Key  = clat
    617 !Config  Desc = centre du zoom, latitude
    618 !Config  Def  = 0
    619 !Config  Help = latitude en degres du centre du zoom
    620 !Config         
    621        clat = 0.
    622        CALL getin('clat',clat)
    623 
    624 !Config  Key  = grossismx
    625 !Config  Desc = zoom en longitude
    626 !Config  Def  = 1.0
    627 !Config  Help = facteur de grossissement du zoom,
    628 !Config         selon la longitude
    629        grossismx = 1.0
    630        CALL getin('grossismx',grossismx)
    631 
    632 !Config  Key  = grossismy
    633 !Config  Desc = zoom en latitude
    634 !Config  Def  = 1.0
    635 !Config  Help = facteur de grossissement du zoom,
    636 !Config         selon la latitude
    637        grossismy = 1.0
    638        CALL getin('grossismy',grossismy)
    639 
    640       IF( grossismx.LT.1. )  THEN
    641         write(lunout,*)                                                        &
    642      &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    643          STOP
    644       ELSE
    645          alphax = 1. - 1./ grossismx
    646       ENDIF
    647 
    648 
    649       IF( grossismy.LT.1. )  THEN
    650         write(lunout,*)                                                        &
    651      &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    652          STOP
    653       ELSE
    654          alphay = 1. - 1./ grossismy
    655       ENDIF
    656 
    657       write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
    658 !
    659 !    alphax et alphay sont les anciennes formulat. des grossissements
    660 !
    661 !
    662 
    663 !Config  Key  = fxyhypb
    664 !Config  Desc = Fonction  hyperbolique
    665 !Config  Def  = y
    666 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    667 !Config         sinon  sinusoidale
    668        fxyhypb = .TRUE.
    669        CALL getin('fxyhypb',fxyhypb)
    670 
    671 !Config  Key  = dzoomx
    672 !Config  Desc = extension en longitude
    673 !Config  Def  = 0
    674 !Config  Help = extension en longitude  de la zone du zoom 
    675 !Config         ( fraction de la zone totale)
    676        dzoomx = 0.0
    677        CALL getin('dzoomx',dzoomx)
    678 
    679 !Config  Key  = dzoomy
    680 !Config  Desc = extension en latitude
    681 !Config  Def  = 0
    682 !Config  Help = extension en latitude de la zone  du zoom 
    683 !Config         ( fraction de la zone totale)
    684        dzoomy = 0.0
    685        CALL getin('dzoomy',dzoomy)
    686 
    687 !Config  Key  = taux
    688 !Config  Desc = raideur du zoom en  X
    689 !Config  Def  = 3
    690 !Config  Help = raideur du zoom en  X
    691        taux = 3.0
    692        CALL getin('taux',taux)
    693 
    694 !Config  Key  = tauy
    695 !Config  Desc = raideur du zoom en  Y
    696 !Config  Def  = 3
    697 !Config  Help = raideur du zoom en  Y
    698        tauy = 3.0
    699        CALL getin('tauy',tauy)
    700 
    701 !Config  Key  = ysinus
    702 !Config  IF   = !fxyhypb
    703 !Config  Desc = Fonction en Sinus
    704 !Config  Def  = y
    705 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    706 !Config         sinon y = latit.
    707        ysinus = .TRUE.
    708        CALL getin('ysinus',ysinus)
    709 c
    710 c----------------------------------------
    711        else ! etatinit=false
    712 c----------------------------------------
    713 
    714 !Config  Key  = clon
    715 !Config  Desc = centre du zoom, longitude
    716 !Config  Def  = 0
    717 !Config  Help = longitude en degres du centre
    718 !Config         du zoom
    719        clonn = 0.
    720        CALL getin('clon',clonn)
    721 
    722 !Config  Key  = clat
    723 !Config  Desc = centre du zoom, latitude
    724 !Config  Def  = 0
    725 !Config  Help = latitude en degres du centre du zoom
    726 !Config         
    727        clatt = 0.
    728        CALL getin('clat',clatt)
    729 
    730 c
    731 c
    732       IF( ABS(clat - clatt).GE. 0.001 )  THEN
    733         write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',     &
    734      &    ' est differente de celle lue sur le fichier  start '
     605  test_etatinit: IF (.not. etatinit) then
     606     !Config  Key  = clon
     607     !Config  Desc = centre du zoom, longitude
     608     !Config  Def  = 0
     609     !Config  Help = longitude en degres du centre
     610     !Config         du zoom
     611     clonn = 0.
     612     CALL getin('clon',clonn)
     613
     614     !Config  Key  = clat
     615     !Config  Desc = centre du zoom, latitude
     616     !Config  Def  = 0
     617     !Config  Help = latitude en degres du centre du zoom
     618     !Config         
     619     clatt = 0.
     620     CALL getin('clat',clatt)
     621
     622     IF( ABS(clat - clatt).GE. 0.001 )  THEN
     623        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
     624             ' est differente de celle lue sur le fichier  start '
    735625        STOP
    736       ENDIF
    737 
    738 !Config  Key  = grossismx
    739 !Config  Desc = zoom en longitude
    740 !Config  Def  = 1.0
    741 !Config  Help = facteur de grossissement du zoom,
    742 !Config         selon la longitude
    743        grossismxx = 1.0
    744        CALL getin('grossismx',grossismxx)
    745 
    746 
    747       IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    748         write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',       &
    749      &  'run.def est differente de celle lue sur le fichier  start '
     626     ENDIF
     627
     628     !Config  Key  = grossismx
     629     !Config  Desc = zoom en longitude
     630     !Config  Def  = 1.0
     631     !Config  Help = facteur de grossissement du zoom,
     632     !Config         selon la longitude
     633     grossismxx = 1.0
     634     CALL getin('grossismx',grossismxx)
     635
     636     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
     637        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
     638             'run.def est differente de celle lue sur le fichier  start '
    750639        STOP
    751       ENDIF
    752 
    753 !Config  Key  = grossismy
    754 !Config  Desc = zoom en latitude
    755 !Config  Def  = 1.0
    756 !Config  Help = facteur de grossissement du zoom,
    757 !Config         selon la latitude
    758        grossismyy = 1.0
    759        CALL getin('grossismy',grossismyy)
    760 
    761       IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
    762         write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',        &
    763      & 'run.def est differente de celle lue sur le fichier  start '
     640     ENDIF
     641
     642     !Config  Key  = grossismy
     643     !Config  Desc = zoom en latitude
     644     !Config  Def  = 1.0
     645     !Config  Help = facteur de grossissement du zoom,
     646     !Config         selon la latitude
     647     grossismyy = 1.0
     648     CALL getin('grossismy',grossismyy)
     649
     650     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
     651        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
     652             'run.def est differente de celle lue sur le fichier  start '
    764653        STOP
    765       ENDIF
    766      
    767       IF( grossismx.LT.1. )  THEN
    768         write(lunout,*)                                                        &
    769      &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    770          STOP
    771       ELSE
    772          alphax = 1. - 1./ grossismx
    773       ENDIF
    774 
    775 
    776       IF( grossismy.LT.1. )  THEN
    777         write(lunout,*)                                                        &
    778      &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    779          STOP
    780       ELSE
    781          alphay = 1. - 1./ grossismy
    782       ENDIF
    783 
    784       write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
    785 !
    786 !    alphax et alphay sont les anciennes formulat. des grossissements
    787 !
    788 !
    789 
    790 !Config  Key  = fxyhypb
    791 !Config  Desc = Fonction  hyperbolique
    792 !Config  Def  = y
    793 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    794 !Config         sinon  sinusoidale
    795        fxyhypbb = .TRUE.
    796        CALL getin('fxyhypb',fxyhypbb)
    797 
    798       IF( .NOT.fxyhypb )  THEN
    799          IF( fxyhypbb )     THEN
    800             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    801             write(lunout,*)' *** fxyhypb lu sur le fichier start est ',     &
    802      &       'F alors  qu il est  T  sur  run.def  ***'
     654     ENDIF
     655
     656     IF( grossismx.LT.1. )  THEN
     657        write(lunout,*) &
     658             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
     659        STOP
     660     ELSE
     661        alphax = 1. - 1./ grossismx
     662     ENDIF
     663
     664     IF( grossismy.LT.1. )  THEN
     665        write(lunout,*) &
     666             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
     667        STOP
     668     ELSE
     669        alphay = 1. - 1./ grossismy
     670     ENDIF
     671
     672     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
     673
     674     !    alphax et alphay sont les anciennes formulat. des grossissements
     675
     676     !Config  Key  = fxyhypb
     677     !Config  Desc = Fonction  hyperbolique
     678     !Config  Def  = y
     679     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     680     !Config         sinon  sinusoidale
     681     fxyhypbb = .TRUE.
     682     CALL getin('fxyhypb',fxyhypbb)
     683
     684     IF( .NOT.fxyhypb )  THEN
     685        IF( fxyhypbb )     THEN
     686           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     687           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
     688                'F alors  qu il est  T  sur  run.def  ***'
     689           STOP
     690        ENDIF
     691     ELSE
     692        IF( .NOT.fxyhypbb )   THEN
     693           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     694           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
     695                'T alors  qu il est  F  sur  run.def  ****  '
     696           STOP
     697        ENDIF
     698     ENDIF
     699
     700     !Config  Key  = dzoomx
     701     !Config  Desc = extension en longitude
     702     !Config  Def  = 0
     703     !Config  Help = extension en longitude  de la zone du zoom 
     704     !Config         ( fraction de la zone totale)
     705     dzoomxx = 0.0
     706     CALL getin('dzoomx',dzoomxx)
     707
     708     IF( fxyhypb )  THEN
     709        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
     710           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
     711                'run.def est differente de celle lue sur le fichier  start '
     712           STOP
     713        ENDIF
     714     ENDIF
     715
     716     !Config  Key  = dzoomy
     717     !Config  Desc = extension en latitude
     718     !Config  Def  = 0
     719     !Config  Help = extension en latitude de la zone  du zoom 
     720     !Config         ( fraction de la zone totale)
     721     dzoomyy = 0.0
     722     CALL getin('dzoomy',dzoomyy)
     723
     724     IF( fxyhypb )  THEN
     725        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
     726           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
     727                'run.def est differente de celle lue sur le fichier  start '
     728           STOP
     729        ENDIF
     730     ENDIF
     731
     732     !Config  Key  = taux
     733     !Config  Desc = raideur du zoom en  X
     734     !Config  Def  = 3
     735     !Config  Help = raideur du zoom en  X
     736     tauxx = 3.0
     737     CALL getin('taux',tauxx)
     738
     739     IF( fxyhypb )  THEN
     740        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
     741           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
     742                'run.def est differente de celle lue sur le fichier  start '
     743           STOP
     744        ENDIF
     745     ENDIF
     746
     747     !Config  Key  = tauyy
     748     !Config  Desc = raideur du zoom en  Y
     749     !Config  Def  = 3
     750     !Config  Help = raideur du zoom en  Y
     751     tauyy = 3.0
     752     CALL getin('tauy',tauyy)
     753
     754     IF( fxyhypb )  THEN
     755        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
     756           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
     757                'run.def est differente de celle lue sur le fichier  start '
     758           STOP
     759        ENDIF
     760     ENDIF
     761
     762     !c
     763     IF( .NOT.fxyhypb  )  THEN
     764
     765        !Config  Key  = ysinus
     766        !Config  IF   = !fxyhypb
     767        !Config  Desc = Fonction en Sinus
     768        !Config  Def  = y
     769        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     770        !Config         sinon y = latit.
     771        ysinuss = .TRUE.
     772        CALL getin('ysinus',ysinuss)
     773
     774        IF( .NOT.ysinus )  THEN
     775           IF( ysinuss )     THEN
     776              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     777              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
     778                   ' alors  qu il est  T  sur  run.def  ***'
    803779              STOP
    804          ENDIF
    805       ELSE
    806          IF( .NOT.fxyhypbb )   THEN
    807             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    808             write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',    &
    809      &        'T alors  qu il est  F  sur  run.def  ****  '
     780           ENDIF
     781        ELSE
     782           IF( .NOT.ysinuss )   THEN
     783              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     784              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
     785                   ' alors  qu il est  F  sur  run.def  ****  '
    810786              STOP
    811          ENDIF
    812       ENDIF
    813 !
    814 !Config  Key  = dzoomx
    815 !Config  Desc = extension en longitude
    816 !Config  Def  = 0
    817 !Config  Help = extension en longitude  de la zone du zoom 
    818 !Config         ( fraction de la zone totale)
    819        dzoomxx = 0.0
    820        CALL getin('dzoomx',dzoomxx)
    821 
    822       IF( fxyhypb )  THEN
    823        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    824         write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',         &
    825      &  'run.def est differente de celle lue sur le fichier  start '
     787           ENDIF
     788        ENDIF
     789     ENDIF ! of IF( .NOT.fxyhypb  )
     790  else
     791     !Config  Key  = clon
     792     !Config  Desc = centre du zoom, longitude
     793     !Config  Def  = 0
     794     !Config  Help = longitude en degres du centre
     795     !Config         du zoom
     796     clon = 0.
     797     CALL getin('clon',clon)
     798
     799     !Config  Key  = clat
     800     !Config  Desc = centre du zoom, latitude
     801     !Config  Def  = 0
     802     !Config  Help = latitude en degres du centre du zoom
     803     !Config         
     804     clat = 0.
     805     CALL getin('clat',clat)
     806
     807     !Config  Key  = grossismx
     808     !Config  Desc = zoom en longitude
     809     !Config  Def  = 1.0
     810     !Config  Help = facteur de grossissement du zoom,
     811     !Config         selon la longitude
     812     grossismx = 1.0
     813     CALL getin('grossismx',grossismx)
     814
     815     !Config  Key  = grossismy
     816     !Config  Desc = zoom en latitude
     817     !Config  Def  = 1.0
     818     !Config  Help = facteur de grossissement du zoom,
     819     !Config         selon la latitude
     820     grossismy = 1.0
     821     CALL getin('grossismy',grossismy)
     822
     823     IF( grossismx.LT.1. )  THEN
     824        write(lunout,*) &
     825             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    826826        STOP
    827        ENDIF
    828       ENDIF
    829 
    830 !Config  Key  = dzoomy
    831 !Config  Desc = extension en latitude
    832 !Config  Def  = 0
    833 !Config  Help = extension en latitude de la zone  du zoom 
    834 !Config         ( fraction de la zone totale)
    835        dzoomyy = 0.0
    836        CALL getin('dzoomy',dzoomyy)
    837 
    838       IF( fxyhypb )  THEN
    839        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    840         write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',          &
    841      & 'run.def est differente de celle lue sur le fichier  start '
     827     ELSE
     828        alphax = 1. - 1./ grossismx
     829     ENDIF
     830
     831     IF( grossismy.LT.1. )  THEN
     832        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
    842833        STOP
    843        ENDIF
    844       ENDIF
    845      
    846 !Config  Key  = taux
    847 !Config  Desc = raideur du zoom en  X
    848 !Config  Def  = 3
    849 !Config  Help = raideur du zoom en  X
    850        tauxx = 3.0
    851        CALL getin('taux',tauxx)
    852 
    853       IF( fxyhypb )  THEN
    854        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    855         write(lunout,*)'conf_gcm: La valeur de taux passee par ',           &
    856      & 'run.def est differente de celle lue sur le fichier  start '
    857         STOP
    858        ENDIF
    859       ENDIF
    860 
    861 !Config  Key  = tauyy
    862 !Config  Desc = raideur du zoom en  Y
    863 !Config  Def  = 3
    864 !Config  Help = raideur du zoom en  Y
    865        tauyy = 3.0
    866        CALL getin('tauy',tauyy)
    867 
    868       IF( fxyhypb )  THEN
    869        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    870         write(lunout,*)'conf_gcm: La valeur de tauy passee par ',           &
    871      & 'run.def est differente de celle lue sur le fichier  start '
    872         STOP
    873        ENDIF
    874       ENDIF
    875 
    876 cc
    877       IF( .NOT.fxyhypb  )  THEN
    878 
    879 !Config  Key  = ysinus
    880 !Config  IF   = !fxyhypb
    881 !Config  Desc = Fonction en Sinus
    882 !Config  Def  = y
    883 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    884 !Config         sinon y = latit.
    885        ysinuss = .TRUE.
    886        CALL getin('ysinus',ysinuss)
    887 
    888         IF( .NOT.ysinus )  THEN
    889           IF( ysinuss )     THEN
    890             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    891             write(lunout,*)' *** ysinus lu sur le fichier start est F',     &
    892      &       ' alors  qu il est  T  sur  run.def  ***'
    893             STOP
    894           ENDIF
    895         ELSE
    896           IF( .NOT.ysinuss )   THEN
    897             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    898             write(lunout,*)' *** ysinus lu sur le fichier start est T',     &
    899      &        ' alors  qu il est  F  sur  run.def  ****  '
    900               STOP
    901           ENDIF
    902         ENDIF
    903       ENDIF ! of IF( .NOT.fxyhypb  )
    904 
    905       endif ! etatinit
     834     ELSE
     835        alphay = 1. - 1./ grossismy
     836     ENDIF
     837
     838     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
     839
     840     !    alphax et alphay sont les anciennes formulat. des grossissements
     841
     842     !Config  Key  = fxyhypb
     843     !Config  Desc = Fonction  hyperbolique
     844     !Config  Def  = y
     845     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     846     !Config         sinon  sinusoidale
     847     fxyhypb = .TRUE.
     848     CALL getin('fxyhypb',fxyhypb)
     849
     850     !Config  Key  = dzoomx
     851     !Config  Desc = extension en longitude
     852     !Config  Def  = 0
     853     !Config  Help = extension en longitude  de la zone du zoom 
     854     !Config         ( fraction de la zone totale)
     855     dzoomx = 0.0
     856     CALL getin('dzoomx',dzoomx)
     857
     858     !Config  Key  = dzoomy
     859     !Config  Desc = extension en latitude
     860     !Config  Def  = 0
     861     !Config  Help = extension en latitude de la zone  du zoom 
     862     !Config         ( fraction de la zone totale)
     863     dzoomy = 0.0
     864     CALL getin('dzoomy',dzoomy)
     865
     866     !Config  Key  = taux
     867     !Config  Desc = raideur du zoom en  X
     868     !Config  Def  = 3
     869     !Config  Help = raideur du zoom en  X
     870     taux = 3.0
     871     CALL getin('taux',taux)
     872
     873     !Config  Key  = tauy
     874     !Config  Desc = raideur du zoom en  Y
     875     !Config  Def  = 3
     876     !Config  Help = raideur du zoom en  Y
     877     tauy = 3.0
     878     CALL getin('tauy',tauy)
     879
     880     !Config  Key  = ysinus
     881     !Config  IF   = !fxyhypb
     882     !Config  Desc = Fonction en Sinus
     883     !Config  Def  = y
     884     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     885     !Config         sinon y = latit.
     886     ysinus = .TRUE.
     887     CALL getin('ysinus',ysinus)
     888
     889  end IF test_etatinit
    906890!----------------------------------------
    907891
    908892
    909       write(lunout,*)' #########################################'
    910       write(lunout,*)' Configuration des parametres lus via run.def '
    911       write(lunout,*)' planet_type = ', planet_type
    912       write(lunout,*)' calend = ', calend
    913       write(lunout,*)' dayref = ', dayref
    914       write(lunout,*)' anneeref = ', anneeref
    915       write(lunout,*)' nday = ', nday
    916       if (ndynstep.ne.-9999) write(lunout,*)' ndynstep = ', ndynstep
    917       if (less1day) write(lunout,*)' fractday = ', fractday
    918       write(lunout,*)' day_step = ', day_step
    919       write(lunout,*)' iperiod = ', iperiod
    920       write(lunout,*)' nsplit_phys = ', nsplit_phys
    921       write(lunout,*)' iconser = ', iconser
    922       write(lunout,*)' iecri = ', iecri
    923       write(lunout,*)' periodav = ', periodav
    924       write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    925       write(lunout,*)' dissip_period = ', dissip_period
    926       write(lunout,*)' lstardis = ', lstardis
    927       write(lunout,*)' nitergdiv = ', nitergdiv
    928       write(lunout,*)' nitergrot = ', nitergrot
    929       write(lunout,*)' niterh = ', niterh
    930       write(lunout,*)' tetagdiv = ', tetagdiv
    931       write(lunout,*)' tetagrot = ', tetagrot
    932       write(lunout,*)' tetatemp = ', tetatemp
    933       write(lunout,*)' coefdis = ', coefdis
    934       write(lunout,*)' purmats = ', purmats
    935       write(lunout,*)' read_start = ', read_start
    936       write(lunout,*)' iflag_phys = ', iflag_phys
    937       write(lunout,*)' iphysiq = ', iphysiq
    938       write(lunout,*)' iflag_trac = ', iflag_trac
    939       write(lunout,*)' clon = ', clon
    940       write(lunout,*)' clat = ', clat
    941       write(lunout,*)' grossismx = ', grossismx
    942       write(lunout,*)' grossismy = ', grossismy
    943       write(lunout,*)' fxyhypb = ', fxyhypb
    944       write(lunout,*)' dzoomx = ', dzoomx
    945       write(lunout,*)' dzoomy = ', dzoomy
    946       write(lunout,*)' taux = ', taux
    947       write(lunout,*)' tauy = ', tauy
    948       write(lunout,*)' offline = ', offline
    949       write(lunout,*)' type_trac = ', type_trac
    950       write(lunout,*)' config_inca = ', config_inca
    951       write(lunout,*)' ok_dynzon = ', ok_dynzon
    952       write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    953       write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
    954       write(lunout,*)' ok_strato = ', ok_strato
    955       write(lunout,*)' ok_gradsfile = ', ok_gradsfile
    956       write(lunout,*)' ok_limit = ', ok_limit
    957       write(lunout,*)' ok_etat0 = ', ok_etat0
    958       if (planet_type=="titan") then
    959        write(lunout,*)' moyzon_mu = ', moyzon_mu
    960        write(lunout,*)' moyzon_ch = ', moyzon_ch
    961       endif
    962 
    963       RETURN
    964       END
     893 write(lunout,*)' #########################################'
     894 write(lunout,*)' Configuration des parametres lus via run.def '
     895 write(lunout,*)' planet_type = ', planet_type
     896 write(lunout,*)' calend = ', calend
     897 write(lunout,*)' dayref = ', dayref
     898 write(lunout,*)' anneeref = ', anneeref
     899 write(lunout,*)' nday = ', nday
     900 if (ndynstep.ne.-9999) write(lunout,*)' ndynstep = ', ndynstep
     901 if (less1day) write(lunout,*)' fractday = ', fractday
     902 write(lunout,*)' day_step = ', day_step
     903 write(lunout,*)' iperiod = ', iperiod
     904 write(lunout,*)' nsplit_phys = ', nsplit_phys
     905 write(lunout,*)' iconser = ', iconser
     906 write(lunout,*)' iecri = ', iecri
     907 write(lunout,*)' periodav = ', periodav
     908 write(lunout,*)' output_grads_dyn = ', output_grads_dyn
     909 write(lunout,*)' dissip_period = ', dissip_period
     910 write(lunout,*)' lstardis = ', lstardis
     911 write(lunout,*)' nitergdiv = ', nitergdiv
     912 write(lunout,*)' nitergrot = ', nitergrot
     913 write(lunout,*)' niterh = ', niterh
     914 write(lunout,*)' tetagdiv = ', tetagdiv
     915 write(lunout,*)' tetagrot = ', tetagrot
     916 write(lunout,*)' tetatemp = ', tetatemp
     917 write(lunout,*)' coefdis = ', coefdis
     918 write(lunout,*)' purmats = ', purmats
     919 write(lunout,*)' read_start = ', read_start
     920 write(lunout,*)' iflag_phys = ', iflag_phys
     921 write(lunout,*)' iphysiq = ', iphysiq
     922 write(lunout,*)' iflag_trac = ', iflag_trac
     923 write(lunout,*)' clon = ', clon
     924 write(lunout,*)' clat = ', clat
     925 write(lunout,*)' grossismx = ', grossismx
     926 write(lunout,*)' grossismy = ', grossismy
     927 write(lunout,*)' fxyhypb = ', fxyhypb
     928 write(lunout,*)' dzoomx = ', dzoomx
     929 write(lunout,*)' dzoomy = ', dzoomy
     930 write(lunout,*)' taux = ', taux
     931 write(lunout,*)' tauy = ', tauy
     932 write(lunout,*)' offline = ', offline
     933 write(lunout,*)' type_trac = ', type_trac
     934 write(lunout,*)' config_inca = ', config_inca
     935 write(lunout,*)' ok_dynzon = ', ok_dynzon
     936 write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
     937 write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
     938 write(lunout,*)' ok_strato = ', ok_strato
     939 write(lunout,*)' ok_gradsfile = ', ok_gradsfile
     940 write(lunout,*)' ok_limit = ', ok_limit
     941 write(lunout,*)' ok_etat0 = ', ok_etat0
     942 if (planet_type=="titan") then
     943   write(lunout,*)' moyzon_mu = ', moyzon_mu
     944   write(lunout,*)' moyzon_ch = ', moyzon_ch
     945 endif
     946
     947END SUBROUTINE conf_gcm
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r1302 r1391  
    180180!#ifdef CPP_IOIPSL
    181181      CALL conf_gcm( 99, .TRUE. )
     182      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
     183     s "iphysiq must be a multiple of iperiod", 1)
    182184!#else
    183185!      CALL defrun( 99, .TRUE. , clesphy0 )
  • trunk/LMDZ.COMMON/libf/dyn3d/getparam.F90

    r1 r1391  
    1111
    1212   INTERFACE getpar
    13      MODULE PROCEDURE ini_getparam,fin_getparam,getparamr,getparami,getparaml
     13     MODULE PROCEDURE getparamr,getparami,getparaml
    1414   END INTERFACE
     15   private getparamr,getparami,getparaml
    1516
    1617   INTEGER, PARAMETER :: out_eff=99
  • trunk/LMDZ.COMMON/libf/dyn3d/guide_mod.F90

    r1302 r1391  
    7171    INCLUDE "netcdf.inc"
    7272
     73    ! For grossismx:
     74    include "serre.h"
     75
    7376    INTEGER                :: error,ncidpl,rid,rcod
    7477    CHARACTER (len = 80)   :: abort_message
     
    8790    CALL getpar('guide_teta',.false.,guide_teta,'guidage de T par Teta')
    8891
    89     CALL getpar('guide_add',.false.,guide_add,'for�age constant?')
     92    CALL getpar('guide_add',.false.,guide_add,'forage constant?')
    9093    CALL getpar('guide_zon',.false.,guide_zon,'guidage moy zonale')
     94    if (guide_zon .and. abs(grossismx - 1.) > 0.01) &
     95         call abort_gcm("guide_init", &
     96         "zonal nudging requires grid regular in longitude", 1)
    9197
    9298!   Constantes de rappel. Unite : fraction de jour
     
    104110    CALL getpar('guide_BL',.true.,guide_BL,'guidage dans C.Lim')
    105111   
    106 ! Sauvegarde du for�age
     112! Sauvegarde du forage
    107113    CALL getpar('guide_sav',.false.,guide_sav,'sauvegarde guidage')
    108114    CALL getpar('iguide_sav',4,iguide_sav,'freq. sauvegarde guidage')
    109115    ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois.
    110116    IF (iguide_sav.GT.0) THEN
    111         iguide_sav=day_step/iguide_sav
     117       iguide_sav=day_step/iguide_sav
     118    ELSE if (iguide_sav == 0) then
     119       iguide_sav = huge(0)
    112120    ELSE
    113         iguide_sav=day_step*iguide_sav
     121       iguide_sav=day_step*iguide_sav
    114122    ENDIF
    115123
     
    125133! Parametres pour lecture des fichiers
    126134    CALL getpar('iguide_read',4,iguide_read,'freq. lecture guidage')
    127     CALL getpar('iguide_int',4,iguide_int,'freq. lecture guidage')
    128     IF (iguide_int.GT.0) THEN
     135    CALL getpar('iguide_int',4,iguide_int,'freq. interpolation vert')
     136    IF (iguide_int.EQ.0) THEN
     137        iguide_int=1
     138    ELSEIF (iguide_int.GT.0) THEN
    129139        iguide_int=day_step/iguide_int
    130140    ELSE
     
    10031013    ENDIF ! guide_reg
    10041014
     1015    if (.not. guide_add) alpha = 1. - exp(- alpha)
     1016
    10051017  END SUBROUTINE tau2alpha
    10061018
     
    15781590#endif
    15791591! --------------------------------------------------------------------
    1580 ! Cr�ation des variables sauvegard�es
     1592! Cr�ation des variables sauvegard�es
    15811593! --------------------------------------------------------------------
    15821594        ierr = NF_REDEF(nid)
     
    16811693!===========================================================================
    16821694END MODULE guide_mod
    1683 
  • trunk/LMDZ.COMMON/libf/dyn3d/integrd.F

    r907 r1391  
    109109         write(lunout,*) " psm1(ij)=",psm1(ij)," dt=",dt,
    110110     &                   " dp(ij)=",dp(ij)
    111          stop
     111         call abort_gcm("integrd", "", 1)
    112112        ENDIF
    113113      ENDDO
  • trunk/LMDZ.COMMON/libf/dyn3d_common/disvert.F90

    r1302 r1391  
    2727!-------------------------------------------------------------------------------
    2828! Read    in "comvert.h":
    29 ! pa                         !--- PURE PRESSURE COORDINATE FOR P<pa (in Pascals)
     29
     30! pa !--- vertical coordinate is close to a PRESSURE COORDINATE FOR P
     31! < 0.3 * pa (relative variation of p on a model level is < 0.1 %)
     32
    3033! preff                      !--- REFERENCE PRESSURE                 (101325 Pa)
    3134! Written in "comvert.h":
  • trunk/LMDZ.COMMON/libf/dyn3d_common/grid_atob.F

    r1300 r1391  
    11!
    2 ! $Id: grid_atob.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: grid_atob.F 2197 2015-02-09 07:13:05Z emillour $
    33!
    44      SUBROUTINE grille_m(imdep, jmdep, xdata, ydata, entree,
     
    5252      REAL zzmin
    5353#endif
     54      include "iniprint.h"
    5455c
    5556      IF (imar.GT.2200 .OR. jmar.GT.1100) THEN
     
    118119         sortie(i,j) = sortie(i,j) / number(i,j)
    119120         ELSE
    120          PRINT*, 'probleme,i,j=', i,j
     121         if (prt_level >= 1) PRINT*, 'probleme,i,j=', i,j
    121122ccc         CALL ABORT_GCM("", "", 1)
    122123         CALL dist_sphe(x(i),y(j),xdata,ydata,imdep,jmdep,distans)
     
    135136         j_proche = (ij_proche-1)/imdep + 1
    136137         i_proche = ij_proche - (j_proche-1)*imdep
    137          PRINT*, "solution:", ij_proche, i_proche, j_proche
     138         if (prt_level >= 1) PRINT*, "solution:", ij_proche, i_proche,
     139     $        j_proche
    138140         sortie(i,j) = entree(i_proche,j_proche)
    139141         ENDIF
     
    258260            PRINT*, 'Probleme grave,i,j,indx,indy=',
    259261     .              i,j,indx(i,j),indy(i,j)
    260             CALL abort_gcm("", "", 1)
     262            call abort_gcm("", "", 1)
    261263         ENDIF
    262264      ENDDO
     
    449451      REAL zzmin
    450452#endif
     453      include "iniprint.h"
    451454c
    452455      IF (imar.GT.400 .OR. jmar.GT.400) THEN
     
    512515            sortie(i,j) = EXP(sortie(i,j))
    513516         ELSE
    514             PRINT*, 'probleme,i,j=', i,j
     517            if (prt_level >= 1) PRINT*, 'probleme,i,j=', i,j
    515518ccc            CALL ABORT_GCM("", "", 1)
    516519         CALL dist_sphe(x(i),y(j),xdata,ydata,imdep,jmdep,distans)
     
    529532         j_proche = (ij_proche-1)/imdep + 1
    530533         i_proche = ij_proche - (j_proche-1)*imdep
    531          PRINT*, "solution:", ij_proche, i_proche, j_proche
     534         if (prt_level >= 1) PRINT*, "solution:", ij_proche, i_proche,
     535     $        j_proche
    532536         sortie(i,j) = entree(i_proche,j_proche)
    533537         ENDIF
     
    574578      REAL zzmin
    575579#endif
     580      include "iniprint.h"
    576581c
    577582      IF (imar.GT.400 .OR. jmar.GT.400) THEN
     
    641646           ENDIF
    642647         ELSE
    643            PRINT*, 'probleme,i,j=', i,j
     648           if (prt_level >= 1) PRINT*, 'probleme,i,j=', i,j
    644649ccc           CALL ABORT_GCM("", "", 1)
    645650         CALL dist_sphe(x(i),y(j),xdata,ydata,imdep,jmdep,distans)
     
    658663         j_proche = (ij_proche-1)/imdep + 1
    659664         i_proche = ij_proche - (j_proche-1)*imdep
    660          PRINT*, "solution:", ij_proche, i_proche, j_proche
     665         if (prt_level >= 1) PRINT*, "solution:", ij_proche, i_proche,
     666     $        j_proche
    661667         IF (NINT(glace01(i_proche,j_proche)).EQ.1 ) THEN
    662668            frac_ice(i,j) = 1.0
     
    710716      INTEGER i_proche, j_proche, ij_proche
    711717c
     718      include "iniprint.h"
     719
    712720      IF (immod.GT.2200 .OR. jmmod.GT.1100) THEN
    713721         PRINT*, 'immod ou jmmod trop grand', immod, jmmod
     
    874882         rugs(i,j) = EXP(rugs(i,j))
    875883         ELSE
    876          PRINT*, 'probleme,i,j=', i,j
     884         if (prt_level >= 1) PRINT*, 'probleme,i,j=', i,j
    877885ccc         CALL ABORT_GCM("", "", 1)
    878886         CALL dist_sphe(xmod(i),ymod(j),xtmp,ytmp,imtmp,jmtmp,distans)
     
    891899         j_proche = (ij_proche-1)/imtmp + 1
    892900         i_proche = ij_proche - (j_proche-1)*imtmp
    893          PRINT*, "solution:", ij_proche, i_proche, j_proche
     901         if (prt_level >= 1) PRINT*, "solution:", ij_proche, i_proche,
     902     $        j_proche
    894903         rugs(i,j) = LOG(MAX(0.001_8,cham2tmp(i_proche,j_proche)))
    895904         ENDIF
     
    927936c
    928937      SUBROUTINE dist_sphe(rf_lon,rf_lat,rlon,rlat,im,jm,distance)
     938      IMPLICIT NONE
    929939c
    930940c Auteur: Laurent Li (le 30 decembre 1996)
     
    949959      REAL radius
    950960      PARAMETER (radius=6371229.)
     961      INTEGER i,j
    951962c
    952963      pi = 4.0 * ATAN(1.0)
  • trunk/LMDZ.COMMON/libf/dyn3d_common/infotrac.F90

    r1300 r1391  
    55! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
    66  INTEGER, SAVE :: nqtot
     7! CR: add number of tracers for water (for Earth model only!!)
     8  INTEGER, SAVE :: nqo
    79
    810! nbtr : number of tracers not including higher order of moment or water vapor or liquid
     
    2729
    2830  CHARACTER(len=4),SAVE :: type_trac
     31  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
    2932 
    3033CONTAINS
     
    6063
    6164    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    62     CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tracnam ! name from INCA
    6365    CHARACTER(len=3), DIMENSION(30) :: descrq
    6466    CHARACTER(len=1), DIMENSION(3)  :: txts
     
    9496       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
    9597            type_trac,' config_inca=',config_inca
    96        IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     98       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
    9799          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
    98100          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     
    179181!
    180182    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
    181     ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
     183    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
    182184    conv_flg(:) = 1 ! convection activated for all tracers
    183185    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
     
    240242       END IF
    241243       
     244!CR: nombre de traceurs de l eau
     245       if (tnom_0(3) == 'H2Oi') then
     246          nqo=3
     247       else
     248          nqo=2
     249       endif
     250
    242251       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
    243252       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
     
    262271
    263272       DO iq =3,nqtrue
    264           tnom_0(iq)=tracnam(iq-2)
     273          tnom_0(iq)=solsym(iq-2)
    265274       END DO
     275       nqo = 2
    266276
    267277     END IF ! type_trac
     
    430440!
    431441    DEALLOCATE(tnom_0, hadv, vadv)
    432     DEALLOCATE(tracnam)
     442
    433443
    434444  END SUBROUTINE infotrac_init
  • trunk/LMDZ.COMMON/libf/dyn3d_common/iniacademic.F90

    r1302 r1391  
    44SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
    6   USE filtreg_mod
     6  USE filtreg_mod, ONLY: inifilr
    77  USE infotrac, ONLY : nqtot
    88  USE control_mod, ONLY: day_step,planet_type
    99#ifdef CPP_IOIPSL
    10   USE IOIPSL
     10  USE IOIPSL, ONLY: getin
    1111#else
    1212  ! if not using IOIPSL, we still need to use (a local version of) getin
    13   USE ioipsl_getincom
     13  USE ioipsl_getincom, ONLY: getin
    1414#endif
    1515  USE Write_Field
     
    4040  !   ----------
    4141
    42   real time_0
    43 
    44   !   variables dynamiques
    45   REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    46   REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    47   REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    48   REAL ps(ip1jmp1)                       ! pression  au sol
    49   REAL masse(ip1jmp1,llm)                ! masse d'air
    50   REAL phis(ip1jmp1)                     ! geopotentiel au sol
     42  REAL,INTENT(OUT) :: time_0
     43
     44  !   fields
     45  REAL,INTENT(OUT) :: vcov(ip1jm,llm) ! meridional covariant wind
     46  REAL,INTENT(OUT) :: ucov(ip1jmp1,llm) ! zonal covariant wind
     47  REAL,INTENT(OUT) :: teta(ip1jmp1,llm) ! potential temperature (K)
     48  REAL,INTENT(OUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers (.../kg_of_air)
     49  REAL,INTENT(OUT) :: ps(ip1jmp1) ! surface pressure (Pa)
     50  REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass in grid cell (kg)
     51  REAL,INTENT(OUT) :: phis(ip1jmp1) ! surface geopotential
    5152
    5253  !   Local:
     
    7677  character(len=80) :: abort_message
    7778
     79
     80  ! Sanity check: verify that options selected by user are not incompatible
     81  if ((iflag_phys==1).and. .not. read_start) then
     82    write(lunout,*) trim(modname)," error: if read_start is set to ", &
     83    " false then iflag_phys should not be 1"
     84    write(lunout,*) "You most likely want an aquaplanet initialisation", &
     85    " (iflag_phys >= 100)"
     86    call abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.false.",1)
     87  endif
     88 
    7889  !-----------------------------------------------------------------------
    7990  ! 1. Initializations for Earth-like case
  • trunk/LMDZ.COMMON/libf/dyn3d_common/interpre.F

    r1300 r1391  
    2929      real   masse(iip1,jjp1,llm)
    3030      real   massebx(iip1,jjp1,llm),masseby(iip1,jjm,llm)     
    31       real   w(iip1,jjp1,llm+1)
     31      real   w(iip1,jjp1,llm)
    3232      real   fluxwppm(iim,jjp1,llm)
    3333      real   pbaru(iip1,jjp1,llm )
  • trunk/LMDZ.COMMON/libf/dyn3d_common/juldate.F

    r1300 r1391  
    11!
    2 ! $Id: juldate.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: juldate.F 2197 2015-02-09 07:13:05Z emillour $
    33!
    44        subroutine juldate(ian,imoi,ijou,oh,om,os,tjd,tjdsec)
     
    77c       En entree:an,mois,jour,heure,min.,sec.
    88c       En sortie:tjd
    9         implicit real (a-h,o-z)
     9        IMPLICIT NONE
     10        INTEGER,INTENT(IN) :: ian,imoi,ijou,oh,om,os
     11        REAL,INTENT(OUT) :: tjd,tjdsec
     12       
     13        REAL frac,year,rmon,cf,a,b
     14        INTEGER ojou
     15       
    1016        frac=((os/60.+om)/60.+oh)/24.
    1117        ojou=dble(ijou)+frac
  • trunk/LMDZ.COMMON/libf/dyn3d_common/massbar.F

    r1300 r1391  
    33!
    44      SUBROUTINE massbar(  masse, massebx, masseby )
     5      IMPLICIT NONE
    56c
    67c **********************************************************************
     
    2425      REAL    masse( ip1jmp1,llm ), massebx( ip1jmp1,llm )  ,
    2526     *      masseby(   ip1jm,llm )
     27      INTEGER ij,l
    2628c
    2729c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/massbarxy.F

    r1300 r1391  
    33!
    44      SUBROUTINE massbarxy(  masse, massebxy )
     5      IMPLICIT NONE
    56c
    67c **********************************************************************
     
    2324c
    2425       REAL  masse( ip1jmp1,llm ), massebxy( ip1jm,llm )
     26       INTEGER ij,l
    2527c
    2628
  • trunk/LMDZ.COMMON/libf/dyn3d_common/ppm3d.F

    r1300 r1391  
    11!
    2 ! $Id: ppm3d.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: ppm3d.F 2197 2015-02-09 07:13:05Z emillour $
    33!
    44
     
    6666     &                  JNP,j1,NLAY,AP,BP,PT,AE,fill,dum,Umax)
    6767
    68 c      implicit none
     68      implicit none
    6969
    7070c     rajout de déclarations
     
    270270C     User modifiable parameters
    271271C
    272       parameter (Jmax = 361, kmax = 150)
     272      integer,parameter :: Jmax = 361, kmax = 150
    273273C
    274274C ****6***0*********0*********0*********0*********0*********0**********72
     
    299299      data NDT0, NSTEP /0, 0/
    300300      data cross /.true./
     301      REAL DTDY, DTDY5, RCAP
     302      INTEGER JS0, JN0, IML, JMR, IMJM
    301303      SAVE DTDY, DTDY5, RCAP, JS0, JN0, IML,
    302304     &     DTDX, DTDX5, ACOSP, COSP, COSE, DAP,DBK
    303305C
     306      INTEGER NDT0, NSTEP, j2, k,j,i,ic,l,JS,JN,IMH
     307      INTEGER IU,IIU,JT,iad,jad,krd
     308      REAL r23,r3,PI,DL,DP,DT,CR1,MAXDT,ZTC,D5
     309      REAL sum1,sum2,ru
    304310           
    305311      JMR = JNP -1
     
    756762      subroutine FZPPM(IMR,JNP,NLAY,j1,DQ,WZ,P,DC,DQDT,AR,AL,A6,
    757763     &                 flux,wk1,wk2,wz2,delp,KORD)
    758       parameter ( kmax = 150 )
    759       parameter ( R23 = 2./3., R3 = 1./3.)
     764      implicit none
     765      integer,parameter :: kmax = 150
     766      real,parameter :: R23 = 2./3., R3 = 1./3.
     767      integer IMR,JNP,NLAY,J1,KORD
    760768      real WZ(IMR,JNP,NLAY),P(IMR,JNP,NLAY),DC(IMR,JNP,NLAY),
    761769     &     wk1(IMR,*),delp(IMR,JNP,NLAY),DQ(IMR,JNP,NLAY),
     
    764772      real AR(IMR,*),AL(IMR,*),A6(IMR,*),flux(IMR,*),wk2(IMR,*),
    765773     &     wz2(IMR,*)
     774      integer JMR,IMJM,NLAYM1,LMT,K,I,J
     775      real c0,c1,c2,tmp,qmax,qmin,a,b,fct,a1,a2,cm,cp
    766776C
    767777      JMR = JNP - 1
     
    922932      subroutine xtp(IMR,JNP,IML,j1,j2,JN,JS,PU,DQ,Q,UC,
    923933     &               fx1,xmass,IORD)
     934      implicit none
     935      integer IMR,JNP,IML,j1,j2,JN,JS,IORD
     936      real PU,DQ,Q,UC,fx1,xmass
     937      real dc,qtmp
     938      integer ISAVE(IMR)
    924939      dimension UC(IMR,*),DC(-IML:IMR+IML+1),xmass(IMR,JNP)
    925940     &    ,fx1(IMR+1),DQ(IMR,JNP),qtmp(-IML:IMR+1+IML)
    926       dimension PU(IMR,JNP),Q(IMR,JNP),ISAVE(IMR)
     941      dimension PU(IMR,JNP),Q(IMR,JNP)
     942      integer jvan,j1vl,j2vl,j,i,iu,itmp,ist,imp
     943      real rut
    927944C
    928945      IMP = IMR + 1
     
    10311048C
    10321049      subroutine fxppm(IMR,IML,UT,P,DC,flux,IORD)
    1033       parameter ( R3 = 1./3., R23 = 2./3. )
     1050      implicit none
     1051      integer IMR,IML,IORD
     1052      real UT,P,DC,flux
     1053      real,parameter ::  R3 = 1./3., R23 = 2./3.
    10341054      DIMENSION UT(*),flux(*),P(-IML:IMR+IML+1),DC(-IML:IMR+IML+1)
    1035       DIMENSION AR(0:IMR),AL(0:IMR),A6(0:IMR)
    1036       integer LMT 
     1055      REAL :: AR(0:IMR),AL(0:IMR),A6(0:IMR)
     1056      integer LMT,IMP,JLVL,i
    10371057c      logical first
    10381058c      data first /.true./
     
    10881108C
    10891109      subroutine xmist(IMR,IML,P,DC)
    1090       parameter( R24 = 1./24.)
    1091       dimension P(-IML:IMR+1+IML),DC(-IML:IMR+1+IML)
     1110      implicit none
     1111      integer IMR,IML
     1112      real,parameter :: R24 = 1./24.
     1113      real :: P(-IML:IMR+1+IML),DC(-IML:IMR+1+IML)
     1114      integer :: i
     1115      real :: tmp,pmax,pmin
    10921116C
    10931117      do 10  i=1,IMR
     
    11011125      subroutine ytp(IMR,JNP,j1,j2,acosp,RCAP,DQ,P,VC,DC2
    11021126     &              ,ymass,fx,A6,AR,AL,JORD)
     1127      implicit none
     1128      integer :: IMR,JNP,j1,j2,JORD
     1129      real :: acosp,RCAP,DQ,P,VC,DC2,ymass,fx,A6,AR,AL
    11031130      dimension P(IMR,JNP),VC(IMR,JNP),ymass(IMR,JNP)
    11041131     &       ,DC2(IMR,JNP),DQ(IMR,JNP),acosp(JNP)
    11051132C Work array
    11061133      DIMENSION fx(IMR,JNP),AR(IMR,JNP),AL(IMR,JNP),A6(IMR,JNP)
     1134      integer :: JMR,len,i,jt,j
     1135      real :: sum1,sum2
    11071136C
    11081137      JMR = JNP - 1
     
    11611190C
    11621191      subroutine  ymist(IMR,JNP,j1,P,DC,ID)
    1163       parameter ( R24 = 1./24. )
    1164       dimension P(IMR,JNP),DC(IMR,JNP)
     1192      implicit none
     1193      integer :: IMR,JNP,j1,ID
     1194      real,parameter :: R24 = 1./24.
     1195      real :: P(IMR,JNP),DC(IMR,JNP)
     1196      integer :: iimh,jmr,ijm3,imh,i
     1197      real :: pmax,pmin,tmp
    11651198C
    11661199      IMH = IMR / 2
     
    12391272C
    12401273      subroutine fyppm(VC,P,DC,flux,IMR,JNP,j1,j2,A6,AR,AL,JORD)
    1241       parameter ( R3 = 1./3., R23 = 2./3. )
     1274      implicit none
     1275      integer IMR,JNP,j1,j2,JORD
     1276      real,parameter :: R3 = 1./3., R23 = 2./3.
    12421277      real VC(IMR,*),flux(IMR,*),P(IMR,*),DC(IMR,*)
    12431278C Local work arrays.
    12441279      real AR(IMR,JNP),AL(IMR,JNP),A6(IMR,JNP)
    1245       integer LMT
     1280      integer LMT,i
     1281      integer IMH,JMR,j11,IMJM1,len
    12461282c      logical first
    12471283C      data first /.true./
     
    13151351C
    13161352        subroutine yadv(IMR,JNP,j1,j2,p,VA,ady,wk,IAD)
     1353        implicit none
     1354        integer IMR,JNP,j1,j2,IAD
    13171355        REAL p(IMR,JNP),ady(IMR,JNP),VA(IMR,JNP)
    13181356        REAL WK(IMR,-1:JNP+2)
     1357        INTEGER JMR,IMH,i,j,jp
     1358        REAL rv,a1,b1,sum1,sum2
    13191359C
    13201360        JMR = JNP-1
     
    14011441C
    14021442        subroutine xadv(IMR,JNP,j1,j2,p,UA,JS,JN,IML,adx,IAD)
     1443        implicit none
     1444        INTEGER IMR,JNP,j1,j2,JS,JN,IML,IAD
    14031445        REAL p(IMR,JNP),adx(IMR,JNP),qtmp(-IMR:IMR+IMR),UA(IMR,JNP)
     1446        INTEGER JMR,j,i,ip,iu,iiu
     1447        REAL ru,a1,b1
    14041448C
    14051449        JMR = JNP-1
     
    14891533C
    14901534      subroutine lmtppm(DC,A6,AR,AL,P,IM,LMT)
     1535      implicit none
    14911536C
    14921537C A6 =  CURVATURE OF THE TEST PARABOLA
     
    15031548C LMT = 2: POSITIVE-DEFINITE CONSTRAINT
    15041549C
    1505       parameter ( R12 = 1./12. )
    1506       dimension A6(IM),AR(IM),AL(IM),P(IM),DC(IM)
     1550      real,parameter :: R12 = 1./12.
     1551      real :: A6(IM),AR(IM),AL(IM),P(IM),DC(IM)
     1552      integer :: IM,LMT
     1553      INTEGER i
     1554      REAL da1,da2,a6da,fmin
    15071555C
    15081556      if(LMT.eq.0) then
     
    15641612C
    15651613      subroutine A2C(U,V,IMR,JMR,j1,j2,CRX,CRY,dtdx5,DTDY5)
    1566       dimension U(IMR,*),V(IMR,*),CRX(IMR,*),CRY(IMR,*),DTDX5(*)
     1614      implicit none
     1615      integer IMR,JMR,j1,j2
     1616      real :: U(IMR,*),V(IMR,*),CRX(IMR,*),CRY(IMR,*),DTDX5(*),DTDY5
     1617      integer i,j
    15671618C
    15681619      do 35 j=j1,j2
     
    15791630C
    15801631      subroutine cosa(cosp,cose,JNP,PI,DP)
    1581       dimension cosp(*),cose(*)
     1632      implicit none
     1633      integer JNP
     1634      real :: cosp(*),cose(*),PI,DP
     1635      integer JMR,j,jeq
     1636      real ph5
    15821637      JMR = JNP-1
    15831638      do 55 j=2,JNP
     
    16061661C
    16071662      subroutine cosc(cosp,cose,JNP,PI,DP)
    1608       dimension cosp(*),cose(*)
     1663      implicit none
     1664      integer JNP
     1665      real :: cosp(*),cose(*),PI,DP
     1666      real phi
     1667      integer j
    16091668C
    16101669      phi = -0.5*PI
     
    16281687     &                   cross,IC,NSTEP)
    16291688C
    1630       parameter( tiny = 1.E-60 )
    1631       DIMENSION Q(IMR,JNP,NLAY),qtmp(IMR,JNP),cosp(*),acosp(*)
     1689      real,parameter :: tiny = 1.E-60
     1690      INTEGER :: IMR,JNP,NLAY,j1,j2,IC,NSTEP
     1691      REAL :: Q(IMR,JNP,NLAY),qtmp(IMR,JNP),cosp(*),acosp(*)
    16321692      logical cross
     1693      INTEGER :: NLAYM1,len,ip,L,icr,ipy,ipx,i
     1694      real :: qup,qly,dup,sum
    16331695C
    16341696      NLAYM1 = NLAY-1
     
    17301792C
    17311793      subroutine filcr(q,IMR,JNP,j1,j2,cosp,acosp,icr,tiny)
    1732       dimension q(IMR,*),cosp(*),acosp(*)
     1794      implicit none
     1795      integer :: IMR,JNP,j1,j2,icr
     1796      real :: q(IMR,*),cosp(*),acosp(*),tiny
     1797      integer :: i,j
     1798      real :: dq,dn,d0,d1,ds,d2
    17331799      icr = 0
    17341800      do 65 j=j1+1,j2-1
     
    18281894C
    18291895      subroutine filns(q,IMR,JNP,j1,j2,cosp,acosp,ipy,tiny)
    1830       dimension q(IMR,*),cosp(*),acosp(*)
     1896      implicit none
     1897      integer :: IMR,JNP,j1,j2,ipy
     1898      real :: q(IMR,*),cosp(*),acosp(*),tiny
     1899      real :: DP,CAP1,dq,dn,d0,d1,ds,d2
     1900      INTEGER :: i,j
    18311901c      logical first
    18321902c      data first /.true./
     
    19101980C
    19111981      subroutine filew(q,qtmp,IMR,JNP,j1,j2,ipx,tiny)
    1912       dimension q(IMR,*),qtmp(JNP,IMR)
     1982      implicit none
     1983      integer :: IMR,JNP,j1,j2,ipx
     1984      real :: q(IMR,*),qtmp(JNP,IMR),tiny
     1985      integer :: i,j
     1986      real :: d0,d1,d2
    19131987C
    19141988      ipx = 0
     
    19832057C
    19842058      subroutine zflip(q,im,km,nc)
     2059      implicit none
    19852060C This routine flip the array q (in the vertical).
     2061      integer :: im,km,nc
    19862062      real q(im,km,nc)
    19872063C local dynamic array
    19882064      real qtmp(im,km)
     2065      integer IC,k,i
    19892066C
    19902067      do 4000 IC = 1, nc
  • trunk/LMDZ.COMMON/libf/dyn3d_common/ran1.F

    r1300 r1391  
    11!
    2 ! $Id: ran1.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: ran1.F 2197 2015-02-09 07:13:05Z emillour $
    33!
    44      FUNCTION RAN1(IDUM)
    5       DIMENSION R(97)
    6       save r
    7       save iff,ix1,ix2,ix3
    8       PARAMETER (M1=259200,IA1=7141,IC1=54773,RM1=3.8580247E-6)
    9       PARAMETER (M2=134456,IA2=8121,IC2=28411,RM2=7.4373773E-6)
    10       PARAMETER (M3=243000,IA3=4561,IC3=51349)
    11       DATA IFF /0/
     5      IMPLICIT NONE
     6      REAL RAN1
     7      REAL,SAVE :: R(97)
     8      REAL,PARAMETER :: RM1=3.8580247E-6,RM2=7.4373773E-6
     9      INTEGER,SAVE :: IFF=0
     10      integer,save :: ix1,ix2,ix3
     11      INTEGER,PARAMETER :: M1=259200,IA1=7141,IC1=54773
     12      INTEGER,PARAMETER :: M2=134456,IA2=8121,IC2=28411
     13      INTEGER,PARAMETER :: M3=243000,IA3=4561,IC3=51349
     14      INTEGER :: IDUM,J
     15
    1216      IF (IDUM.LT.0.OR.IFF.EQ.0) THEN
    1317        IFF=1
  • trunk/LMDZ.COMMON/libf/dyn3d_common/sortvarc.F

    r1300 r1391  
    11!
    2 ! $Id: sortvarc.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: sortvarc.F 2083 2014-07-09 14:43:31Z emillour $
    33!
    44      SUBROUTINE sortvarc
     
    66     $ vcov )
    77
    8       use control_mod,only:resetvarc
     8      USE control_mod, ONLY: resetvarc
    99      IMPLICIT NONE
     10
    1011
    1112c=======================================================================
     
    2425c   -------------
    2526
    26 #include "dimensions.h"
    27 #include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    30 #include "comgeom.h"
    31 #include "ener.h"
    32 #include "logic.h"
    33 #include "temps.h"
     27      INCLUDE "dimensions.h"
     28      INCLUDE "paramet.h"
     29      INCLUDE "comconst.h"
     30      INCLUDE "comvert.h"
     31      INCLUDE "comgeom.h"
     32      INCLUDE "ener.h"
     33      INCLUDE "logic.h"
     34      INCLUDE "temps.h"
     35      INCLUDE "iniprint.h"
    3436
    3537c   Arguments:
    3638c   ----------
    3739
    38       INTEGER itau
    39       REAL ucov(ip1jmp1,llm),teta(ip1jmp1,llm),masse(ip1jmp1,llm)
    40       REAL vcov(ip1jm,llm)
    41       REAL ps(ip1jmp1),phis(ip1jmp1)
    42       REAL vorpot(ip1jm,llm)
    43       REAL phi(ip1jmp1,llm),bern(ip1jmp1,llm)
    44       REAL dp(ip1jmp1)
    45       REAL time
    46       REAL pk(ip1jmp1,llm)
     40      INTEGER,INTENT(IN) :: itau
     41      REAL,INTENT(IN) :: ucov(ip1jmp1,llm)
     42      REAL,INTENT(IN) :: teta(ip1jmp1,llm)
     43      REAL,INTENT(IN) :: masse(ip1jmp1,llm)
     44      REAL,INTENT(IN) :: vcov(ip1jm,llm)
     45      REAL,INTENT(IN) :: ps(ip1jmp1)
     46      REAL,INTENT(IN) :: phis(ip1jmp1)
     47      REAL,INTENT(IN) :: vorpot(ip1jm,llm)
     48      REAL,INTENT(IN) :: phi(ip1jmp1,llm)
     49      REAL,INTENT(IN) :: bern(ip1jmp1,llm)
     50      REAL,INTENT(IN) :: dp(ip1jmp1)
     51      REAL,INTENT(IN) :: time
     52      REAL,INTENT(IN) :: pk(ip1jmp1,llm)
    4753
    4854c   Local:
     
    5763
    5864      REAL       SSUM
    59 
    60       logical  firstcal
    61       data     firstcal/.true./
    62       save     firstcal
     65      LOGICAL,SAVE :: firstcal=.true.
     66      CHARACTER(LEN=*),PARAMETER :: modname="sortvarc"
    6367
    6468c-----------------------------------------------------------------------
     
    143147
    144148      IF (firstcal.and.resetvarc) then
    145          PRINT 3500, itau, rjour, heure,time
    146          PRINT*,'WARNING!!! On recalcule les valeurs initiales de :'
    147          PRINT*,'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
    148          PRINT *, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
     149         WRITE(lunout,3500) itau, rjour, heure, time
     150         WRITE(lunout,*) trim(modname),
     151     &     ' WARNING!!! Recomputing initial values of : '
     152         WRITE(lunout,*) 'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
     153         WRITE(lunout,*) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
    149154         etot0 = etot
    150155         ptot0 = ptot
     
    185190      firstcal = .false.
    186191
    187       PRINT 3500, itau, rjour, heure, time
    188       PRINT 4000, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
    189 
    190       RETURN
     192      WRITE(lunout,3500) itau, rjour, heure, time
     193      WRITE(lunout,4000) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
    191194
    1921953500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x
  • trunk/LMDZ.COMMON/libf/dyn3dpar/abort_gcm.F

    r1300 r1391  
    2727C         ierr    = severity of situation ( = 0 normal )
    2828
    29       character(len=*) modname
     29      character(len=*), intent(in):: modname
    3030      integer ierr, ierror_mpi
    31       character(len=*) message
     31      character(len=*), intent(in):: message
    3232
    3333      write(lunout,*) 'in abort_gcm'
     
    5353        write(lunout,*) 'Everything is cool'
    5454      else
    55         write(lunout,*) 'Houston, we have a problem ', ierr
     55        write(lunout,*) 'Houston, we have a problem, ierr = ', ierr
    5656#ifdef CPP_MPI
    5757C$OMP CRITICAL (MPI_ABORT_GCM)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90

    r1390 r1391  
    44!
    55!
    6       SUBROUTINE conf_gcm( tapedef, etatinit )
     6SUBROUTINE conf_gcm( tapedef, etatinit )
    77!
    88#ifdef CPP_IOIPSL
    9       use IOIPSL
     9  use IOIPSL
    1010#else
    1111! if not using IOIPSL, we still need to use (a local version of) getin
    12       use ioipsl_getincom
     12  use ioipsl_getincom
    1313#endif
    14       use misc_mod
    15       use mod_filtre_fft, ONLY : use_filtre_fft
    16       use mod_hallo, ONLY : use_mpi_alloc
    17       USE control_mod
    18       USE infotrac, ONLY : type_trac
    19       use assert_m, only: assert
    20       use sponge_mod_p, only: callsponge,mode_sponge,nsponge,tetasponge
    21       IMPLICIT NONE
     14  use misc_mod
     15  use mod_filtre_fft, ONLY : use_filtre_fft
     16  use mod_hallo, ONLY : use_mpi_alloc
     17  USE control_mod
     18  USE infotrac, ONLY : type_trac
     19  use assert_m, only: assert
     20  use sponge_mod_p, only: callsponge,mode_sponge,nsponge,tetasponge
     21  IMPLICIT NONE
    2222!-----------------------------------------------------------------------
    2323!     Auteurs :   L. Fairhead , P. Le Van  .
     
    2929!     -metres  du zoom  avec  celles lues sur le fichier start .
    3030!
    31        LOGICAL etatinit
    32        INTEGER tapedef
     31  LOGICAL etatinit
     32  INTEGER tapedef
    3333
    3434!   Declarations :
    3535!   --------------
    36 #include "dimensions.h"
    37 #include "paramet.h"
    38 #include "logic.h"
    39 #include "serre.h"
    40 #include "comdissnew.h"
    41 #include "iniprint.h"
    42 #include "temps.h"
    43 #include "comconst.h"
     36  include "dimensions.h"
     37  include "paramet.h"
     38  include "logic.h"
     39  include "serre.h"
     40  include "comdissnew.h"
     41  include "iniprint.h"
     42  include "temps.h"
     43  include "comconst.h"
    4444
    4545! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     
    5050!   ------
    5151
    52       CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
    53       REAL clonn,clatt,grossismxx,grossismyy
    54       REAL dzoomxx,dzoomyy, tauxx,tauyy
    55       LOGICAL  fxyhypbb, ysinuss
    56       INTEGER i
    57       character(len=*),parameter :: modname="conf_gcm"
    58       character (len=80) :: abort_message
     52  CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
     53  REAL clonn,clatt,grossismxx,grossismyy
     54  REAL dzoomxx,dzoomyy, tauxx,tauyy
     55  LOGICAL  fxyhypbb, ysinuss
     56  INTEGER i
     57  character(len=*),parameter :: modname="conf_gcm"
     58  character (len=80) :: abort_message
    5959#ifdef CPP_OMP
    6060      integer,external :: OMP_GET_NUM_THREADS
     
    9494!Config  Help = unite de fichier pour les impressions
    9595!Config         (defaut sortie standard = 6)
    96       lunout=6
    97       CALL getin('lunout', lunout)
    98       IF (lunout /= 5 .and. lunout /= 6) THEN
    99         OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
    100      &          STATUS='unknown',FORM='formatted')
    101 
    102       ENDIF
    103 
    104       adjust=.false.
    105       call getin('adjust',adjust)
     96  lunout=6
     97  CALL getin('lunout', lunout)
     98  IF (lunout /= 5 .and. lunout /= 6) THEN
     99        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                      &
     100          STATUS='unknown',FORM='formatted')
     101  ENDIF
     102
     103  adjust=.false.
     104  call getin('adjust',adjust)
    106105     
    107106#ifdef CPP_OMP
    108       ! adjust=y not implemented in case of OpenMP threads...
     107  ! adjust=y not implemented in case of OpenMP threads...
    109108!$OMP PARALLEL
    110       if ((OMP_GET_NUM_THREADS()>1).and.adjust) then
    111         write(lunout,*)'conf_gcm: Error, adjust should be set to n'
    112      &,' when running with OpenMP threads'
    113         abort_message = 'Wrong value for adjust'
    114         call abort_gcm(modname,abort_message,1)
    115       endif
     109  if ((OMP_GET_NUM_THREADS()>1).and.adjust) then
     110    write(lunout,*)'conf_gcm: Error, adjust should be set to n' &
     111         ,' when running with OpenMP threads'
     112    abort_message = 'Wrong value for adjust'
     113    call abort_gcm(modname,abort_message,1)
     114  endif
    116115!$OMP END PARALLEL         
    117116#endif
    118117
    119       itaumax=0
    120       call getin('itaumax',itaumax);
    121       if (itaumax<=0) itaumax=HUGE(itaumax)
     118  itaumax=0
     119  call getin('itaumax',itaumax);
     120  if (itaumax<=0) itaumax=HUGE(itaumax)
    122121     
    123122!Config  Key  = prt_level
     
    126125!Config  Help = Niveau d'impression pour le débogage
    127126!Config         (0 = minimum d'impression)
    128       prt_level = 0
    129       CALL getin('prt_level',prt_level)
    130 
    131 c-----------------------------------------------------------------------
    132 c  Parametres de controle du run:
    133 c-----------------------------------------------------------------------
     127  prt_level = 0
     128  CALL getin('prt_level',prt_level)
     129
     130!-----------------------------------------------------------------------
     131!  Parametres de controle du run:
     132!-----------------------------------------------------------------------
    134133!Config  Key  = planet_type
    135134!Config  Desc = planet type ("earth", "mars", "venus", ...)
    136135!Config  Def  = earth
    137136!Config  Help = this flag sets the type of atymosphere that is considered
    138       planet_type="earth"
    139       CALL getin('planet_type',planet_type)
     137  planet_type="earth"
     138  CALL getin('planet_type',planet_type)
    140139
    141140!Config  Key  = calend
     
    144143!Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
    145144!Config         
    146       calend = 'earth_360d'
    147       CALL getin('calend', calend)
     145  calend = 'earth_360d'
     146  CALL getin('calend', calend)
    148147
    149148!Config  Key  = dayref
     
    152151!Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
    153152!Config         par expl. ,comme ici ) ... A completer
    154       dayref=1
    155       CALL getin('dayref', dayref)
     153  dayref=1
     154  CALL getin('dayref', dayref)
    156155
    157156!Config  Key  = anneeref
     
    160159!Config  Help = Annee de l'etat  initial
    161160!Config         (   avec  4  chiffres   ) ... A completer
    162       anneeref = 1998
    163       CALL getin('anneeref',anneeref)
     161  anneeref = 1998
     162  CALL getin('anneeref',anneeref)
    164163
    165164!Config  Key  = raz_date
     
    170169!Config         1 prise en compte de la date de gcm.def avec remise a zero
    171170!Config         des compteurs de pas de temps
    172       raz_date = 0
    173       CALL getin('raz_date', raz_date)
     171  raz_date = 0
     172  CALL getin('raz_date', raz_date)
    174173
    175174!Config  Key  = resetvarc
     
    177176!Config  Def  = n
    178177!Config  Help = Reinit des variables de controle
    179       resetvarc = .false.
    180       CALL getin('resetvarc',resetvarc)
     178  resetvarc = .false.
     179  CALL getin('resetvarc',resetvarc)
    181180
    182181!Config  Key  = nday
     
    185184!Config  Help = Nombre de jours d'integration
    186185!Config         ... On pourait aussi permettre des mois ou des annees !
    187       nday = 10
    188       CALL getin('nday',nday)
    189 
    190       ! alternative to specifying nday (see also 'less1day' and 'fractday'
    191       ! options below: sopecify numbre of dynamic steps to run:
    192       ndynstep = -9999 ! default value ; if ndynstep <0 then option not used.
    193       call getin('ndynstep',ndynstep)
     186  nday = 10
     187  CALL getin('nday',nday)
     188
     189  ! alternative to specifying nday (see also 'less1day' and 'fractday'
     190  ! options below: sopecify numbre of dynamic steps to run:
     191  ndynstep = -9999 ! default value ; if ndynstep <0 then option not used.
     192  call getin('ndynstep',ndynstep)
    194193     
    195194!Config  Key  = starttime
     
    198197!Config  Help = Heure de depart de la simulation
    199198!Config         en jour
    200       starttime = 0
    201       CALL getin('starttime',starttime)
    202 
    203       ! Mars: time of start for run in "start.nc" (when there are multiple time
    204       !       steps stored in the file)
    205       timestart=-9999 ! default value; if <0, use last stored time
    206       call getin("timestart",timestart)
     199  starttime = 0
     200  CALL getin('starttime',starttime)
     201
     202  ! Mars: time of start for run in "start.nc" (when there are multiple time
     203  !       steps stored in the file)
     204  timestart=-9999 ! default value; if <0, use last stored time
     205  call getin("timestart",timestart)
    207206     
    208207!Config  Key  = less1day
     
    210209!Config  Def  = n
    211210!Config  Help = Possibilite d'integrer moins d'un jour
    212       less1day = .false.
    213       CALL getin('less1day',less1day)
     211  less1day = .false.
     212  CALL getin('less1day',less1day)
    214213
    215214!Config  Key  = fractday
     
    217216!Config  Def  = 0.01
    218217!Config  Help = integration sur une fraction de jour
    219       fractday = 0.01
    220       CALL getin('fractday',fractday)
     218  fractday = 0.01
     219  CALL getin('fractday',fractday)
    221220
    222221!Config  Key  = day_step
     
    225224!Config  Help = nombre de pas par jour (multiple de iperiod) (
    226225!Config          ici pour  dt = 1 min )
    227        day_step = 240
    228        CALL getin('day_step',day_step)
     226  day_step = 240
     227  CALL getin('day_step',day_step)
    229228
    230229!Config  Key  = nsplit_phys
     
    232231!Config  Def  = 1
    233232!Config  Help = nombre de subdivisions par pas physique
    234        nsplit_phys = 1
    235        CALL getin('nsplit_phys',nsplit_phys)
     233  nsplit_phys = 1
     234  CALL getin('nsplit_phys',nsplit_phys)
    236235
    237236!Config  Key  = iperiod
     
    239238!Config  Def  = 5
    240239!Config  Help = periode pour le pas Matsuno (en pas de temps)
    241        iperiod = 5
    242        CALL getin('iperiod',iperiod)
     240  iperiod = 5
     241  CALL getin('iperiod',iperiod)
    243242
    244243!Config  Key  = iapp_tracvl
     
    246245!Config  Def  = iperiod
    247246!Config  Help = frequence du groupement des flux (en pas de temps)
    248        iapp_tracvl = iperiod
    249        CALL getin('iapp_tracvl',iapp_tracvl)
     247  iapp_tracvl = iperiod
     248  CALL getin('iapp_tracvl',iapp_tracvl)
    250249
    251250!Config  Key  = iconser
     
    254253!Config  Help = periode de sortie des variables de controle
    255254!Config         (En pas de temps)
    256        iconser = 240 
    257        CALL getin('iconser', iconser)
     255  iconser = 240 
     256  CALL getin('iconser', iconser)
    258257
    259258!Config  Key  = iecri
     
    261260!Config  Def  = 1
    262261!Config  Help = periode d'ecriture du fichier histoire (en jour)
    263        iecri = 1
    264        CALL getin('iecri',iecri)
    265 
     262  iecri = 1
     263  CALL getin('iecri',iecri)
    266264
    267265!Config  Key  = periodav
     
    269267!Config  Def  = 1
    270268!Config  Help = periode de stockage fichier histmoy (en jour)
    271        periodav = 1.
    272        CALL getin('periodav',periodav)
     269  periodav = 1.
     270  CALL getin('periodav',periodav)
    273271
    274272!Config  Key  = output_grads_dyn
     
    276274!Config  Def  = n
    277275!Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
    278        output_grads_dyn=.false.
    279        CALL getin('output_grads_dyn',output_grads_dyn)
     276  output_grads_dyn=.false.
     277  CALL getin('output_grads_dyn',output_grads_dyn)
    280278
    281279!Config  Key  = dissip_period
     
    285283!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
    286284!Config  dissip_period>0 => on prend cette valeur
    287        dissip_period = 0
    288        call getin('idissip',dissip_period) ! old Mars/Genreic model parameter
    289        ! if there is a "dissip_period" in run.def, it overrides "idissip"
    290        CALL getin('dissip_period',dissip_period)
     285  dissip_period = 0
     286  call getin('idissip',dissip_period) ! old Mars/Genreic model parameter
     287  ! if there is a "dissip_period" in run.def, it overrides "idissip"
     288  CALL getin('dissip_period',dissip_period)
    291289
    292290!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     
    299297!Config         'y' si on veut star et 'n' si on veut non-start !
    300298!Config         Moi y en a pas comprendre !
    301        lstardis = .TRUE.
    302        CALL getin('lstardis',lstardis)
     299  lstardis = .TRUE.
     300  CALL getin('lstardis',lstardis)
    303301
    304302
     
    308306!Config  Help = nombre d'iterations de l'operateur de dissipation
    309307!Config         gradiv
    310        nitergdiv = 1
    311        CALL getin('nitergdiv',nitergdiv)
     308  nitergdiv = 1
     309  CALL getin('nitergdiv',nitergdiv)
    312310
    313311!Config  Key  = nitergrot
     
    316314!Config  Help = nombre d'iterations de l'operateur de dissipation 
    317315!Config         nxgradrot
    318        nitergrot = 2
    319        CALL getin('nitergrot',nitergrot)
    320 
     316  nitergrot = 2
     317  CALL getin('nitergrot',nitergrot)
    321318
    322319!Config  Key  = niterh
     
    325322!Config  Help = nombre d'iterations de l'operateur de dissipation
    326323!Config         divgrad
    327        niterh = 2
    328        CALL getin('niterh',niterh)
    329 
     324  niterh = 2
     325  CALL getin('niterh',niterh)
    330326
    331327!Config  Key  = tetagdiv
     
    334330!Config  Help = temps de dissipation des plus petites longeur
    335331!Config         d'ondes pour u,v (gradiv)
    336        tetagdiv = 7200.
    337        CALL getin('tetagdiv',tetagdiv)
     332  tetagdiv = 7200.
     333  CALL getin('tetagdiv',tetagdiv)
    338334
    339335!Config  Key  = tetagrot
     
    342338!Config  Help = temps de dissipation des plus petites longeur
    343339!Config         d'ondes pour u,v (nxgradrot)
    344        tetagrot = 7200.
    345        CALL getin('tetagrot',tetagrot)
     340  tetagrot = 7200.
     341  CALL getin('tetagrot',tetagrot)
    346342
    347343!Config  Key  = tetatemp
     
    350346!Config  Help =  temps de dissipation des plus petites longeur
    351347!Config         d'ondes pour h (divgrad)   
    352        tetatemp  = 7200.
    353        CALL getin('tetatemp',tetatemp )
     348  tetatemp  = 7200.
     349  CALL getin('tetatemp',tetatemp )
    354350
    355351! For Earth model only:
     
    359355! avec ok_strato=y
    360356
    361        dissip_factz=4.
    362        dissip_deltaz=10.
    363        dissip_zref=30.
    364        CALL getin('dissip_factz',dissip_factz )
    365        CALL getin('dissip_deltaz',dissip_deltaz )
    366        CALL getin('dissip_zref',dissip_zref )
     357  dissip_factz=4.
     358  dissip_deltaz=10.
     359  dissip_zref=30.
     360  CALL getin('dissip_factz',dissip_factz )
     361  CALL getin('dissip_deltaz',dissip_deltaz )
     362  CALL getin('dissip_zref',dissip_zref )
    367363
    368364! For other planets:
     
    371367! Actifs uniquement avec ok_strato=y
    372368
    373        dissip_fac_mid=2.
    374        dissip_fac_up=10.
    375        dissip_deltaz=10.! Intervalle (km) pour le changement mid / up
    376        dissip_hdelta=5. ! scale height (km) dans la zone de la transition(m)
    377        dissip_pupstart=1.e3  ! pression (Pa) au bas la transition mid / up
    378        CALL getin('dissip_fac_mid',dissip_fac_mid )
    379        CALL getin('dissip_fac_up',dissip_fac_up )
    380        CALL getin('dissip_deltaz',dissip_deltaz )
    381        CALL getin('dissip_hdelta',dissip_hdelta )
    382        CALL getin('dissip_pupstart',dissip_pupstart )
     369  dissip_fac_mid=2.
     370  dissip_fac_up=10.
     371  dissip_deltaz=10.! Intervalle (km) pour le changement mid / up
     372  dissip_hdelta=5. ! scale height (km) dans la zone de la transition(m)
     373  dissip_pupstart=1.e3  ! pression (Pa) au bas la transition mid / up
     374  CALL getin('dissip_fac_mid',dissip_fac_mid )
     375  CALL getin('dissip_fac_up',dissip_fac_up )
     376  CALL getin('dissip_deltaz',dissip_deltaz )
     377  CALL getin('dissip_hdelta',dissip_hdelta )
     378  CALL getin('dissip_pupstart',dissip_pupstart )
    383379
    384380! top_bound sponge: only active if iflag_top_bound!=0
     
    386382!                   iflag_top_bound=1 for sponge over 4 topmost layers
    387383!                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
    388        iflag_top_bound=0
    389        CALL getin('iflag_top_bound',iflag_top_bound)
     384  iflag_top_bound=0
     385  CALL getin('iflag_top_bound',iflag_top_bound)
    390386
    391387! mode_top_bound : fields towards which sponge relaxation will be done:
     
    394390!                  mode_top_bound=2: u and v relax towards their zonal mean
    395391!                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
    396        mode_top_bound=3
    397        CALL getin('mode_top_bound',mode_top_bound)
     392  mode_top_bound=3
     393  CALL getin('mode_top_bound',mode_top_bound)
    398394
    399395! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
    400        tau_top_bound=1.e-5
    401        CALL getin('tau_top_bound',tau_top_bound)
     396  tau_top_bound=1.e-5
     397  CALL getin('tau_top_bound',tau_top_bound)
    402398
    403399! the other possible sponge layer (sponge_mod)
    404        callsponge=.false. ! default value; don't use the sponge
    405        call getin("callsponge",callsponge)
    406        ! check that user is not trying to use both sponge models
    407        if ((iflag_top_bound.ge.1).and.callsponge) then
    408          write(lunout,*)'Bad choice of options:'
    409          write(lunout,*)' iflag_top_bound=',iflag_top_bound
    410          write(lunout,*)' and callsponge=.true.'
    411          write(lunout,*)'But both sponge models should not be',
    412      &                  ' used simultaneously!'
    413          stop
    414        endif
     400  callsponge=.false. ! default value; don't use the sponge
     401  call getin("callsponge",callsponge)
     402  ! check that user is not trying to use both sponge models
     403  if ((iflag_top_bound.ge.1).and.callsponge) then
     404    write(lunout,*)'Bad choice of options:'
     405    write(lunout,*)' iflag_top_bound=',iflag_top_bound
     406    write(lunout,*)' and callsponge=.true.'
     407    write(lunout,*)'But both sponge models should not be', &
     408                   ' used simultaneously!'
     409    stop
     410  endif
    415411       
    416412! nsponge: number of atmospheric layers over which the sponge extends
    417        nsponge=3 ! default value
    418        call getin("nsponge",nsponge)
     413  nsponge=3 ! default value
     414  call getin("nsponge",nsponge)
    419415
    420416! mode_sponge: (quenching is towards ... over the upper nsponge layers)
     
    422418!      1: (h=hmean,u=umean,v=0)
    423419!      2: (h=hmean,u=umean,v=vmean)"
    424        mode_sponge=2 ! default value
    425        call getin("mode_sponge",mode_sponge)
     420  mode_sponge=2 ! default value
     421  call getin("mode_sponge",mode_sponge)
    426422
    427423! tetasponge: characteristic time scale (seconds) at topmost layer
    428424!            (time scale then doubles with decreasing layer index)."
    429        tetasponge=50000.0
    430        call getin("tetasponge",tetasponge)
     425  tetasponge=50000.0
     426  call getin("tetasponge",tetasponge)
    431427
    432428! FOR TITAN: tidal forces
    433        tidal=.TRUE.
    434        CALL getin('tidal',tidal)
     429  if (planet_type=="titan") then
     430    tidal=.TRUE.
     431    CALL getin('tidal',tidal)
     432  else
     433    tidal=.false.
     434  endif
    435435
    436436!Config  Key  = coefdis
     
    438438!Config  Def  = 0
    439439!Config  Help = coefficient pour gamdissip 
    440        coefdis = 0.
    441        CALL getin('coefdis',coefdis)
     440  coefdis = 0.
     441  CALL getin('coefdis',coefdis)
    442442
    443443!Config  Key  = purmats
     
    446446!Config  Help = Choix du schema d'integration temporel.
    447447!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
    448        purmats = .FALSE.
    449        CALL getin('purmats',purmats)
     448  purmats = .FALSE.
     449  CALL getin('purmats',purmats)
    450450
    451451!Config  Key  = ok_guide
     
    453453!Config  Def  = n
    454454!Config  Help = Guidage
    455        ok_guide = .FALSE.
    456        CALL getin('ok_guide',ok_guide)
     455  ok_guide = .FALSE.
     456  CALL getin('ok_guide',ok_guide)
    457457
    458458!     ...............................................................
     
    463463!Config  Help = y: intialize dynamical fields using a 'start.nc' file
    464464!               n: fields are initialized by 'iniacademic' routine
    465        read_start= .true.
    466        CALL getin('read_start',read_start)
     465  read_start= .true.
     466  CALL getin('read_start',read_start)
    467467
    468468!Config  Key  = iflag_phys
     
    471471!Config  Help = Permet de faire tourner le modele sans
    472472!Config         physique.
    473        iflag_phys = 1
    474        CALL getin('iflag_phys',iflag_phys)
     473  iflag_phys = 1
     474  CALL getin('iflag_phys',iflag_phys)
    475475
    476476
     
    479479!Config  Def  = 5
    480480!Config  Help = Periode de la physique en pas de temps de la dynamique.
    481        iphysiq = 5
    482        CALL getin('iphysiq', iphysiq)
     481  iphysiq = 5
     482  CALL getin('iphysiq', iphysiq)
    483483
    484484!Config  Key  = iflag_trac
     
    487487!Config  Help = Permet de faire tourner le modele sans traceurs
    488488!Config         
    489        iflag_trac = 1
    490        CALL getin('iflag_trac',iflag_trac)
     489  iflag_trac = 1
     490  CALL getin('iflag_trac',iflag_trac)
    491491
    492492!Config  Key  = ip_ebil_dyn
     
    498498!Config         1 pas de print
    499499!Config         2 print,
    500        ip_ebil_dyn = 0
    501        CALL getin('ip_ebil_dyn',ip_ebil_dyn)
     500  ip_ebil_dyn = 0
     501  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
    502502
    503503!Config  Key  = offline
     
    506506!Config  Help = Permet de mettre en route la
    507507!Config         nouvelle parametrisation de l'eau liquide !
    508        offline = .FALSE.
    509        CALL getin('offline',offline)
    510        IF (offline .AND. adjust) THEN
    511           WRITE(lunout,*)
    512      &         'WARNING : option offline does not work with adjust=y :'
    513           WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
    514      &         'and fluxstokev.nc will not be created'
    515           WRITE(lunout,*)
    516      &         'only the file phystoke.nc will still be created '
    517        END IF
     508  offline = .FALSE.
     509  CALL getin('offline',offline)
     510  IF (offline .AND. adjust) THEN
     511    WRITE(lunout,*)'WARNING : option offline does not work with adjust=y :'
     512    WRITE(lunout,*)'the files defstoke.nc, fluxstoke.nc ', &
     513                   'and fluxstokev.nc will not be created'
     514    WRITE(lunout,*) 'only the file phystoke.nc will still be created '
     515  END IF
    518516       
    519517!Config  Key  = type_trac
     
    524522!Config         'inca' = model de chime INCA
    525523!Config         'repr' = model de chime REPROBUS
    526       type_trac = 'lmdz'
    527       CALL getin('type_trac',type_trac)
     524  type_trac = 'lmdz'
     525  CALL getin('type_trac',type_trac)
    528526
    529527!Config  Key  = config_inca
     
    534532!Config         'chem' = INCA avec calcul de chemie
    535533!Config         'aero' = INCA avec calcul des aerosols
    536       config_inca = 'none'
    537       CALL getin('config_inca',config_inca)
     534  config_inca = 'none'
     535  CALL getin('config_inca',config_inca)
    538536
    539537!Config  Key  = ok_dynzon
     
    542540!Config  Help = Permet de mettre en route le calcul des transports
    543541!Config         
    544       ok_dynzon = .FALSE.
    545       CALL getin('ok_dynzon',ok_dynzon)
     542  ok_dynzon = .FALSE.
     543  CALL getin('ok_dynzon',ok_dynzon)
    546544
    547545!Config  Key  = ok_dyn_ins
     
    550548!Config  Help =
    551549!Config         
    552       ok_dyn_ins = .FALSE.
    553       CALL getin('ok_dyn_ins',ok_dyn_ins)
     550  ok_dyn_ins = .FALSE.
     551  CALL getin('ok_dyn_ins',ok_dyn_ins)
    554552
    555553!Config  Key  = ok_dyn_ave
     
    558556!Config  Help =
    559557!Config         
    560       ok_dyn_ave = .FALSE.
    561       CALL getin('ok_dyn_ave',ok_dyn_ave)
     558  ok_dyn_ave = .FALSE.
     559  CALL getin('ok_dyn_ave',ok_dyn_ave)
    562560
    563561!Config  Key  = use_filtre_fft
     
    566564!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
    567565!Config         le filtrage aux poles.
    568       use_filtre_fft=.FALSE.
    569       CALL getin('use_filtre_fft',use_filtre_fft)
     566  use_filtre_fft=.FALSE.
     567  CALL getin('use_filtre_fft',use_filtre_fft)
    570568
    571569! Ehouarn: at this point grossismx is undefined...
     
    585583!Config         Cela peut ameliorer la bande passante des transferts MPI
    586584!Config         d'un facteur 2 
    587       use_mpi_alloc=.FALSE.
    588       CALL getin('use_mpi_alloc',use_mpi_alloc)
     585  use_mpi_alloc=.FALSE.
     586  CALL getin('use_mpi_alloc',use_mpi_alloc)
    589587
    590588!Config key = ok_strato
     
    593591!Config  Help = active la version stratosphérique de LMDZ de F. Lott
    594592
    595       ok_strato=.TRUE.
    596       CALL getin('ok_strato',ok_strato)
     593  ok_strato=.TRUE.
     594  CALL getin('ok_strato',ok_strato)
    597595
    598596! NB: vert_prof_dissip is Earth-specific; should not impact other models
    599       if (planet_type=="earth") then
    600        vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
    601        CALL getin('vert_prof_dissip', vert_prof_dissip)
    602        call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
    603      $     "bad value for vert_prof_dissip")
    604       else
    605        vert_prof_dissip=0 ! default for planets !
    606        if (planet_type=="mars") then
    607          vert_prof_dissip=1 ! use fac_mid & fac_up & startalt & delta
    608        endif
    609       endif
     597  if (planet_type=="earth") then
     598    vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     599    CALL getin('vert_prof_dissip', vert_prof_dissip)
     600    call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,&
     601               "bad value for vert_prof_dissip")
     602  else
     603    vert_prof_dissip=0 ! default for planets !
     604    if (planet_type=="mars") then
     605      vert_prof_dissip=1 ! use fac_mid & fac_up & startalt & delta
     606    endif
     607  endif
    610608
    611609!Config  Key  = ok_gradsfile
     
    614612!Config  Help = active les sorties grads du guidage
    615613
    616        ok_gradsfile = .FALSE.
    617        CALL getin('ok_gradsfile',ok_gradsfile)
     614  ok_gradsfile = .FALSE.
     615  CALL getin('ok_gradsfile',ok_gradsfile)
    618616
    619617!Config  Key  = ok_limit
     
    622620!Config  Help = production du fichier limit.nc requise
    623621
    624        ok_limit = .TRUE.
    625        CALL getin('ok_limit',ok_limit)
     622  ok_limit = .TRUE.
     623  CALL getin('ok_limit',ok_limit)
    626624
    627625!Config  Key  = ok_etat0
     
    630628!Config  Help = production des fichiers start.nc, startphy.nc requise
    631629
    632       ok_etat0 = .TRUE.
    633       CALL getin('ok_etat0',ok_etat0)
     630  ok_etat0 = .TRUE.
     631  CALL getin('ok_etat0',ok_etat0)
    634632
    635633!----------------------------------------
    636634! Parameters for zonal averages in the case of Titan
    637       moyzon_mu = .false.
    638       moyzon_ch = .false.
    639       if (planet_type=="titan") then
    640        CALL getin('moyzon_mu', moyzon_mu)
    641        CALL getin('moyzon_ch', moyzon_ch)
    642       endif
     635  moyzon_mu = .false.
     636  moyzon_ch = .false.
     637  if (planet_type=="titan") then
     638    CALL getin('moyzon_mu', moyzon_mu)
     639    CALL getin('moyzon_ch', moyzon_ch)
     640  endif
    643641!----------------------------------------
    644642
     
    650648!
    651649!----------------------------------------
    652       IF( etatinit ) then
    653 
    654 !Config  Key  = clon
    655 !Config  Desc = centre du zoom, longitude
    656 !Config  Def  = 0
    657 !Config  Help = longitude en degres du centre
    658 !Config         du zoom
    659        clon = 0.
    660        CALL getin('clon',clon)
    661 
    662 !Config  Key  = clat
    663 !Config  Desc = centre du zoom, latitude
    664 !Config  Def  = 0
    665 !Config  Help = latitude en degres du centre du zoom
    666 !Config         
    667        clat = 0.
    668        CALL getin('clat',clat)
    669 
    670 !Config  Key  = grossismx
    671 !Config  Desc = zoom en longitude
    672 !Config  Def  = 1.0
    673 !Config  Help = facteur de grossissement du zoom,
    674 !Config         selon la longitude
    675        grossismx = 1.0
    676        CALL getin('grossismx',grossismx)
    677        IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
    678          write(lunout,*)'WARNING !!! '
    679          write(lunout,*)"the zoom in longitude grossismx=",grossismx,
    680      &                  " is not compatible with an FFT filter",
    681      &                  "---> FFT filter not active"
    682          use_filtre_fft=.FALSE.
    683        ENDIF
    684 
    685 !Config  Key  = grossismy
    686 !Config  Desc = zoom en latitude
    687 !Config  Def  = 1.0
    688 !Config  Help = facteur de grossissement du zoom,
    689 !Config         selon la latitude
    690        grossismy = 1.0
    691        CALL getin('grossismy',grossismy)
    692 
    693       IF( grossismx.LT.1. )  THEN
    694         write(lunout,*)
    695      &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    696          STOP
    697       ELSE
    698          alphax = 1. - 1./ grossismx
    699       ENDIF
    700 
    701 
    702       IF( grossismy.LT.1. )  THEN
    703         write(lunout,*)
    704      &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    705          STOP
    706       ELSE
    707          alphay = 1. - 1./ grossismy
    708       ENDIF
    709 
    710       write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
    711 !
    712 !    alphax et alphay sont les anciennes formulat. des grossissements
    713 !
    714 !
    715 
    716 !Config  Key  = fxyhypb
    717 !Config  Desc = Fonction  hyperbolique
    718 !Config  Def  = y
    719 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    720 !Config         sinon  sinusoidale
    721        fxyhypb = .TRUE.
    722        CALL getin('fxyhypb',fxyhypb)
    723 
    724 !Config  Key  = dzoomx
    725 !Config  Desc = extension en longitude
    726 !Config  Def  = 0
    727 !Config  Help = extension en longitude  de la zone du zoom 
    728 !Config         ( fraction de la zone totale)
    729        dzoomx = 0.0
    730        CALL getin('dzoomx',dzoomx)
    731 
    732 !Config  Key  = dzoomy
    733 !Config  Desc = extension en latitude
    734 !Config  Def  = 0
    735 !Config  Help = extension en latitude de la zone  du zoom 
    736 !Config         ( fraction de la zone totale)
    737        dzoomy = 0.0
    738        CALL getin('dzoomy',dzoomy)
    739 
    740 !Config  Key  = taux
    741 !Config  Desc = raideur du zoom en  X
    742 !Config  Def  = 3
    743 !Config  Help = raideur du zoom en  X
    744        taux = 3.0
    745        CALL getin('taux',taux)
    746 
    747 !Config  Key  = tauy
    748 !Config  Desc = raideur du zoom en  Y
    749 !Config  Def  = 3
    750 !Config  Help = raideur du zoom en  Y
    751        tauy = 3.0
    752        CALL getin('tauy',tauy)
    753 
    754 !Config  Key  = ysinus
    755 !Config  IF   = !fxyhypb
    756 !Config  Desc = Fonction en Sinus
    757 !Config  Def  = y
    758 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    759 !Config         sinon y = latit.
    760        ysinus = .TRUE.
    761        CALL getin('ysinus',ysinus)
    762 !
    763 !----------------------------------------
    764        else ! etatinit=false
    765 !----------------------------------------
    766 
    767 !Config  Key  = clon
    768 !Config  Desc = centre du zoom, longitude
    769 !Config  Def  = 0
    770 !Config  Help = longitude en degres du centre
    771 !Config         du zoom
    772        clonn = 0.
    773        CALL getin('clon',clonn)
    774 
    775 !Config  Key  = clat
    776 !Config  Desc = centre du zoom, latitude
    777 !Config  Def  = 0
    778 !Config  Help = latitude en degres du centre du zoom
    779 !Config         
    780        clatt = 0.
    781        CALL getin('clat',clatt)
    782 
    783 !
    784 !
    785       IF( ABS(clat - clatt).GE. 0.001 )  THEN
    786         write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
    787      &    ' est differente de celle lue sur le fichier  start '
     650  test_etatinit: IF (.not. etatinit) then
     651     !Config  Key  = clon
     652     !Config  Desc = centre du zoom, longitude
     653     !Config  Def  = 0
     654     !Config  Help = longitude en degres du centre
     655     !Config         du zoom
     656     clonn = 0.
     657     CALL getin('clon',clonn)
     658
     659     !Config  Key  = clat
     660     !Config  Desc = centre du zoom, latitude
     661     !Config  Def  = 0
     662     !Config  Help = latitude en degres du centre du zoom
     663     !Config         
     664     clatt = 0.
     665     CALL getin('clat',clatt)
     666
     667     IF( ABS(clat - clatt).GE. 0.001 )  THEN
     668        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
     669             ' est differente de celle lue sur le fichier  start '
    788670        STOP
    789       ENDIF
    790 
    791 !Config  Key  = grossismx
    792 !Config  Desc = zoom en longitude
    793 !Config  Def  = 1.0
    794 !Config  Help = facteur de grossissement du zoom,
    795 !Config         selon la longitude
    796        grossismxx = 1.0
    797        CALL getin('grossismx',grossismxx)
    798 
    799 
    800       IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    801         write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
    802      &  'run.def est differente de celle lue sur le fichier  start '
     671     ENDIF
     672
     673     !Config  Key  = grossismx
     674     !Config  Desc = zoom en longitude
     675     !Config  Def  = 1.0
     676     !Config  Help = facteur de grossissement du zoom,
     677     !Config         selon la longitude
     678     grossismxx = 1.0
     679     CALL getin('grossismx',grossismxx)
     680
     681     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
     682        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
     683             'run.def est differente de celle lue sur le fichier  start '
    803684        STOP
    804       ENDIF
    805 
    806 !Config  Key  = grossismy
    807 !Config  Desc = zoom en latitude
    808 !Config  Def  = 1.0
    809 !Config  Help = facteur de grossissement du zoom,
    810 !Config         selon la latitude
    811        grossismyy = 1.0
    812        CALL getin('grossismy',grossismyy)
    813 
    814       IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
    815         write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
    816      & 'run.def est differente de celle lue sur le fichier  start '
     685     ENDIF
     686
     687     !Config  Key  = grossismy
     688     !Config  Desc = zoom en latitude
     689     !Config  Def  = 1.0
     690     !Config  Help = facteur de grossissement du zoom,
     691     !Config         selon la latitude
     692     grossismyy = 1.0
     693     CALL getin('grossismy',grossismyy)
     694
     695     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
     696        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
     697             'run.def est differente de celle lue sur le fichier  start '
    817698        STOP
    818       ENDIF
    819      
    820       IF( grossismx.LT.1. )  THEN
    821         write(lunout,*)
    822      &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    823          STOP
    824       ELSE
    825          alphax = 1. - 1./ grossismx
    826       ENDIF
    827 
    828 
    829       IF( grossismy.LT.1. )  THEN
    830         write(lunout,*)
    831      &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    832          STOP
    833       ELSE
    834          alphay = 1. - 1./ grossismy
    835       ENDIF
    836 
    837       write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
    838 !
    839 !    alphax et alphay sont les anciennes formulat. des grossissements
    840 !
    841 !
    842 
    843 !Config  Key  = fxyhypb
    844 !Config  Desc = Fonction  hyperbolique
    845 !Config  Def  = y
    846 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    847 !Config         sinon  sinusoidale
    848        fxyhypbb = .TRUE.
    849        CALL getin('fxyhypb',fxyhypbb)
    850 
    851       IF( .NOT.fxyhypb )  THEN
    852          IF( fxyhypbb )     THEN
    853             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    854             write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
    855      *       'F alors  qu il est  T  sur  run.def  ***'
     699     ENDIF
     700
     701     IF( grossismx.LT.1. )  THEN
     702        write(lunout,*) &
     703             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
     704        STOP
     705     ELSE
     706        alphax = 1. - 1./ grossismx
     707     ENDIF
     708
     709     IF( grossismy.LT.1. )  THEN
     710        write(lunout,*) &
     711             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
     712        STOP
     713     ELSE
     714        alphay = 1. - 1./ grossismy
     715     ENDIF
     716
     717     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
     718
     719     !    alphax et alphay sont les anciennes formulat. des grossissements
     720
     721     !Config  Key  = fxyhypb
     722     !Config  Desc = Fonction  hyperbolique
     723     !Config  Def  = y
     724     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     725     !Config         sinon  sinusoidale
     726     fxyhypbb = .TRUE.
     727     CALL getin('fxyhypb',fxyhypbb)
     728
     729     IF( .NOT.fxyhypb )  THEN
     730        IF( fxyhypbb )     THEN
     731           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     732           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
     733                'F alors  qu il est  T  sur  run.def  ***'
     734           STOP
     735        ENDIF
     736     ELSE
     737        IF( .NOT.fxyhypbb )   THEN
     738           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     739           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
     740                'T alors  qu il est  F  sur  run.def  ****  '
     741           STOP
     742        ENDIF
     743     ENDIF
     744
     745     !Config  Key  = dzoomx
     746     !Config  Desc = extension en longitude
     747     !Config  Def  = 0
     748     !Config  Help = extension en longitude  de la zone du zoom 
     749     !Config         ( fraction de la zone totale)
     750     dzoomxx = 0.0
     751     CALL getin('dzoomx',dzoomxx)
     752
     753     IF( fxyhypb )  THEN
     754        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
     755           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
     756                'run.def est differente de celle lue sur le fichier  start '
     757           STOP
     758        ENDIF
     759     ENDIF
     760
     761     !Config  Key  = dzoomy
     762     !Config  Desc = extension en latitude
     763     !Config  Def  = 0
     764     !Config  Help = extension en latitude de la zone  du zoom 
     765     !Config         ( fraction de la zone totale)
     766     dzoomyy = 0.0
     767     CALL getin('dzoomy',dzoomyy)
     768
     769     IF( fxyhypb )  THEN
     770        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
     771           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
     772                'run.def est differente de celle lue sur le fichier  start '
     773           STOP
     774        ENDIF
     775     ENDIF
     776
     777     !Config  Key  = taux
     778     !Config  Desc = raideur du zoom en  X
     779     !Config  Def  = 3
     780     !Config  Help = raideur du zoom en  X
     781     tauxx = 3.0
     782     CALL getin('taux',tauxx)
     783
     784     IF( fxyhypb )  THEN
     785        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
     786           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
     787                'run.def est differente de celle lue sur le fichier  start '
     788           STOP
     789        ENDIF
     790     ENDIF
     791
     792     !Config  Key  = tauyy
     793     !Config  Desc = raideur du zoom en  Y
     794     !Config  Def  = 3
     795     !Config  Help = raideur du zoom en  Y
     796     tauyy = 3.0
     797     CALL getin('tauy',tauyy)
     798
     799     IF( fxyhypb )  THEN
     800        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
     801           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
     802                'run.def est differente de celle lue sur le fichier  start '
     803           STOP
     804        ENDIF
     805     ENDIF
     806
     807     !c
     808     IF( .NOT.fxyhypb  )  THEN
     809
     810        !Config  Key  = ysinus
     811        !Config  IF   = !fxyhypb
     812        !Config  Desc = Fonction en Sinus
     813        !Config  Def  = y
     814        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     815        !Config         sinon y = latit.
     816        ysinuss = .TRUE.
     817        CALL getin('ysinus',ysinuss)
     818
     819        IF( .NOT.ysinus )  THEN
     820           IF( ysinuss )     THEN
     821              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     822              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
     823                   ' alors  qu il est  T  sur  run.def  ***'
    856824              STOP
    857          ENDIF
    858       ELSE
    859          IF( .NOT.fxyhypbb )   THEN
    860             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    861             write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
    862      *        'T alors  qu il est  F  sur  run.def  ****  '
     825           ENDIF
     826        ELSE
     827           IF( .NOT.ysinuss )   THEN
     828              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     829              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
     830                   ' alors  qu il est  F  sur  run.def  ****  '
    863831              STOP
    864          ENDIF
    865       ENDIF
    866 !
    867 !Config  Key  = dzoomx
    868 !Config  Desc = extension en longitude
    869 !Config  Def  = 0
    870 !Config  Help = extension en longitude  de la zone du zoom 
    871 !Config         ( fraction de la zone totale)
    872        dzoomxx = 0.0
    873        CALL getin('dzoomx',dzoomxx)
    874 
    875       IF( fxyhypb )  THEN
    876        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    877         write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
    878      *  'run.def est differente de celle lue sur le fichier  start '
     832           ENDIF
     833        ENDIF
     834     ENDIF ! of IF( .NOT.fxyhypb  )
     835
     836  else
     837     !Config  Key  = clon
     838     !Config  Desc = centre du zoom, longitude
     839     !Config  Def  = 0
     840     !Config  Help = longitude en degres du centre
     841     !Config         du zoom
     842     clon = 0.
     843     CALL getin('clon',clon)
     844
     845     !Config  Key  = clat
     846     !Config  Desc = centre du zoom, latitude
     847     !Config  Def  = 0
     848     !Config  Help = latitude en degres du centre du zoom
     849     !Config         
     850     clat = 0.
     851     CALL getin('clat',clat)
     852
     853     !Config  Key  = grossismx
     854     !Config  Desc = zoom en longitude
     855     !Config  Def  = 1.0
     856     !Config  Help = facteur de grossissement du zoom,
     857     !Config         selon la longitude
     858     grossismx = 1.0
     859     CALL getin('grossismx',grossismx)
     860
     861     !Config  Key  = grossismy
     862     !Config  Desc = zoom en latitude
     863     !Config  Def  = 1.0
     864     !Config  Help = facteur de grossissement du zoom,
     865     !Config         selon la latitude
     866     grossismy = 1.0
     867     CALL getin('grossismy',grossismy)
     868
     869     IF( grossismx.LT.1. )  THEN
     870        write(lunout,*) &
     871             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    879872        STOP
    880        ENDIF
    881       ENDIF
    882 
    883 !Config  Key  = dzoomy
    884 !Config  Desc = extension en latitude
    885 !Config  Def  = 0
    886 !Config  Help = extension en latitude de la zone  du zoom 
    887 !Config         ( fraction de la zone totale)
    888        dzoomyy = 0.0
    889        CALL getin('dzoomy',dzoomyy)
    890 
    891       IF( fxyhypb )  THEN
    892        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    893         write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
    894      * 'run.def est differente de celle lue sur le fichier  start '
     873     ELSE
     874        alphax = 1. - 1./ grossismx
     875     ENDIF
     876
     877     IF( grossismy.LT.1. )  THEN
     878        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
    895879        STOP
    896        ENDIF
    897       ENDIF
    898      
    899 !Config  Key  = taux
    900 !Config  Desc = raideur du zoom en  X
    901 !Config  Def  = 3
    902 !Config  Help = raideur du zoom en  X
    903        tauxx = 3.0
    904        CALL getin('taux',tauxx)
    905 
    906       IF( fxyhypb )  THEN
    907        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    908         write(lunout,*)'conf_gcm: La valeur de taux passee par ',
    909      * 'run.def est differente de celle lue sur le fichier  start '
    910         STOP
    911        ENDIF
    912       ENDIF
    913 
    914 !Config  Key  = tauyy
    915 !Config  Desc = raideur du zoom en  Y
    916 !Config  Def  = 3
    917 !Config  Help = raideur du zoom en  Y
    918        tauyy = 3.0
    919        CALL getin('tauy',tauyy)
    920 
    921       IF( fxyhypb )  THEN
    922        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    923         write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
    924      * 'run.def est differente de celle lue sur le fichier  start '
    925         STOP
    926        ENDIF
    927       ENDIF
    928 
    929 !c
    930       IF( .NOT.fxyhypb  )  THEN
    931 
    932 !Config  Key  = ysinus
    933 !Config  IF   = !fxyhypb
    934 !Config  Desc = Fonction en Sinus
    935 !Config  Def  = y
    936 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    937 !Config         sinon y = latit.
    938        ysinuss = .TRUE.
    939        CALL getin('ysinus',ysinuss)
    940 
    941         IF( .NOT.ysinus )  THEN
    942           IF( ysinuss )     THEN
    943             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    944             write(lunout,*)' *** ysinus lu sur le fichier start est F',
    945      *       ' alors  qu il est  T  sur  run.def  ***'
    946             STOP
    947           ENDIF
    948         ELSE
    949           IF( .NOT.ysinuss )   THEN
    950             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    951             write(lunout,*)' *** ysinus lu sur le fichier start est T',
    952      *        ' alors  qu il est  F  sur  run.def  ****  '
    953               STOP
    954           ENDIF
    955         ENDIF
    956       ENDIF ! of IF( .NOT.fxyhypb  )
    957 
    958       endif ! etatinit
     880     ELSE
     881        alphay = 1. - 1./ grossismy
     882     ENDIF
     883
     884     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
     885
     886     !    alphax et alphay sont les anciennes formulat. des grossissements
     887
     888     !Config  Key  = fxyhypb
     889     !Config  Desc = Fonction  hyperbolique
     890     !Config  Def  = y
     891     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     892     !Config         sinon  sinusoidale
     893     fxyhypb = .TRUE.
     894     CALL getin('fxyhypb',fxyhypb)
     895
     896     !Config  Key  = dzoomx
     897     !Config  Desc = extension en longitude
     898     !Config  Def  = 0
     899     !Config  Help = extension en longitude  de la zone du zoom 
     900     !Config         ( fraction de la zone totale)
     901     dzoomx = 0.0
     902     CALL getin('dzoomx',dzoomx)
     903
     904     !Config  Key  = dzoomy
     905     !Config  Desc = extension en latitude
     906     !Config  Def  = 0
     907     !Config  Help = extension en latitude de la zone  du zoom 
     908     !Config         ( fraction de la zone totale)
     909     dzoomy = 0.0
     910     CALL getin('dzoomy',dzoomy)
     911
     912     !Config  Key  = taux
     913     !Config  Desc = raideur du zoom en  X
     914     !Config  Def  = 3
     915     !Config  Help = raideur du zoom en  X
     916     taux = 3.0
     917     CALL getin('taux',taux)
     918
     919     !Config  Key  = tauy
     920     !Config  Desc = raideur du zoom en  Y
     921     !Config  Def  = 3
     922     !Config  Help = raideur du zoom en  Y
     923     tauy = 3.0
     924     CALL getin('tauy',tauy)
     925
     926     !Config  Key  = ysinus
     927     !Config  IF   = !fxyhypb
     928     !Config  Desc = Fonction en Sinus
     929     !Config  Def  = y
     930     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     931     !Config         sinon y = latit.
     932     ysinus = .TRUE.
     933     CALL getin('ysinus',ysinus)
     934  endif test_etatinit
    959935!----------------------------------------
    960936
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r1315 r1391  
    180180!#ifdef CPP_IOIPSL
    181181      CALL conf_gcm( 99, .TRUE. )
     182      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
     183     s "iphysiq must be a multiple of iperiod", 1)
    182184!#else
    183185!      CALL defrun( 99, .TRUE. , clesphy0 )
     
    264266     $        iphysiq,day_step,nday,
    265267     $        nbsrf, is_oce,is_sic,
    266      $        is_ter,is_lic)
     268     $        is_ter,is_lic, calend)
    267269
    268270         call init_inca_para(
  • trunk/LMDZ.COMMON/libf/dyn3dpar/getparam.F90

    r1019 r1391  
    11!
    2 ! $Id: getparam.F90 1279 2009-12-10 09:02:56Z fairhead $
     2! $Id: getparam.F90 2094 2014-07-16 16:55:47Z lguez $
    33!
    44MODULE getparam
     
    1111
    1212   INTERFACE getpar
    13      MODULE PROCEDURE ini_getparam,fin_getparam,getparamr,getparami,getparaml
     13     MODULE PROCEDURE getparamr,getparami,getparaml
    1414   END INTERFACE
     15   private getparamr,getparami,getparaml
    1516
    1617   INTEGER, PARAMETER :: out_eff=99
  • trunk/LMDZ.COMMON/libf/dyn3dpar/guide_p_mod.F90

    r1302 r1391  
    6767
    6868  SUBROUTINE guide_init
    69    
     69
    7070    USE control_mod
     71
    7172    IMPLICIT NONE
    7273 
     
    7475    INCLUDE "paramet.h"
    7576    INCLUDE "netcdf.inc"
     77
     78    ! For grossismx:
     79    include "serre.h"
    7680
    7781    INTEGER                :: error,ncidpl,rid,rcod
     
    9195    CALL getpar('guide_teta',.false.,guide_teta,'guidage de T par Teta')
    9296
    93     CALL getpar('guide_add',.false.,guide_add,'for�age constant?')
     97    CALL getpar('guide_add',.false.,guide_add,'forage constant?')
    9498    CALL getpar('guide_zon',.false.,guide_zon,'guidage moy zonale')
     99    if (guide_zon .and. abs(grossismx - 1.) > 0.01) &
     100         call abort_gcm("guide_init", &
     101         "zonal nudging requires grid regular in longitude", 1)
    95102
    96103!   Constantes de rappel. Unite : fraction de jour
     
    108115    CALL getpar('guide_BL',.true.,guide_BL,'guidage dans C.Lim')
    109116   
    110 ! Sauvegarde du for�age
     117! Sauvegarde du forage
    111118    CALL getpar('guide_sav',.false.,guide_sav,'sauvegarde guidage')
    112119    CALL getpar('iguide_sav',4,iguide_sav,'freq. sauvegarde guidage')
    113120    ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois.
    114121    IF (iguide_sav.GT.0) THEN
    115         iguide_sav=day_step/iguide_sav
     122       iguide_sav=day_step/iguide_sav
     123    ELSE if (iguide_sav == 0) then
     124       iguide_sav = huge(0)
    116125    ELSE
    117         iguide_sav=day_step*iguide_sav
     126       iguide_sav=day_step*iguide_sav
    118127    ENDIF
    119128
     
    155164    ncidpl=-99
    156165    if (guide_plevs.EQ.1) then
    157        if (ncidpl.eq.-99) then 
     166       if (ncidpl.eq.-99) then
    158167          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
    159168          if (rcod.NE.NF_NOERR) THEN
     
    163172       endif
    164173    elseif (guide_plevs.EQ.2) then
    165        if (ncidpl.EQ.-99) then 
     174       if (ncidpl.EQ.-99) then
    166175          rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
    167176          if (rcod.NE.NF_NOERR) THEN
     
    374383    ENDIF
    375384     
    376      PRINT *,'---> on rentre dans guide_main'
    377385!    CALL AllGather_Field(ucov,ip1jmp1,llm)
    378386!    CALL AllGather_Field(vcov,ip1jm,llm)
     
    12511259    ENDIF ! guide_reg
    12521260
     1261    if (.not. guide_add) alpha = 1. - exp(- alpha)
     1262
    12531263  END SUBROUTINE tau2alpha
    12541264
     
    15481558! Ap et Bp si niveaux de pression hybrides
    15491559         if (guide_plevs.EQ.1) then
    1550              print *,'Lecture du guidage sur niveaux mod�le'
     1560             print *,'Lecture du guidage sur niveaux modle'
    15511561             rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
    15521562             IF (rcode.NE.NF_NOERR) THEN
     
    18891899#endif
    18901900! --------------------------------------------------------------------
    1891 ! Cr�ation des variables sauvegard�es
     1901! Cr�ation des variables sauvegard�es
    18921902! --------------------------------------------------------------------
    18931903        ierr = NF_REDEF(nid)
     
    20002010!===========================================================================
    20012011END MODULE guide_p_mod
    2002 
  • trunk/LMDZ.COMMON/libf/dyn3dpar/integrd_p.F

    r1019 r1391  
    147147         write(lunout,*) " psm1(ij)=",psm1(stop_it)," dt=",dt,
    148148     &                   " dp(ij)=",dp(stop_it)
     149         call abort_gcm("integrd_p", "negative surface pressure", 1)
    149150        ENDIF
    150151
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1345 r1391  
    852852           CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
    853853         endif
     854c$OMP BARRIER
    854855! Compute geopotential (physics might need it)
    855          CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    856 c$OMP BARRIER
     856         CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
     857
    857858           jD_cur = jD_ref + day_ini - day_ref
    858859     $        + itau/day_step
     
    15951596c$OMP MASTER
    15961597              call fin_getparam
    1597               call finalize_parallel
     1598c$OMP END MASTER
     1599#ifdef INCA
     1600                 call finalize_inca
     1601#endif
     1602c$OMP MASTER
     1603               call finalize_parallel
    15981604c$OMP END MASTER
    15991605              abort_message = 'Simulation finished'
  • trunk/LMDZ.COMMON/libf/filtrez/acc.F

    r1 r1391  
    33!
    44        subroutine acc(vec,d,im)
    5         dimension vec(im,im),d(im)
     5        implicit none
     6        integer :: im
     7        real :: vec(im,im),d(im)
     8        integer :: i,j
     9        real ::sum
     10        real,external :: ssum
    611        do j=1,im
    712          do i=1,im
  • trunk/LMDZ.COMMON/libf/filtrez/eigen.F

    r1 r1391  
    33!
    44      SUBROUTINE eigen( e,d)
     5      IMPLICIT NONE
    56#include "dimensions.h"
    6       dimension e( iim,iim ), d( iim )
    7       dimension asm( iim )
     7      real :: e( iim,iim ), d( iim )
     8      real :: asm( iim )
     9      integer :: im,i,j
    810      im=iim
    911c
  • trunk/LMDZ.COMMON/makelmdz

    r1302 r1391  
    118118[-parallel none/mpi/omp/mpi_omp] : parallelism (default: none) : mpi, openmp or mixted mpi_openmp
    119119[-g GRI]                   : grid configuration in dyn3d/GRI_xy.h  (default: reg, inclues a zoom)
    120 [-io IO]                   : Input/Output library (default: ioipsl)
     120[-io ioipsl/mix/xios]                   : Input/Output library (default: ioipsl)
    121121[-include INCLUDES]        : extra include path to add
    122122[-cpp CPP_KEY]             : additional preprocessing definitions
     
    209209
    210210###############################################################
    211 # lecture des chemins propres à l'architecture de la machine #
     211# lecture des chemins propres \`a l'architecture de la machine #
    212212###############################################################
    213213rm -f .void_file
     
    424424   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR}"
    425425   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl"
    426 elif [[ $io == xios ]]
     426elif [[ $io == mix ]]
    427427then
    428428   # For now, xios implies also using ioipsl
    429429   CPP_KEY="$CPP_KEY CPP_IOIPSL CPP_XIOS"
     430   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR} -I${XIOS_INCDIR}"
     431   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl -L${XIOS_LIBDIR} -l${LIBPREFIX}stdc++ -l${LIBPREFIX}xios"
     432elif [[ $io == xios ]]
     433then
     434   # For now, xios implies also using ioipsl
     435   CPP_KEY="$CPP_KEY CPP_IOIPSL CPP_XIOS CPP_IOIPSL_NO_OUTPUT"
    430436   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR} -I${XIOS_INCDIR}"
    431437   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl -L${XIOS_LIBDIR} -l${LIBPREFIX}stdc++ -l${LIBPREFIX}xios"
     
    551557cd $LMDGCM
    552558
    553 #cleanup for a full recompilation, if requested
     559########################################################################
     560# library directory name:
     561########################################################################
     562
     563nomlib=`echo ${arch}_${physique}_${dim_full}_${grille}_${compil_mod}_parall${parallel}_${CPP_KEY}_${FLAG_PARA} | sed -e 's/ //g' -e 's/-//g ' | sed -e 's/CPP_//g'`
     564echo "Path to library: "$nomlib
     565
     566########################################################################
     567#  Cleanup for a full recompilation, if requested
     568########################################################################
     569
    554570if [[ $full == "full" ]]
    555571then
    556 # remove makefile and $libo/*
    557   cd $LMDGCM
     572# remove makefile and libraries
     573  echo "-full option: recompiling from scratch"
    558574  \rm -f makefile
    559   \rm -rf $LIBOGCM/*
     575  \rm -rf "${LIBOGCM}/${nomlib}"
    560576fi
    561577
     
    650666  fi
    651667fi
    652 
    653 # library directory name:
    654 nomlib=`echo ${arch}_${physique}_${dim_full}_${grille}_${compil_mod}_parall${parallel}_${CPP_KEY}_${FLAG_PARA} | sed -e 's/ //g' -e 's/-//g ' | sed -e 's/CPP_//g'`
    655 echo $nomlib
    656668
    657669if [[ ! -d "${LIBOGCM}/${nomlib}" ]]
  • trunk/LMDZ.COMMON/makelmdz_fcm

    r1302 r1391  
    8989[-parallel none/mpi/omp/mpi_omp] : parallelism (default: none) : mpi, openmp or mixted mpi_openmp
    9090[-g GRI]                   : grid configuration in dyn3d/GRI_xy.h  (default: reg, inclues a zoom)
    91 [-io IO]                   : Input/Output library (default: ioipsl)
     91[-io ioipsl/mix/xios]                   : Input/Output library (default: ioipsl)
    9292[-include INCLUDES]        : extra include path to add
    9393[-cpp CPP_KEY]             : additional preprocessing definitions
     
    326326   CPP_KEY="$CPP_KEY CPP_SISVAT"
    327327   SISVAT_PATH="$LIBFGCM/%PHYS/sisvat"
    328    #sed -e 's/^#src::sisvat/src::sisvat/' bld.cfg > bld.tmp
    329    #mv bld.tmp bld.cfg
    330328fi
    331329
     
    334332   CPP_KEY="$CPP_KEY CPP_RRTM"
    335333   RRTM_PATH="$LIBFGCM/%PHYS/rrtm"
    336    #sed -e 's/^#src::rrtm/src::rrtm/' bld.cfg > bld.tmp
    337    #mv bld.tmp bld.cfg
    338334fi
    339335
     
    343339   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR}"
    344340   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl"
    345 elif [[ $io == xios ]]
     341elif [[ $io == mix ]]
    346342then
    347343   # For now, xios implies also using ioipsl
    348344   CPP_KEY="$CPP_KEY CPP_IOIPSL CPP_XIOS"
     345   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR} -I${XIOS_INCDIR}"
     346   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl -L${XIOS_LIBDIR} -l${LIBPREFIX}stdc++ -l${LIBPREFIX}xios"
     347elif [[ $io == xios ]]
     348then
     349   # For now, xios implies also using ioipsl
     350   CPP_KEY="$CPP_KEY CPP_IOIPSL CPP_XIOS CPP_IOIPSL_NO_OUTPUT"
    349351   INCLUDE="$INCLUDE -I${IOIPSL_INCDIR} -I${XIOS_INCDIR}"
    350352   LIB="$LIB -L${IOIPSL_LIBDIR} -l${LIBPREFIX}ioipsl -L${XIOS_LIBDIR} -l${LIBPREFIX}stdc++ -l${LIBPREFIX}xios"
Note: See TracChangeset for help on using the changeset viewer.