Ignore:
Timestamp:
10/12/16 16:14:03 (8 years ago)
Author:
ymipsl
Message:

New version independant of netcd I/O for benchmarking.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/time.f90

    r347 r488  
    105105  CHARACTER(LEN=255) :: time_frequency 
    106106 
     107  IF (no_io) RETURN 
    107108  CALL getin("dt",dt) 
    108109 
    109110!$OMP BARRIER 
    110111!$OMP MASTER   
    111     IF (is_mpi_root) THEN  
     112    IF (is_mpi_root ) THEN  
    112113      status = NF90_CREATE('time_counter.nc', NF90_CLOBBER, ncid) 
    113114      status = NF90_DEF_DIM(ncid,'time_counter',NF90_UNLIMITED,timeid) 
     
    141142  REAL(rstd) ::time_array(1) 
    142143 
     144  IF (no_io) RETURN 
     145 
    143146!$OMP BARRIER 
    144147!$OMP MASTER 
     
    160163  IMPLICIT NONE 
    161164    INTEGER :: status 
     165 
     166    IF (no_io) RETURN 
    162167     
    163168!$OMP BARRIER 
Note: See TracChangeset for help on using the changeset viewer.