File: elemental_function_overloaded_compare.f90

package info (click to toggle)
lfortran 0.45.0-1
  • links: PTS, VCS
  • area: main
  • in suites: sid, trixie
  • size: 46,332 kB
  • sloc: cpp: 137,068; f90: 51,260; python: 6,444; ansic: 4,277; yacc: 2,285; fortran: 806; sh: 524; makefile: 30; javascript: 15
file content (55 lines) | stat: -rw-r--r-- 1,880 bytes parent folder | download
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
54
55
! program extracted as MRE from https://github.com/fortran-lang/stdlib
! there is missing implementation of functions/subroutines like
! check_logical, eq_string_char, new_string_from_integer_int32 etc.
! but as that's not need to be able to compile and run the MRE,
! that's being skipped for now, actually we tried having their implementation
! as well, but the program failed to run (take that as a TODO)
module mod_elemental_function_overloaded_compare
    use iso_fortran_env, only: int32
    implicit none
    !> String type holding an arbitrary sequence of characters.

    interface operator(==)
        module procedure :: eq_string_char
    end interface operator(==)

    type :: string_type
        sequence
        private
        character(len=:), allocatable :: raw
    end type string_type

    contains

    subroutine check_logical(expression)
        logical, intent(in) :: expression
        if (.not. expression) then
            print *, "Condition not fulfilled"
        end if
    end subroutine check_logical

    elemental function eq_string_char(lhs, rhs) result(is_eq)
        type(string_type), intent(in) :: lhs
        character(len=*), intent(in) :: rhs
        logical :: is_eq
    end function eq_string_char

    elemental module function new_string_from_integer_int32(val) result(new)
        integer(int32), intent(in) :: val
        type(string_type) :: new
    end function new_string_from_integer_int32

    subroutine test_constructor()
        character(len=128) :: flc

        write(flc, '(i0)') -1026191
        call check_logical(new_string_from_integer_int32(-1026191) == trim(flc))
    end subroutine test_constructor

end module mod_elemental_function_overloaded_compare

program test_elemental_function_overloaded_compare
    use mod_elemental_function_overloaded_compare
    implicit none
    call test_constructor()
end program