forked from fortran-lang/stdlib
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathtest_logicalloc.f90
154 lines (114 loc) · 3.74 KB
/
test_logicalloc.f90
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
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
! SPDX-Identifier: MIT
module test_logicalloc
use stdlib_array, only : trueloc, falseloc
use stdlib_string_type, only : string_type, len
use testdrive, only : new_unittest, unittest_type, error_type, check
implicit none
private
public :: collect_logicalloc
contains
!> Collect all exported unit tests
subroutine collect_logicalloc(testsuite)
!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)
testsuite = [ &
new_unittest("trueloc-where", test_trueloc_where), &
new_unittest("trueloc-merge", test_trueloc_merge), &
new_unittest("falseloc-where", test_falseloc_where), &
new_unittest("falseloc-merge", test_falseloc_merge) &
]
end subroutine collect_logicalloc
subroutine test_trueloc_where(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
integer :: ndim
real, allocatable :: avec(:), bvec(:), cvec(:)
do ndim = 100, 12000, 100
allocate(avec(ndim))
call random_number(avec)
avec(:) = avec - 0.5
bvec = avec
bvec(trueloc(bvec > 0)) = 0.0
cvec = avec
where(cvec > 0) cvec = 0.0
call check(error, all(bvec == cvec))
deallocate(avec, bvec, cvec)
if (allocated(error)) exit
end do
end subroutine test_trueloc_where
subroutine test_trueloc_merge(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
integer :: ndim
real, allocatable :: avec(:), bvec(:), cvec(:)
do ndim = 100, 12000, 100
allocate(avec(ndim))
call random_number(avec)
avec(:) = avec - 0.5
bvec = avec
bvec(trueloc(bvec > 0)) = 0.0
cvec = avec
cvec(:) = merge(0.0, cvec, cvec > 0)
call check(error, all(bvec == cvec))
deallocate(avec, bvec, cvec)
if (allocated(error)) exit
end do
end subroutine test_trueloc_merge
subroutine test_falseloc_where(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
integer :: ndim
real, allocatable :: avec(:), bvec(:), cvec(:)
do ndim = 100, 12000, 100
allocate(avec(ndim))
call random_number(avec)
avec(:) = avec - 0.5
bvec = avec
bvec(falseloc(bvec > 0)) = 0.0
cvec = avec
where(.not.(cvec > 0)) cvec = 0.0
call check(error, all(bvec == cvec))
deallocate(avec, bvec, cvec)
if (allocated(error)) exit
end do
end subroutine test_falseloc_where
subroutine test_falseloc_merge(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
integer :: ndim
real, allocatable :: avec(:), bvec(:), cvec(:)
do ndim = 100, 12000, 100
allocate(avec(ndim))
call random_number(avec)
avec(:) = avec - 0.5
bvec = avec
bvec(falseloc(bvec > 0)) = 0.0
cvec = avec
cvec(:) = merge(cvec, 0.0, cvec > 0)
call check(error, all(bvec == cvec))
deallocate(avec, bvec, cvec)
if (allocated(error)) exit
end do
end subroutine test_falseloc_merge
end module test_logicalloc
program tester
use, intrinsic :: iso_fortran_env, only : error_unit
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
use test_logicalloc, only : collect_logicalloc
implicit none
integer :: stat, is
type(testsuite_type), allocatable :: testsuites(:)
character(len=*), parameter :: fmt = '("#", *(1x, a))'
stat = 0
testsuites = [ &
new_testsuite("logicalloc", collect_logicalloc) &
]
do is = 1, size(testsuites)
write(error_unit, fmt) "Testing:", testsuites(is)%name
call run_testsuite(testsuites(is)%collect, error_unit, stat)
end do
if (stat > 0) then
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
error stop
end if
end program