Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions .github/workflows/ci_modular.yml
Original file line number Diff line number Diff line change
Expand Up @@ -56,8 +56,8 @@ jobs:
-DCMAKE_MAXIMUM_RANK:String=4
-DCMAKE_INSTALL_PREFIX=$PWD/_dist
-DFIND_BLAS:STRING=FALSE
-DSTDLIB_NO_BITSET:STRING=${{ matrix.with_bitset }}
-DSTDLIB_NO_STATS:STRING=${{ matrix.with_stats }}
-DSTDLIB_BITSET:STRING=${{ matrix.with_bitset }}
-DSTDLIB_STATS:STRING=${{ matrix.with_stats }}
-S . -B ${{ env.BUILD_DIR }}

- name: Build and compile
Expand Down
18 changes: 12 additions & 6 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -49,18 +49,24 @@ if(NOT DEFINED CMAKE_MAXIMUM_RANK)
set(CMAKE_MAXIMUM_RANK 4 CACHE STRING "Maximum array rank for generated procedures")
endif()

option(STDLIB_NO_BITSET "Does not compile STDLIB BITSET" OFF)
option(STDLIB_BITSET "Compile STDLIB BITSET" ON)

if(STDLIB_NO_BITSET)
if(STDLIB_BITSET)
message(STATUS "Enable stdlib bitset module")
add_compile_definitions(STDLIB_BITSET=1)
else()
message(STATUS "Disable stdlib bitset module")
add_compile_definitions(STDLIB_NO_BITSET)
add_compile_definitions(STDLIB_BITSET=0)
endif()

option(STDLIB_NO_STATS "Does not compile STDLIB STATS" OFF)
option(STDLIB_STATS "Compile STDLIB STATS" ON)

if(STDLIB_NO_STATS)
if(STDLIB_STATS)
message(STATUS "Enable stdlib stats module")
add_compile_definitions(STDLIB_STATS=1)
else()
message(STATUS "Disable stdlib stats module")
add_compile_definitions(STDLIB_NO_STATS)
add_compile_definitions(STDLIB_STATS=0)
endif()

option(FIND_BLAS "Find external BLAS and LAPACK" ON)
Expand Down
4 changes: 2 additions & 2 deletions example/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ endmacro(ADD_EXAMPLEPP)
add_subdirectory(ansi)
add_subdirectory(array)
add_subdirectory(ascii)
if (NOT STDLIB_NO_BITSET)
if (STDLIB_BITSET)
add_subdirectory(bitsets)
endif()
add_subdirectory(constants)
Expand All @@ -38,7 +38,7 @@ add_subdirectory(selection)
add_subdirectory(sorting)
add_subdirectory(specialfunctions_gamma)
add_subdirectory(specialmatrices)
if (NOT STDLIB_NO_STATS)
if (STDLIB_STATS)
add_subdirectory(stats)
add_subdirectory(stats_distribution_exponential)
add_subdirectory(stats_distribution_normal)
Expand Down
2 changes: 1 addition & 1 deletion example/sorting/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,6 @@ ADD_EXAMPLE(sort)
ADD_EXAMPLE(sort_adjoint)
ADD_EXAMPLE(sort_index)
ADD_EXAMPLE(radix_sort)
if (NOT STDLIB_NO_BITSET)
if (STDLIB_BITSET)
ADD_EXAMPLE(sort_bitset)
endif()
2 changes: 1 addition & 1 deletion include/common.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ $:"s" if cmplx=="c" else "d" if cmplx=="z" else "x" if cmplx=="y" else "q" if cm
#:set BITSET_INIT = ["" for k in BITSET_KINDS]

#! Bitset CPP directive to be considered during templating
#:set BITSET_CPPS = ["STDLIB_BITSET == 1" for k in BITSET_KINDS]
#:set BITSET_CPPS = ["STDLIB_BITSET" for k in BITSET_KINDS]

#! Collected (kind, type) tuples for bitset types
#:set BITSET_KINDS_TYPES = list(zip(BITSET_KINDS, BITSET_TYPES, BITSET_INIT, BITSET_CPPS))
Expand Down
8 changes: 2 additions & 6 deletions include/macros.inc
Original file line number Diff line number Diff line change
@@ -1,14 +1,10 @@

