time.F90 Source File


This file depends on

sourcefile~~time.f90~~EfferentGraph sourcefile~time.f90 time.F90 sourcefile~core.f90 core.F90 sourcefile~time.f90->sourcefile~core.f90 sourcefile~input.f90 input.F90 sourcefile~time.f90->sourcefile~input.f90 sourcefile~allocate.f90 allocate.F90 sourcefile~core.f90->sourcefile~allocate.f90 sourcefile~check_range.f90 check_range.F90 sourcefile~core.f90->sourcefile~check_range.f90 sourcefile~deallocate.f90 deallocate.F90 sourcefile~core.f90->sourcefile~deallocate.f90 sourcefile~error.f90 error.F90 sourcefile~core.f90->sourcefile~error.f90 sourcefile~fortran_utils.f90 fortran_utils.F90 sourcefile~core.f90->sourcefile~fortran_utils.f90 sourcefile~string_utils.f90 string_utils.F90 sourcefile~core.f90->sourcefile~string_utils.f90 sourcefile~types.f90 types.F90 sourcefile~core.f90->sourcefile~types.f90 sourcefile~unique.f90 unique.F90 sourcefile~core.f90->sourcefile~unique.f90 sourcefile~vtk.f90 vtk.F90 sourcefile~core.f90->sourcefile~vtk.f90 sourcefile~vtk_constants.f90 vtk_constants.F90 sourcefile~core.f90->sourcefile~vtk_constants.f90 sourcefile~input_interface.f90 input_interface.F90 sourcefile~input.f90->sourcefile~input_interface.f90 sourcefile~allocate.f90->sourcefile~error.f90 sourcefile~deallocate.f90->sourcefile~error.f90 sourcefile~memory_stats_wrapper.f90 memory_stats_wrapper.F90 sourcefile~fortran_utils.f90->sourcefile~memory_stats_wrapper.f90 sourcefile~signal_flag_wrapper.f90 signal_flag_wrapper.F90 sourcefile~fortran_utils.f90->sourcefile~signal_flag_wrapper.f90 sourcefile~system_info_wrapper.f90 system_info_wrapper.F90 sourcefile~fortran_utils.f90->sourcefile~system_info_wrapper.f90 sourcefile~input_interface.f90->sourcefile~core.f90 sourcefile~project_settings.f90 project_settings.F90 sourcefile~input_interface.f90->sourcefile~project_settings.f90 sourcefile~string_utils.f90->sourcefile~allocate.f90 sourcefile~array.f90 array.F90 sourcefile~types.f90->sourcefile~array.f90 sourcefile~gauss.f90 gauss.F90 sourcefile~types.f90->sourcefile~gauss.f90 sourcefile~pointer.f90 pointer.F90 sourcefile~types.f90->sourcefile~pointer.f90 sourcefile~variable.f90 variable.F90 sourcefile~types.f90->sourcefile~variable.f90 sourcefile~vector.f90 vector.F90 sourcefile~types.f90->sourcefile~vector.f90 sourcefile~unique.f90->sourcefile~allocate.f90 sourcefile~vtk.f90->sourcefile~allocate.f90 sourcefile~vtk.f90->sourcefile~deallocate.f90 sourcefile~vtk.f90->sourcefile~unique.f90 sourcefile~vtk.f90->sourcefile~vtk_constants.f90 sourcefile~vtk.f90->sourcefile~array.f90 sourcefile~vtk_wrapper.f90 vtk_wrapper.F90 sourcefile~vtk.f90->sourcefile~vtk_wrapper.f90 sourcefile~vtu_wrapper.f90 vtu_wrapper.F90 sourcefile~vtk.f90->sourcefile~vtu_wrapper.f90 sourcefile~array.f90->sourcefile~allocate.f90 sourcefile~array.f90->sourcefile~deallocate.f90 sourcefile~c_utils.f90 c_utils.F90 sourcefile~memory_stats_wrapper.f90->sourcefile~c_utils.f90 sourcefile~project_settings.f90->sourcefile~core.f90 sourcefile~signal_flag.f90 signal_flag.F90 sourcefile~signal_flag_wrapper.f90->sourcefile~signal_flag.f90 sourcefile~system_info_wrapper.f90->sourcefile~c_utils.f90 sourcefile~variable.f90->sourcefile~allocate.f90 sourcefile~c_utils.f90->sourcefile~signal_flag.f90 sourcefile~memory_stats.f90 memory_stats.F90 sourcefile~c_utils.f90->sourcefile~memory_stats.f90 sourcefile~system_info.f90 system_info.F90 sourcefile~c_utils.f90->sourcefile~system_info.f90

Files dependent on this one

sourcefile~~time.f90~~AfferentGraph sourcefile~time.f90 time.F90 sourcefile~control.f90 control.F90 sourcefile~control.f90->sourcefile~time.f90 sourcefile~ftdss.f90 ftdss.F90 sourcefile~ftdss.f90->sourcefile~control.f90 sourcefile~thermal_interface.f90 thermal_interface.F90 sourcefile~ftdss.f90->sourcefile~thermal_interface.f90 sourcefile~output.f90 output.F90 sourcefile~ftdss.f90->sourcefile~output.f90 sourcefile~output_interface.f90 output_interface.F90 sourcefile~output_interface.f90->sourcefile~control.f90 sourcefile~thermal_interface.f90->sourcefile~control.f90 sourcefile~output.f90->sourcefile~output_interface.f90 sourcefile~output_base.f90 output_base.F90 sourcefile~output_base.f90->sourcefile~output_interface.f90 sourcefile~output_observation.f90 output_observation.F90 sourcefile~output_observation.f90->sourcefile~output_interface.f90 sourcefile~output_overall_base.f90 output_overall_base.F90 sourcefile~output_overall_base.f90->sourcefile~output_interface.f90 sourcefile~output_overall_vtk.f90 output_overall_vtk.F90 sourcefile~output_overall_vtk.f90->sourcefile~output_interface.f90 sourcefile~output_overall_vtu.f90 output_overall_vtu.F90 sourcefile~output_overall_vtu.f90->sourcefile~output_interface.f90 sourcefile~output_system_logger.f90 output_system_logger.F90 sourcefile~output_system_logger.f90->sourcefile~output_interface.f90 sourcefile~thermal.f90 thermal.F90 sourcefile~thermal.f90->sourcefile~thermal_interface.f90 sourcefile~thermal_3phase.f90 thermal_3phase.F90 sourcefile~thermal_3phase.f90->sourcefile~thermal_interface.f90

Source Code

module control_time
    use, intrinsic :: iso_fortran_env, only: int32, real64, int64
!$  use omp_lib
    use :: module_core, only:allocate_array
    use :: module_input, only:type_Input

    implicit none
    private

    public :: type_time

    type :: type_time_record
        character(len=10) :: label
        character(len=10) :: date
        character(len=10) :: time
        character(len=10) :: zone
    end type type_time_record

    type :: type_profiler_section
        character(len=20) :: label
        real(real64) :: total_time = 0.0d0
#ifdef _OPENMP
        real(real64) :: start_time_wtime = 0.0d0
#else
        integer(kind=int64) :: start_tick = 0
#endif
    end type type_profiler_section

    type :: type_time
        real(real64) :: start_time
        real(real64) :: end_time
        real(real64) :: time
        real(real64) :: time_old
        real(real64) :: dt
        real(real64), allocatable :: dt_old(:)
        real(real64) :: dt_min
        real(real64) :: dt_max
        type(type_time_record) :: start
        type(type_time_record) :: end
        type(type_profiler_section), allocatable :: sections(:)
#ifndef _OPENMP
        integer(int32) :: tick_rate = 0
#endif
    contains
        procedure, public, pass(self) :: initialize    => initialize_type_time !&
        procedure, public, pass(self) :: record        => record_timestamp !&
        procedure, public, pass(self) :: profile_start => profile_start_timer !&
        procedure, public, pass(self) :: profile_stop  => profile_stop_timer !&
    end type type_time

