Ignore:
Timestamp:
Jun 26, 2014, 6:07:05 PM (10 years ago)
Author:
emillour
Message:

Common dynamics:
Some updates to keep up with LMDZ5 Earth model evolution
(up to LMDZ5 rev 2070). See file "DOC/chantiers/commit_importants.log"
for detailed list of changes.
Note that the updates of exner* routines change (as expected) results
at numerical roundoff level.
EM

File:
1 edited

Legend:

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

    r1189 r1302  
    22! $Id: conf_gcm.F 1418 2010-07-19 15:11:24Z jghattas $
    33!
    4 c
    5 c
     4!
     5!
    66      SUBROUTINE conf_gcm( tapedef, etatinit )
    7 c
     7!
    88      USE control_mod
    99#ifdef CPP_IOIPSL
     
    1818
    1919      IMPLICIT NONE
    20 c-----------------------------------------------------------------------
    21 c     Auteurs :   L. Fairhead , P. Le Van  .
    22 c
    23 c     Arguments :
    24 c
    25 c     tapedef   :
    26 c     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
    27 c     -metres  du zoom  avec  celles lues sur le fichier start .
    28 c
     20!-----------------------------------------------------------------------
     21!     Auteurs :   L. Fairhead , P. Le Van  .
     22!
     23!     Arguments :
     24!
     25!     tapedef   :
     26!     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
     27!     -metres  du zoom  avec  celles lues sur le fichier start .
     28!
    2929       LOGICAL etatinit
    3030       INTEGER tapedef
    3131
    32 c   Declarations :
    33 c   --------------
     32!   Declarations :
     33!   --------------
    3434#include "dimensions.h"
    3535#include "paramet.h"
     
    4343! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    4444! #include "clesphys.h"
    45 c
    46 c
    47 c   local:
    48 c   ------
     45!
     46!
     47!   local:
     48!   ------
    4949
    5050      CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
     
    5454      INTEGER i
    5555      LOGICAL use_filtre_fft
    56 c
    57 c  -------------------------------------------------------------------
    58 c
    59 c       .........     Version  du 29/04/97       ..........
    60 c
    61 c   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
    62 c      tetatemp   ajoutes  pour la dissipation   .
    63 c
    64 c   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
    65 c
    66 c  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
    67 c    Sinon , choix de fxynew  , a derivee sinusoidale  ..
    68 c
    69 c   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
    70 c         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
    71 c                de limit.dat ( dic)                        ...........
    72 c           Sinon  etatinit = . FALSE .
    73 c
    74 c   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
    75 c    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
    76 c   celles passees  par run.def ,  au debut du gcm, apres l'appel a
    77 c    lectba . 
    78 c   Ces parmetres definissant entre autres la grille et doivent etre
    79 c   pareils et coherents , sinon il y aura  divergence du gcm .
    80 c
    81 c-----------------------------------------------------------------------
    82 c   initialisations:
    83 c   ----------------
     56!
     57!  -------------------------------------------------------------------
     58!
     59!       .........     Version  du 29/04/97       ..........
     60!
     61!   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
     62!      tetatemp   ajoutes  pour la dissipation   .
     63!
     64!   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
     65!
     66!  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
     67!    Sinon , choix de fxynew  , a derivee sinusoidale  ..
     68!
     69!   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
     70!         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
     71!                de limit.dat ( dic)                        ...........
     72!           Sinon  etatinit = . FALSE .
     73!
     74!   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
     75!    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
     76!   celles passees  par run.def ,  au debut du gcm, apres l'appel a
     77!    lectba . 
     78!   Ces parmetres definissant entre autres la grille et doivent etre
     79!   pareils et coherents , sinon il y aura  divergence du gcm .
     80!
     81!-----------------------------------------------------------------------
     82!   initialisations:
     83!   ----------------
    8484
    8585!Config  Key  = lunout
     
    9191      CALL getin('lunout', lunout)
    9292      IF (lunout /= 5 .and. lunout /= 6) THEN
    93         OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',
     93        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                     &
    9494     &          STATUS='unknown',FORM='formatted')
    9595      ENDIF
     
    103103      CALL getin('prt_level',prt_level)
    104104
    105 c-----------------------------------------------------------------------
    106 c  Parametres de controle du run:
    107 c-----------------------------------------------------------------------
     105!-----------------------------------------------------------------------
     106!  Parametres de controle du run:
     107!-----------------------------------------------------------------------
    108108!Config  Key  = planet_type
    109109!Config  Desc = planet type ("earth", "mars", "venus", ...)
     
    264264       CALL getin('dissip_period',dissip_period)
    265265
    266 ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
    267 ccc
     266!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
     267!cc
    268268
    269269!Config  Key  = lstardis
     
    430430       CALL getin('ok_guide',ok_guide)
    431431
    432 c    ...............................................................
     432!    ...............................................................
    433433
    434434!Config  Key  =  read_start
     
    587587      CALL getin('ok_etat0',ok_etat0)
    588588
    589 !Config  Key  = grilles_gcm_netcdf
    590 !Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
    591 !Config  Def  = n
    592       grilles_gcm_netcdf = .FALSE.
    593       CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
    594 
    595 c----------------------------------------
    596 c Parameters for zonal averages in the case of Titan
     589!----------------------------------------
     590! Parameters for zonal averages in the case of Titan
    597591      moyzon_mu = .false.
    598592      moyzon_ch = .false.
     
    601595       CALL getin('moyzon_ch', moyzon_ch)
    602596      endif
    603 c----------------------------------------
    604 
    605 c----------------------------------------
    606 ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
    607 c     .........   (  modif  le 17/04/96 )   .........
    608 c
    609 C ZOOM PARAMETERS ... the ones read in start.nc prevail anyway ! (SL, 2012)
    610 c
    611 c----------------------------------------
     597!----------------------------------------
     598
     599!----------------------------------------
     600!cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
     601!     .........   (  modif  le 17/04/96 )   .........
     602!
     603! ZOOM PARAMETERS ... the ones read in start.nc prevail anyway ! (SL, 2012)
     604!
     605!----------------------------------------
    612606      IF( etatinit ) then
    613607
     
    645639
    646640      IF( grossismx.LT.1. )  THEN
    647         write(lunout,*)
    648      &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
     641        write(lunout,*)                                                        &
     642     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    649643         STOP
    650644      ELSE
     
    654648
    655649      IF( grossismy.LT.1. )  THEN
    656         write(lunout,*)
    657      &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
     650        write(lunout,*)                                                        &
     651     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    658652         STOP
    659653      ELSE
     
    662656
    663657      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
    664 c
    665 c    alphax et alphay sont les anciennes formulat. des grossissements
    666 c
    667 c
     658!
     659!    alphax et alphay sont les anciennes formulat. des grossissements
     660!
     661!
    668662
    669663!Config  Key  = fxyhypb
     
    737731c
    738732      IF( ABS(clat - clatt).GE. 0.001 )  THEN
    739         write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
     733        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',     &
    740734     &    ' est differente de celle lue sur le fichier  start '
    741735        STOP
     
    752746
    753747      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    754         write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
     748        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',       &
    755749     &  'run.def est differente de celle lue sur le fichier  start '
    756750        STOP
     
    766760
    767761      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
    768         write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
     762        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',        &
    769763     & 'run.def est differente de celle lue sur le fichier  start '
    770764        STOP
     
    772766     
    773767      IF( grossismx.LT.1. )  THEN
    774         write(lunout,*)
     768        write(lunout,*)                                                        &
    775769     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    776770         STOP
     
    781775
    782776      IF( grossismy.LT.1. )  THEN
    783         write(lunout,*)
     777        write(lunout,*)                                                        &
    784778     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    785779         STOP
     
    789783
    790784      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
    791 c
    792 c    alphax et alphay sont les anciennes formulat. des grossissements
    793 c
    794 c
     785!
     786!    alphax et alphay sont les anciennes formulat. des grossissements
     787!
     788!
    795789
    796790!Config  Key  = fxyhypb
     
    805799         IF( fxyhypbb )     THEN
    806800            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    807             write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
    808      *       'F alors  qu il est  T  sur  run.def  ***'
     801            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',     &
     802     &       'F alors  qu il est  T  sur  run.def  ***'
    809803              STOP
    810804         ENDIF
     
    812806         IF( .NOT.fxyhypbb )   THEN
    813807            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    814             write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
    815      *        'T alors  qu il est  F  sur  run.def  ****  '
     808            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',     &
     809     &        'T alors  qu il est  F  sur  run.def  ****  '
    816810              STOP
    817811         ENDIF
    818812      ENDIF
    819 c
     813!
    820814!Config  Key  = dzoomx
    821815!Config  Desc = extension en longitude
     
    828822      IF( fxyhypb )  THEN
    829823       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    830         write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
    831      *  'run.def est differente de celle lue sur le fichier  start '
     824        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',         &
     825     &  'run.def est differente de celle lue sur le fichier  start '
    832826        STOP
    833827       ENDIF
     
    844838      IF( fxyhypb )  THEN
    845839       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    846         write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
    847      * 'run.def est differente de celle lue sur le fichier  start '
     840        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',          &
     841     & 'run.def est differente de celle lue sur le fichier  start '
    848842        STOP
    849843       ENDIF
     
    859853      IF( fxyhypb )  THEN
    860854       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    861         write(lunout,*)'conf_gcm: La valeur de taux passee par ',
    862      * 'run.def est differente de celle lue sur le fichier  start '
     855        write(lunout,*)'conf_gcm: La valeur de taux passee par ',           &
     856     & 'run.def est differente de celle lue sur le fichier  start '
    863857        STOP
    864858       ENDIF
     
    874868      IF( fxyhypb )  THEN
    875869       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    876         write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
    877      * 'run.def est differente de celle lue sur le fichier  start '
     870        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',           &
     871     & 'run.def est differente de celle lue sur le fichier  start '
    878872        STOP
    879873       ENDIF
     
    895889          IF( ysinuss )     THEN
    896890            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    897             write(lunout,*)' *** ysinus lu sur le fichier start est F',
    898      *       ' alors  qu il est  T  sur  run.def  ***'
     891            write(lunout,*)' *** ysinus lu sur le fichier start est F',     &
     892     &       ' alors  qu il est  T  sur  run.def  ***'
    899893            STOP
    900894          ENDIF
     
    902896          IF( .NOT.ysinuss )   THEN
    903897            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
    904             write(lunout,*)' *** ysinus lu sur le fichier start est T',
    905      *        ' alors  qu il est  F  sur  run.def  ****  '
     898            write(lunout,*)' *** ysinus lu sur le fichier start est T',     &
     899     &        ' alors  qu il est  F  sur  run.def  ****  '
    906900              STOP
    907901          ENDIF
     
    910904
    911905      endif ! etatinit
    912 c----------------------------------------
     906!----------------------------------------
    913907
    914908
     
    962956      write(lunout,*)' ok_limit = ', ok_limit
    963957      write(lunout,*)' ok_etat0 = ', ok_etat0
    964       write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    965958      if (planet_type=="titan") then
    966959       write(lunout,*)' moyzon_mu = ', moyzon_mu
Note: See TracChangeset for help on using the changeset viewer.