Ignore:
Timestamp:
Nov 14, 2014, 2:32:39 PM (10 years ago)
Author:
lguez
Message:

dyn3d/conf_gcm.F, fixed source form, was included in lmdz1d.F90, free source
form, did not work. So converted conf_gcm.F to free source form. Also
converted dyn3dpar and dyn3dmem versions.

File:
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/conf_gcm.F90

    r2141 r2142  
    1 !
     1
    22! $Id$
    3 !
    4 !
    5 !
    6       SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
    7 !
    8       USE control_mod
     3
     4SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
     5
     6  USE 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 
    18       IMPLICIT NONE
    19 !-----------------------------------------------------------------------
    20 !     Auteurs :   L. Fairhead , P. Le Van  .
    21 !
    22 !     Arguments :
    23 !
    24 !     tapedef   :
    25 !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
    26 !     -metres  du zoom  avec  celles lues sur le fichier start .
    27 !      clesphy0 :  sortie  .
    28 !
    29        LOGICAL etatinit
    30        INTEGER tapedef
    31 
    32        INTEGER        longcles
    33        PARAMETER(     longcles = 20 )
    34        REAL clesphy0( longcles )
    35 !
    36 !   Declarations :
    37 !   --------------
    38 #include "dimensions.h"
    39 #include "paramet.h"
    40 #include "logic.h"
    41 #include "serre.h"
    42 #include "comdissnew.h"
    43 #include "temps.h"
    44 #include "comconst.h"
    45 
    46 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    47 ! #include "clesphys.h"
    48 #include "iniprint.h"
    49 !
    50 !
    51 !   local:
    52 !   ------
    53 
    54       CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
    55       REAL clonn,clatt,grossismxx,grossismyy
    56       REAL dzoomxx,dzoomyy, tauxx,tauyy
    57       LOGICAL  fxyhypbb, ysinuss
    58       INTEGER i
    59       LOGICAL use_filtre_fft
    60 !
    61 !  -------------------------------------------------------------------
    62 !
    63 !       .........     Version  du 29/04/97       ..........
    64 !
    65 !   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
    66 !      tetatemp   ajoutes  pour la dissipation   .
    67 !
    68 !   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
    69 !
    70 !  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
    71 !    Sinon , choix de fxynew  , a derivee sinusoidale  ..
    72 !
    73 !   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
    74 !         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
    75 !                de limit.dat ( dic)                        ...........
    76 !           Sinon  etatinit = . FALSE .
    77 !
    78 !   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
    79 !    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
    80 !   celles passees  par run.def ,  au debut du gcm, apres l'appel a
    81 !    lectba . 
    82 !   Ces parmetres definissant entre autres la grille et doivent etre
    83 !   pareils et coherents , sinon il y aura  divergence du gcm .
    84 !
    85 !-----------------------------------------------------------------------
    86 !   initialisations:
    87 !   ----------------
    88 
    89 !Config  Key  = lunout
    90 !Config  Desc = unite de fichier pour les impressions
    91 !Config  Def  = 6
    92 !Config  Help = unite de fichier pour les impressions
    93 !Config         (defaut sortie standard = 6)
    94       lunout=6
    95       CALL getin('lunout', lunout)
    96       IF (lunout /= 5 .and. lunout /= 6) THEN
    97         OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                     &
    98      &          STATUS='unknown',FORM='formatted')
    99       ENDIF
    100 
    101 !Config  Key  = prt_level
    102 !Config  Desc = niveau d'impressions de débogage
    103 !Config  Def  = 0
    104 !Config  Help = Niveau d'impression pour le débogage
    105 !Config         (0 = minimum d'impression)
    106       prt_level = 0
    107       CALL getin('prt_level',prt_level)
    108 
    109 !-----------------------------------------------------------------------
    110 !  Parametres de controle du run:
    111 !-----------------------------------------------------------------------
    112 !Config  Key  = planet_type
    113 !Config  Desc = planet type ("earth", "mars", "venus", ...)
    114 !Config  Def  = earth
    115 !Config  Help = this flag sets the type of atymosphere that is considered
    116       planet_type="earth"
    117       CALL getin('planet_type',planet_type)
    118 
    119 !Config  Key  = calend
    120 !Config  Desc = type de calendrier utilise
    121 !Config  Def  = earth_360d
    122 !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
    123 !Config         
    124       calend = 'earth_360d'
    125       CALL getin('calend', calend)
    126 
    127 !Config  Key  = dayref
    128 !Config  Desc = Jour de l'etat initial
    129 !Config  Def  = 1
    130 !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
    131 !Config         par expl. ,comme ici ) ... A completer
    132       dayref=1
    133       CALL getin('dayref', dayref)
    134 
    135 !Config  Key  = anneeref
    136 !Config  Desc = Annee de l'etat initial
    137 !Config  Def  = 1998
    138 !Config  Help = Annee de l'etat  initial
    139 !Config         (   avec  4  chiffres   ) ... A completer
    140       anneeref = 1998
    141       CALL getin('anneeref',anneeref)
    142 
    143 !Config  Key  = raz_date
    144 !Config  Desc = Remise a zero de la date initiale
    145 !Config  Def  = 0 (pas de remise a zero)
    146 !Config  Help = Remise a zero de la date initiale
    147 !Config         0 pas de remise a zero, on garde la date du fichier restart
    148 !Config         1 prise en compte de la date de gcm.def avec remise a zero
    149 !Config         des compteurs de pas de temps
    150       raz_date = 0
    151       CALL getin('raz_date', raz_date)
    152 
    153 !Config  Key  = resetvarc
    154 !Config  Desc = Reinit des variables de controle
    155 !Config  Def  = n
    156 !Config  Help = Reinit des variables de controle
    157       resetvarc = .false.
    158       CALL getin('resetvarc',resetvarc)
    159 
    160 !Config  Key  = nday
    161 !Config  Desc = Nombre de jours d'integration
    162 !Config  Def  = 10
    163 !Config  Help = Nombre de jours d'integration
    164 !Config         ... On pourait aussi permettre des mois ou des annees !
    165       nday = 10
    166       CALL getin('nday',nday)
    167 
    168 !Config  Key  = starttime
    169 !Config  Desc = Heure de depart de la simulation
    170 !Config  Def  = 0
    171 !Config  Help = Heure de depart de la simulation
    172 !Config         en jour
    173       starttime = 0
    174       CALL getin('starttime',starttime)
    175 
    176 !Config  Key  = day_step
    177 !Config  Desc = nombre de pas par jour
    178 !Config  Def  = 240
    179 !Config  Help = nombre de pas par jour (multiple de iperiod) (
    180 !Config          ici pour  dt = 1 min )
    181        day_step = 240
    182        CALL getin('day_step',day_step)
    183 
    184 !Config  Key  = nsplit_phys
    185        nsplit_phys = 1
    186        CALL getin('nsplit_phys',nsplit_phys)
    187 
    188 !Config  Key  = iperiod
    189 !Config  Desc = periode pour le pas Matsuno
    190 !Config  Def  = 5
    191 !Config  Help = periode pour le pas Matsuno (en pas de temps)
    192        iperiod = 5
    193        CALL getin('iperiod',iperiod)
    194 
    195 !Config  Key  = iapp_tracvl
    196 !Config  Desc = frequence du groupement des flux
    197 !Config  Def  = iperiod
    198 !Config  Help = frequence du groupement des flux (en pas de temps)
    199        iapp_tracvl = iperiod
    200        CALL getin('iapp_tracvl',iapp_tracvl)
    201 
    202 !Config  Key  = iconser
    203 !Config  Desc = periode de sortie des variables de controle
    204 !Config  Def  = 240 
    205 !Config  Help = periode de sortie des variables de controle
    206 !Config         (En pas de temps)
    207        iconser = 240 
    208        CALL getin('iconser', iconser)
    209 
    210 !Config  Key  = iecri
    211 !Config  Desc = periode d'ecriture du fichier histoire
    212 !Config  Def  = 1
    213 !Config  Help = periode d'ecriture du fichier histoire (en jour)
    214        iecri = 1
    215        CALL getin('iecri',iecri)
    216 
    217 
    218 !Config  Key  = periodav
    219 !Config  Desc = periode de stockage fichier histmoy
    220 !Config  Def  = 1
    221 !Config  Help = periode de stockage fichier histmoy (en jour)
    222        periodav = 1.
    223        CALL getin('periodav',periodav)
    224 
    225 !Config  Key  = output_grads_dyn
    226 !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
    227 !Config  Def  = n
    228 !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
    229        output_grads_dyn=.false.
    230        CALL getin('output_grads_dyn',output_grads_dyn)
    231 
    232 !Config  Key  = dissip_period
    233 !Config  Desc = periode de la dissipation
    234 !Config  Def  = 0
    235 !Config  Help = periode de la dissipation
    236 !Config  dissip_period=0 => la valeur sera calcule dans inidissip       
    237 !Config  dissip_period>0 => on prend cette valeur
    238        dissip_period = 0
    239        CALL getin('dissip_period',dissip_period)
    240 
    241 !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
    242 !cc
    243 
    244 !Config  Key  = lstardis
    245 !Config  Desc = choix de l'operateur de dissipation
    246 !Config  Def  = y
    247 !Config  Help = choix de l'operateur de dissipation
    248 !Config         'y' si on veut star et 'n' si on veut non-start !
    249 !Config         Moi y en a pas comprendre !
    250        lstardis = .TRUE.
    251        CALL getin('lstardis',lstardis)
    252 
    253 
    254 !Config  Key  = nitergdiv
    255 !Config  Desc = Nombre d'iteration de gradiv
    256 !Config  Def  = 1
    257 !Config  Help = nombre d'iterations de l'operateur de dissipation
    258 !Config         gradiv
    259        nitergdiv = 1
    260        CALL getin('nitergdiv',nitergdiv)
    261 
    262 !Config  Key  = nitergrot
    263 !Config  Desc = nombre d'iterations de nxgradrot
    264 !Config  Def  = 2
    265 !Config  Help = nombre d'iterations de l'operateur de dissipation 
    266 !Config         nxgradrot
    267        nitergrot = 2
    268        CALL getin('nitergrot',nitergrot)
    269 
    270 
    271 !Config  Key  = niterh
    272 !Config  Desc = nombre d'iterations de divgrad
    273 !Config  Def  = 2
    274 !Config  Help = nombre d'iterations de l'operateur de dissipation
    275 !Config         divgrad
    276        niterh = 2
    277        CALL getin('niterh',niterh)
    278 
    279 
    280 !Config  Key  = tetagdiv
    281 !Config  Desc = temps de dissipation pour div
    282 !Config  Def  = 7200
    283 !Config  Help = temps de dissipation des plus petites longeur
    284 !Config         d'ondes pour u,v (gradiv)
    285        tetagdiv = 7200.
    286        CALL getin('tetagdiv',tetagdiv)
    287 
    288 !Config  Key  = tetagrot
    289 !Config  Desc = temps de dissipation pour grad
    290 !Config  Def  = 7200
    291 !Config  Help = temps de dissipation des plus petites longeur
    292 !Config         d'ondes pour u,v (nxgradrot)
    293        tetagrot = 7200.
    294        CALL getin('tetagrot',tetagrot)
    295 
    296 !Config  Key  = tetatemp
    297 !Config  Desc = temps de dissipation pour h
    298 !Config  Def  = 7200
    299 !Config  Help =  temps de dissipation des plus petites longeur
    300 !Config         d'ondes pour h (divgrad)   
    301        tetatemp  = 7200.
    302        CALL getin('tetatemp',tetatemp )
    303 
    304 ! Parametres controlant la variation sur la verticale des constantes de
    305 ! dissipation.
    306 ! Pour le moment actifs uniquement dans la version a 39 niveaux
    307 ! avec ok_strato=y
    308 
    309        dissip_factz=4.
    310        dissip_deltaz=10.
    311        dissip_zref=30.
    312        CALL getin('dissip_factz',dissip_factz )
    313        CALL getin('dissip_deltaz',dissip_deltaz )
    314        CALL getin('dissip_zref',dissip_zref )
    315 
    316 ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
    317 !                   iflag_top_bound=0 for no sponge
    318 !                   iflag_top_bound=1 for sponge over 4 topmost layers
    319 !                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
    320        iflag_top_bound=1
    321        CALL getin('iflag_top_bound',iflag_top_bound)
    322 
    323 ! mode_top_bound : fields towards which sponge relaxation will be done:
    324 !                  mode_top_bound=0: no relaxation
    325 !                  mode_top_bound=1: u and v relax towards 0
    326 !                  mode_top_bound=2: u and v relax towards their zonal mean
    327 !                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
    328        mode_top_bound=3
    329        CALL getin('mode_top_bound',mode_top_bound)
    330 
    331 ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
    332        tau_top_bound=1.e-5
    333        CALL getin('tau_top_bound',tau_top_bound)
    334 
    335 !Config  Key  = coefdis
    336 !Config  Desc = coefficient pour gamdissip
    337 !Config  Def  = 0
    338 !Config  Help = coefficient pour gamdissip 
    339        coefdis = 0.
    340        CALL getin('coefdis',coefdis)
    341 
    342 !Config  Key  = purmats
    343 !Config  Desc = Schema d'integration
    344 !Config  Def  = n
    345 !Config  Help = Choix du schema d'integration temporel.
    346 !Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
    347        purmats = .FALSE.
    348        CALL getin('purmats',purmats)
    349 
    350 !Config  Key  = ok_guide
    351 !Config  Desc = Guidage
    352 !Config  Def  = n
    353 !Config  Help = Guidage
    354        ok_guide = .FALSE.
    355        CALL getin('ok_guide',ok_guide)
    356 
    357 !Config  Key  =  read_start
    358 !Config  Desc = Initialize model using a 'start.nc' file
    359 !Config  Def  = y
    360 !Config  Help = y: intialize dynamical fields using a 'start.nc' file
    361 !               n: fields are initialized by 'iniacademic' routine
    362        read_start= .true.
    363        CALL getin('read_start',read_start)
    364 
    365 !Config  Key  = iflag_phys
    366 !Config  Desc = Avec ls physique
    367 !Config  Def  = 1
    368 !Config  Help = Permet de faire tourner le modele sans
    369 !Config         physique.
    370        iflag_phys = 1
    371        CALL getin('iflag_phys',iflag_phys)
    372 
    373 
    374 !Config  Key  =  iphysiq
    375 !Config  Desc = Periode de la physique
    376 !Config  Def  = 5
    377 !Config  Help = Periode de la physique en pas de temps de la dynamique.
    378        iphysiq = 5
    379        CALL getin('iphysiq', iphysiq)
    380 
    381        if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    382      $      "iphysiq must be a multiple of iperiod", 1)
    383 
    384 !Config  Key  = ip_ebil_dyn
    385 !Config  Desc = PRINT level for energy conserv. diag.
    386 !Config  Def  = 0
    387 !Config  Help = PRINT level for energy conservation diag. ;
    388 !               les options suivantes existent :
    389 !Config         0 pas de print
    390 !Config         1 pas de print
    391 !Config         2 print,
    392        ip_ebil_dyn = 0
    393        CALL getin('ip_ebil_dyn',ip_ebil_dyn)
    394 !
    395 
    396       DO i = 1, longcles
    397        clesphy0(i) = 0.
    398       ENDDO
    399 
    400 !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
    401 !     .........   (  modif  le 17/04/96 )   .........
    402 !
    403       IF( etatinit ) GO TO 100
    404 
    405 !Config  Key  = clon
    406 !Config  Desc = centre du zoom, longitude
    407 !Config  Def  = 0
    408 !Config  Help = longitude en degres du centre
    409 !Config         du zoom
    410        clonn = 0.
    411        CALL getin('clon',clonn)
    412 
    413 !Config  Key  = clat
    414 !Config  Desc = centre du zoom, latitude
    415 !Config  Def  = 0
    416 !Config  Help = latitude en degres du centre du zoom
    417 !Config         
    418        clatt = 0.
    419        CALL getin('clat',clatt)
    420 
    421 !
    422 !
    423       IF( ABS(clat - clatt).GE. 0.001 )  THEN
    424         write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
    425      &    ' est differente de celle lue sur le fichier  start '
     13  USE infotrac, ONLY : type_trac
     14  use assert_m, only: assert
     15
     16  IMPLICIT NONE
     17  !-----------------------------------------------------------------------
     18  !     Auteurs :   L. Fairhead , P. Le Van  .
     19
     20  !     Arguments :
     21
     22  !     tapedef   :
     23  !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
     24  !     -metres  du zoom  avec  celles lues sur le fichier start .
     25  !      clesphy0 :  sortie  .
     26
     27  LOGICAL etatinit
     28  INTEGER tapedef
     29
     30  INTEGER        longcles
     31  PARAMETER(     longcles = 20 )
     32  REAL clesphy0( longcles )
     33
     34  !   Declarations :
     35  !   --------------
     36  include "dimensions.h"
     37  include "paramet.h"
     38  include "logic.h"
     39  include "serre.h"
     40  include "comdissnew.h"
     41  include "temps.h"
     42  include "comconst.h"
     43
     44  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     45  ! include "clesphys.h"
     46  include "iniprint.h"
     47
     48  !   local:
     49  !   ------
     50
     51  CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
     52  REAL clonn,clatt,grossismxx,grossismyy
     53  REAL dzoomxx,dzoomyy, tauxx,tauyy
     54  LOGICAL  fxyhypbb, ysinuss
     55  INTEGER i
     56  LOGICAL use_filtre_fft
     57
     58  !  -------------------------------------------------------------------
     59
     60  !       .........     Version  du 29/04/97       ..........
     61
     62  !   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
     63  !      tetatemp   ajoutes  pour la dissipation   .
     64
     65  !   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
     66
     67  !  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
     68  !    Sinon , choix de fxynew  , a derivee sinusoidale  ..
     69
     70  !   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
     71  !         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
     72  !                de limit.dat ( dic)                        ...........
     73  !           Sinon  etatinit = . FALSE .
     74
     75  !   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
     76  !    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
     77  !   celles passees  par run.def ,  au debut du gcm, apres l'appel a
     78  !    lectba . 
     79  !   Ces parmetres definissant entre autres la grille et doivent etre
     80  !   pareils et coherents , sinon il y aura  divergence du gcm .
     81
     82  !-----------------------------------------------------------------------
     83  !   initialisations:
     84  !   ----------------
     85
     86  !Config  Key  = lunout
     87  !Config  Desc = unite de fichier pour les impressions
     88  !Config  Def  = 6
     89  !Config  Help = unite de fichier pour les impressions
     90  !Config         (defaut sortie standard = 6)
     91  lunout=6
     92  CALL getin('lunout', lunout)
     93  IF (lunout /= 5 .and. lunout /= 6) THEN
     94     OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                      &
     95          STATUS='unknown',FORM='formatted')
     96  ENDIF
     97
     98  !Config  Key  = prt_level
     99  !Config  Desc = niveau d'impressions de débogage
     100  !Config  Def  = 0
     101  !Config  Help = Niveau d'impression pour le débogage
     102  !Config         (0 = minimum d'impression)
     103  prt_level = 0
     104  CALL getin('prt_level',prt_level)
     105
     106  !-----------------------------------------------------------------------
     107  !  Parametres de controle du run:
     108  !-----------------------------------------------------------------------
     109  !Config  Key  = planet_type
     110  !Config  Desc = planet type ("earth", "mars", "venus", ...)
     111  !Config  Def  = earth
     112  !Config  Help = this flag sets the type of atymosphere that is considered
     113  planet_type="earth"
     114  CALL getin('planet_type',planet_type)
     115
     116  !Config  Key  = calend
     117  !Config  Desc = type de calendrier utilise
     118  !Config  Def  = earth_360d
     119  !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
     120  !Config         
     121  calend = 'earth_360d'
     122  CALL getin('calend', calend)
     123
     124  !Config  Key  = dayref
     125  !Config  Desc = Jour de l'etat initial
     126  !Config  Def  = 1
     127  !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
     128  !Config         par expl. ,comme ici ) ... A completer
     129  dayref=1
     130  CALL getin('dayref', dayref)
     131
     132  !Config  Key  = anneeref
     133  !Config  Desc = Annee de l'etat initial
     134  !Config  Def  = 1998
     135  !Config  Help = Annee de l'etat  initial
     136  !Config         (   avec  4  chiffres   ) ... A completer
     137  anneeref = 1998
     138  CALL getin('anneeref',anneeref)
     139
     140  !Config  Key  = raz_date
     141  !Config  Desc = Remise a zero de la date initiale
     142  !Config  Def  = 0 (pas de remise a zero)
     143  !Config  Help = Remise a zero de la date initiale
     144  !Config         0 pas de remise a zero, on garde la date du fichier restart
     145  !Config         1 prise en compte de la date de gcm.def avec remise a zero
     146  !Config         des compteurs de pas de temps
     147  raz_date = 0
     148  CALL getin('raz_date', raz_date)
     149
     150  !Config  Key  = resetvarc
     151  !Config  Desc = Reinit des variables de controle
     152  !Config  Def  = n
     153  !Config  Help = Reinit des variables de controle
     154  resetvarc = .false.
     155  CALL getin('resetvarc',resetvarc)
     156
     157  !Config  Key  = nday
     158  !Config  Desc = Nombre de jours d'integration
     159  !Config  Def  = 10
     160  !Config  Help = Nombre de jours d'integration
     161  !Config         ... On pourait aussi permettre des mois ou des annees !
     162  nday = 10
     163  CALL getin('nday',nday)
     164
     165  !Config  Key  = starttime
     166  !Config  Desc = Heure de depart de la simulation
     167  !Config  Def  = 0
     168  !Config  Help = Heure de depart de la simulation
     169  !Config         en jour
     170  starttime = 0
     171  CALL getin('starttime',starttime)
     172
     173  !Config  Key  = day_step
     174  !Config  Desc = nombre de pas par jour
     175  !Config  Def  = 240
     176  !Config  Help = nombre de pas par jour (multiple de iperiod) (
     177  !Config          ici pour  dt = 1 min )
     178  day_step = 240
     179  CALL getin('day_step',day_step)
     180
     181  !Config  Key  = nsplit_phys
     182  nsplit_phys = 1
     183  CALL getin('nsplit_phys',nsplit_phys)
     184
     185  !Config  Key  = iperiod
     186  !Config  Desc = periode pour le pas Matsuno
     187  !Config  Def  = 5
     188  !Config  Help = periode pour le pas Matsuno (en pas de temps)
     189  iperiod = 5
     190  CALL getin('iperiod',iperiod)
     191
     192  !Config  Key  = iapp_tracvl
     193  !Config  Desc = frequence du groupement des flux
     194  !Config  Def  = iperiod
     195  !Config  Help = frequence du groupement des flux (en pas de temps)
     196  iapp_tracvl = iperiod
     197  CALL getin('iapp_tracvl',iapp_tracvl)
     198
     199  !Config  Key  = iconser
     200  !Config  Desc = periode de sortie des variables de controle
     201  !Config  Def  = 240 
     202  !Config  Help = periode de sortie des variables de controle
     203  !Config         (En pas de temps)
     204  iconser = 240 
     205  CALL getin('iconser', iconser)
     206
     207  !Config  Key  = iecri
     208  !Config  Desc = periode d'ecriture du fichier histoire
     209  !Config  Def  = 1
     210  !Config  Help = periode d'ecriture du fichier histoire (en jour)
     211  iecri = 1
     212  CALL getin('iecri',iecri)
     213
     214  !Config  Key  = periodav
     215  !Config  Desc = periode de stockage fichier histmoy
     216  !Config  Def  = 1
     217  !Config  Help = periode de stockage fichier histmoy (en jour)
     218  periodav = 1.
     219  CALL getin('periodav',periodav)
     220
     221  !Config  Key  = output_grads_dyn
     222  !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
     223  !Config  Def  = n
     224  !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
     225  output_grads_dyn=.false.
     226  CALL getin('output_grads_dyn',output_grads_dyn)
     227
     228  !Config  Key  = dissip_period
     229  !Config  Desc = periode de la dissipation
     230  !Config  Def  = 0
     231  !Config  Help = periode de la dissipation
     232  !Config  dissip_period=0 => la valeur sera calcule dans inidissip       
     233  !Config  dissip_period>0 => on prend cette valeur
     234  dissip_period = 0
     235  CALL getin('dissip_period',dissip_period)
     236
     237  !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     238  !cc
     239
     240  !Config  Key  = lstardis
     241  !Config  Desc = choix de l'operateur de dissipation
     242  !Config  Def  = y
     243  !Config  Help = choix de l'operateur de dissipation
     244  !Config         'y' si on veut star et 'n' si on veut non-start !
     245  !Config         Moi y en a pas comprendre !
     246  lstardis = .TRUE.
     247  CALL getin('lstardis',lstardis)
     248
     249  !Config  Key  = nitergdiv
     250  !Config  Desc = Nombre d'iteration de gradiv
     251  !Config  Def  = 1
     252  !Config  Help = nombre d'iterations de l'operateur de dissipation
     253  !Config         gradiv
     254  nitergdiv = 1
     255  CALL getin('nitergdiv',nitergdiv)
     256
     257  !Config  Key  = nitergrot
     258  !Config  Desc = nombre d'iterations de nxgradrot
     259  !Config  Def  = 2
     260  !Config  Help = nombre d'iterations de l'operateur de dissipation 
     261  !Config         nxgradrot
     262  nitergrot = 2
     263  CALL getin('nitergrot',nitergrot)
     264
     265  !Config  Key  = niterh
     266  !Config  Desc = nombre d'iterations de divgrad
     267  !Config  Def  = 2
     268  !Config  Help = nombre d'iterations de l'operateur de dissipation
     269  !Config         divgrad
     270  niterh = 2
     271  CALL getin('niterh',niterh)
     272
     273  !Config  Key  = tetagdiv
     274  !Config  Desc = temps de dissipation pour div
     275  !Config  Def  = 7200
     276  !Config  Help = temps de dissipation des plus petites longeur
     277  !Config         d'ondes pour u,v (gradiv)
     278  tetagdiv = 7200.
     279  CALL getin('tetagdiv',tetagdiv)
     280
     281  !Config  Key  = tetagrot
     282  !Config  Desc = temps de dissipation pour grad
     283  !Config  Def  = 7200
     284  !Config  Help = temps de dissipation des plus petites longeur
     285  !Config         d'ondes pour u,v (nxgradrot)
     286  tetagrot = 7200.
     287  CALL getin('tetagrot',tetagrot)
     288
     289  !Config  Key  = tetatemp
     290  !Config  Desc = temps de dissipation pour h
     291  !Config  Def  = 7200
     292  !Config  Help =  temps de dissipation des plus petites longeur
     293  !Config         d'ondes pour h (divgrad)   
     294  tetatemp  = 7200.
     295  CALL getin('tetatemp',tetatemp )
     296
     297  ! Parametres controlant la variation sur la verticale des constantes de
     298  ! dissipation.
     299  ! Pour le moment actifs uniquement dans la version a 39 niveaux
     300  ! avec ok_strato=y
     301
     302  dissip_factz=4.
     303  dissip_deltaz=10.
     304  dissip_zref=30.
     305  CALL getin('dissip_factz',dissip_factz )
     306  CALL getin('dissip_deltaz',dissip_deltaz )
     307  CALL getin('dissip_zref',dissip_zref )
     308
     309  ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
     310  !                   iflag_top_bound=0 for no sponge
     311  !                   iflag_top_bound=1 for sponge over 4 topmost layers
     312  !                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
     313  iflag_top_bound=1
     314  CALL getin('iflag_top_bound',iflag_top_bound)
     315
     316  ! mode_top_bound : fields towards which sponge relaxation will be done:
     317  !                  mode_top_bound=0: no relaxation
     318  !                  mode_top_bound=1: u and v relax towards 0
     319  !                  mode_top_bound=2: u and v relax towards their zonal mean
     320  !                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
     321  mode_top_bound=3
     322  CALL getin('mode_top_bound',mode_top_bound)
     323
     324  ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
     325  tau_top_bound=1.e-5
     326  CALL getin('tau_top_bound',tau_top_bound)
     327
     328  !Config  Key  = coefdis
     329  !Config  Desc = coefficient pour gamdissip
     330  !Config  Def  = 0
     331  !Config  Help = coefficient pour gamdissip 
     332  coefdis = 0.
     333  CALL getin('coefdis',coefdis)
     334
     335  !Config  Key  = purmats
     336  !Config  Desc = Schema d'integration
     337  !Config  Def  = n
     338  !Config  Help = Choix du schema d'integration temporel.
     339  !Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
     340  purmats = .FALSE.
     341  CALL getin('purmats',purmats)
     342
     343  !Config  Key  = ok_guide
     344  !Config  Desc = Guidage
     345  !Config  Def  = n
     346  !Config  Help = Guidage
     347  ok_guide = .FALSE.
     348  CALL getin('ok_guide',ok_guide)
     349
     350  !Config  Key  =  read_start
     351  !Config  Desc = Initialize model using a 'start.nc' file
     352  !Config  Def  = y
     353  !Config  Help = y: intialize dynamical fields using a 'start.nc' file
     354  !               n: fields are initialized by 'iniacademic' routine
     355  read_start= .true.
     356  CALL getin('read_start',read_start)
     357
     358  !Config  Key  = iflag_phys
     359  !Config  Desc = Avec ls physique
     360  !Config  Def  = 1
     361  !Config  Help = Permet de faire tourner le modele sans
     362  !Config         physique.
     363  iflag_phys = 1
     364  CALL getin('iflag_phys',iflag_phys)
     365
     366  !Config  Key  =  iphysiq
     367  !Config  Desc = Periode de la physique
     368  !Config  Def  = 5
     369  !Config  Help = Periode de la physique en pas de temps de la dynamique.
     370  iphysiq = 5
     371  CALL getin('iphysiq', iphysiq)
     372
     373  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
     374       "iphysiq must be a multiple of iperiod", 1)
     375
     376  !Config  Key  = ip_ebil_dyn
     377  !Config  Desc = PRINT level for energy conserv. diag.
     378  !Config  Def  = 0
     379  !Config  Help = PRINT level for energy conservation diag. ;
     380  !               les options suivantes existent :
     381  !Config         0 pas de print
     382  !Config         1 pas de print
     383  !Config         2 print,
     384  ip_ebil_dyn = 0
     385  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
     386
     387  DO i = 1, longcles
     388     clesphy0(i) = 0.
     389  ENDDO
     390
     391  !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
     392  !     .........   (  modif  le 17/04/96 )   .........
     393
     394  test_etatinit: IF (.not. etatinit) then
     395     !Config  Key  = clon
     396     !Config  Desc = centre du zoom, longitude
     397     !Config  Def  = 0
     398     !Config  Help = longitude en degres du centre
     399     !Config         du zoom
     400     clonn = 0.
     401     CALL getin('clon',clonn)
     402
     403     !Config  Key  = clat
     404     !Config  Desc = centre du zoom, latitude
     405     !Config  Def  = 0
     406     !Config  Help = latitude en degres du centre du zoom
     407     !Config         
     408     clatt = 0.
     409     CALL getin('clat',clatt)
     410
     411     IF( ABS(clat - clatt).GE. 0.001 )  THEN
     412        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
     413             ' est differente de celle lue sur le fichier  start '
    426414        STOP
    427       ENDIF
    428 
    429 !Config  Key  = grossismx
    430 !Config  Desc = zoom en longitude
    431 !Config  Def  = 1.0
    432 !Config  Help = facteur de grossissement du zoom,
    433 !Config         selon la longitude
    434        grossismxx = 1.0
    435        CALL getin('grossismx',grossismxx)
    436 
    437 
    438       IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    439         write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
    440      &  'run.def est differente de celle lue sur le fichier  start '
     415     ENDIF
     416
     417     !Config  Key  = grossismx
     418     !Config  Desc = zoom en longitude
     419     !Config  Def  = 1.0
     420     !Config  Help = facteur de grossissement du zoom,
     421     !Config         selon la longitude
     422     grossismxx = 1.0
     423     CALL getin('grossismx',grossismxx)
     424
     425     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
     426        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
     427             'run.def est differente de celle lue sur le fichier  start '
    441428        STOP
    442       ENDIF
    443 
    444 !Config  Key  = grossismy
    445 !Config  Desc = zoom en latitude
    446 !Config  Def  = 1.0
    447 !Config  Help = facteur de grossissement du zoom,
    448 !Config         selon la latitude
    449        grossismyy = 1.0
    450        CALL getin('grossismy',grossismyy)
    451 
    452       IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
    453         write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
    454      & 'run.def est differente de celle lue sur le fichier  start '
     429     ENDIF
     430
     431     !Config  Key  = grossismy
     432     !Config  Desc = zoom en latitude
     433     !Config  Def  = 1.0
     434     !Config  Help = facteur de grossissement du zoom,
     435     !Config         selon la latitude
     436     grossismyy = 1.0
     437     CALL getin('grossismy',grossismyy)
     438
     439     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
     440        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
     441             'run.def est differente de celle lue sur le fichier  start '
    455442        STOP
    456       ENDIF
    457      
    458       IF( grossismx.LT.1. )  THEN
    459         write(lunout,*)
    460      &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    461          STOP
    462       ELSE
    463          alphax = 1. - 1./ grossismx
    464       ENDIF
    465 
    466 
    467       IF( grossismy.LT.1. )  THEN
    468         write(lunout,*)
    469      &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    470          STOP
    471       ELSE
    472          alphay = 1. - 1./ grossismy
    473       ENDIF
    474 
    475       write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
    476 !
    477 !    alphax et alphay sont les anciennes formulat. des grossissements
    478 !
    479 !
    480 
    481 !Config  Key  = fxyhypb
    482 !Config  Desc = Fonction  hyperbolique
    483 !Config  Def  = y
    484 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    485 !Config         sinon  sinusoidale
    486        fxyhypbb = .TRUE.
    487        CALL getin('fxyhypb',fxyhypbb)
    488 
    489       IF( .NOT.fxyhypb )  THEN
    490          IF( fxyhypbb )     THEN
    491             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    492             write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
    493      *       'F alors  qu il est  T  sur  run.def  ***'
     443     ENDIF
     444
     445     IF( grossismx.LT.1. )  THEN
     446        write(lunout,*) &
     447             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
     448        STOP
     449     ELSE
     450        alphax = 1. - 1./ grossismx
     451     ENDIF
     452
     453     IF( grossismy.LT.1. )  THEN
     454        write(lunout,*) &
     455             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
     456        STOP
     457     ELSE
     458        alphay = 1. - 1./ grossismy
     459     ENDIF
     460
     461     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
     462
     463     !    alphax et alphay sont les anciennes formulat. des grossissements
     464
     465     !Config  Key  = fxyhypb
     466     !Config  Desc = Fonction  hyperbolique
     467     !Config  Def  = y
     468     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     469     !Config         sinon  sinusoidale
     470     fxyhypbb = .TRUE.
     471     CALL getin('fxyhypb',fxyhypbb)
     472
     473     IF( .NOT.fxyhypb )  THEN
     474        IF( fxyhypbb )     THEN
     475           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     476           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
     477                'F alors  qu il est  T  sur  run.def  ***'
     478           STOP
     479        ENDIF
     480     ELSE
     481        IF( .NOT.fxyhypbb )   THEN
     482           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     483           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
     484                'T alors  qu il est  F  sur  run.def  ****  '
     485           STOP
     486        ENDIF
     487     ENDIF
     488
     489     !Config  Key  = dzoomx
     490     !Config  Desc = extension en longitude
     491     !Config  Def  = 0
     492     !Config  Help = extension en longitude  de la zone du zoom 
     493     !Config         ( fraction de la zone totale)
     494     dzoomxx = 0.0
     495     CALL getin('dzoomx',dzoomxx)
     496
     497     IF( fxyhypb )  THEN
     498        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
     499           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
     500                'run.def est differente de celle lue sur le fichier  start '
     501           STOP
     502        ENDIF
     503     ENDIF
     504
     505     !Config  Key  = dzoomy
     506     !Config  Desc = extension en latitude
     507     !Config  Def  = 0
     508     !Config  Help = extension en latitude de la zone  du zoom 
     509     !Config         ( fraction de la zone totale)
     510     dzoomyy = 0.0
     511     CALL getin('dzoomy',dzoomyy)
     512
     513     IF( fxyhypb )  THEN
     514        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
     515           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
     516                'run.def est differente de celle lue sur le fichier  start '
     517           STOP
     518        ENDIF
     519     ENDIF
     520
     521     !Config  Key  = taux
     522     !Config  Desc = raideur du zoom en  X
     523     !Config  Def  = 3
     524     !Config  Help = raideur du zoom en  X
     525     tauxx = 3.0
     526     CALL getin('taux',tauxx)
     527
     528     IF( fxyhypb )  THEN
     529        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
     530           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
     531                'run.def est differente de celle lue sur le fichier  start '
     532           STOP
     533        ENDIF
     534     ENDIF
     535
     536     !Config  Key  = tauyy
     537     !Config  Desc = raideur du zoom en  Y
     538     !Config  Def  = 3
     539     !Config  Help = raideur du zoom en  Y
     540     tauyy = 3.0
     541     CALL getin('tauy',tauyy)
     542
     543     IF( fxyhypb )  THEN
     544        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
     545           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
     546                'run.def est differente de celle lue sur le fichier  start '
     547           STOP
     548        ENDIF
     549     ENDIF
     550
     551     !c
     552     IF( .NOT.fxyhypb  )  THEN
     553
     554        !Config  Key  = ysinus
     555        !Config  IF   = !fxyhypb
     556        !Config  Desc = Fonction en Sinus
     557        !Config  Def  = y
     558        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     559        !Config         sinon y = latit.
     560        ysinuss = .TRUE.
     561        CALL getin('ysinus',ysinuss)
     562
     563        IF( .NOT.ysinus )  THEN
     564           IF( ysinuss )     THEN
     565              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     566              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
     567                   ' alors  qu il est  T  sur  run.def  ***'
    494568              STOP
    495          ENDIF
    496       ELSE
    497          IF( .NOT.fxyhypbb )   THEN
    498             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    499             write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
    500      *        'T alors  qu il est  F  sur  run.def  ****  '
     569           ENDIF
     570        ELSE
     571           IF( .NOT.ysinuss )   THEN
     572              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     573              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
     574                   ' alors  qu il est  F  sur  run.def  ****  '
    501575              STOP
    502          ENDIF
    503       ENDIF
    504 !
    505 !Config  Key  = dzoomx
    506 !Config  Desc = extension en longitude
    507 !Config  Def  = 0
    508 !Config  Help = extension en longitude  de la zone du zoom 
    509 !Config         ( fraction de la zone totale)
    510        dzoomxx = 0.0
    511        CALL getin('dzoomx',dzoomxx)
    512 
    513       IF( fxyhypb )  THEN
    514        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    515         write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
    516      *  'run.def est differente de celle lue sur le fichier  start '
     576           ENDIF
     577        ENDIF
     578     ENDIF ! of IF( .NOT.fxyhypb  )
     579
     580     !Config  Key  = offline
     581     !Config  Desc = Nouvelle eau liquide
     582     !Config  Def  = n
     583     !Config  Help = Permet de mettre en route la
     584     !Config         nouvelle parametrisation de l'eau liquide !
     585     offline = .FALSE.
     586     CALL getin('offline',offline)
     587
     588     !Config  Key  = type_trac
     589     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     590     !Config  Def  = lmdz
     591     !Config  Help =
     592     !Config         'lmdz' = pas de couplage, pur LMDZ
     593     !Config         'inca' = model de chime INCA
     594     !Config         'repr' = model de chime REPROBUS
     595     type_trac = 'lmdz'
     596     CALL getin('type_trac',type_trac)
     597
     598     !Config  Key  = config_inca
     599     !Config  Desc = Choix de configuration de INCA
     600     !Config  Def  = none
     601     !Config  Help = Choix de configuration de INCA :
     602     !Config         'none' = sans INCA
     603     !Config         'chem' = INCA avec calcul de chemie
     604     !Config         'aero' = INCA avec calcul des aerosols
     605     config_inca = 'none'
     606     CALL getin('config_inca',config_inca)
     607
     608     !Config  Key  = ok_dynzon
     609     !Config  Desc = calcul et sortie des transports
     610     !Config  Def  = n
     611     !Config  Help = Permet de mettre en route le calcul des transports
     612     !Config         
     613     ok_dynzon = .FALSE.
     614     CALL getin('ok_dynzon',ok_dynzon)
     615
     616     !Config  Key  = ok_dyn_ins
     617     !Config  Desc = sorties instantanees dans la dynamique
     618     !Config  Def  = n
     619     !Config  Help =
     620     !Config         
     621     ok_dyn_ins = .FALSE.
     622     CALL getin('ok_dyn_ins',ok_dyn_ins)
     623
     624     !Config  Key  = ok_dyn_ave
     625     !Config  Desc = sorties moyennes dans la dynamique
     626     !Config  Def  = n
     627     !Config  Help =
     628     !Config         
     629     ok_dyn_ave = .FALSE.
     630     CALL getin('ok_dyn_ave',ok_dyn_ave)
     631
     632     write(lunout,*)' #########################################'
     633     write(lunout,*)' Configuration des parametres du gcm: '
     634     write(lunout,*)' planet_type = ', planet_type
     635     write(lunout,*)' calend = ', calend
     636     write(lunout,*)' dayref = ', dayref
     637     write(lunout,*)' anneeref = ', anneeref
     638     write(lunout,*)' nday = ', nday
     639     write(lunout,*)' day_step = ', day_step
     640     write(lunout,*)' iperiod = ', iperiod
     641     write(lunout,*)' nsplit_phys = ', nsplit_phys
     642     write(lunout,*)' iconser = ', iconser
     643     write(lunout,*)' iecri = ', iecri
     644     write(lunout,*)' periodav = ', periodav
     645     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
     646     write(lunout,*)' dissip_period = ', dissip_period
     647     write(lunout,*)' lstardis = ', lstardis
     648     write(lunout,*)' nitergdiv = ', nitergdiv
     649     write(lunout,*)' nitergrot = ', nitergrot
     650     write(lunout,*)' niterh = ', niterh
     651     write(lunout,*)' tetagdiv = ', tetagdiv
     652     write(lunout,*)' tetagrot = ', tetagrot
     653     write(lunout,*)' tetatemp = ', tetatemp
     654     write(lunout,*)' coefdis = ', coefdis
     655     write(lunout,*)' purmats = ', purmats
     656     write(lunout,*)' read_start = ', read_start
     657     write(lunout,*)' iflag_phys = ', iflag_phys
     658     write(lunout,*)' iphysiq = ', iphysiq
     659     write(lunout,*)' clonn = ', clonn
     660     write(lunout,*)' clatt = ', clatt
     661     write(lunout,*)' grossismx = ', grossismx
     662     write(lunout,*)' grossismy = ', grossismy
     663     write(lunout,*)' fxyhypbb = ', fxyhypbb
     664     write(lunout,*)' dzoomxx = ', dzoomxx
     665     write(lunout,*)' dzoomy = ', dzoomyy
     666     write(lunout,*)' tauxx = ', tauxx
     667     write(lunout,*)' tauyy = ', tauyy
     668     write(lunout,*)' offline = ', offline
     669     write(lunout,*)' type_trac = ', type_trac
     670     write(lunout,*)' config_inca = ', config_inca
     671     write(lunout,*)' ok_dynzon = ', ok_dynzon
     672     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
     673     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
     674  else
     675     !Config  Key  = clon
     676     !Config  Desc = centre du zoom, longitude
     677     !Config  Def  = 0
     678     !Config  Help = longitude en degres du centre
     679     !Config         du zoom
     680     clon = 0.
     681     CALL getin('clon',clon)
     682
     683     !Config  Key  = clat
     684     !Config  Desc = centre du zoom, latitude
     685     !Config  Def  = 0
     686     !Config  Help = latitude en degres du centre du zoom
     687     !Config         
     688     clat = 0.
     689     CALL getin('clat',clat)
     690
     691     !Config  Key  = grossismx
     692     !Config  Desc = zoom en longitude
     693     !Config  Def  = 1.0
     694     !Config  Help = facteur de grossissement du zoom,
     695     !Config         selon la longitude
     696     grossismx = 1.0
     697     CALL getin('grossismx',grossismx)
     698
     699     !Config  Key  = grossismy
     700     !Config  Desc = zoom en latitude
     701     !Config  Def  = 1.0
     702     !Config  Help = facteur de grossissement du zoom,
     703     !Config         selon la latitude
     704     grossismy = 1.0
     705     CALL getin('grossismy',grossismy)
     706
     707     IF( grossismx.LT.1. )  THEN
     708        write(lunout,*) &
     709             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    517710        STOP
    518        ENDIF
    519       ENDIF
    520 
    521 !Config  Key  = dzoomy
    522 !Config  Desc = extension en latitude
    523 !Config  Def  = 0
    524 !Config  Help = extension en latitude de la zone  du zoom 
    525 !Config         ( fraction de la zone totale)
    526        dzoomyy = 0.0
    527        CALL getin('dzoomy',dzoomyy)
    528 
    529       IF( fxyhypb )  THEN
    530        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    531         write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
    532      * 'run.def est differente de celle lue sur le fichier  start '
     711     ELSE
     712        alphax = 1. - 1./ grossismx
     713     ENDIF
     714
     715     IF( grossismy.LT.1. )  THEN
     716        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
    533717        STOP
    534        ENDIF
    535       ENDIF
    536      
    537 !Config  Key  = taux
    538 !Config  Desc = raideur du zoom en  X
    539 !Config  Def  = 3
    540 !Config  Help = raideur du zoom en  X
    541        tauxx = 3.0
    542        CALL getin('taux',tauxx)
    543 
    544       IF( fxyhypb )  THEN
    545        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    546         write(lunout,*)'conf_gcm: La valeur de taux passee par ',
    547      * 'run.def est differente de celle lue sur le fichier  start '
    548         STOP
    549        ENDIF
    550       ENDIF
    551 
    552 !Config  Key  = tauyy
    553 !Config  Desc = raideur du zoom en  Y
    554 !Config  Def  = 3
    555 !Config  Help = raideur du zoom en  Y
    556        tauyy = 3.0
    557        CALL getin('tauy',tauyy)
    558 
    559       IF( fxyhypb )  THEN
    560        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    561         write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
    562      * 'run.def est differente de celle lue sur le fichier  start '
    563         STOP
    564        ENDIF
    565       ENDIF
    566 
    567 !c
    568       IF( .NOT.fxyhypb  )  THEN
    569 
    570 !Config  Key  = ysinus
    571 !Config  IF   = !fxyhypb
    572 !Config  Desc = Fonction en Sinus
    573 !Config  Def  = y
    574 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    575 !Config         sinon y = latit.
    576        ysinuss = .TRUE.
    577        CALL getin('ysinus',ysinuss)
    578 
    579         IF( .NOT.ysinus )  THEN
    580           IF( ysinuss )     THEN
    581             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    582             write(lunout,*)' *** ysinus lu sur le fichier start est F',
    583      *       ' alors  qu il est  T  sur  run.def  ***'
    584             STOP
    585           ENDIF
    586         ELSE
    587           IF( .NOT.ysinuss )   THEN
    588             write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    589             write(lunout,*)' *** ysinus lu sur le fichier start est T',
    590      *        ' alors  qu il est  F  sur  run.def  ****  '
    591               STOP
    592           ENDIF
    593         ENDIF
    594       ENDIF ! of IF( .NOT.fxyhypb  )
    595 !
    596 !Config  Key  = offline
    597 !Config  Desc = Nouvelle eau liquide
    598 !Config  Def  = n
    599 !Config  Help = Permet de mettre en route la
    600 !Config         nouvelle parametrisation de l'eau liquide !
    601        offline = .FALSE.
    602        CALL getin('offline',offline)
    603      
    604 !Config  Key  = type_trac
    605 !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
    606 !Config  Def  = lmdz
    607 !Config  Help =
    608 !Config         'lmdz' = pas de couplage, pur LMDZ
    609 !Config         'inca' = model de chime INCA
    610 !Config         'repr' = model de chime REPROBUS
    611       type_trac = 'lmdz'
    612       CALL getin('type_trac',type_trac)
    613 
    614 !Config  Key  = config_inca
    615 !Config  Desc = Choix de configuration de INCA
    616 !Config  Def  = none
    617 !Config  Help = Choix de configuration de INCA :
    618 !Config         'none' = sans INCA
    619 !Config         'chem' = INCA avec calcul de chemie
    620 !Config         'aero' = INCA avec calcul des aerosols
    621       config_inca = 'none'
    622       CALL getin('config_inca',config_inca)
    623 
    624 !Config  Key  = ok_dynzon
    625 !Config  Desc = calcul et sortie des transports
    626 !Config  Def  = n
    627 !Config  Help = Permet de mettre en route le calcul des transports
    628 !Config         
    629       ok_dynzon = .FALSE.
    630       CALL getin('ok_dynzon',ok_dynzon)
    631 
    632 !Config  Key  = ok_dyn_ins
    633 !Config  Desc = sorties instantanees dans la dynamique
    634 !Config  Def  = n
    635 !Config  Help =
    636 !Config         
    637       ok_dyn_ins = .FALSE.
    638       CALL getin('ok_dyn_ins',ok_dyn_ins)
    639 
    640 !Config  Key  = ok_dyn_ave
    641 !Config  Desc = sorties moyennes dans la dynamique
    642 !Config  Def  = n
    643 !Config  Help =
    644 !Config         
    645       ok_dyn_ave = .FALSE.
    646       CALL getin('ok_dyn_ave',ok_dyn_ave)
    647 
    648       write(lunout,*)' #########################################'
    649       write(lunout,*)' Configuration des parametres du gcm: '
    650       write(lunout,*)' planet_type = ', planet_type
    651       write(lunout,*)' calend = ', calend
    652       write(lunout,*)' dayref = ', dayref
    653       write(lunout,*)' anneeref = ', anneeref
    654       write(lunout,*)' nday = ', nday
    655       write(lunout,*)' day_step = ', day_step
    656       write(lunout,*)' iperiod = ', iperiod
    657       write(lunout,*)' nsplit_phys = ', nsplit_phys
    658       write(lunout,*)' iconser = ', iconser
    659       write(lunout,*)' iecri = ', iecri
    660       write(lunout,*)' periodav = ', periodav
    661       write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    662       write(lunout,*)' dissip_period = ', dissip_period
    663       write(lunout,*)' lstardis = ', lstardis
    664       write(lunout,*)' nitergdiv = ', nitergdiv
    665       write(lunout,*)' nitergrot = ', nitergrot
    666       write(lunout,*)' niterh = ', niterh
    667       write(lunout,*)' tetagdiv = ', tetagdiv
    668       write(lunout,*)' tetagrot = ', tetagrot
    669       write(lunout,*)' tetatemp = ', tetatemp
    670       write(lunout,*)' coefdis = ', coefdis
    671       write(lunout,*)' purmats = ', purmats
    672       write(lunout,*)' read_start = ', read_start
    673       write(lunout,*)' iflag_phys = ', iflag_phys
    674       write(lunout,*)' iphysiq = ', iphysiq
    675       write(lunout,*)' clonn = ', clonn
    676       write(lunout,*)' clatt = ', clatt
    677       write(lunout,*)' grossismx = ', grossismx
    678       write(lunout,*)' grossismy = ', grossismy
    679       write(lunout,*)' fxyhypbb = ', fxyhypbb
    680       write(lunout,*)' dzoomxx = ', dzoomxx
    681       write(lunout,*)' dzoomy = ', dzoomyy
    682       write(lunout,*)' tauxx = ', tauxx
    683       write(lunout,*)' tauyy = ', tauyy
    684       write(lunout,*)' offline = ', offline
    685       write(lunout,*)' type_trac = ', type_trac
    686       write(lunout,*)' config_inca = ', config_inca
    687       write(lunout,*)' ok_dynzon = ', ok_dynzon
    688       write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    689       write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
    690 
    691       RETURN
    692 !   ...............................................
    693 !
    694 100   CONTINUE
    695 !Config  Key  = clon
    696 !Config  Desc = centre du zoom, longitude
    697 !Config  Def  = 0
    698 !Config  Help = longitude en degres du centre
    699 !Config         du zoom
    700        clon = 0.
    701        CALL getin('clon',clon)
    702 
    703 !Config  Key  = clat
    704 !Config  Desc = centre du zoom, latitude
    705 !Config  Def  = 0
    706 !Config  Help = latitude en degres du centre du zoom
    707 !Config         
    708        clat = 0.
    709        CALL getin('clat',clat)
    710 
    711 !Config  Key  = grossismx
    712 !Config  Desc = zoom en longitude
    713 !Config  Def  = 1.0
    714 !Config  Help = facteur de grossissement du zoom,
    715 !Config         selon la longitude
    716        grossismx = 1.0
    717        CALL getin('grossismx',grossismx)
    718 
    719 !Config  Key  = grossismy
    720 !Config  Desc = zoom en latitude
    721 !Config  Def  = 1.0
    722 !Config  Help = facteur de grossissement du zoom,
    723 !Config         selon la latitude
    724        grossismy = 1.0
    725        CALL getin('grossismy',grossismy)
    726 
    727       IF( grossismx.LT.1. )  THEN
    728         write(lunout,*)
    729      &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    730          STOP
    731       ELSE
    732          alphax = 1. - 1./ grossismx
    733       ENDIF
    734 
    735 
    736       IF( grossismy.LT.1. )  THEN
    737         write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
    738          STOP
    739       ELSE
    740          alphay = 1. - 1./ grossismy
    741       ENDIF
    742 
    743       write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
    744 !
    745 !    alphax et alphay sont les anciennes formulat. des grossissements
    746 !
    747 !
    748 
    749 !Config  Key  = fxyhypb
    750 !Config  Desc = Fonction  hyperbolique
    751 !Config  Def  = y
    752 !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
    753 !Config         sinon  sinusoidale
    754        fxyhypb = .TRUE.
    755        CALL getin('fxyhypb',fxyhypb)
    756 
    757 !Config  Key  = dzoomx
    758 !Config  Desc = extension en longitude
    759 !Config  Def  = 0
    760 !Config  Help = extension en longitude  de la zone du zoom 
    761 !Config         ( fraction de la zone totale)
    762        dzoomx = 0.0
    763        CALL getin('dzoomx',dzoomx)
    764 
    765 !Config  Key  = dzoomy
    766 !Config  Desc = extension en latitude
    767 !Config  Def  = 0
    768 !Config  Help = extension en latitude de la zone  du zoom 
    769 !Config         ( fraction de la zone totale)
    770        dzoomy = 0.0
    771        CALL getin('dzoomy',dzoomy)
    772 
    773 !Config  Key  = taux
    774 !Config  Desc = raideur du zoom en  X
    775 !Config  Def  = 3
    776 !Config  Help = raideur du zoom en  X
    777        taux = 3.0
    778        CALL getin('taux',taux)
    779 
    780 !Config  Key  = tauy
    781 !Config  Desc = raideur du zoom en  Y
    782 !Config  Def  = 3
    783 !Config  Help = raideur du zoom en  Y
    784        tauy = 3.0
    785        CALL getin('tauy',tauy)
    786 
    787 !Config  Key  = ysinus
    788 !Config  IF   = !fxyhypb
    789 !Config  Desc = Fonction en Sinus
    790 !Config  Def  = y
    791 !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
    792 !Config         sinon y = latit.
    793        ysinus = .TRUE.
    794        CALL getin('ysinus',ysinus)
    795 !
    796 !Config  Key  = offline
    797 !Config  Desc = Nouvelle eau liquide
    798 !Config  Def  = n
    799 !Config  Help = Permet de mettre en route la
    800 !Config         nouvelle parametrisation de l'eau liquide !
    801        offline = .FALSE.
    802        CALL getin('offline',offline)
    803 
    804 !Config  Key  = type_trac
    805 !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
    806 !Config  Def  = lmdz
    807 !Config  Help =
    808 !Config         'lmdz' = pas de couplage, pur LMDZ
    809 !Config         'inca' = model de chime INCA
    810 !Config         'repr' = model de chime REPROBUS
    811       type_trac = 'lmdz'
    812       CALL getin('type_trac',type_trac)
    813 
    814 !Config  Key  = config_inca
    815 !Config  Desc = Choix de configuration de INCA
    816 !Config  Def  = none
    817 !Config  Help = Choix de configuration de INCA :
    818 !Config         'none' = sans INCA
    819 !Config         'chem' = INCA avec calcul de chemie
    820 !Config         'aero' = INCA avec calcul des aerosols
    821       config_inca = 'none'
    822       CALL getin('config_inca',config_inca)
    823 
    824 !Config  Key  = ok_dynzon
    825 !Config  Desc = sortie des transports zonaux dans la dynamique
    826 !Config  Def  = n
    827 !Config  Help = Permet de mettre en route le calcul des transports
    828 !Config         
    829       ok_dynzon = .FALSE.
    830       CALL getin('ok_dynzon',ok_dynzon)
    831 
    832 !Config  Key  = ok_dyn_ins
    833 !Config  Desc = sorties instantanees dans la dynamique
    834 !Config  Def  = n
    835 !Config  Help =
    836 !Config         
    837       ok_dyn_ins = .FALSE.
    838       CALL getin('ok_dyn_ins',ok_dyn_ins)
    839 
    840 !Config  Key  = ok_dyn_ave
    841 !Config  Desc = sorties moyennes dans la dynamique
    842 !Config  Def  = n
    843 !Config  Help =
    844 !Config         
    845       ok_dyn_ave = .FALSE.
    846       CALL getin('ok_dyn_ave',ok_dyn_ave)
    847 
    848 !Config  Key  = use_filtre_fft
    849 !Config  Desc = flag d'activation des FFT pour le filtre
    850 !Config  Def  = false
    851 !Config  Help = permet d'activer l'utilisation des FFT pour effectuer
    852 !Config         le filtrage aux poles.
    853 ! Le filtre fft n'est pas implemente dans dyn3d
    854       use_filtre_fft=.FALSE.
    855       CALL getin('use_filtre_fft',use_filtre_fft)
    856 
    857       IF (use_filtre_fft) THEN
     718     ELSE
     719        alphay = 1. - 1./ grossismy
     720     ENDIF
     721
     722     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
     723
     724     !    alphax et alphay sont les anciennes formulat. des grossissements
     725
     726     !Config  Key  = fxyhypb
     727     !Config  Desc = Fonction  hyperbolique
     728     !Config  Def  = y
     729     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
     730     !Config         sinon  sinusoidale
     731     fxyhypb = .TRUE.
     732     CALL getin('fxyhypb',fxyhypb)
     733
     734     !Config  Key  = dzoomx
     735     !Config  Desc = extension en longitude
     736     !Config  Def  = 0
     737     !Config  Help = extension en longitude  de la zone du zoom 
     738     !Config         ( fraction de la zone totale)
     739     dzoomx = 0.0
     740     CALL getin('dzoomx',dzoomx)
     741
     742     !Config  Key  = dzoomy
     743     !Config  Desc = extension en latitude
     744     !Config  Def  = 0
     745     !Config  Help = extension en latitude de la zone  du zoom 
     746     !Config         ( fraction de la zone totale)
     747     dzoomy = 0.0
     748     CALL getin('dzoomy',dzoomy)
     749
     750     !Config  Key  = taux
     751     !Config  Desc = raideur du zoom en  X
     752     !Config  Def  = 3
     753     !Config  Help = raideur du zoom en  X
     754     taux = 3.0
     755     CALL getin('taux',taux)
     756
     757     !Config  Key  = tauy
     758     !Config  Desc = raideur du zoom en  Y
     759     !Config  Def  = 3
     760     !Config  Help = raideur du zoom en  Y
     761     tauy = 3.0
     762     CALL getin('tauy',tauy)
     763
     764     !Config  Key  = ysinus
     765     !Config  IF   = !fxyhypb
     766     !Config  Desc = Fonction en Sinus
     767     !Config  Def  = y
     768     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
     769     !Config         sinon y = latit.
     770     ysinus = .TRUE.
     771     CALL getin('ysinus',ysinus)
     772
     773     !Config  Key  = offline
     774     !Config  Desc = Nouvelle eau liquide
     775     !Config  Def  = n
     776     !Config  Help = Permet de mettre en route la
     777     !Config         nouvelle parametrisation de l'eau liquide !
     778     offline = .FALSE.
     779     CALL getin('offline',offline)
     780
     781     !Config  Key  = type_trac
     782     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     783     !Config  Def  = lmdz
     784     !Config  Help =
     785     !Config         'lmdz' = pas de couplage, pur LMDZ
     786     !Config         'inca' = model de chime INCA
     787     !Config         'repr' = model de chime REPROBUS
     788     type_trac = 'lmdz'
     789     CALL getin('type_trac',type_trac)
     790
     791     !Config  Key  = config_inca
     792     !Config  Desc = Choix de configuration de INCA
     793     !Config  Def  = none
     794     !Config  Help = Choix de configuration de INCA :
     795     !Config         'none' = sans INCA
     796     !Config         'chem' = INCA avec calcul de chemie
     797     !Config         'aero' = INCA avec calcul des aerosols
     798     config_inca = 'none'
     799     CALL getin('config_inca',config_inca)
     800
     801     !Config  Key  = ok_dynzon
     802     !Config  Desc = sortie des transports zonaux dans la dynamique
     803     !Config  Def  = n
     804     !Config  Help = Permet de mettre en route le calcul des transports
     805     !Config         
     806     ok_dynzon = .FALSE.
     807     CALL getin('ok_dynzon',ok_dynzon)
     808
     809     !Config  Key  = ok_dyn_ins
     810     !Config  Desc = sorties instantanees dans la dynamique
     811     !Config  Def  = n
     812     !Config  Help =
     813     !Config         
     814     ok_dyn_ins = .FALSE.
     815     CALL getin('ok_dyn_ins',ok_dyn_ins)
     816
     817     !Config  Key  = ok_dyn_ave
     818     !Config  Desc = sorties moyennes dans la dynamique
     819     !Config  Def  = n
     820     !Config  Help =
     821     !Config         
     822     ok_dyn_ave = .FALSE.
     823     CALL getin('ok_dyn_ave',ok_dyn_ave)
     824
     825     !Config  Key  = use_filtre_fft
     826     !Config  Desc = flag d'activation des FFT pour le filtre
     827     !Config  Def  = false
     828     !Config  Help = permet d'activer l'utilisation des FFT pour effectuer
     829     !Config         le filtrage aux poles.
     830     ! Le filtre fft n'est pas implemente dans dyn3d
     831     use_filtre_fft=.FALSE.
     832     CALL getin('use_filtre_fft',use_filtre_fft)
     833
     834     IF (use_filtre_fft) THEN
    858835        write(lunout,*)'STOP !!!'
    859836        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
    860837        STOP 1
    861       ENDIF
    862      
    863 !Config key = ok_strato
    864 !Config  Desc = activation de la version strato
    865 !Config  Def  = .FALSE.
    866 !Config  Help = active la version stratosphérique de LMDZ de F. Lott
    867 
    868       ok_strato=.FALSE.
    869       CALL getin('ok_strato',ok_strato)
    870 
    871       vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
    872       CALL getin('vert_prof_dissip', vert_prof_dissip)
    873       call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
    874      $     "bad value for vert_prof_dissip")
    875 
    876 !Config  Key  = ok_gradsfile
    877 !Config  Desc = activation des sorties grads du guidage
    878 !Config  Def  = n
    879 !Config  Help = active les sorties grads du guidage
    880 
    881        ok_gradsfile = .FALSE.
    882        CALL getin('ok_gradsfile',ok_gradsfile)
    883 
    884 !Config  Key  = ok_limit
    885 !Config  Desc = creation des fichiers limit dans create_etat0_limit
    886 !Config  Def  = y
    887 !Config  Help = production du fichier limit.nc requise
    888 
    889        ok_limit = .TRUE.
    890        CALL getin('ok_limit',ok_limit)
    891 
    892 !Config  Key  = ok_etat0
    893 !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
    894 !Config  Def  = y
    895 !Config  Help = production des fichiers start.nc, startphy.nc requise
    896 
    897       ok_etat0 = .TRUE.
    898       CALL getin('ok_etat0',ok_etat0)
    899 
    900       write(lunout,*)' #########################################'
    901       write(lunout,*)' Configuration des parametres de cel0'
    902      &             //'_limit: '
    903       write(lunout,*)' planet_type = ', planet_type
    904       write(lunout,*)' calend = ', calend
    905       write(lunout,*)' dayref = ', dayref
    906       write(lunout,*)' anneeref = ', anneeref
    907       write(lunout,*)' nday = ', nday
    908       write(lunout,*)' day_step = ', day_step
    909       write(lunout,*)' iperiod = ', iperiod
    910       write(lunout,*)' iconser = ', iconser
    911       write(lunout,*)' iecri = ', iecri
    912       write(lunout,*)' periodav = ', periodav
    913       write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    914       write(lunout,*)' dissip_period = ', dissip_period
    915       write(lunout,*)' lstardis = ', lstardis
    916       write(lunout,*)' nitergdiv = ', nitergdiv
    917       write(lunout,*)' nitergrot = ', nitergrot
    918       write(lunout,*)' niterh = ', niterh
    919       write(lunout,*)' tetagdiv = ', tetagdiv
    920       write(lunout,*)' tetagrot = ', tetagrot
    921       write(lunout,*)' tetatemp = ', tetatemp
    922       write(lunout,*)' coefdis = ', coefdis
    923       write(lunout,*)' purmats = ', purmats
    924       write(lunout,*)' read_start = ', read_start
    925       write(lunout,*)' iflag_phys = ', iflag_phys
    926       write(lunout,*)' iphysiq = ', iphysiq
    927       write(lunout,*)' clon = ', clon
    928       write(lunout,*)' clat = ', clat
    929       write(lunout,*)' grossismx = ', grossismx
    930       write(lunout,*)' grossismy = ', grossismy
    931       write(lunout,*)' fxyhypb = ', fxyhypb
    932       write(lunout,*)' dzoomx = ', dzoomx
    933       write(lunout,*)' dzoomy = ', dzoomy
    934       write(lunout,*)' taux = ', taux
    935       write(lunout,*)' tauy = ', tauy
    936       write(lunout,*)' offline = ', offline
    937       write(lunout,*)' type_trac = ', type_trac
    938       write(lunout,*)' config_inca = ', config_inca
    939       write(lunout,*)' ok_dynzon = ', ok_dynzon
    940       write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    941       write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
    942       write(lunout,*)' ok_strato = ', ok_strato
    943       write(lunout,*)' ok_gradsfile = ', ok_gradsfile
    944       write(lunout,*)' ok_limit = ', ok_limit
    945       write(lunout,*)' ok_etat0 = ', ok_etat0
    946 !
    947       RETURN
    948       END
     838     ENDIF
     839
     840     !Config key = ok_strato
     841     !Config  Desc = activation de la version strato
     842     !Config  Def  = .FALSE.
     843     !Config  Help = active la version stratosphérique de LMDZ de F. Lott
     844
     845     ok_strato=.FALSE.
     846     CALL getin('ok_strato',ok_strato)
     847
     848     vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     849     CALL getin('vert_prof_dissip', vert_prof_dissip)
     850     call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
     851          "bad value for vert_prof_dissip")
     852
     853     !Config  Key  = ok_gradsfile
     854     !Config  Desc = activation des sorties grads du guidage
     855     !Config  Def  = n
     856     !Config  Help = active les sorties grads du guidage
     857
     858     ok_gradsfile = .FALSE.
     859     CALL getin('ok_gradsfile',ok_gradsfile)
     860
     861     !Config  Key  = ok_limit
     862     !Config  Desc = creation des fichiers limit dans create_etat0_limit
     863     !Config  Def  = y
     864     !Config  Help = production du fichier limit.nc requise
     865
     866     ok_limit = .TRUE.
     867     CALL getin('ok_limit',ok_limit)
     868
     869     !Config  Key  = ok_etat0
     870     !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
     871     !Config  Def  = y
     872     !Config  Help = production des fichiers start.nc, startphy.nc requise
     873
     874     ok_etat0 = .TRUE.
     875     CALL getin('ok_etat0',ok_etat0)
     876
     877     write(lunout,*)' #########################################'
     878     write(lunout,*)' Configuration des parametres de cel0' &
     879          //'_limit: '
     880     write(lunout,*)' planet_type = ', planet_type
     881     write(lunout,*)' calend = ', calend
     882     write(lunout,*)' dayref = ', dayref
     883     write(lunout,*)' anneeref = ', anneeref
     884     write(lunout,*)' nday = ', nday
     885     write(lunout,*)' day_step = ', day_step
     886     write(lunout,*)' iperiod = ', iperiod
     887     write(lunout,*)' iconser = ', iconser
     888     write(lunout,*)' iecri = ', iecri
     889     write(lunout,*)' periodav = ', periodav
     890     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
     891     write(lunout,*)' dissip_period = ', dissip_period
     892     write(lunout,*)' lstardis = ', lstardis
     893     write(lunout,*)' nitergdiv = ', nitergdiv
     894     write(lunout,*)' nitergrot = ', nitergrot
     895     write(lunout,*)' niterh = ', niterh
     896     write(lunout,*)' tetagdiv = ', tetagdiv
     897     write(lunout,*)' tetagrot = ', tetagrot
     898     write(lunout,*)' tetatemp = ', tetatemp
     899     write(lunout,*)' coefdis = ', coefdis
     900     write(lunout,*)' purmats = ', purmats
     901     write(lunout,*)' read_start = ', read_start
     902     write(lunout,*)' iflag_phys = ', iflag_phys
     903     write(lunout,*)' iphysiq = ', iphysiq
     904     write(lunout,*)' clon = ', clon
     905     write(lunout,*)' clat = ', clat
     906     write(lunout,*)' grossismx = ', grossismx
     907     write(lunout,*)' grossismy = ', grossismy
     908     write(lunout,*)' fxyhypb = ', fxyhypb
     909     write(lunout,*)' dzoomx = ', dzoomx
     910     write(lunout,*)' dzoomy = ', dzoomy
     911     write(lunout,*)' taux = ', taux
     912     write(lunout,*)' tauy = ', tauy
     913     write(lunout,*)' offline = ', offline
     914     write(lunout,*)' type_trac = ', type_trac
     915     write(lunout,*)' config_inca = ', config_inca
     916     write(lunout,*)' ok_dynzon = ', ok_dynzon
     917     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
     918     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
     919     write(lunout,*)' ok_strato = ', ok_strato
     920     write(lunout,*)' ok_gradsfile = ', ok_gradsfile
     921     write(lunout,*)' ok_limit = ', ok_limit
     922     write(lunout,*)' ok_etat0 = ', ok_etat0
     923  end IF test_etatinit
     924
     925END SUBROUTINE conf_gcm
Note: See TracChangeset for help on using the changeset viewer.