!Default: compile the bitset module
#ifdef STDLIB_NO_BITSET
#define STDLIB_BITSET 0
#else
#if !defined STDLIB_BITSET
#define STDLIB_BITSET 1
#endif

!Default: compile the stats module
#ifdef STDLIB_NO_STATS
#define STDLIB_STATS 0
#else
#if !defined STDLIB_STATS
#define STDLIB_STATS 1
#endif
10 changes: 5 additions & 5 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
if (NOT STDLIB_NO_BITSET)
if (STDLIB_BITSET)
add_subdirectory(bitsets)
endif()
add_subdirectory(blas)
add_subdirectory(lapack)
add_subdirectory(lapack_extended)
if (NOT STDLIB_NO_STATS)
if (STDLIB_STATS)
add_subdirectory(stats)
endif()

Expand Down Expand Up @@ -114,6 +114,6 @@ set(f90Files
configure_stdlib_target(${PROJECT_NAME} f90Files fppFiles cppFiles)

target_link_libraries(${PROJECT_NAME} PUBLIC
$<$<NOT:$<BOOL:${STDLIB_NO_BITSET}>>:bitsets>
$<$<NOT:$<BOOL:${STDLIB_NO_STATS}>>:stats>
blas lapack lapack_extended)
$<$<BOOL:${STDLIB_BITSET}>:bitsets>
$<$<BOOL:${STDLIB_STATS}>:stats>
blas lapack lapack_extended)
2 changes: 1 addition & 1 deletion src/stdlib_math.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
module stdlib_math
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
use stdlib_optval, only: optval
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
use stdlib_bitsets, only: bitset_64, bitset_large
#endif

Expand Down
2 changes: 1 addition & 1 deletion src/stdlib_sorting.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -135,7 +135,7 @@ module stdlib_sorting
use stdlib_string_type, only: string_type, assignment(=), operator(>), &
operator(>=), operator(<), operator(<=)

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
use stdlib_bitsets, only: bitset_64, bitset_large, &
assignment(=), operator(>), operator(>=), operator(<), operator(<=)
#endif
Expand Down
4 changes: 2 additions & 2 deletions test/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ endmacro(ADDTESTPP)

