C++Guns – RoboBlog

01.09.2014

Fortran progressmeter nice code

Filed under: Allgemein — Tags: — Thomas @ 22:09



! use modulo to determine when to print progress
! not independet of called algorithm speed
! possible output:
! 0.0  % done
! 0.01 % done
! 0,02 % done
! 0,03 % done
! or only one output
! 80.0 % done
! We can do better!
subroutine variant1(n)
  implicit none
  integer, intent(in) :: n
  integer :: i
  
  do i=1, n
    if(mod(i, 1000) == 0) write(*,*) 100.0*i/n, "% done"
    
    ! call some algorithm
    ! ...
  end do
end subroutine

! check in every iteration if progress is 10%, 20% u.s.w.
! pro: independet of called algorithm speed
! contra: more code
! possible output:
! 10 % done
! 20 % done
! 30 % done
! 80 % done
! 90 % done
! We can do better!
subroutine variant2(n)
  implicit none
  integer, intent(in) :: n
  integer :: i
  real :: percent, thr
  
  thr = 1.0 / n * 100.0  
  do i=1, n
    percent = 100.0*i/n
    if(percent > 10.0 .and. percent < 10.0+thr) write(*,*) "10 % done"
    if(percent > 20.0 .and. percent < 20.0+thr) write(*,*) "20 % done"
    if(percent > 30.0 .and. percent < 30.0+thr) write(*,*) "30 % done"
    if(percent > 40.0 .and. percent < 40.0+thr) write(*,*) "40 % done"
    if(percent > 50.0 .and. percent < 50.0+thr) write(*,*) "50 % done"
    if(percent > 60.0 .and. percent < 60.0+thr) write(*,*) "60 % done"
    if(percent > 70.0 .and. percent < 70.0+thr) write(*,*) "70 % done"
    if(percent > 80.0 .and. percent < 80.0+thr) write(*,*) "80 % done"
    if(percent > 90.0 .and. percent < 90.0+thr) write(*,*) "90 % done"      
    
    ! call some algorithm
    ! ...
  end do
end subroutine

! recalc threshold in every iteration
! possible output:
! 10 % done
! 20 % done
! 30 % done
! ...
! 90 % done
! almost done!
! we have to avoid duplicate code; copy&paste erros
subroutine variant3(n)
  implicit none
  integer, intent(in) :: n
  integer :: i
  real :: percent
  integer :: thr
  
  thr = 10
  do i=1, n
    percent = 100.0*i/n
    if(percent > thr) then
      write(*,*) thr, "% done"
      thr = thr +  10
    endif
    
    ! call some algorithm
    ! ...
  end do
end subroutine


! to avoid duplicate code and copy&paste errors, we move the code into a class and provide a progress function as interface
module ProgressMeterClass
  implicit none
  private
  public :: createProgressMeter

  type, public :: ProgressMeter
      integer, private :: n
      integer, private :: thr
    contains

      procedure :: progress
  end type
  
  interface createProgressMeter
    module procedure newProgressMeter
  end interface

  contains

  function newProgressMeter(n) result(this)
    implicit none
    type(ProgressMeter) :: this
    integer, intent(in) :: n

    this%n = n
    this%thr = 10
  end function

  subroutine progress(this, i)
    implicit none
    class(ProgressMeter), intent(inout) :: this
    integer, intent(in) :: i

    if(100.0*i/this%n > this%thr) then
      write(*,*) this%thr, "% done"
      this%thr = this%thr + 10
    endif
  end subroutine
end module


!> we use OO techniques. The progressmeter code is now in the ProgressMeterClass module.
!> We simply create an object of this type and call progress() on it in every iteration
subroutine variant4(n)
  use ProgressMeterClass
  implicit none
  integer, intent(in) :: n
  integer :: i
  type(ProgressMeter) :: pm
  
  ! we can pass a step and filehandle variable too
  pm = createProgressMeter(n)
  do i=1, n
    call pm%progress(i)
    
    ! call some algorithm
    ! ...
  end do
end subroutine

program Progressmeter  
  implicit none
  integer :: n

  n = 10000000

!   call variant1(n)
!   call variant2(n)  
!   call variant3(n)  
  call variant4(n)  
end program

No Comments

No comments yet.

RSS feed for comments on this post.

Sorry, the comment form is closed at this time.

Powered by WordPress