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/libf/dyn3d
Files:
5 edited
1 moved

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.