Ignore:
Timestamp:
Aug 18, 2011, 12:09:27 PM (13 years ago)
Author:
emillour
Message:

Ehouarn: Mise a jour des dynamiques (seq et ) pour suivre
les changements et developpements de LMDZ5 terrestre
(mise a niveau avec LMDZ5 trunk, rev 1560). Ce qui ne devrais pas changer grand chose au fonctionnement de base du GCM).
Modification importante: correction du bug sur le cumul des flux de masse pour le transport des traceurs (mais dans les faits semble avoir peu d'impact).
(voir "commit_importants.log" pour les details des ajouts et modifications).

File:
1 edited

Legend:

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

    r119 r270  
    11!
    2 ! $Id: conf_gcm.F 1438 2010-10-08 10:19:34Z jghattas $
     2! $Id: conf_gcm.F 1418 2010-07-19 15:11:24Z jghattas $
    33!
    44c
     
    66      SUBROUTINE conf_gcm( tapedef, etatinit )
    77c
     8      USE control_mod
    89#ifdef CPP_IOIPSL
    910      use IOIPSL
     
    1213      use ioipsl_getincom
    1314#endif
    14       use misc_mod
    15       use mod_filtre_fft, ONLY : use_filtre_fft
    16       use mod_hallo, ONLY : use_mpi_alloc
    17       use parallel, ONLY : omp_chunk
    18       USE control_mod
    1915      IMPLICIT NONE
    2016c-----------------------------------------------------------------------
     
    3733#include "serre.h"
    3834#include "comdissnew.h"
    39 !#include "clesphys.h"
    40 #include "iniprint.h"
    4135#include "temps.h"
    4236#include "comconst.h"
    4337
    4438! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
     39! #include "clesphys.h"
     40#include "iniprint.h"
    4541c
    4642c
     
    5349      LOGICAL  fxyhypbb, ysinuss
    5450      INTEGER i
    55      
     51      LOGICAL use_filtre_fft
    5652c
    5753c  -------------------------------------------------------------------
     
    8278c   initialisations:
    8379c   ----------------
    84       adjust=.false.
    85       call getin('adjust',adjust)
    86      
    87       itaumax=0
    88       call getin('itaumax',itaumax);
    89       if (itaumax<=0) itaumax=HUGE(itaumax)
    90      
     80
    9181!Config  Key  = lunout
    9282!Config  Desc = unite de fichier pour les impressions
     
    190180
    191181!Config  Key  = nsplit_phys
    192 !Config  Desc = nombre d'iteration de la physique
    193 !Config  Def  = 240
    194 !Config  Help = nombre d'itration de la physique
    195 !
     182!Config  Desc = nombre de subdivisions par pas physique
     183!Config  Def  = 1
     184!Config  Help = nombre de subdivisions par pas physique
    196185       nsplit_phys = 1
    197186       CALL getin('nsplit_phys',nsplit_phys)
     
    241230       CALL getin('output_grads_dyn',output_grads_dyn)
    242231
    243 !Config  Key  = idissip
     232!Config  Key  = dissip_period
    244233!Config  Desc = periode de la dissipation
    245 !Config  Def  = 10
     234!Config  Def  = 0
    246235!Config  Help = periode de la dissipation
    247 !Config         (en pas) ... a completer !
    248        idissip = 10
    249        CALL getin('idissip',idissip)
     236!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
     237!Config  dissip_period>0 => on prend cette valeur
     238       dissip_period = 0
     239       CALL getin('dissip_period',dissip_period)
    250240
    251241ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     
    340330       CALL getin('tau_top_bound',tau_top_bound)
    341331
    342 !
    343332!Config  Key  = coefdis
    344333!Config  Desc = coefficient pour gamdissip
     
    407396       ip_ebil_dyn = 0
    408397       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
    409 !
    410 
    411398
    412399ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
     
    613600       offline = .FALSE.
    614601       CALL getin('offline',offline)
    615        IF (offline .AND. adjust) THEN
    616           WRITE(lunout,*)
    617      &         'WARNING : option offline does not work with adjust=y :'
    618           WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
    619      &         'and fluxstokev.nc will not be created'
    620           WRITE(lunout,*)
    621      &         'only the file phystoke.nc will still be created '
    622        END IF
    623        
     602
    624603!Config  Key  = config_inca
    625604!Config  Desc = Choix de configuration de INCA
     
    655634      ok_dyn_ave = .FALSE.
    656635      CALL getin('ok_dyn_ave',ok_dyn_ave)
     636
    657637
    658638      write(lunout,*)' #########################################'
     
    669649      write(lunout,*)' day_step = ', day_step
    670650      write(lunout,*)' iperiod = ', iperiod
    671       write(lunout,*)' nsplit_phys = ', nsplit_phys
    672651      write(lunout,*)' iconser = ', iconser
    673652      write(lunout,*)' iecri = ', iecri
    674653      write(lunout,*)' periodav = ', periodav
    675654      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    676       write(lunout,*)' idissip = ', idissip
     655      write(lunout,*)' dissip_period = ', dissip_period
    677656      write(lunout,*)' lstardis = ', lstardis
    678657      write(lunout,*)' nitergdiv = ', nitergdiv
     
    816795       offline = .FALSE.
    817796       CALL getin('offline',offline)
    818        IF (offline .AND. adjust) THEN
    819           WRITE(lunout,*)
    820      &         'WARNING : option offline does not work with adjust=y :'
    821           WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
    822      &         'and fluxstokev.nc will not be created'
    823           WRITE(lunout,*)
    824      &         'only the file phystoke.nc will still be created '
    825        END IF
    826797
    827798!Config  Key  = config_inca
     
    836807
    837808!Config  Key  = ok_dynzon
    838 !Config  Desc = calcul et sortie des transports
     809!Config  Desc = sortie des transports zonaux dans la dynamique
    839810!Config  Def  = n
    840 !Config  Help = Permet de mettre en route le calcul des transports
     811!Config  Help =
    841812!Config         
    842       ok_dynzon = .FALSE.
    843       CALL getin('ok_dynzon',ok_dynzon)
     813       ok_dynzon = .FALSE.
     814       CALL getin('ok_dynzon',ok_dynzon)
    844815
    845816!Config  Key  = ok_dyn_ins
     
    863834!Config  Def  = false
    864835!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
    865 !Config         le filtrage aux poles.
     836!Config         le filtrage aux poles.
     837! Le filtre fft n'est pas implemente dans dyn3d
    866838      use_filtre_fft=.FALSE.
    867839      CALL getin('use_filtre_fft',use_filtre_fft)
    868840
    869       IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
    870         write(lunout,*)'WARNING !!! '
    871         write(lunout,*)"Le zoom en longitude est incompatible",
    872      &                 " avec l'utilisation du filtre FFT ",
    873      &                 "---> filtre FFT désactivé "
    874        use_filtre_fft=.FALSE.
     841      IF (use_filtre_fft) THEN
     842        write(lunout,*)'STOP !!!'
     843        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
     844        STOP
    875845      ENDIF
    876846     
    877  
    878      
    879 !Config  Key  = use_mpi_alloc
    880 !Config  Desc = Utilise un buffer MPI en m�moire globale
    881 !Config  Def  = false
    882 !Config  Help = permet d'activer l'utilisation d'un buffer MPI
    883 !Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
    884 !Config         Cela peut am�liorer la bande passante des transferts MPI
    885 !Config         d'un facteur 2 
    886       use_mpi_alloc=.FALSE.
    887       CALL getin('use_mpi_alloc',use_mpi_alloc)
    888 
    889 !Config  Key  = omp_chunk
    890 !Config  Desc = taille des blocs openmp
    891 !Config  Def  = 1
    892 !Config  Help = defini la taille des packets d'it�ration openmp
    893 !Config         distribu�e � chaque t�che lors de l'entr�e dans une
    894 !Config         boucle parall�lis�e
    895  
    896       omp_chunk=1
    897       CALL getin('omp_chunk',omp_chunk)
    898 
    899847!Config key = ok_strato
    900848!Config  Desc = activation de la version strato
     
    902850!Config  Help = active la version stratosphérique de LMDZ de F. Lott
    903851
    904       ok_strato=.FALSE.
     852      ok_strato=.TRUE.
    905853      CALL getin('ok_strato',ok_strato)
    906854
     
    928876      ok_etat0 = .TRUE.
    929877      CALL getin('ok_etat0',ok_etat0)
     878
     879!Config  Key  = grilles_gcm_netcdf
     880!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
     881!Config  Def  = n
     882      grilles_gcm_netcdf = .FALSE.
     883      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
    930884
    931885      write(lunout,*)' #########################################'
     
    943897      write(lunout,*)' periodav = ', periodav
    944898      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    945       write(lunout,*)' idissip = ', idissip
     899      write(lunout,*)' dissip_period = ', dissip_period
    946900      write(lunout,*)' lstardis = ', lstardis
    947901      write(lunout,*)' nitergdiv = ', nitergdiv
     
    968922      write(lunout,*)' offline = ', offline
    969923      write(lunout,*)' config_inca = ', config_inca
    970       write(lunout,*)' ok_dynzon = ', ok_dynzon 
     924      write(lunout,*)' ok_dynzon = ', ok_dynzon
    971925      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    972926      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
    973       write(lunout,*)' use_filtre_fft = ', use_filtre_fft
    974       write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
    975       write(lunout,*)' omp_chunk = ', omp_chunk
    976927      write(lunout,*)' ok_strato = ', ok_strato
    977928      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
    978929      write(lunout,*)' ok_limit = ', ok_limit
    979930      write(lunout,*)' ok_etat0 = ', ok_etat0
     931      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    980932c
    981933      RETURN
Note: See TracChangeset for help on using the changeset viewer.