add_subdirectory(array)
add_subdirectory(ascii)
if (NOT STDLIB_NO_BITSET)
if (STDLIB_BITSET)
add_subdirectory(bitsets)
endif()
add_subdirectory(constants)
Expand All @@ -44,7 +44,7 @@ add_subdirectory(optval)
add_subdirectory(selection)
add_subdirectory(sorting)
add_subdirectory(specialfunctions)
if (NOT STDLIB_NO_STATS)
if (STDLIB_STATS)
add_subdirectory(stats)
endif()
add_subdirectory(string)
Expand Down
2 changes: 1 addition & 1 deletion test/math/test_stdlib_math.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -370,7 +370,7 @@ contains
if (allocated(error)) return
end subroutine test_swap_stt

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine test_swap_bitset_64(error)
use stdlib_bitsets
type(error_type), allocatable, intent(out) :: error
Expand Down
34 changes: 17 additions & 17 deletions test/sorting/test_sorting.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module test_sorting
use stdlib_sorting, only: sort, sort_index, sort_adjoint, ord_sort, radix_sort, int_index, int_index_low
use stdlib_string_type, only: string_type, assignment(=), operator(>), &
operator(<), write(formatted)
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
use stdlib_bitsets, only: bitset_64, bitset_large, &
assignment(=), operator(>), operator(<)
#endif
Expand All @@ -25,7 +25,7 @@ module test_sorting
integer(int32), parameter :: test_size = 2_int32**test_power
integer(int32), parameter :: char_size = char_set_size**4
integer(int32), parameter :: string_size = char_set_size**3
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
integer(int32), parameter :: bitset_size = char_set_size**3
#endif
integer(int32), parameter :: block_size = test_size/6
Expand All @@ -50,7 +50,7 @@ module test_sorting
string_decrease(0:string_size-1), &
string_increase(0:string_size-1), &
string_rand(0:string_size-1)
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
type(bitset_large) :: &
bitsetl_decrease(0:bitset_size-1), &
bitsetl_increase(0:bitset_size-1), &
Expand All @@ -65,7 +65,7 @@ module test_sorting
real(sp) :: real_dummy(0:test_size-1)
character(len=4) :: char_dummy(0:char_size-1)
type(string_type) :: string_dummy(0:string_size-1)
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
type(bitset_large) :: bitsetl_dummy(0:bitset_size-1)
type(bitset_64) :: bitset64_dummy(0:bitset_size-1)
#endif
Expand All @@ -74,7 +74,7 @@ module test_sorting
integer(int32) :: work(0:test_size/2-1)
character(len=4) :: char_work(0:char_size/2-1)
type(string_type) :: string_work(0:string_size/2-1)
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
type(bitset_large) :: bitsetl_work(0:bitset_size/2-1)
type(bitset_64) :: bitset64_work(0:bitset_size/2-1)
#endif
Expand All @@ -88,7 +88,7 @@ module test_sorting
integer :: lun
character(len=4) :: char_temp
type(string_type) :: string_temp
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
type(bitset_large) :: bitsetl_temp
type(bitset_64) :: bitset64_temp
#endif
Expand All @@ -106,7 +106,7 @@ contains
testsuite = [ &
new_unittest('char_ord_sorts', test_char_ord_sorts), &
new_unittest('string_ord_sorts', test_string_ord_sorts), &
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
new_unittest('bitset_large_ord_sorts', test_bitsetl_ord_sorts), &
new_unittest('bitset_64_ord_sorts', test_bitset64_ord_sorts), &
#endif
Expand All @@ -115,15 +115,15 @@ contains
new_unittest('int_sorts', test_int_sorts), &
new_unittest('char_sorts', test_char_sorts), &
new_unittest('string_sorts', test_string_sorts), &
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
new_unittest('bitset_large_sorts', test_bitsetl_sorts), &
new_unittest('bitset_64_sorts', test_bitset64_sorts), &
#endif
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
new_unittest('int_sort_indexes_${namei}$', test_int_sort_indexes_${namei}$), &
new_unittest('char_sort_indexes_${namei}$', test_char_sort_indexes_${namei}$), &
new_unittest('string_sort_indexes_${namei}$', test_string_sort_indexes_${namei}$), &
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
new_unittest('bitset_large_sort_indexes_${namei}$', test_bitsetl_sort_indexes_${namei}$), &
new_unittest('bitset_64_sort_indexes_${namei}$', test_bitset64_sort_indexes_${namei}$), &
#endif
Expand All @@ -132,7 +132,7 @@ contains
new_unittest('int_sort_adjointes_${namei}$', test_int_sort_adjointes_${namei}$), &
new_unittest('char_sort_adjointes_${namei}$', test_char_sort_adjointes_${namei}$), &
new_unittest('string_sort_adjointes_${namei}$', test_string_sort_adjointes_${namei}$), &
#if STDLIB_BITSET == 1
#if STDLIB_BITSET
new_unittest('bitset_large_sort_adjointes_${namei}$', test_bitsetl_sort_adjointes_${namei}$), &
new_unittest('bitset_64_sort_adjointes_${namei}$', test_bitset64_sort_adjointes_${namei}$), &
#endif
Expand Down Expand Up @@ -240,7 +240,7 @@ contains
string_rand(index1) = string_temp
end do

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
do i = 0, bitset_size-1
write(bin32,'(b32.32)') i
call bitsetl_increase(i)%from_string(bin32)
Expand Down Expand Up @@ -556,7 +556,7 @@ contains

end subroutine test_string_ord_sort

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine test_bitsetl_ord_sorts(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -1113,7 +1113,7 @@ contains

end subroutine test_string_sort

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine test_bitsetl_sorts(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -1467,7 +1467,7 @@ contains

end subroutine test_string_sort_index_${namei}$

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine test_bitsetl_sort_indexes_${namei}$(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -1807,7 +1807,7 @@ contains

end subroutine test_string_sort_adjoint_${namei}$

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine test_bitsetl_sort_adjointes_${namei}$(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -2108,7 +2108,7 @@ contains

end subroutine verify_string_sort

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine verify_bitsetl_sort( a, valid, i )
type(bitset_large), intent(in) :: a(0:)
logical, intent(out) :: valid
Expand Down Expand Up @@ -2222,7 +2222,7 @@ contains

end subroutine verify_string_reverse_sort

#if STDLIB_BITSET == 1
#if STDLIB_BITSET
subroutine verify_bitsetl_reverse_sort( a, valid, i )
type(bitset_large), intent(in) :: a(0:)
logical, intent(out) :: valid
Expand Down
Loading