Ignore:
Timestamp:
Jan 11, 2013, 10:19:19 AM (11 years ago)
Author:
Laurent Fairhead
Message:

Version testing basée sur la r1706


Testing release based on r1706

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dmem/conf_gcm.F

    r1669 r1707  
    11!
    2 ! $Id: conf_gcm.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id$
    33!
    44c
     
    66      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
    77c
     8      USE control_mod
    89#ifdef CPP_IOIPSL
    910      use IOIPSL
     
    1718      use mod_hallo, ONLY : use_mpi_alloc
    1819      use parallel, ONLY : omp_chunk
    19       USE control_mod
     20      USE infotrac, ONLY : type_trac
     21      use assert_m, only: assert
     22
    2023      IMPLICIT NONE
    2124c-----------------------------------------------------------------------
     
    4346#include "serre.h"
    4447#include "comdissnew.h"
    45 !#include "clesphys.h"
    46 #include "iniprint.h"
    4748#include "temps.h"
    4849#include "comconst.h"
    4950
    5051! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     52! #include "clesphys.h"
     53#include "iniprint.h"
    5154c
    5255c
     
    103106      CALL getin('lunout', lunout)
    104107      IF (lunout /= 5 .and. lunout /= 6) THEN
    105         OPEN(lunout,FILE='lmdz.out')
     108        OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
     109     &          STATUS='unknown',FORM='formatted')
    106110      ENDIF
    107111
     
    166170      CALL getin('nday',nday)
    167171
     172!Config  Key  = starttime
     173!Config  Desc = Heure de depart de la simulation
     174!Config  Def  = 0
     175!Config  Help = Heure de depart de la simulation
     176!Config         en jour
     177      starttime = 0
     178      CALL getin('starttime',starttime)
     179
    168180!Config  Key  = day_step
    169181!Config  Desc = nombre de pas par jour
     
    175187
    176188!Config  Key  = nsplit_phys
    177 !Config  Desc = nombre d'iteration de la physique
    178 !Config  Def  = 240
    179 !Config  Help = nombre d'itration de la physique
    180 !
    181189       nsplit_phys = 1
    182190       CALL getin('nsplit_phys',nsplit_phys)
     
    226234       CALL getin('output_grads_dyn',output_grads_dyn)
    227235
    228 !Config  Key  = idissip
     236!Config  Key  = dissip_period
    229237!Config  Desc = periode de la dissipation
    230 !Config  Def  = 10
     238!Config  Def  = 0
    231239!Config  Help = periode de la dissipation
    232 !Config         (en pas) ... a completer !
    233        idissip = 10
    234        CALL getin('idissip',idissip)
     240!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
     241!Config  dissip_period>0 => on prend cette valeur
     242       dissip_period = 0
     243       CALL getin('dissip_period',dissip_period)
    235244
    236245ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     
    314323       CALL getin('tau_top_bound',tau_top_bound)
    315324
    316 !
    317325!Config  Key  = coefdis
    318326!Config  Desc = coefficient pour gamdissip
     
    579587       offline = .FALSE.
    580588       CALL getin('offline',offline)
     589       IF (offline .AND. adjust) THEN
     590          WRITE(lunout,*)
     591     &         'WARNING : option offline does not work with adjust=y :'
     592          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
     593     &         'and fluxstokev.nc will not be created'
     594          WRITE(lunout,*)
     595     &         'only the file phystoke.nc will still be created '
     596       END IF
     597       
     598!Config  Key  = type_trac
     599!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     600!Config  Def  = lmdz
     601!Config  Help =
     602!Config         'lmdz' = pas de couplage, pur LMDZ
     603!Config         'inca' = model de chime INCA
     604!Config         'repr' = model de chime REPROBUS
     605      type_trac = 'lmdz'
     606      CALL getin('type_trac',type_trac)
    581607
    582608!Config  Key  = config_inca
     
    628654      write(lunout,*)' periodav = ', periodav
    629655      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    630       write(lunout,*)' idissip = ', idissip
     656      write(lunout,*)' dissip_period = ', dissip_period
    631657      write(lunout,*)' lstardis = ', lstardis
    632658      write(lunout,*)' nitergdiv = ', nitergdiv
     
    651677      write(lunout,*)' tauyy = ', tauyy
    652678      write(lunout,*)' offline = ', offline
     679      write(lunout,*)' type_trac = ', type_trac
    653680      write(lunout,*)' config_inca = ', config_inca
    654681      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    769796       offline = .FALSE.
    770797       CALL getin('offline',offline)
     798       IF (offline .AND. adjust) THEN
     799          WRITE(lunout,*)
     800     &         'WARNING : option offline does not work with adjust=y :'
     801          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
     802     &         'and fluxstokev.nc will not be created'
     803          WRITE(lunout,*)
     804     &         'only the file phystoke.nc will still be created '
     805       END IF
     806
     807!Config  Key  = type_trac
     808!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     809!Config  Def  = lmdz
     810!Config  Help =
     811!Config         'lmdz' = pas de couplage, pur LMDZ
     812!Config         'inca' = model de chime INCA
     813!Config         'repr' = model de chime REPROBUS
     814      type_trac = 'lmdz'
     815      CALL getin('type_trac',type_trac)
    771816
    772817!Config  Key  = config_inca
     
    781826
    782827!Config  Key  = ok_dynzon
    783 !Config  Desc = calcul et sortie des transports
     828!Config  Desc = sortie des transports zonaux dans la dynamique
    784829!Config  Def  = n
    785830!Config  Help = Permet de mettre en route le calcul des transports
     
    817862        write(lunout,*)"Le zoom en longitude est incompatible",
    818863     &                 " avec l'utilisation du filtre FFT ",
    819      &                 "---> filtre FFT désactivé "
     864     &                 "---> FFT filter not active"
    820865       use_filtre_fft=.FALSE.
    821866      ENDIF
     
    851896      CALL getin('ok_strato',ok_strato)
    852897
     898      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     899      CALL getin('vert_prof_dissip', vert_prof_dissip)
     900      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
     901     $     "bad value for vert_prof_dissip")
     902
    853903!Config  Key  = ok_gradsfile
    854904!Config  Desc = activation des sorties grads du guidage
     
    874924      ok_etat0 = .TRUE.
    875925      CALL getin('ok_etat0',ok_etat0)
     926
     927!Config  Key  = grilles_gcm_netcdf
     928!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
     929!Config  Def  = n
     930      grilles_gcm_netcdf = .FALSE.
     931      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
    876932
    877933      write(lunout,*)' #########################################'
     
    889945      write(lunout,*)' periodav = ', periodav
    890946      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    891       write(lunout,*)' idissip = ', idissip
     947      write(lunout,*)' dissip_period = ', dissip_period
    892948      write(lunout,*)' lstardis = ', lstardis
    893949      write(lunout,*)' nitergdiv = ', nitergdiv
     
    912968      write(lunout,*)' tauy = ', tauy
    913969      write(lunout,*)' offline = ', offline
     970      write(lunout,*)' type_trac = ', type_trac
    914971      write(lunout,*)' config_inca = ', config_inca
    915       write(lunout,*)' ok_dynzon = ', ok_dynzon 
     972      write(lunout,*)' ok_dynzon = ', ok_dynzon
    916973      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    917974      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
     
    923980      write(lunout,*)' ok_limit = ', ok_limit
    924981      write(lunout,*)' ok_etat0 = ', ok_etat0
     982      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    925983c
    926984      RETURN
Note: See TracChangeset for help on using the changeset viewer.