Ignore:
Timestamp:
Jun 11, 2009, 4:18:47 PM (16 years ago)
Author:
jghattas
Message:
  • Ajout de l'interpolation vertical pour les nouveaux fichiers de forcage des aerosols. Utilisant les anciennes fichiers de SO4 pas d'interpolation possible. Convergence numerique avec la version precedente en utilisant les anciens fichiers des SO4. aerosol_optic.F90 change du nom pour readaerosol_optic.F90 (lecture d'aerosol + optic) Les fichiers de forcage aerosol doit maintenant avoir le suffix .nc.
  • Correction des bugs pour inca et certain diagnostiques optionelles de radlwsw.
  • Ajout de test pour le choix advection schema.
Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/infotrac.F90

    r1117 r1179  
     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)   
    2522
    2623! Variables for INCA
    2724  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
    2825  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
    29 !!$OMP THREADPRIVATE(conv_flg, pbl_flg)   
    3026
    3127CONTAINS
     
    305301    END DO
    306302
     303!
     304! Test for advection schema.
     305! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
     306!
     307    DO iq=1,nqtot
     308       IF (iadv(iq)/=10 .AND. iadv(iq)/=14) THEN
     309          WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     310          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
     311       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
     312          WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     313          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
     314       END IF
     315    END DO
     316
    307317!-----------------------------------------------------------------------
    308318! Finalize :
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/pres2lev.F

    r1046 r1179  
    1 !
    2 ! $Header$
     1! $Id$
    32!
    43c******************************************************
     
    2120c  ARGUMENTS
    2221c  """""""""
    23        LOGICAL ok_invertp
    24        INTEGER lmo ! dimensions ancienne couches (input)
    25        INTEGER lmn ! dimensions nouvelle couches (input)
    26        INTEGER lmomx ! dimensions ancienne couches (input)
    27        INTEGER lmnmx ! dimensions nouvelle couches (input)
     22       LOGICAL, INTENT(IN) :: ok_invertp
     23       INTEGER, INTENT(IN) :: lmo ! dimensions ancienne couches
     24       INTEGER, INTENT(IN) :: lmn ! dimensions nouvelle couches
     25       INTEGER lmomx ! dimensions ancienne couches
     26       INTEGER lmnmx ! dimensions nouvelle couches
    2827
    2928       parameter(lmomx=10000,lmnmx=10000)
    3029
    31         real po(ni,nj,lmo)! niveau de pression ancienne grille
    32         real pn(ni,nj,lmn) ! niveau de pression nouvelle grille
     30        real, INTENT(IN) :: po(ni,nj,lmo) ! niveau de pression ancienne grille
     31        real, INTENT(IN) :: pn(ni,nj,lmn) ! niveau de pression nouvelle grille
    3332
    34        INTEGER i,j,Nhoriz,ni,nj ! nombre de point horizontale (input)
     33       INTEGER, INTENT(IN) :: ni,nj ! nombre de point horizontale
    3534
    36        REAL varo(ni,nj,lmo) ! var dans l'ancienne grille (input)
    37        REAL varn(ni,nj,lmn) ! var dans la nouvelle grille (output)
     35       REAL, INTENT(IN)  :: varo(ni,nj,lmo) ! var dans l'ancienne grille
     36       REAL, INTENT(OUT) :: varn(ni,nj,lmn) ! var dans la nouvelle grille
    3837
    3938       real zvaro(lmomx),zpo(lmomx)
     
    4140c Autres variables
    4241c """"""""""""""""
    43        INTEGER n, ln ,lo 
     42       INTEGER n, ln ,lo, i, j, Nhoriz
    4443       REAL coef
    4544
Note: See TracChangeset for help on using the changeset viewer.