File: modules_47.f90

package info (click to toggle)
lfortran 0.58.0-4
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 54,512 kB
  • sloc: cpp: 162,179; f90: 68,251; python: 17,476; ansic: 6,278; yacc: 2,334; sh: 1,317; fortran: 892; makefile: 33; javascript: 15
file content (53 lines) | stat: -rw-r--r-- 1,394 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
module modules_47_tomlf_datetime
implicit none

    public :: toml_time

    type :: toml_time
        integer :: hour = 0
        integer :: minute = 0
        integer :: second = 0
        integer, allocatable :: millisec
        character(len=:), allocatable :: zone
    end type

contains

subroutine time_to_string(lhs, rhs)
    character(len=:), allocatable, intent(out) :: lhs
    class(toml_time), intent(in) :: rhs
    if (allocated(rhs%millisec)) then
        allocate(character(len=12) :: lhs)
        write(lhs, '(i2.2,":",i2.2,":",i2.2,".",i3.3)') &
            &  rhs%hour, rhs%minute, rhs%second, rhs%millisec
    else
        allocate(character(len=8) :: lhs)
        write(lhs, '(i2.2,":",i2.2,":",i2.2)') &
            &  rhs%hour, rhs%minute, rhs%second
    end if
    if (allocated(rhs%zone)) lhs = lhs // trim(rhs%zone)
end subroutine time_to_string

end module modules_47_tomlf_datetime

program modules_47
use modules_47_tomlf_datetime
implicit none

character(len=:), allocatable :: lhs
type(toml_time) :: rhs

if( allocated(rhs%millisec) ) error stop
allocate(rhs%millisec)
rhs%millisec = 100
print *, rhs%millisec, allocated(rhs%millisec)
if( rhs%hour /= 0 ) error stop
if( rhs%minute /= 0 ) error stop
if( rhs%second /= 0 ) error stop
if( rhs%millisec /= 100 ) error stop

call time_to_string(lhs, rhs)
print *, lhs
if( .not. allocated(lhs) ) error stop

end program