Skip to content
Snippets Groups Projects
Commit 5386e8d6 authored by Luis Kornblueh's avatar Luis Kornblueh
Browse files

Added posic string output to hl interface.

parent 274dd085
No related branches found
No related tags found
No related merge requests found
......@@ -71,15 +71,6 @@
*
*/
/** @page examples1 How to use events
*
* A first tool which might be implemented is a managment facility for
* events.
*
* @snippet example.f90 example_event_manager
*
*/
/** @defgroup libmtime Library application area
*
* This library provides time, calenendar, and event handling
......
......@@ -22,10 +22,8 @@ MODULE error_handling
PUBLIC :: MAX_ERROR_STR_LEN
INTEGER, PARAMETER :: MAX_ERROR_STR_LEN = 256
!> Base class for error info, storing the details of the
! circumstances in which the error occured. Making a distinction
! between the error and the associated information simplifies the
......@@ -42,7 +40,6 @@ MODULE error_handling
TYPE, EXTENDS(t_error_info) :: t_arithmetic_error
END TYPE t_arithmetic_error
!> Base class for errors
TYPE t_error
CLASS(t_error_info), POINTER :: info => NULL()
......@@ -67,7 +64,6 @@ CONTAINS
END IF
END SUBROUTINE create_error
!> Transfers the error from @p inform to the @p ifail argument.
!
! Thus, the responsibility of the error can be transferred to the
......@@ -80,7 +76,6 @@ CONTAINS
new_error%info => inform%info
END SUBROUTINE transfer_error
!> Outputs the given error.
!
SUBROUTINE error_report(this)
......@@ -93,7 +88,6 @@ CONTAINS
CALL this%discard()
END SUBROUTINE error_report
!> Indicates that the given error has been taken care of and can be
! silenced safely.
!
......
......@@ -34,7 +34,6 @@ module mtime_hl
contains
procedure :: day => t_datetime_day
procedure :: to_string => t_datetime_to_string
procedure :: assign_string => t_datetime_assign_string
procedure :: add_timedelta => t_datetime_add_timedelta
procedure :: sub_timedelta => t_datetime_sub_timedelta
......@@ -46,16 +45,21 @@ module mtime_hl
procedure :: less_or_equal_datetime => t_datetime_less_or_equal
procedure :: greater_or_equal_datetime => t_datetime_greater_or_equal
generic :: assignment(=) => assign_string
generic :: operator(+) => add_timedelta
generic :: operator(-) => sub_timedelta
generic :: operator(-) => sub_datetime
generic :: operator(==) => equal_datetime
generic :: operator(/=) => not_equal_datetime
generic :: operator(<) => less_than_datetime
generic :: operator(>) => greater_than_datetime
generic :: operator(<=) => less_or_equal_datetime
generic :: operator(>=) => greater_or_equal_datetime
procedure :: t_datetime_to_string
procedure :: t_datetime_to_posix_string
generic :: to_string => t_datetime_to_string, t_datetime_to_posix_string
generic :: assignment(=) => assign_string
generic :: operator(+) => add_timedelta
generic :: operator(-) => sub_timedelta
generic :: operator(-) => sub_datetime
generic :: operator(==) => equal_datetime
generic :: operator(/=) => not_equal_datetime
generic :: operator(<) => less_than_datetime
generic :: operator(>) => greater_than_datetime
generic :: operator(<=) => less_or_equal_datetime
generic :: operator(>=) => greater_or_equal_datetime
end type t_datetime
......@@ -72,10 +76,13 @@ module mtime_hl
contains
procedure :: to_string => t_timedelta_to_string
procedure :: assign_string => t_timedelta_assign_string
procedure :: assign_ms => t_timedelta_assign_ms
procedure :: t_timedelta_to_string
generic :: to_string => t_timedelta_to_string
generic :: assignment(=) => assign_string, assign_ms
end type t_timedelta
......@@ -117,6 +124,29 @@ contains
call deallocatedatetime(dt_tmp)
end function t_datetime_to_string
! Convert t_datetime object to string.
!
function t_datetime_to_posix_string(this, format_string, opt_error)
character(len=max_datetime_str_len) :: t_datetime_to_posix_string
character(len=*), intent(in) :: format_string
type(t_error), intent(out), optional :: opt_error
class (t_datetime) :: this
type(datetime), pointer :: dt_tmp
integer :: errno
character(len=max_error_str_len) :: error_str
dt_tmp => newdatetime(this%dt)
if (present(opt_error)) then
call datetimetoposixstring(dt_tmp, t_datetime_to_posix_string, format_string, errno)
if (errno /= 0) then
call mtime_strerror(errno, error_str)
call create_error(opt_error, t_mtime_error(error_str))
end if
else
call datetimetostring(dt_tmp, t_datetime_to_posix_string)
end if
call deallocatedatetime(dt_tmp)
end function t_datetime_to_posix_string
! Assignment operator: this = "date string".
!
subroutine t_datetime_assign_string(this, dt_string)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment