Ignore:
Timestamp:
10/09/15 16:13:43 (9 years ago)
Author:
dubos
Message:

Bugfix : memory leak in transfert_mpi / New : detect send_message not paired with wait_message

File:
1 edited

Legend:

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

    r363 r364  
    195195    !$OMP MASTER 
    196196    CALL SYSTEM_CLOCK(start_clock) 
     197    CALL SYSTEM_CLOCK(count_rate=rate_clock) 
    197198    !$OMP END MASTER    
    198199 
     
    203204    DO it=itau0+1,itau0+itaumax 
    204205 
    205        CALL check_conserve_detailed('detailed_budget 0', & 
    206             f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it) 
    207  
    208        IF (xios_output) CALL xios_update_calendar(it) 
     206       IF (is_master) CALL print_iteration(it, itau0, itaumax, start_clock, rate_clock) 
     207       IF (xios_output) THEN 
     208          CALL xios_update_calendar(it) 
     209       ELSE 
     210          CALL update_time_counter(dt*it) 
     211       END IF 
     212 
    209213       IF (it==itau0+1 .OR. MOD(it,itau_sync)==0) THEN 
    210214          CALL send_message(f_ps,req_ps0) 
     
    220224       ENDIF 
    221225 
    222        IF (is_master) PRINT *,"It No :",It,"   t :",dt*It 
    223  
    224226       IF (mod(it,itau_out)==0 ) THEN 
    225           CALL update_time_counter(dt*it) 
    226227          CALL write_output_fields_basic(f_ps, f_u, f_q) 
    227228       ENDIF 
     229 
     230       CALL check_conserve_detailed('detailed_budget 0', & 
     231            f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it) 
    228232 
    229233       CALL guided(it*dt,f_ps,f_theta_rhodz,f_u,f_q) 
     
    235239          CALL HEVI_scheme(it, fluxt_zero) 
    236240       END SELECT 
    237  
     241        
    238242       CALL check_conserve_detailed('detailed_budget 1', & 
    239243            f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it) 
     
    266270        
    267271       IF(MOD(it,itau_adv)==0) THEN 
    268           IF(nqtot>0) CALL advect_tracer(f_hfluxt,f_wfluxt,f_u, f_q,f_rhodz)  ! update q and rhodz after RK step 
     272          CALL advect_tracer(f_hfluxt,f_wfluxt,f_u, f_q,f_rhodz)  ! update q and rhodz after RK step 
    269273          fluxt_zero=.TRUE. 
    270274          ! FIXME : check that rhodz is consistent with ps 
     
    278282             END DO 
    279283          ENDIF 
    280            
    281284       END IF 
    282285        
     
    301304    !$OMP MASTER 
    302305    CALL SYSTEM_CLOCK(stop_clock) 
    303     CALL SYSTEM_CLOCK(count_rate=rate_clock) 
    304306     
    305307    IF (mpi_rank==0) THEN  
     
    310312    ! CONTAINS 
    311313  END SUBROUTINE timeloop 
    312    
     314 
     315  SUBROUTINE print_iteration(it,itau0,itaumax,start_clock,rate_clock) 
     316    INTEGER :: it, itau0, itaumax, start_clock, stop_clock, rate_clock, throughput 
     317    REAL :: per_step,total, elapsed 
     318    WRITE(*,'(A,I7,A,F8.1)') "It No :",it,"   t :",dt*it 
     319    IF(MOD(it,10)==0) THEN 
     320       CALL SYSTEM_CLOCK(stop_clock) 
     321       elapsed = (stop_clock-start_clock)*1./rate_clock 
     322       per_step = elapsed/(it-itau0) 
     323       throughput = dt/per_step 
     324       total = per_step*(itaumax-itau0) 
     325       WRITE(*,'(A,I5,A,F6.2,A,I6)') 'Time spent (s):',INT(elapsed), & 
     326            '  -- ms/step : ', 1000*per_step, & 
     327            '  -- Throughput :', throughput 
     328       WRITE(*,'(A,I5,A,I5)') 'Whole job (min) :', INT(total/60.), & 
     329            '  -- Completion in (min) : ', INT((total-elapsed)/60.) 
     330    END IF 
     331  END SUBROUTINE print_iteration 
     332 
    313333END MODULE timeloop_gcm_mod 
Note: See TracChangeset for help on using the changeset viewer.