Ignore:
Timestamp:
Aug 19, 2011, 9:17:40 AM (13 years ago)
Author:
emillour
Message:

Petit oubli lors de la mise a jour de la dynamique de la ver 270.
Ehouarn

File:
1 edited

Legend:

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

    r270 r271  
    11!
    2 ! $Id: conf_gcm.F 1418 2010-07-19 15:11:24Z jghattas $
     2! $Id: conf_gcm.F 1438 2010-10-08 10:19:34Z jghattas $
    33!
    44c
     
    66      SUBROUTINE conf_gcm( tapedef, etatinit )
    77c
    8       USE control_mod
    98#ifdef CPP_IOIPSL
    109      use IOIPSL
     
    1312      use ioipsl_getincom
    1413#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
    1519      IMPLICIT NONE
    1620c-----------------------------------------------------------------------
     
    3337#include "serre.h"
    3438#include "comdissnew.h"
     39!#include "clesphys.h"
     40#include "iniprint.h"
    3541#include "temps.h"
    3642#include "comconst.h"
    3743
    3844! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    39 ! #include "clesphys.h"
    40 #include "iniprint.h"
    4145c
    4246c
     
    4953      LOGICAL  fxyhypbb, ysinuss
    5054      INTEGER i
    51       LOGICAL use_filtre_fft
     55     
    5256c
    5357c  -------------------------------------------------------------------
     
    7882c   initialisations:
    7983c   ----------------
    80 
     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     
    8191!Config  Key  = lunout
    8292!Config  Desc = unite de fichier pour les impressions
     
    180190
    181191!Config  Key  = nsplit_phys
    182 !Config  Desc = nombre de subdivisions par pas physique
    183 !Config  Def  = 1
    184 !Config  Help = nombre de subdivisions par pas physique
     192!Config  Desc = nombre d'iteration de la physique
     193!Config  Def  = 240
     194!Config  Help = nombre d'itration de la physique
     195!
    185196       nsplit_phys = 1
    186197       CALL getin('nsplit_phys',nsplit_phys)
     
    330341       CALL getin('tau_top_bound',tau_top_bound)
    331342
     343!
    332344!Config  Key  = coefdis
    333345!Config  Desc = coefficient pour gamdissip
     
    396408       ip_ebil_dyn = 0
    397409       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
     410!
     411
    398412
    399413ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
     
    600614       offline = .FALSE.
    601615       CALL getin('offline',offline)
    602 
     616       IF (offline .AND. adjust) THEN
     617          WRITE(lunout,*)
     618     &         'WARNING : option offline does not work with adjust=y :'
     619          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
     620     &         'and fluxstokev.nc will not be created'
     621          WRITE(lunout,*)
     622     &         'only the file phystoke.nc will still be created '
     623       END IF
     624       
    603625!Config  Key  = config_inca
    604626!Config  Desc = Choix de configuration de INCA
     
    634656      ok_dyn_ave = .FALSE.
    635657      CALL getin('ok_dyn_ave',ok_dyn_ave)
    636 
    637658
    638659      write(lunout,*)' #########################################'
     
    649670      write(lunout,*)' day_step = ', day_step
    650671      write(lunout,*)' iperiod = ', iperiod
     672      write(lunout,*)' nsplit_phys = ', nsplit_phys
    651673      write(lunout,*)' iconser = ', iconser
    652674      write(lunout,*)' iecri = ', iecri
     
    795817       offline = .FALSE.
    796818       CALL getin('offline',offline)
     819       IF (offline .AND. adjust) THEN
     820          WRITE(lunout,*)
     821     &         'WARNING : option offline does not work with adjust=y :'
     822          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
     823     &         'and fluxstokev.nc will not be created'
     824          WRITE(lunout,*)
     825     &         'only the file phystoke.nc will still be created '
     826       END IF
    797827
    798828!Config  Key  = config_inca
     
    807837
    808838!Config  Key  = ok_dynzon
    809 !Config  Desc = sortie des transports zonaux dans la dynamique
     839!Config  Desc = calcul et sortie des transports
    810840!Config  Def  = n
    811 !Config  Help =
     841!Config  Help = Permet de mettre en route le calcul des transports
    812842!Config         
    813        ok_dynzon = .FALSE.
    814        CALL getin('ok_dynzon',ok_dynzon)
     843      ok_dynzon = .FALSE.
     844      CALL getin('ok_dynzon',ok_dynzon)
    815845
    816846!Config  Key  = ok_dyn_ins
     
    834864!Config  Def  = false
    835865!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
    836 !Config         le filtrage aux poles.
    837 ! Le filtre fft n'est pas implemente dans dyn3d
     866!Config         le filtrage aux poles.
    838867      use_filtre_fft=.FALSE.
    839868      CALL getin('use_filtre_fft',use_filtre_fft)
    840869
    841       IF (use_filtre_fft) THEN
    842         write(lunout,*)'STOP !!!'
    843         write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
    844         STOP
     870      IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
     871        write(lunout,*)'WARNING !!! '
     872        write(lunout,*)"Le zoom en longitude est incompatible",
     873     &                 " avec l'utilisation du filtre FFT ",
     874     &                 "---> filtre FFT désactivé "
     875       use_filtre_fft=.FALSE.
    845876      ENDIF
    846877     
     878 
     879     
     880!Config  Key  = use_mpi_alloc
     881!Config  Desc = Utilise un buffer MPI en m�moire globale
     882!Config  Def  = false
     883!Config  Help = permet d'activer l'utilisation d'un buffer MPI
     884!Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
     885!Config         Cela peut am�liorer la bande passante des transferts MPI
     886!Config         d'un facteur 2 
     887      use_mpi_alloc=.FALSE.
     888      CALL getin('use_mpi_alloc',use_mpi_alloc)
     889
     890!Config  Key  = omp_chunk
     891!Config  Desc = taille des blocs openmp
     892!Config  Def  = 1
     893!Config  Help = defini la taille des packets d'it�ration openmp
     894!Config         distribu�e � chaque t�che lors de l'entr�e dans une
     895!Config         boucle parall�lis�e
     896 
     897      omp_chunk=1
     898      CALL getin('omp_chunk',omp_chunk)
     899
    847900!Config key = ok_strato
    848901!Config  Desc = activation de la version strato
     
    922975      write(lunout,*)' offline = ', offline
    923976      write(lunout,*)' config_inca = ', config_inca
    924       write(lunout,*)' ok_dynzon = ', ok_dynzon
     977      write(lunout,*)' ok_dynzon = ', ok_dynzon 
    925978      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
    926979      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
     980      write(lunout,*)' use_filtre_fft = ', use_filtre_fft
     981      write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
     982      write(lunout,*)' omp_chunk = ', omp_chunk
    927983      write(lunout,*)' ok_strato = ', ok_strato
    928984      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
Note: See TracChangeset for help on using the changeset viewer.