File: tests.f90

package info (click to toggle)
fortran-regex 1.1.2-1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 404 kB
  • sloc: f90: 1,355; makefile: 39
file content (134 lines) | stat: -rw-r--r-- 3,594 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
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
program tests
    use regex_module
    use regex_test_1
    use regex_test_2
    use regex_test_m_regex
    use iso_fortran_env, only: output_unit
    implicit none

    integer :: nfailed = 0
    integer :: npassed = 0

    integer :: i,length
    logical :: valid
    character(len=30) :: pattern,str


    ! Test #1
    do i=1,size(test1data,2)
       call get_test1(i,valid,pattern,str,length)
       call add_test(run_test1(valid,pattern,trim(str),length))
    end do

    ! Test m_regex
    do i=1,size(testMdata,2)
        call get_m_test(i,valid,pattern,str)
        call add_test(run_m_test(valid,trim(pattern),trim(str)))
    end do

    ! Test #3
    call add_test(test_invalid())
    call add_test(test_main())
    call add_test(test_bracket_space())
    call add_test(test_end_anchor())
    call add_test(test_end_anchor2())
    call add_test(test_read_version())

    ! Test #2
    call add_test(run_test2())

    if (nfailed<=0) then
        print "(*(a,:,i0))", 'SUCCESS! all ',npassed,' tests passed.'
        stop 0
    else
        print "(*(a,:,i0))", 'ERROR: ',nfailed,' tests failed, ',npassed,' passed.'
        stop 1
    end if


    contains

    subroutine add_test(successful_test)
        logical, intent(in) :: successful_test
        if (successful_test) then
            npassed = npassed+1
        else
            nfailed = nfailed+1
        end if
    end subroutine add_test

    ! Test two bug patterns reported by @DavidKorczynski in https://github.com/kokke/tiny-regex-c/issues/44
    logical function test_invalid() result(success)

       type(regex_pattern) :: re

       ! Test 1: inverted set without a closing ']'
       re = parse_pattern("\\\x01[^\\\xff][^")
       success = re%n==0; if (.not.success) return

       ! Test 1: inverted set without a closing ']'
       re = parse_pattern("\\\x01[^\\\xff][\\")
       success = re%n==0; if (.not.success) return

    end function test_invalid

    logical function test_main() result(success)
       use regex_module
       implicit none

       character(*), parameter :: text = 'table football'

       success = check_pattern(text,'foo*',expected="foo")
       if (.not.success) return

    end function test_main

    logical function test_bracket_space() result(success)
       use regex_module
       implicit none

       character(*), parameter :: text = 'table football'

       success = check_pattern(text,'e[ ]f',expected="e f")
       if (.not.success) return

       success = check_pattern(text,'e[ ]+f',expected="e f")
       if (.not.success) return


    end function test_bracket_space

    logical function test_end_anchor() result(success)
       use regex_module
       implicit none

       character(*), parameter :: text = 'table football'

       success = check_pattern(text,'ll$',expected="ll")
       if (.not.success) return

       success = check_pattern(text,'l$',expected="l")
       if (.not.success) return

    end function test_end_anchor

    logical function test_end_anchor2() result(success)
       use regex_module
       implicit none

       character(*), parameter :: text = 'Avida Dollar$'

       success = check_pattern(text,'[A-Z][a-z]+$',expected="")
       if (.not.success) return

    end function test_end_anchor2

    logical function test_read_version() result(success)
       character(*), parameter :: &
       text = 'Intel(R) MPI Library 2021.8 for Linux*Copyright Intel Corporation.ifort version 2021.8.0'

       success = check_pattern(text,'\d+\.\d+\.\d+',expected="2021.8.0")

    end function test_read_version

end program tests