Ignore:
Timestamp:
Jun 18, 2015, 1:53:21 PM (9 years ago)
Author:
ymipsl
Message:

Some missing threadprivate...

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/time_phylmdz_mod.f90

    r3831 r3835  
    22
    33    REAL,SAVE    :: pdtphys     ! physics time step (s)
     4!$OMP THREADPRIVATE(pdtphys)
    45    INTEGER,SAVE :: day_step    ! number of physical steps per day
     6!$OMP THREADPRIVATE(day_step)
    57    INTEGER,SAVE :: ndays       ! number of days to run
     8!$OMP THREADPRIVATE(ndays)
    69    INTEGER,SAVE :: annee_ref   ! reference year from the origin
     10!$OMP THREADPRIVATE(annee_ref)
    711    INTEGER,SAVE :: day_ref     ! reference year of the origin
     12!$OMP THREADPRIVATE(day_ref)
    813    INTEGER,SAVE :: day_ini     ! initial day of the run starting from 1st january of annee_ref
     14!$OMP THREADPRIVATE(day_ini)
    915    INTEGER,SAVE :: day_end     ! final day of the run starting from 1st january of annee_ref
     16!$OMP THREADPRIVATE(day_end)
    1017    REAL,SAVE    :: start_time  ! starting time from the begining of the initial day
     18!$OMP THREADPRIVATE(start_time)
    1119    INTEGER,SAVE :: raz_date
     20!$OMP THREADPRIVATE(raz_date)
    1221
    1322    INTEGER,SAVE :: itau_phy     ! number of physiq iteration from origin
     23!$OMP THREADPRIVATE(itau_phy)
    1424    INTEGER,SAVE :: itaufin      ! final iteration
     25!$OMP THREADPRIVATE(itaufin)
    1526    REAL,SAVE    :: current_time ! current elapsed time (s) from the begining of the run
    16 
     27!$OMP THREADPRIVATE(current_time)
    1728   
    1829
     
    2233  USE ioipsl, ONLY : getin
    2334  USE phys_cal_mod, ONLY: phys_cal_init
     35  USE mod_phys_lmdz_para
    2436  IMPLICIT NONE
    2537  INCLUDE 'YOMCST.h'
     
    4254 
    4355    raz_date = 0
    44     CALL getin('raz_date', raz_date)
     56    IF (is_master) CALL getin('raz_date', raz_date)
     57    CALL bcast(raz_date)
    4558    current_time=0
    4659   
Note: See TracChangeset for help on using the changeset viewer.