Ignore:
Timestamp:
Dec 10, 2009, 10:02:56 AM (15 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3dpar/infotrac.F90

    r1146 r1279  
     1! $Id$
     2!
    13MODULE infotrac
    24
    35! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
    46  INTEGER, SAVE :: nqtot
    5 !!$OMP THREADPRIVATE(nqtot)   
    67
    78! nbtr : number of tracers not including higher order of moment or water vapor or liquid
    89!        number of tracers used in the physics
    910  INTEGER, SAVE :: nbtr
    10 !!$OMP THREADPRIVATE(nbtr)   
    1111
    1212! Name variables
    1313  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    1414  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
    15 !!$OMP THREADPRIVATE(tname,ttext)   
    1615
    1716! iadv  : index of trasport schema for each tracer
    1817  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
    19 !!$OMP THREADPRIVATE(iadv)   
    2018
    2119! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
    2220!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
    2321  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
    24 !!$OMP THREADPRIVATE(niadv)   
    25 
    26 ! Variables for INCA
     22
     23! conv_flg(it)=0 : convection desactivated for tracer number it
    2724  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
     25! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
    2826  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
    29 !!$OMP THREADPRIVATE(conv_flg, pbl_flg)   
    30 
     27
     28  CHARACTER(len=4),SAVE :: type_trac
     29 
    3130CONTAINS
    3231
     
    5756    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
    5857
    59     CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     58    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    6059    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tracnam ! name from INCA
    6160    CHARACTER(len=3), DIMENSION(30) :: descrq
     
    8483    descrq(20)='SLP'
    8584    descrq(30)='PRA'
     85   
     86
     87    IF (config_inca=='none') THEN
     88       type_trac='lmdz'
     89    ELSE
     90       type_trac='inca'
     91    END IF
    8692
    8793!-----------------------------------------------------------------------
     
    9197!
    9298!-----------------------------------------------------------------------
    93     IF (config_inca == 'none') THEN
     99    IF (type_trac == 'lmdz') THEN
    94100       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    95101       IF(ierr.EQ.0) THEN
     
    113119    END IF
    114120!
    115 ! Allocate variables depending on nqtrue
     121! Allocate variables depending on nqtrue and nbtr
    116122!
    117123    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
    118 
    119     IF (config_inca /= 'none') THEN
    120        ! Varaibles only needed in case of INCA
    121        ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
    122     END IF
    123        
     124    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
     125    conv_flg(:) = 1 ! convection activated for all tracers
     126    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
     127
    124128!-----------------------------------------------------------------------
    125129! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
     
    148152!    Get choice of advection schema from file tracer.def or from INCA
    149153!---------------------------------------------------------------------
    150     IF (config_inca == 'none') THEN
     154    IF (type_trac == 'lmdz') THEN
    151155       IF(ierr.EQ.0) THEN
    152156          ! Continue to read tracer.def
     
    176180       END DO
    177181
    178     ELSE  ! config_inca='aero' ou 'chem'
     182    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
    179183! le module de chimie fournit les noms des traceurs
    180184! et les schemas d'advection associes.
     
    195199       END DO
    196200
    197     END IF ! config_inca
     201    END IF ! type_trac
    198202
    199203!-----------------------------------------------------------------------
     
    299303
    300304
    301     WRITE(lunout,*) 'Information stored in dimtrac :'
     305    WRITE(lunout,*) 'Information stored in infotrac :'
    302306    WRITE(lunout,*) 'iadv  niadv tname  ttext :'
    303307    DO iq=1,nqtot
     
    305309    END DO
    306310
     311!
     312! Test for advection schema.
     313! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
     314!
     315    DO iq=1,nqtot
     316       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
     317          WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     318          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
     319       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
     320          WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     321          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
     322       END IF
     323    END DO
     324
    307325!-----------------------------------------------------------------------
    308326! Finalize :
    309327!
    310328    DEALLOCATE(tnom_0, hadv, vadv)
    311     IF (config_inca /= 'none') DEALLOCATE(tracnam)
    312 
    313 999 FORMAT (i2,1x,i2,1x,a8)
     329    DEALLOCATE(tracnam)
     330
     331999 FORMAT (i2,1x,i2,1x,a15)
    314332
    315333  END SUBROUTINE infotrac_init
Note: See TracChangeset for help on using the changeset viewer.