contains

    subroutine initialize_type_time(self, input, profiler_sections)
        implicit none
        class(type_time), intent(inout) :: self
        type(type_Input), intent(in), optional :: input
        character(*), intent(in), optional :: profiler_sections(:)

        integer(int32) :: i
        integer(int32) :: dummy

        if (present(input)) then
            select case (trim(input%conditions%time_control%time_stepping%unit))
            case ("second")
                self%dt     = input%conditions%time_control%time_stepping%initial_step !&
                self%dt_max = input%conditions%time_control%time_stepping%max_step !&
                self%dt_min = input%conditions%time_control%time_stepping%min_step !&
            case ("minute")
                self%dt     = input%conditions%time_control%time_stepping%initial_step * 60.0d0 !&
                self%dt_max = input%conditions%time_control%time_stepping%max_step * 60.0d0 !&
                self%dt_min = input%conditions%time_control%time_stepping%min_step * 60.0d0 !&
            case ("hour")
                self%dt     = input%conditions%time_control%time_stepping%initial_step * 3600.0d0 !&
                self%dt_max = input%conditions%time_control%time_stepping%max_step * 3600.0d0 !&
                self%dt_min = input%conditions%time_control%time_stepping%min_step * 3600.0d0 !&
            case ("day")
                self%dt     = input%conditions%time_control%time_stepping%initial_step * 86400.0d0 !&
                self%dt_max = input%conditions%time_control%time_stepping%max_step * 86400.0d0 !&
                self%dt_min = input%conditions%time_control%time_stepping%min_step * 86400.0d0 !&
            case ("year")
                self%dt     = input%conditions%time_control%time_stepping%initial_step * 31557600.0d0 !&
                self%dt_max = input%conditions%time_control%time_stepping%max_step * 31557600.0d0 !&
                self%dt_min = input%conditions%time_control%time_stepping%min_step * 31557600.0d0 !&
            case default
                write (*, *) "Error: Unknown time unit in Calculation_TimeUnit"
                stop
            end select

            select case (trim(input%conditions%time_control%simulation_period%unit))
            case ("second")
                self%start_time = input%conditions%time_control%simulation_period%start !&
                self%end_time   = input%conditions%time_control%simulation_period%end !&
            case ("minute")
                self%start_time = input%conditions%time_control%simulation_period%start * 60.0d0 !&
                self%end_time   = input%conditions%time_control%simulation_period%end * 60.0d0 !&
            case ("hour")
                self%start_time = input%conditions%time_control%simulation_period%start * 3600.0d0 !&
                self%end_time   = input%conditions%time_control%simulation_period%end * 3600.0d0 !&
            case ("day")
                self%start_time = input%conditions%time_control%simulation_period%start * 86400.0d0 !&
                self%end_time   = input%conditions%time_control%simulation_period%end * 86400.0d0 !&
            case ("year")
                self%start_time = input%conditions%time_control%simulation_period%start * 31557600.0d0 !&
                self%end_time   = input%conditions%time_control%simulation_period%end * 31557600.0d0 !&
            case default
                write (*, *) "Error: Unknown time unit in Input_TimeUnit"
                stop
            end select

            call Allocate_Array(self%dt_old, input%basic%solver_settings%bdf_order)
        end if

        if (present(profiler_sections)) then
            if (size(profiler_sections) > 0) then
#ifndef _OPENMP
                call system_clock(dummy, self%tick_rate)
#endif
                allocate (self%sections(size(profiler_sections)))
                do i = 1, size(profiler_sections)
                    self%sections(i)%label = trim(profiler_sections(i))
                end do
            end if
        end if
    end subroutine initialize_type_time

    subroutine record_timestamp(self, label)
        implicit none
        class(type_time), intent(inout) :: self
        character(*), intent(in) :: label

        select case (trim(label))
        case ("Start")
            call date_and_time(date=self%start%date, time=self%start%time, zone=self%start%zone)
            self%start%label = label
        case ("End")
            call date_and_time(date=self%end%date, time=self%end%time, zone=self%end%zone)
            self%end%label = label
        case default
            write (*, *) "Error: Unknown time label"
            stop
        end select
    end subroutine record_timestamp

    subroutine profile_start_timer(self, label)
        class(type_time), intent(inout) :: self
        character(len=*), intent(in) :: label
        integer :: i
        do i = 1, size(self%sections)
            if (trim(self%sections(i)%label) == trim(label)) then
#ifdef _OPENMP
                self%sections(i)%start_time_wtime = omp_get_wtime()
#else
                call system_clock(count=self%sections(i)%start_tick)
#endif
                return
            end if
        end do
        write (*, '(3a)') "Error: Profiling section '", trim(label), "' not found. Timer not started."
    end subroutine profile_start_timer

    subroutine profile_stop_timer(self, label)
        class(type_time), intent(inout) :: self
        character(len=*), intent(in) :: label
        integer :: i
        real(real64) :: duration
#ifdef _OPENMP
        real(real64) :: end_time_wtime
        end_time_wtime = omp_get_wtime()
#else
        integer(kind=int64) :: end_tick
        call system_clock(count=end_tick)
#endif
        do i = 1, size(self%sections)
            if (trim(self%sections(i)%label) == trim(label)) then
#ifdef _OPENMP
                duration = end_time_wtime - self%sections(i)%start_time_wtime
#else
                if (self%tick_rate > 0) then
                    duration = real(end_tick - self%sections(i)%start_tick, real64) / real(self%tick_rate, real64)
                else
                    duration = 0.0d0
                end if
#endif
                self%sections(i)%total_time = self%sections(i)%total_time + duration
                return
            end if
        end do
        write (*, '(3a)') "Error: Profiling section '", trim(label), "' not found. Timer not stopped."
    end subroutine profile_stop_timer

end module control_time