From e9028231d1e7e9151a9c8a3bb4612f67affeb5c1 Mon Sep 17 00:00:00 2001 From: zoziha13 <1325686572@qq.com> Date: Fri, 30 Jul 2021 19:30:18 +0800 Subject: [PATCH 1/3] Add empty function. --- doc/specs/stdlib_linalg.md | 54 +++++++++++++++++++++++ src/stdlib_linalg.fypp | 30 ++++++++++++- src/tests/Makefile.manual | 1 + src/tests/linalg/CMakeLists.txt | 1 + src/tests/linalg/Makefile.manual | 4 ++ src/tests/linalg/test_linalg_empty.f90 | 59 ++++++++++++++++++++++++++ 6 files changed, 148 insertions(+), 1 deletion(-) create mode 100644 src/tests/linalg/Makefile.manual create mode 100644 src/tests/linalg/test_linalg_empty.f90 diff --git a/doc/specs/stdlib_linalg.md b/doc/specs/stdlib_linalg.md index cab16279c..d72357a44 100644 --- a/doc/specs/stdlib_linalg.md +++ b/doc/specs/stdlib_linalg.md @@ -206,3 +206,57 @@ program demo_outer_product !A = reshape([3., 6., 9., 4., 8., 12.], [3,2]) end program demo_outer_product ``` + +## `empty` - `empty` creates a new vector or matrix of `integer` type and given shape, without initializing values. + +### Status + +Experimental + +### Class + +Pure function. + +### Description + +`empty` creates a new vector or matrix of `integer` type and given shape, without initializing values. + +`empty`, unlike `zeros`, does not set the array values to zero, and may therefore be marginally faster. On the other hand, it requires the user to manually set all the values in the array, and should be used with caution. + +### Syntax + +For vector: +`result = [[stdlib_linalg(module):empty(interface)]](dim)` + +For matrix: +`result = [[stdlib_linalg(module):empty(interface)]](dim1, dim2)` + +### Arguments + +`dim/dim1`: Shall be an `integer` type. + +`dim2`: Shall be an `integer` type. + +### Return value + +Returns a new vector or matrix of `integer` type and given shape, without initializing values. + +### Example + +```fortran +program demo_linlag_empty + + use stdlib_linlag, only: empty + implicit none + integer, allocatable :: i(:,:) + + print *, empty(2, 1) + print *, 0.0*empty(2) !! 0.00000000 0.00000000 + print *, empty(2) + empty(2) + print *, (0.1, 0.1)*empty(2) + (0.2, 0.2)*empty(2) + + i = empty(2,2) + print *, i + +end program demo_linalg_empty +``` \ No newline at end of file diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp index 5e0388c0b..3473103d5 100644 --- a/src/stdlib_linalg.fypp +++ b/src/stdlib_linalg.fypp @@ -9,6 +9,7 @@ module stdlib_linalg private public :: diag + public :: empty public :: eye public :: trace public :: outer_product @@ -53,6 +54,14 @@ module stdlib_linalg #:endfor end interface + !> Version: experimental + !> + !> `empty` creates a new vector or matrix of `integer` type and given shape, + !> without initializing values. + interface empty + procedure :: empty_1_default, empty_2_default + end interface empty + ! Matrix trace interface trace @@ -108,4 +117,23 @@ contains end do end function trace_${t1[0]}$${k1}$ #:endfor -end module + + !> `empty` creates an empty vector with `integer` type. + pure function empty_1_default(dim) result(result) + + implicit none + integer, intent(in) :: dim + integer :: result(dim) + + end function empty_1_default + + !> `empty` creates an empty matrix with `integer` type. + pure function empty_2_default(dim1, dim2) result(result) + + implicit none + integer, intent(in) :: dim1, dim2 + integer :: result(dim1, dim2) + + end function empty_2_default + +end module stdlib_linalg diff --git a/src/tests/Makefile.manual b/src/tests/Makefile.manual index 7ab184016..c29170e24 100644 --- a/src/tests/Makefile.manual +++ b/src/tests/Makefile.manual @@ -11,3 +11,4 @@ all test clean: $(MAKE) -f Makefile.manual --directory=stats $@ $(MAKE) -f Makefile.manual --directory=string $@ $(MAKE) -f Makefile.manual --directory=math $@ + $(MAKE) -f Makefile.manual --directory=linalg $@ diff --git a/src/tests/linalg/CMakeLists.txt b/src/tests/linalg/CMakeLists.txt index f1098405b..89c4f98b4 100644 --- a/src/tests/linalg/CMakeLists.txt +++ b/src/tests/linalg/CMakeLists.txt @@ -1,2 +1,3 @@ ADDTEST(linalg) +ADDTEST(linalg_empty) diff --git a/src/tests/linalg/Makefile.manual b/src/tests/linalg/Makefile.manual new file mode 100644 index 000000000..b3311eca5 --- /dev/null +++ b/src/tests/linalg/Makefile.manual @@ -0,0 +1,4 @@ +PROGS_SRC = test_linalg_empty.f90 + + +include ../Makefile.manual.test.mk \ No newline at end of file diff --git a/src/tests/linalg/test_linalg_empty.f90 b/src/tests/linalg/test_linalg_empty.f90 new file mode 100644 index 000000000..053ca4260 --- /dev/null +++ b/src/tests/linalg/test_linalg_empty.f90 @@ -0,0 +1,59 @@ +! SPDX-Identifier: MIT +module test_linalg_empty + + use stdlib_error, only: check + use stdlib_linalg, only: empty + use stdlib_ascii, only: to_string + implicit none + +contains + + subroutine check_shape(actual, expected, description) + integer, intent(in) :: actual, expected + character(len=*), intent(in) :: description + logical :: stat + character(len=:), allocatable :: msg + + if (actual /= expected) then + msg = description//new_line("a")// & + & "Expected: '"//to_string(expected)//"' but got '"//to_string(actual)//"'" + stat = .false. + else + print '(" - ", a, /, " Result: ''", a, "''")', description, to_string(actual) + stat = .true. + end if + + call check(stat, msg) + + end subroutine check_shape + + subroutine test_linalg_empty_integer + call check_shape(size(empty(2)), 2, "test_linalg_empty_integer, vector:") + call check_shape(size(empty(1,2)), 2, "test_linalg_empty_integer, matrix:") + end subroutine test_linalg_empty_integer + + subroutine test_linalg_empty_real + call check_shape(size(0.0*empty(2)), 2, "test_linalg_empty_real, vector:") + call check_shape(size(0.0*empty(1,2)), 2, "test_linalg_empty_real, matrix:") + end subroutine test_linalg_empty_real + + subroutine test_linalg_empty_cmplx + call check_shape(size((0.0,0.0)*empty(2)), 2, "test_linalg_empty_cmplx, vector:") + call check_shape(size((0.0,0.0)*empty(1,2)), 2, "test_linalg_empty_cmplx, matrix:") + end subroutine test_linalg_empty_cmplx + +end module test_linalg_empty + +program tester + + use test_linalg_empty + + call test_linalg_empty_integer + call test_linalg_empty_real + call test_linalg_empty_cmplx + + print *, empty(2) + empty(3), size(empty(2) + empty(3)) + !!TODO: ?? + !! 44 0 3? / 2? + +end program tester From d2296a769e386dd8f1f4745a3d9095a62bd2fb50 Mon Sep 17 00:00:00 2001 From: zoziha13 <1325686572@qq.com> Date: Tue, 3 Aug 2021 10:43:18 +0800 Subject: [PATCH 2/3] Update empty function: 1. automatic array -> allocatable array. 2. add `empty` tests for `real/complex` type. --- doc/specs/stdlib_linalg.md | 44 ++++++++++++++++++++----- src/stdlib_linalg.fypp | 10 +++--- src/tests/linalg/test_linalg_empty.f90 | 45 +++++++++----------------- 3 files changed, 56 insertions(+), 43 deletions(-) diff --git a/doc/specs/stdlib_linalg.md b/doc/specs/stdlib_linalg.md index d72357a44..7f29dd1f7 100644 --- a/doc/specs/stdlib_linalg.md +++ b/doc/specs/stdlib_linalg.md @@ -207,7 +207,7 @@ program demo_outer_product end program demo_outer_product ``` -## `empty` - `empty` creates a new vector or matrix of `integer` type and given shape, without initializing values. +## `empty` - Create a new vector or matrix of `integer/real/complex` type and given shape, without initializing values. ### Status @@ -219,7 +219,7 @@ Pure function. ### Description -`empty` creates a new vector or matrix of `integer` type and given shape, without initializing values. +`empty` creates a new vector or matrix of `integer/real/complex` type and given shape, without initializing values. `empty`, unlike `zeros`, does not set the array values to zero, and may therefore be marginally faster. On the other hand, it requires the user to manually set all the values in the array, and should be used with caution. @@ -233,18 +233,27 @@ For matrix: ### Arguments -`dim/dim1`: Shall be an `integer` type. +`dim/dim1`: Shall be an `integer` scalar. +This is an `intent(in)` argument. -`dim2`: Shall be an `integer` type. +`dim2`: Shall be an `integer` scalar. +This is an `intent(in)` argument. + +#### Note + +Because of `huge(integer :: i) == 2147483647`, the dimensional maximum length of array created by the `empty` function is `2147483647`. ### Return value -Returns a new vector or matrix of `integer` type and given shape, without initializing values. +Returns a new `vector` or `matrix` of `integer` type and given shape, without initializing values. + +#### Note +If the receiving `array` of the return value of the `empty` function is of a `real/complex` type, conversion from `integer` type to `real/complex` type will occur. ### Example ```fortran -program demo_linlag_empty +program demo_linlag_empty_1 use stdlib_linlag, only: empty implicit none @@ -252,11 +261,30 @@ program demo_linlag_empty print *, empty(2, 1) print *, 0.0*empty(2) !! 0.00000000 0.00000000 - print *, empty(2) + empty(2) + print *, 0.0*empty(2) + 1.0*empty(2) print *, (0.1, 0.1)*empty(2) + (0.2, 0.2)*empty(2) i = empty(2,2) print *, i -end program demo_linalg_empty +end program demo_linalg_empty_1 +``` + +```fortran +program demo_linlag_empty_2 + + use stdlib_linlag, only: empty + implicit none + integer, allocatable :: i(:,:) + real, allocatable :: r(:,:) + complex, allocatable :: c(:,:) + integer :: j(2) + + i = empty(2,1) + r = empty(2,1) + c = empty(2,1) + j = empty(2) + print *, i, r, c, j + +end program demo_linalg_empty_2 ``` \ No newline at end of file diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp index 3473103d5..a732fc7df 100644 --- a/src/stdlib_linalg.fypp +++ b/src/stdlib_linalg.fypp @@ -121,19 +121,19 @@ contains !> `empty` creates an empty vector with `integer` type. pure function empty_1_default(dim) result(result) - implicit none integer, intent(in) :: dim - integer :: result(dim) + integer, allocatable :: result(:) + allocate(result(dim)) end function empty_1_default !> `empty` creates an empty matrix with `integer` type. pure function empty_2_default(dim1, dim2) result(result) - implicit none integer, intent(in) :: dim1, dim2 - integer :: result(dim1, dim2) - + integer, allocatable :: result(:, :) + allocate(result(dim1, dim2)) + end function empty_2_default end module stdlib_linalg diff --git a/src/tests/linalg/test_linalg_empty.f90 b/src/tests/linalg/test_linalg_empty.f90 index 053ca4260..177b91f9b 100644 --- a/src/tests/linalg/test_linalg_empty.f90 +++ b/src/tests/linalg/test_linalg_empty.f90 @@ -3,43 +3,30 @@ module test_linalg_empty use stdlib_error, only: check use stdlib_linalg, only: empty - use stdlib_ascii, only: to_string implicit none - -contains - - subroutine check_shape(actual, expected, description) - integer, intent(in) :: actual, expected - character(len=*), intent(in) :: description - logical :: stat - character(len=:), allocatable :: msg - - if (actual /= expected) then - msg = description//new_line("a")// & - & "Expected: '"//to_string(expected)//"' but got '"//to_string(actual)//"'" - stat = .false. - else - print '(" - ", a, /, " Result: ''", a, "''")', description, to_string(actual) - stat = .true. - end if + logical :: warn = .false. - call check(stat, msg) - - end subroutine check_shape +contains subroutine test_linalg_empty_integer - call check_shape(size(empty(2)), 2, "test_linalg_empty_integer, vector:") - call check_shape(size(empty(1,2)), 2, "test_linalg_empty_integer, matrix:") + call check(size(empty(2)) == 2, msg="size(empty(2)) == 2 failed", warn=warn) + call check(size(empty(1, 2)) == 2, msg="size(empty(1,2)) == 2 failed", warn=warn) end subroutine test_linalg_empty_integer subroutine test_linalg_empty_real - call check_shape(size(0.0*empty(2)), 2, "test_linalg_empty_real, vector:") - call check_shape(size(0.0*empty(1,2)), 2, "test_linalg_empty_real, matrix:") + real, allocatable :: rA(:), rB(:, :) + rA = empty(2) + call check(size(rA) == 2, msg="size(rA) == 2 failed.", warn=warn) + rB = empty(1, 2) + call check(size(rB) == 2, msg="size(rB) == 2 failed.", warn=warn) end subroutine test_linalg_empty_real subroutine test_linalg_empty_cmplx - call check_shape(size((0.0,0.0)*empty(2)), 2, "test_linalg_empty_cmplx, vector:") - call check_shape(size((0.0,0.0)*empty(1,2)), 2, "test_linalg_empty_cmplx, matrix:") + complex, allocatable :: cA(:), cB(:, :) + cA = empty(2) + call check(size(cA) == 2, msg="size(cA) == 2 failed.", warn=warn) + cB = empty(1, 2) + call check(size(cB) == 2, msg="size(cB) == 2 failed.", warn=warn) end subroutine test_linalg_empty_cmplx end module test_linalg_empty @@ -52,8 +39,6 @@ program tester call test_linalg_empty_real call test_linalg_empty_cmplx - print *, empty(2) + empty(3), size(empty(2) + empty(3)) - !!TODO: ?? - !! 44 0 3? / 2? + print *, "All tests in `test_linalg_empty` passed." end program tester From d57e3869677f8a211e52573c41d7cab26beb8515 Mon Sep 17 00:00:00 2001 From: zoziha13 <1325686572@qq.com> Date: Wed, 11 Aug 2021 10:04:46 +0800 Subject: [PATCH 3/3] Improve `empty` func. --- doc/specs/stdlib_linalg.md | 26 +++++++++++--------------- src/stdlib_linalg.fypp | 11 ++++++----- 2 files changed, 17 insertions(+), 20 deletions(-) diff --git a/doc/specs/stdlib_linalg.md b/doc/specs/stdlib_linalg.md index 7f29dd1f7..b99c11fad 100644 --- a/doc/specs/stdlib_linalg.md +++ b/doc/specs/stdlib_linalg.md @@ -207,7 +207,13 @@ program demo_outer_product end program demo_outer_product ``` -## `empty` - Create a new vector or matrix of `integer/real/complex` type and given shape, without initializing values. +## `empty` + +### Description + +`empty` creates a new rank-1 or rank-2 `array` of `integer/real/complex` type and given shape, without initializing values. + +`empty`, unlike `zeros`, does not set the array values to zero, and may therefore be marginally faster. On the other hand, it requires the user to manually set all the values in the array, and should be used with caution. ### Status @@ -217,18 +223,12 @@ Experimental Pure function. -### Description - -`empty` creates a new vector or matrix of `integer/real/complex` type and given shape, without initializing values. - -`empty`, unlike `zeros`, does not set the array values to zero, and may therefore be marginally faster. On the other hand, it requires the user to manually set all the values in the array, and should be used with caution. - ### Syntax -For vector: +For rank-1 `array`: `result = [[stdlib_linalg(module):empty(interface)]](dim)` -For matrix: +For rank-2 `array`: `result = [[stdlib_linalg(module):empty(interface)]](dim1, dim2)` ### Arguments @@ -239,13 +239,9 @@ This is an `intent(in)` argument. `dim2`: Shall be an `integer` scalar. This is an `intent(in)` argument. -#### Note - -Because of `huge(integer :: i) == 2147483647`, the dimensional maximum length of array created by the `empty` function is `2147483647`. - ### Return value -Returns a new `vector` or `matrix` of `integer` type and given shape, without initializing values. +Returns a new rank-1 or rank-2 `array` of `integer` type and given shape, without initializing values. #### Note If the receiving `array` of the return value of the `empty` function is of a `real/complex` type, conversion from `integer` type to `real/complex` type will occur. @@ -265,7 +261,7 @@ program demo_linlag_empty_1 print *, (0.1, 0.1)*empty(2) + (0.2, 0.2)*empty(2) i = empty(2,2) - print *, i + print *, reshape(empty(2*3*4),[2,3,4]) end program demo_linalg_empty_1 ``` diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp index a732fc7df..fecea546b 100644 --- a/src/stdlib_linalg.fypp +++ b/src/stdlib_linalg.fypp @@ -56,8 +56,9 @@ module stdlib_linalg !> Version: experimental !> - !> `empty` creates a new vector or matrix of `integer` type and given shape, + !> `empty` creates a new rank-1 or rank-2 `array` of `integer` type and given shape, !> without initializing values. + !> ([Specification](../page/specs/stdlib_linalg.html#empty)) interface empty procedure :: empty_1_default, empty_2_default end interface empty @@ -118,20 +119,20 @@ contains end function trace_${t1[0]}$${k1}$ #:endfor - !> `empty` creates an empty vector with `integer` type. + !> `empty` creates an empty rank-1 `array` of `integer` type. pure function empty_1_default(dim) result(result) - integer, intent(in) :: dim integer, allocatable :: result(:) + allocate(result(dim)) end function empty_1_default - !> `empty` creates an empty matrix with `integer` type. + !> `empty` creates an empty rank-2 `array` of `integer` type. pure function empty_2_default(dim1, dim2) result(result) - integer, intent(in) :: dim1, dim2 integer, allocatable :: result(:, :) + allocate(result(dim1, dim2)) end function empty_2_default