Changeset 1117


Ignore:
Timestamp:
Mar 11, 2009, 1:47:42 PM (15 years ago)
Author:
yann meurdesoif
Message:

Correction pour bon fonctionnement en OpenMP suite à la mise à jour des modifications sur le nombre de traceur spécifié dynamiquement
YM

Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar
Files:
3 edited

Legend:

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

    r1114 r1117  
    4040      REAL :: vvent(iip1, jjm, llm)
    4141      REAL :: t3d(iip1, jjp1, llm), tpot(iip1, jjp1, llm)
    42       REAL :: q3d(iip1, jjp1, llm,nqtot), qsat(iip1, jjp1, llm)
     42      REAL :: qsat(iip1, jjp1, llm)
     43      REAL,ALLOCATABLE :: q3d(:, :, :,:)
    4344      REAL :: tsol(klon), qsol(klon), sn(klon)
    4445      REAL :: tsolsrf(klon,nbsrf), qsolsrf(klon,nbsrf),snsrf(klon,nbsrf)
     
    170171      !
    171172      CALL inifilr()
     173C init pour traceurs
     174      call infotrac_init
     175      ALLOCATE(q3d(iip1, jjp1, llm,nqtot))
    172176!      CALL phys_state_var_init()
    173177      !
     
    625629      phis(iip1,:) = phis(1,:)
    626630
    627 C init pour traceurs
    628       call infotrac_init
    629631C Ecriture
    630632      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/infotrac.F90

    r1114 r1117  
    33! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
    44  INTEGER, SAVE :: nqtot
    5 !$OMP THREADPRIVATE(nqtot)   
     5!!$OMP THREADPRIVATE(nqtot)   
    66
    77! nbtr : number of tracers not including higher order of moment or water vapor or liquid
    88!        number of tracers used in the physics
    99  INTEGER, SAVE :: nbtr
    10 !$OMP THREADPRIVATE(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)   
     15!!$OMP THREADPRIVATE(tname,ttext)   
    1616
    1717! iadv  : index of trasport schema for each tracer
    1818  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
    19 !$OMP THREADPRIVATE(iadv)   
     19!!$OMP THREADPRIVATE(iadv)   
    2020
    2121! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
    2222!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
    2323  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
    24 !$OMP THREADPRIVATE(niadv)   
     24!!$OMP THREADPRIVATE(niadv)   
    2525
    2626! Variables for INCA
    2727  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
    2828  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
    29 !$OMP THREADPRIVATE(conv_flg, pbl_flg)   
     29!!$OMP THREADPRIVATE(conv_flg, pbl_flg)   
    3030
    3131CONTAINS
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/vlspltgen_p.F

    r1114 r1117  
    6969      INTEGER ijb,ije,iq
    7070      LOGICAL, SAVE :: firstcall=.TRUE.
    71 
     71!$OMP THREADPRIVATE(firstcall)
    7272      type(request) :: MyRequest1
    7373      type(request) :: MyRequest2
     
    8888
    8989c Allocate variables depending on dynamic variable nqtot
     90
    9091         IF (firstcall) THEN
    9192            firstcall=.FALSE.
     93!$OMP MASTER
    9294            ALLOCATE(zm(ip1jmp1,llm,nqtot))
    9395            ALLOCATE(zq(ip1jmp1,llm,nqtot))
     96!$OMP END MASTER
     97!$OMP BARRIER
    9498         END IF
    95 
    9699c-- Calcul de Qsat en chaque point
    97100c-- approximation: au milieu des couches play(l)=(p(l)+p(l+1))/2
Note: See TracChangeset for help on using the changeset viewer.