Ignore:
Timestamp:
Mar 30, 2009, 4:46:54 PM (16 years ago)
Author:
Ehouarn Millour
Message:

Premiere vaque de modifications pour l'unification des dynamiques (planetes-Terre) et un peu de netoyage ...

  • modified 'makegcm' and 'makegcm_fcm' to remove 'CPP_PHYS' key and add 'CPP_EARTH' preprocessing key instead
  • updated 'diagedyn.F' (in dyn3d and dyn3dpar) to use 'CPP_EARTH' key
  • added 'ioipsl_getincom.F90' and 'ioipsl_stringop.F90' to 'dyn3d' and 'dyn3dpar' for future possibility of running without IOIPSL library
  • modified conf_gcm.F ( in d'yn3d' and 'dyn3dpar') to read in flag 'planet_type' (default=='earth') (flag added in 'control.h')
  • modified 'gcm.F' (in 'dyn3d' and 'dyn3dpar') so that flags so that 'read_start' and 'iflag_phys' (known from conf_gcm.F) are used
  • added flag 'output_grads_dyn' (read by conf_gcm.F, stored in 'control.h') to write grads outputs from 'leapfrog.F' and 'leapfrog_p.F'
  • removed 'comdiss.h' from 'dyn3d' and 'dyn3dpar' (it is not used)
  • removed variable 'lstardis' from 'comdissip.h' (it is also in

'comdissnew.h'), in dyn3d as well as in dyn3dpar

  • adapted 'dyn3d/iniacademic.F' to not use 'inicons0.F' but 'iniconst.F'
  • updated 'dyn3d/etat0_netcdf.F' to not use 'inicons0' but 'iniconst' (added prerequisite pa=50000 instruction) and added #ifdef CPP_EARTH keys
  • removed 'inicons0.F' and 'disvert0.F' (not used any more)
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/conf_gcm.F

    r1111 r1140  
    66      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
    77c
     8#ifdef CPP_IOIPSL
    89      use IOIPSL
     10#else
     11! if not using IOIPSL, we still need to use (a local version of) getin
     12      use ioipsl_getincom
     13#endif
    914      use misc_mod
    1015      use mod_filtre_fft, ONLY : use_filtre_fft
     
    99104
    100105!Config  Key  = prt_level
    101 !Config  Desc = niveau d'impressions de dbogage
    102 !Config  Def  = 0
    103 !Config  Help = Niveau d'impression pour le dbogage
     106!Config  Desc = niveau d'impressions de débogage
     107!Config  Def  = 0
     108!Config  Help = Niveau d'impression pour le débogage
    104109!Config         (0 = minimum d'impression)
    105110      prt_level = 0
     
    109114c  Parametres de controle du run:
    110115c-----------------------------------------------------------------------
     116!Config  Key  = planet_type
     117!Config  Desc = planet type ("earth", "mars", "venus", ...)
     118!Config  Def  = earth
     119!Config  Help = this flag sets the type of atymosphere that is considered
     120      planet_type="earth"
     121      CALL getin('planet_type',planet_type)
    111122
    112123!Config  Key  = dayref
     
    189200       CALL getin('periodav',periodav)
    190201
     202!Config  Key  = output_grads_dyn
     203!Config  Desc = output dynamics diagnostics in 'dyn.dat' file
     204!Config  Def  = n
     205!Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
     206       output_grads_dyn=.false.
     207       CALL getin('output_grads_dyn',output_grads_dyn)
     208
    191209!Config  Key  = idissip
    192210!Config  Desc = periode de la dissipation
     
    284302c    ...............................................................
    285303
     304!Config  Key  =  read_start
     305!Config  Desc = Initialize model using a 'start.nc' file
     306!Config  Def  = y
     307!Config  Help = y: intialize dynamical fields using a 'start.nc' file
     308!               n: fields are initialized by 'iniacademic' routine
     309       read_start= .true.
     310       CALL getin('read_start',read_start)
     311
    286312!Config  Key  = iflag_phys
    287313!Config  Desc = Avec ls physique
     
    341367c
    342368      IF( ABS(clat - clatt).GE. 0.001 )  THEN
    343         PRINT *,' La valeur de clat passee par run.def est differente de
    344      * celle lue sur le fichier  start '
     369        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
     370     &    ' est differente de celle lue sur le fichier  start '
    345371        STOP
    346372      ENDIF
     
    356382
    357383      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    358         PRINT *,' La valeur de grossismx passee par run.def est differente 
    359      * de celle lue sur le fichier  start '
     384        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
     385     &  'run.def est differente de celle lue sur le fichier  start '
    360386        STOP
    361387      ENDIF
     
    370396
    371397      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
    372         PRINT *,' La valeur de grossismy passee par run.def est differen
    373      * te de celle lue sur le fichier  start '
     398        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
     399     & 'run.def est differente de celle lue sur le fichier  start '
    374400        STOP
    375401      ENDIF
    376402     
    377403      IF( grossismx.LT.1. )  THEN
    378         PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
     404        write(lunout,*)
     405     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    379406         STOP
    380407      ELSE
     
    384411
    385412      IF( grossismy.LT.1. )  THEN
    386         PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
     413        write(lunout,*)
     414     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    387415         STOP
    388416      ELSE
     
    390418      ENDIF
    391419
    392       PRINT *,' alphax alphay defrun ',alphax,alphay
     420      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
    393421c
    394422c    alphax et alphay sont les anciennes formulat. des grossissements
     
    405433
    406434      IF( .NOT.fxyhypb )  THEN
    407            IF( fxyhypbb )     THEN
    408               PRINT *,' ********  PBS DANS  DEFRUN  ******** '
    409               PRINT *,' *** fxyhypb lu sur le fichier start est F ',
    410      *       'alors  qu il est  T  sur  run.def  ***'
     435         IF( fxyhypbb )     THEN
     436            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     437            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
     438     *       'F alors  qu il est  T  sur  run.def  ***'
    411439              STOP
    412            ENDIF
     440         ENDIF
    413441      ELSE
    414            IF( .NOT.fxyhypbb )   THEN
    415               PRINT *,' ********  PBS DANS  DEFRUN  ******** '
    416               PRINT *,' ***  fxyhypb lu sur le fichier start est T ',
    417      *        'alors  qu il est  F  sur  run.def  ****  '
     442         IF( .NOT.fxyhypbb )   THEN
     443            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     444            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
     445     *        'T alors  qu il est  F  sur  run.def  ****  '
    418446              STOP
    419            ENDIF
     447         ENDIF
    420448      ENDIF
    421449c
     
    430458      IF( fxyhypb )  THEN
    431459       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    432         PRINT *,' La valeur de dzoomx passee par run.def est differente
    433      *  de celle lue sur le fichier  start '
     460        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
     461     *  'run.def est differente de celle lue sur le fichier  start '
    434462        STOP
    435463       ENDIF
     
    446474      IF( fxyhypb )  THEN
    447475       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    448         PRINT *,' La valeur de dzoomy passee par run.def est differente
    449      * de celle lue sur le fichier  start '
     476        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
     477     * 'run.def est differente de celle lue sur le fichier  start '
    450478        STOP
    451479       ENDIF
     
    461489      IF( fxyhypb )  THEN
    462490       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    463         PRINT *,' La valeur de taux passee par run.def est differente
    464      * de celle lue sur le fichier  start '
     491        write(lunout,*)'conf_gcm: La valeur de taux passee par ',
     492     * 'run.def est differente de celle lue sur le fichier  start '
    465493        STOP
    466494       ENDIF
     
    476504      IF( fxyhypb )  THEN
    477505       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    478         PRINT *,' La valeur de tauy passee par run.def est differente
    479      * de celle lue sur le fichier  start '
     506        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
     507     * 'run.def est differente de celle lue sur le fichier  start '
    480508        STOP
    481509       ENDIF
     
    495523
    496524        IF( .NOT.ysinus )  THEN
    497            IF( ysinuss )     THEN
    498               PRINT *,' ********  PBS DANS  DEFRUN  ******** '
    499               PRINT *,' *** ysinus lu sur le fichier start est F ',
    500      *       'alors  qu il est  T  sur  run.def  ***'
     525          IF( ysinuss )     THEN
     526            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     527            write(lunout,*)' *** ysinus lu sur le fichier start est F',
     528     *       ' alors  qu il est  T  sur  run.def  ***'
     529            STOP
     530          ENDIF
     531        ELSE
     532          IF( .NOT.ysinuss )   THEN
     533            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
     534            write(lunout,*)' *** ysinus lu sur le fichier start est T',
     535     *        ' alors  qu il est  F  sur  run.def  ****  '
    501536              STOP
    502            ENDIF
    503         ELSE
    504            IF( .NOT.ysinuss )   THEN
    505               PRINT *,' ********  PBS DANS  DEFRUN  ******** '
    506               PRINT *,' ***  ysinus lu sur le fichier start est T ',
    507      *        'alors  qu il est  F  sur  run.def  ****  '
    508               STOP
    509            ENDIF
     537          ENDIF
    510538        ENDIF
    511       ENDIF
     539      ENDIF ! of IF( .NOT.fxyhypb  )
    512540c
    513541!Config  Key  = offline
     
    532560      write(lunout,*)' #########################################'
    533561      write(lunout,*)' Configuration des parametres du gcm: '
     562      write(lunout,*)' planet_type = ', planet_type
    534563      write(lunout,*)' dayref = ', dayref
    535564      write(lunout,*)' anneeref = ', anneeref
     
    540569      write(lunout,*)' iecri = ', iecri
    541570      write(lunout,*)' periodav = ', periodav
     571      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    542572      write(lunout,*)' idissip = ', idissip
    543573      write(lunout,*)' lstardis = ', lstardis
     
    550580      write(lunout,*)' coefdis = ', coefdis
    551581      write(lunout,*)' purmats = ', purmats
     582      write(lunout,*)' read_start = ', read_start
    552583      write(lunout,*)' iflag_phys = ', iflag_phys
    553584      write(lunout,*)' clonn = ', clonn
     
    600631
    601632      IF( grossismx.LT.1. )  THEN
    602         PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
     633        write(lunout,*)
     634     &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    603635         STOP
    604636      ELSE
     
    608640
    609641      IF( grossismy.LT.1. )  THEN
    610         PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
     642        write(lunout,*)
     643     &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    611644         STOP
    612645      ELSE
     
    614647      ENDIF
    615648
    616       PRINT *,' alphax alphay defrun ',alphax,alphay
     649      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
    617650c
    618651c    alphax et alphay sont les anciennes formulat. des grossissements
     
    697730        write(lunout,*)"Le zoom en longitude est incompatible",
    698731     &                 " avec l'utilisation du filtre FFT ",
    699      &                 "---> filtre FFT désactivé "
     732     &                 "---> filtre FFT désactivé "
    700733       use_filtre_fft=.FALSE.
    701734      ENDIF
     
    704737     
    705738!Config  Key  = use_mpi_alloc
    706 !Config  Desc = Utilise un buffer MPI en mmoire globale
     739!Config  Desc = Utilise un buffer MPI en m�moire globale
    707740!Config  Def  = false
    708741!Config  Help = permet d'activer l'utilisation d'un buffer MPI
    709 !Config         en mmoire globale a l'aide de la fonction MPI_ALLOC.
    710 !Config         Cela peut amliorer la bande passante des transferts MPI
     742!Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
     743!Config         Cela peut am�liorer la bande passante des transferts MPI
    711744!Config         d'un facteur 2 
    712745      use_mpi_alloc=.FALSE.
     
    716749!Config  Desc = taille des blocs openmp
    717750!Config  Def  = 1
    718 !Config  Help = defini la taille des packets d'itration openmp
    719 !Config         distribu�e � chaque t�che lors de l'entr�e dans une
    720 !Config         boucle parall�lis�e
     751!Config  Help = defini la taille des packets d'it�ration openmp
     752!Config         distribu�e � chaque t�che lors de l'entr�e dans une
     753!Config         boucle parall�lis�e
    721754 
    722755      omp_chunk=1
     
    726759!Config  Desc = activation de la version strato
    727760!Config  Def  = .FALSE.
    728 !Config  Help = active la version stratosphrique de LMDZ de F. Lott
     761!Config  Help = active la version stratosph�rique de LMDZ de F. Lott
    729762
    730763      ok_strato=.FALSE.
     
    741774      write(lunout,*)' #########################################'
    742775      write(lunout,*)' Configuration des parametres du gcm: '
     776      write(lunout,*)' planet_type = ', planet_type
    743777      write(lunout,*)' dayref = ', dayref
    744778      write(lunout,*)' anneeref = ', anneeref
     
    749783      write(lunout,*)' iecri = ', iecri
    750784      write(lunout,*)' periodav = ', periodav
     785      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
    751786      write(lunout,*)' idissip = ', idissip
    752787      write(lunout,*)' lstardis = ', lstardis
     
    759794      write(lunout,*)' coefdis = ', coefdis
    760795      write(lunout,*)' purmats = ', purmats
     796      write(lunout,*)' read_start = ', read_start
    761797      write(lunout,*)' iflag_phys = ', iflag_phys
    762798      write(lunout,*)' clon = ', clon
     
    764800      write(lunout,*)' grossismx = ', grossismx
    765801      write(lunout,*)' grossismy = ', grossismy
    766       write(lunout,*)' fxyhypbb = ', fxyhypbb
     802      write(lunout,*)' fxyhypb = ', fxyhypb
    767803      write(lunout,*)' dzoomx = ', dzoomx
    768804      write(lunout,*)' dzoomy = ', dzoomy
Note: See TracChangeset for help on using the changeset viewer.