Ignore:
Timestamp:
Jul 9, 2021, 5:31:31 PM (3 years ago)
Author:
emillour
Message:

Generic GCM:
Some OpenMP fixes in routines initracer.F, nonoro_gwd_ran_mod.F90,
phys_state_var_mod.F90 and sugas_corrk.F90
EM

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/initracer.F

    r2543 r2550  
    55      USE callkeys_mod, only: water
    66      USE recombin_corrk_mod, ONLY: ini_recombin
     7      USE mod_phys_lmdz_para, only: is_master, bcast
    78      IMPLICIT NONE
    89c=======================================================================
     
    4546c-----------------------------------------------------------------------
    4647
    47       moderntracdef=.false. ! For modern traceur.def (default false, old type)
    48 
    49       open(407, form = 'formatted', status = 'old',
     48      if (is_master) then ! only the master proc/thread needs do this
     49
     50        moderntracdef=.false. ! For modern traceur.def (default false, old type)
     51
     52        open(407, form = 'formatted', status = 'old',
    5053     $          file = 'traceur.def', iostat=ierr)
    51       if (ierr /=0) then
    52         call abort_physic('initracer',
    53      $  'Problem in opening traceur.def',1)
    54       end if
     54        if (ierr /=0) then
     55          call abort_physic('initracer',
     56     $    'Problem in opening traceur.def',1)
     57        end if
    5558!! - Modif. by JVO and YJ for modern planetary traceur.def ---------------
    56        READ(407,'(A)') tracline
    57        IF (trim(tracline).ne.'#ModernTrac-v1') THEN ! Test modern traceur.def
     59        READ(407,'(A)') tracline
     60        IF (trim(tracline).ne.'#ModernTrac-v1') THEN ! Test modern traceur.def
    5861          READ(tracline,*) nqtot ! Try standard traceur.def
    59        ELSE
     62        ELSE
    6063         moderntracdef = .true.
    6164         DO
     
    7679           ENDIF
    7780         ENDDO
    78        ENDIF ! if modern or standard traceur.def
     81        ENDIF ! if modern or standard traceur.def
     82       
     83       endif ! of if (is_master)
     84       
     85       ! share the information with other procs/threads (if any)
     86       CALL bcast(nqtot)
     87       CALL bcast(moderntracdef)
     88       
    7989!! -----------------------------------------------------------------------
    8090       !! For the moment number of tracers in dynamics and physics are equal
     
    396406      ! Get data of tracers
    397407      do iq=1,nqtot
    398         read(407,'(A)') tracline
     408        if (is_master) read(407,'(A)') tracline
     409        call bcast(tracline)
    399410        call get_tracdat(iq, tracline)
    400411      enddo
    401412
    402       close(407)
     413      if (is_master) close(407)
    403414
    404415      ! Calculate number of species in the chemistry
  • trunk/LMDZ.GENERIC/libf/phystd/nonoro_gwd_ran_mod.F90

    r2403 r2550  
    77      REAL, allocatable, save :: east_gwstress(:, :) ! Eastward stress profile
    88      REAL, allocatable, save :: west_gwstress(:, :) ! Westward stress profile
    9 
     9!$OMP THREADPRIVATE(du_nonoro_gwd,dv_nonoro_gwd,east_gwstress,west_gwstress)
    1010CONTAINS
    1111
  • trunk/LMDZ.GENERIC/libf/phystd/phys_state_var_mod.F90

    r2537 r2550  
    107107      real,dimension(:,:),allocatable,save :: dEzRadsw  ! Radiative heating (W.m-2)
    108108      real,dimension(:,:),allocatable,save :: dEzRadlw  ! Radiative heating (W.m-2)
    109 !$OMP THREADPRIVATE(dEzdiff,dEzdiffs,dEzRadsw,dEzRadlw)
     109!$OMP THREADPRIVATE(dEzdiff,dEdiff,dEdiffs,dEzRadsw,dEzRadlw)
    110110
    111111      real,dimension(:),allocatable,save :: madjdE      ! Heat from moistadj (W.m-2)
  • trunk/LMDZ.GENERIC/libf/phystd/sugas_corrk.F90

    r2543 r2550  
    6565      if (.not. moderntracdef) use_premix=.true. ! Added by JVO for compatibility with 'old' traceur.def
    6666     
     67!$OMP MASTER
    6768      if (use_premix) then ! use_premix flag added by JVO, thus if pure recombining then premix is skipped
    6869
     
    8485      endif
    8586
    86 !$OMP MASTER
    8787      ! check that database matches varactive toggle
    8888      open(111,file=TRIM(file_path),form='formatted')
     
    765765!$OMP BARRIER
    766766
    767       return
    768767    end subroutine sugas_corrk
Note: See TracChangeset for help on using the changeset viewer.