Ignore:
Timestamp:
Apr 9, 2009, 12:11:35 PM (15 years ago)
Author:
Laurent Fairhead
Message:

Réintegration dans le tronc des modifications issues de la branche LMDZ-dev
comprises entre la révision 1074 et 1145
Validation: une simulation de 1 jour en séquentiel sur PC donne les mêmes
résultats entre la trunk et la dev
LF

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3d/gcm.F

    r962 r1146  
    88#ifdef CPP_IOIPSL
    99      USE IOIPSL
    10 #endif
     10#else
     11! if not using IOIPSL, we still need to use (a local version of) getin
     12      USE ioipsl_getincom
     13#endif
     14
     15      USE filtreg_mod
     16      USE infotrac
    1117
    1218!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    1420! A nettoyer. On ne veut qu'une ou deux routines d'interface
    1521! dynamique -> physique pour l'initialisation
    16 #ifdef CPP_PHYS
     22! Ehouarn: for now these only apply to Earth:
     23#ifdef CPP_EARTH
    1724      USE dimphy
    1825      USE comgeomphy
     
    6875#include "iniprint.h"
    6976#include "tracstoke.h"
    70 #include "advtrac.h"
    7177
    7278      INTEGER         longcles
     
    8389      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    8490      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    85       REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
     91      REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
    8692      REAL ps(ip1jmp1)                       ! pression  au sol
    8793      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
     
    137143c    variables pour l'initialisation de la physique :
    138144c    ------------------------------------------------
    139       INTEGER ngridmx,nq
     145      INTEGER ngridmx
    140146      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    141147      REAL zcufi(ngridmx),zcvfi(ngridmx)
     
    155161      dynhistave_file = 'dyn_hist_ave.nc'
    156162
    157 c initialisation Anne
    158       hadv_flg(:) = 0.
    159       vadv_flg(:) = 0.
    160       conv_flg(:) = 0.
    161       pbl_flg(:)  = 0.
    162       tracnam(:)  = '        '
    163       nprath = 1
    164       nbtrac = 0
    165       mmt_adj(:,:,:,:) = 1
    166 
    167 
    168 c--------------------------------------------------------------------------
    169 c   Iflag_phys controle l'appel a la physique :
    170 c   -------------------------------------------
    171 c      0 : pas de physique
    172 c      1 : Normale (appel a phylmd, phymars ...)
    173 c      2 : rappel Newtonien pour la temperature + friction au sol
    174       iflag_phys=1
    175 
    176 c--------------------------------------------------------------------------
    177 c   Lecture de l'etat initial :
    178 c   ---------------------------
    179 c     T : on lit start.nc
    180 c     F : le modele s'autoinitialise avec un cas academique (iniacademic)
    181       read_start=.true.
    182 #ifdef CPP_IOIPSL
    183 #else
    184       read_start=.false.
    185 #endif
    186 #ifdef CPP_PHYS
    187 #else
    188       read_start=.false.
    189 #endif
     163
    190164
    191165c-----------------------------------------------------------------------
     
    204178c  ---------------------------------------
    205179c
    206 #ifdef CPP_IOIPSL
     180! Ehouarn: dump possibility of using defrun
     181!#ifdef CPP_IOIPSL
    207182      CALL conf_gcm( 99, .TRUE. , clesphy0 )
    208 #else
    209       CALL defrun( 99, .TRUE. , clesphy0 )
    210 #endif
     183!#else
     184!      CALL defrun( 99, .TRUE. , clesphy0 )
     185!#endif
    211186
    212187!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    214189! A nettoyer. On ne veut qu'une ou deux routines d'interface
    215190! dynamique -> physique pour l'initialisation
    216 #ifdef CPP_PHYS
    217       CALL Init_Phys_lmdz(iim,jjp1,llm,nqmx-2,1,(jjm-1)*iim+2)
     191! Ehouarn : temporarily (?) keep this only for Earth
     192      if (planet_type.eq."earth") then
     193#ifdef CPP_EARTH
     194      CALL Init_Phys_lmdz(iim,jjp1,llm,1,(jjm-1)*iim+2)
    218195      call InitComgeomphy
    219196#endif
     197      endif
    220198!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    221199
    222200      IF (config_inca /= 'none') THEN
    223201#ifdef INCA
    224       call init_const_lmdz(nbtrac,anneeref,dayref,iphysiq,day_step,nday)
     202      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
    225203      call init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
    226204#endif
     
    237215c   Initialisation des traceurs
    238216c   ---------------------------
    239 c  Choix du schema pour l'advection
    240 c  dans fichier trac.def ou via INCA
    241 
    242        call iniadvtrac(nq)
    243 c
     217c  Choix du nombre de traceurs et du schema pour l'advection
     218c  dans fichier traceur.def, par default ou via INCA
     219      call infotrac_init
     220
     221c Allocation de la tableau q : champs advectes   
     222      allocate(q(ip1jmp1,llm,nqtot))
     223
    244224c-----------------------------------------------------------------------
    245225c   Lecture de l'etat initial :
     
    248228c  lecture du fichier start.nc
    249229      if (read_start) then
    250 #ifdef CPP_IOIPSL
    251          CALL dynetat0("start.nc",nqmx,vcov,ucov,
     230      ! we still need to run iniacademic to initialize some
     231      ! constants & fields, if we run the 'newtonian' case:
     232        if (iflag_phys.eq.2) then
     233          CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
     234        endif
     235!#ifdef CPP_IOIPSL
     236        if (planet_type.eq."earth") then
     237#ifdef CPP_EARTH
     238! Load an Earth-format start file
     239         CALL dynetat0("start.nc",vcov,ucov,
    252240     .              teta,q,masse,ps,phis, time_0)
     241#endif
     242        endif ! of if (planet_type.eq."earth")
    253243c       write(73,*) 'ucov',ucov
    254244c       write(74,*) 'vcov',vcov
     
    257247c       write(77,*) 'q',q
    258248
    259 #endif
    260       endif
     249      endif ! of if (read_start)
    261250
    262251      IF (config_inca /= 'none') THEN
     
    270259c le cas echeant, creation d un etat initial
    271260      IF (prt_level > 9) WRITE(lunout,*)
    272      .                 'AVANT iniacademic AVANT AVANT AVANT AVANT'
     261     .              'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
    273262      if (.not.read_start) then
    274          CALL iniacademic(nqmx,vcov,ucov,teta,q,masse,ps,phis,time_0)
     263         CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    275264      endif
    276265
     
    304293      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
    305294        write(lunout,*)
    306      .  ' Attention les dates initiales lues dans le fichier'
     295     .  'GCM: Attention les dates initiales lues dans le fichier'
    307296        write(lunout,*)
    308297     .  ' restart ne correspondent pas a celles lues dans '
     
    310299        if (raz_date .ne. 1) then
    311300          write(lunout,*)
    312      .    ' On garde les dates du fichier restart'
     301     .    'GCM: On garde les dates du fichier restart'
    313302        else
    314303          annee_ref = anneeref
     
    319308          time_0 = 0.
    320309          write(lunout,*)
    321      .   ' On reinitialise a la date lue dans gcm.def'
     310     .   'GCM: On reinitialise a la date lue dans gcm.def'
    322311        endif
    323312      ELSE
     
    356345c   Initialisation de la physique :
    357346c   -------------------------------
    358 #ifdef CPP_PHYS
    359       IF (call_iniphys.and.iflag_phys.eq.1) THEN
     347
     348      IF (call_iniphys.and.(iflag_phys.eq.1)) THEN
    360349         latfi(1)=rlatu(1)
    361350         lonfi(1)=0.
     
    376365         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    377366         WRITE(lunout,*)
    378      .           'WARNING!!! vitesse verticale nulle dans la physique'
     367     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
     368! Earth:
     369         if (planet_type.eq."earth") then
     370#ifdef CPP_EARTH
    379371         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys ,
    380372     ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
     373#endif
     374         endif ! of if (planet_type.eq."earth")
    381375         call_iniphys=.false.
    382       ENDIF
    383 #endif
     376      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
     377!#endif
    384378
    385379c  numero de stockage pour les fichiers de redemarrage:
     
    392386      day_end = day_ini + nday
    393387      WRITE(lunout,300)day_ini,day_end
     388 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     389
     390      if (planet_type.eq."earth") then
     391#ifdef CPP_EARTH
     392      CALL dynredem0("restart.nc", day_end, phis)
     393#endif
     394      endif
     395
     396      ecripar = .TRUE.
    394397
    395398#ifdef CPP_IOIPSL
    396       CALL dynredem0("restart.nc", day_end, phis, nqmx)
    397 
    398       ecripar = .TRUE.
    399 
    400399      if ( 1.eq.1) then
    401400      time_step = zdtvr
     
    403402      t_wrt = iecri * daysec
    404403      CALL inithist(dynhist_file,day_ref,annee_ref,time_step,
    405      .              t_ops, t_wrt, nqmx, histid, histvid)
    406 
    407       t_ops = iperiod * time_step
    408       t_wrt = periodav * daysec
    409       CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
    410      .              t_ops, t_wrt, nqmx, histaveid)
    411 
     404     .              t_ops, t_wrt, histid, histvid)
     405
     406      IF (ok_dynzon) THEN
     407         t_ops = iperiod * time_step
     408         t_wrt = periodav * daysec
     409         CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
     410     .        t_ops, t_wrt, histaveid)
     411      END IF
    412412      dtav = iperiod*dtvr/daysec
    413413      endif
     
    415415
    416416#endif
     417! #endif of #ifdef CPP_IOIPSL
    417418
    418419c  Choix des frequences de stokage pour le offline
     
    435436
    436437
    437       CALL leapfrog(ucov,vcov,teta,ps,masse,phis,nq,q,clesphy0,
     438      CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    438439     .              time_0)
    439440
    440 
    441 
    442  300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x,
    443      . 'c''est a dire du jour',i7,3x,'au jour',i7//)
    444441      END
    445442
Note: See TracChangeset for help on using the changeset viewer.