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/dyn3dpar
Files:
6 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/abort_gcm.F

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

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

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

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

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

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

    r1345 r1391  
    852852           CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
    853853         endif
     854c$OMP BARRIER
    854855! Compute geopotential (physics might need it)
    855          CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    856 c$OMP BARRIER
     856         CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
     857
    857858           jD_cur = jD_ref + day_ini - day_ref
    858859     $        + itau/day_step
     
    15951596c$OMP MASTER
    15961597              call fin_getparam
    1597               call finalize_parallel
     1598c$OMP END MASTER
     1599#ifdef INCA
     1600                 call finalize_inca
     1601#endif
     1602c$OMP MASTER
     1603               call finalize_parallel
    15981604c$OMP END MASTER
    15991605              abort_message = 'Simulation finished'
Note: See TracChangeset for help on using the changeset viewer.