Ignore:
Timestamp:
Jul 24, 2024, 2:54:37 PM (2 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/times.F90

    r5113 r5116  
    1313  integer, parameter :: suspended = 3
    1414 
    15   integer :: max_size
     15  INTEGER :: max_size
    1616  real,    allocatable, dimension(:,:,:) :: timer_table
    1717  real,    allocatable, dimension(:,:,:) :: timer_table_sqr
     
    5050  SUBROUTINE start_timer(no_timer)
    5151    IMPLICIT NONE
    52     integer :: no_timer
    53    
    54     if (AllTimer_IsActive) then
    55    
    56       if (timer_state(no_timer)/=stopped) then
     52    INTEGER :: no_timer
     53   
     54    if (AllTimer_IsActive) THEN
     55      if (timer_state(no_timer)/=stopped) THEN
    5756        CALL abort_gcm("times","start_timer :: timer is already running or suspended",1)
    5857      else
     
    6968  SUBROUTINE suspend_timer(no_timer)
    7069    IMPLICIT NONE
    71     integer :: no_timer
     70    INTEGER :: no_timer
    7271     
    73     if (AllTimer_IsActive) then   
    74       if (timer_state(no_timer)/=running) then
     72    if (AllTimer_IsActive) THEN
     73      if (timer_state(no_timer)/=running) THEN
    7574         CALL abort_gcm("times","suspend_timer :: timer is not running",1)
    7675      else
     
    8685  SUBROUTINE resume_timer(no_timer)
    8786    IMPLICIT NONE
    88     integer :: no_timer
     87    INTEGER :: no_timer
    8988     
    90     if (AllTimer_IsActive) then   
    91       if (timer_state(no_timer)/=suspended) then
     89    if (AllTimer_IsActive) THEN
     90      if (timer_state(no_timer)/=suspended) THEN
    9291        CALL abort_gcm("times","resume_timer :: timer is not suspended",1)
    9392      else
     
    103102    USE parallel_lmdz
    104103    IMPLICIT NONE
    105     integer :: no_timer
    106     integer :: N
    107     real :: V,V2
    108    
    109     if (AllTimer_IsActive) then
    110        
    111       if (timer_state(no_timer)/=running) then
     104    INTEGER :: no_timer
     105    INTEGER :: N
     106    REAL :: V,V2
     107   
     108    if (AllTimer_IsActive) THEN
     109      if (timer_state(no_timer)/=running) THEN
    112110        CALL abort_gcm("times","stop_timer :: timer is not running",1)
    113111      else
     
    123121      timer_iteration(jj_nb,no_timer,mpi_rank)=timer_iteration(jj_nb,no_timer,mpi_rank)+1
    124122      timer_average(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)/timer_iteration(jj_nb,no_timer,mpi_rank)
    125       if (timer_iteration(jj_nb,no_timer,mpi_rank)>=2) then
     123      if (timer_iteration(jj_nb,no_timer,mpi_rank)>=2) THEN
    126124        N=timer_iteration(jj_nb,no_timer,mpi_rank)
    127125        V2=timer_table_sqr(jj_nb,no_timer,mpi_rank)
     
    140138    IMPLICIT NONE
    141139
    142     integer :: ierr
    143     integer :: data_size
     140    INTEGER :: ierr
     141    INTEGER :: data_size
    144142    real, allocatable,dimension(:,:) :: tmp_table
    145143
    146144    IF (using_mpi) THEN   
    147145   
    148       if (AllTimer_IsActive) then
    149    
    150    
     146      if (AllTimer_IsActive) THEN
    151147      allocate(tmp_table(max_size,nb_timer))
    152148   
     
    169165    USE lmdz_mpi
    170166    IMPLICIT NONE
    171     integer :: ierr
    172     integer :: data_size
     167    INTEGER :: ierr
     168    INTEGER :: data_size
    173169    real, allocatable,dimension(:,:),target :: tmp_table
    174170    integer, allocatable,dimension(:,:),target :: tmp_iter
    175     integer :: istats
     171    INTEGER :: istats
    176172
    177173    IF (using_mpi) THEN
    178174       
    179       if (AllTimer_IsActive) then
    180    
     175      if (AllTimer_IsActive) THEN
    181176      allocate(tmp_table(max_size,nb_timer))
    182177      allocate(tmp_iter(max_size,nb_timer))
     
    199194  SUBROUTINE InitTime
    200195  IMPLICIT NONE
    201     integer :: count,count_rate,count_max
     196    INTEGER :: count,count_rate,count_max
    202197   
    203198    AllTimer_IsActive=.TRUE.
    204     if (AllTimer_IsActive) then
     199    if (AllTimer_IsActive) THEN
    205200      CALL system_clock(count,count_rate,count_max)
    206201      CALL cpu_time(Last_cpuCount)
     
    212207  IMPLICIT NONE
    213208    double precision :: DiffTime
    214     integer :: count,count_rate,count_max
     209    INTEGER :: count,count_rate,count_max
    215210 
    216211    CALL system_clock(count,count_rate,count_max)
    217     if (Count>=Last_Count) then
     212    if (Count>=Last_Count) THEN
    218213      DiffTime=(1.*(Count-last_Count))/count_rate
    219214    else
     
    221216    endif
    222217    Last_Count=Count
    223   end function DiffTime
     218  END FUNCTION DiffTime
    224219 
    225220  function DiffCpuTime()
    226221  IMPLICIT NONE
    227     real :: DiffCpuTime
    228     real :: Count
     222    REAL :: DiffCpuTime
     223    REAL :: Count
    229224   
    230225    CALL cpu_time(Count)
    231226    DiffCpuTime=Count-Last_cpuCount
    232227    Last_cpuCount=Count
    233   end function DiffCpuTime
     228  END FUNCTION DiffCpuTime
    234229
    235230end module times
Note: See TracChangeset for help on using the changeset viewer.