Ignore:
Timestamp:
Sep 12, 2018, 4:20:27 PM (6 years ago)
Author:
ymipsl
Message:

Some fix for OpenMP

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/src/phylmd/interface_icosa_lmdz.f90

    r4047 r4114  
    2929  INTEGER :: stop_clock
    3030  INTEGER :: count_clock=0
    31  
    32 !  REAL,SAVE :: day_length ! length of a day (s)
    3331 
    3432  INTEGER,SAVE :: nbp_phys
     
    189187
    190188  INTEGER :: run_length 
    191   REAL,SAVE :: day_length ! length of a day (s) ! SAVEd to be OpenMP shared
    192   INTEGER,SAVE :: annee_ref 
    193   INTEGER,SAVE :: day_ref   
     189  REAL :: day_length ! length of a day (s) ! SAVEd to be OpenMP shared <--- NO!!!!
     190  INTEGER :: annee_ref 
     191  INTEGER :: day_ref   
    194192  INTEGER :: day_ini   
    195193  REAL    :: start_time
     
    198196  ! Tracer stuff (SAVEd when needed to be OpenMP shared)
    199197  INTEGER :: nq
    200   INTEGER,SAVE                  :: nqo, nbtr
    201   CHARACTER(len=4),SAVE         :: type_trac
    202   CHARACTER(len=20),ALLOCATABLE,SAVE :: tname(:)    ! tracer short name for restart and diagnostics
     198  INTEGER                       :: nqo, nbtr
     199  CHARACTER(len=4)              :: type_trac
     200  CHARACTER(len=20),ALLOCATABLE :: tname(:)    ! tracer short name for restart and diagnostics
    203201  CHARACTER(len=23),ALLOCATABLE :: ttext(:)     ! tracer long name for diagnostics
    204202  INTEGER,ALLOCATABLE           :: niadv(:)    ! equivalent dyn / physique
     
    235233  INTEGER :: iflag_phys   
    236234
     235
    237236    CALL init_distrib_icosa_lmdz
    238237   
     
    264263    ENDDO
    265264
    266 !$OMP BARRIER
    267      
     265     
    268266    CALL transfer_icosa_to_lmdz(f_ind_cell_glo,ind_cell_glo)
    269267    CALL deallocate_field(f_ind_cell_glo)
     
    280278
    281279    ! Initialize tracer names, numbers, etc. for physics
    282 !$OMP MASTER
    283280    !Config  Key  = type_trac
    284281    !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     
    290287     type_trac = 'lmdz'
    291288     CALL getin('type_trac',type_trac)
    292 !$OMP END MASTER
    293 !$OMP BARRIER
    294289
    295290! allocate some of the tracer arrays
     
    299294
    300295! read "traceur.def" file to know tracer names (and figure out nqo and nbtr)
    301 !$OMP MASTER
    302     OPEN(unit=42,file="traceur.def",form="formatted",status="old",iostat=ierr)
    303     IF (ierr==0) THEN
    304       READ(42,*) nq ! should be the same as nqtot
    305       IF (nq /= nqtot) THEN
    306         WRITE(*,*) "Error: number of tracers in tracer.def should match nqtot!"
    307         WRITE(*,*) "       will just use nqtot=",nqtot," tracers"
     296    IF (is_mpi_root) THEN
     297  !$OMP MASTER
     298      OPEN(unit=42,file="traceur.def",form="formatted",status="old",iostat=ierr)
     299      IF (ierr==0) THEN
     300        READ(42,*) nq ! should be the same as nqtot
     301        IF (nq /= nqtot) THEN
     302          WRITE(*,*) "Error: number of tracers in tracer.def should match nqtot!"
     303          WRITE(*,*) "       will just use nqtot=",nqtot," tracers"
     304        ENDIF
     305        DO i=1,nqtot
     306          READ(42,*) j,k,tname(i)
     307        ENDDO
     308        CLOSE(42)
    308309      ENDIF
     310      ! figure out how many water tracers are present
     311      nqo=0
    309312      DO i=1,nqtot
    310         READ(42,*) j,k,tname(i)
    311       ENDDO
    312       CLOSE(42)
     313        IF (INDEX(tname(i),"H2O")==1) THEN
     314          nqo=nqo+1
     315        ENDIF
     316      ENDDO
     317      nbtr=nqtot-nqo
     318   !$OMP END MASTER
    313319    ENDIF
    314     ! figure out how many water tracers are present
    315     nqo=0
     320 
     321    CALL bcast(nqo)
     322    CALL bcast(nbtr)
    316323    DO i=1,nqtot
    317       IF (INDEX(tname(i),"H2O")==1) THEN
    318         nqo=nqo+1
    319       ENDIF
    320     ENDDO
    321     nbtr=nqtot-nqo
    322 !$OMP END MASTER
    323 !$OMP BARRIER
    324 
     324      CALL bcast(tname(i))
     325    ENDDO
     326   
    325327    ALLOCATE(conv_flg(nbtr))
    326328    ALLOCATE(pbl_flg(nbtr))
     
    374376
    375377   ! Initialize physical constant
    376 !$OMP MASTER
    377378    day_length=86400
    378379    CALL getin('day_length',day_length)
     
    387388    day_ref=1
    388389    CALL getin("dayref",day_ref)
    389 !$OMP END MASTER
    390 !$OMP BARRIER
    391390   
    392391    physics_timestep=dt*itau_physics
Note: See TracChangeset for help on using the changeset viewer.