Skip to content

Commit abf10c6

Browse files
committed
Implemented changes suggested by Jeremie
Made various changes: * in stdlib_sorting.fypp changed "public :: int_size ... integer, parameter :: in_size..." to "integer, parameter, public :: int_size ..." * Eliminated the specific procedures public in stdlib_sorting.fypp and their discussion in stdlib_sorting.md. * replaced specific reference to INT_KINDS and REAL_KINDS in stdlib_sorting_sort.fypp, stdlib_sorting_ord_sort.fypp, and stdlib_sorting_sort_index.fypp with reference to common.fypp. * in stdlib_sorting_ord_sort.fypp made ERROR STOP return the procedure name in which the allocation error occured. [ticket: X]
1 parent e6a376f commit abf10c6

5 files changed

+8
-103
lines changed

doc/specs/stdlib_sorting.md

-39
Original file line numberDiff line numberDiff line change
@@ -479,45 +479,6 @@ Sorting an array of a derived type based on the data in one component
479479
end subroutine sort_a_data
480480
```
481481

482-
#### Specific procedures
483-
484-
Usually the name of a generic procedure is the most convenient way of
485-
invoking it. However sometimes it is necessary to pass a procedure as
486-
an argument to another procedure. In that case it is usually necessary
487-
to know the name of the specific procedure desired. The following
488-
table lists the specific subroutines and the corresponding types of
489-
their `array` arguments.
490-
491-
| Generic Subroutine | Specific Subroutine | Array type |
492-
|--------------------|---------------------|-----------------|
493-
| `ORD_SORT` | `INT8_ORD_SORT` | `INTEGER(INT8)` |
494-
| | `INT16_ORD_SORT` | `INTEGER(INT16)` |
495-
| | `INT32_ORD_SORT` | `INTEGER(INT32)` |
496-
| | `INT64_ORD_SORT` | `INTEGER(INT64)` |
497-
| | `SP_ORD_SORT` | `REAL(SP)` |
498-
| | `DP_ORD_SORT` | `REAL(DP)` |
499-
| | `QP_ORD_SORT` | `REAL(QP)` |
500-
| | `CHAR_ORD_SORT` | `CHARACTER(*)` |
501-
| | `STRING_ORD_SORT` | `STRING_TYPE` |
502-
| `SORT` | `INT8_SORT` | `INTEGER(INT8)` |
503-
| | `INT16_SORT` | `INTEGER(INT16)` |
504-
| | `INT32_SORT` | `INTEGER(INT32)` |
505-
| | `INT64_SORT` | `INTEGER(INT64)` |
506-
| | `SP_SORT` | `REAL(SP)` |
507-
| | `DP_SORT` | `REAL(DP)` |
508-
| | `QP_SORT` | `REAL(QP)` |
509-
| | `CHAR_SORT` | `CHARACTER(*)` |
510-
| | `STRING_SORT` | `STRING_TYPE` |
511-
| `SORT_INDEX` | `INT8_SORT_INDEX` | `INTEGER(INT8)` |
512-
| | `INT16_SORT_INDEX` | `INTEGER(INT16)` |
513-
| | `INT32_SORT_INDEX` | `INTEGER(INT32)` |
514-
| | `INT64_SORT_INDEX` | `INTEGER(INT64)` |
515-
| | `SP_SORT_INDEX` | `REAL(SP)` |
516-
| | `DP_SORT_INDEX` | `REAL(DP)` |
517-
| | `QP_SORT_INDEX` | `REAL(QP)` |
518-
| | `CHAR_SORT_INDEX` | `CHARACTER(*)` |
519-
| | `STRING_SORT_INDEX` | `STRING_TYPE` |
520-
521482

522483
### Performance benchmarks
523484

src/stdlib_sorting.fypp

+1-45
Original file line numberDiff line numberDiff line change
@@ -115,9 +115,7 @@ module stdlib_sorting
115115
implicit none
116116
private
117117

118-
public :: int_size
119-
120-
integer, parameter :: int_size = int64 !! Integer kind for indexing
118+
integer, parameter, public :: int_size = int64 !! Integer kind for indexing
121119

122120
! Constants for use by tim_sort
123121
integer, parameter :: &
@@ -322,48 +320,6 @@ module stdlib_sorting
322320
!! end subroutine sort_a_data
323321
!!```
324322

325-
#:for k1 in INT_KINDS
326-
public ${k1}$_ord_sort
327-
!! Version: experimental
328-
!!
329-
!! `${k1}$_ord_sort` is the specific `ORD_SORT` subroutine for an `array`
330-
!! argument of type `integer(${k1}$)`.
331-
332-
public ${k1}$_sort
333-
!! Version: experimental
334-
!!
335-
!! `${k1}$_sort` is the specific `SORT` subroutine for an `array`
336-
!! argument of type `integer(${k1}$)`.
337-
338-
public ${k1}$_sort_index
339-
!! Version: experimental
340-
!!
341-
!! `${k1}$_sort_index` is the specific `SORT_INDEX` subroutine for an `array`
342-
!! argument of type `integer(${k1}$)`.
343-
344-
#:endfor
345-
346-
#:for k1 in REAL_KINDS
347-
public ${k1}$_ord_sort
348-
!! Version: experimental
349-
!!
350-
!! `${k1}$_ord_sort` is the specific `ORD_SORT` subroutine for an `array`
351-
!! argument of type `real(${k1}$)`.
352-
353-
public ${k1}$_sort
354-
!! Version: experimental
355-
!!
356-
!! `${k1}$_sort` is the specific `SORT` subroutine for an `array`
357-
!! argument of type `real(${k1}$)`.
358-
359-
public ${k1}$_sort_index
360-
!! Version: experimental
361-
!!
362-
!! `${k1}$_sort_index` is the specific `SORT_INDEX` subroutine for an `array`
363-
!! argument of type `real(${k1}$)`.
364-
365-
#:endfor
366-
367323
public char_ord_sort
368324

369325
public char_sort

src/stdlib_sorting_ord_sort.fypp

+5-9
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,4 @@
1-
#! Integer kinds to be considered during templating
2-
#:set INT_KINDS = ["int8", "int16", "int32", "int64"]
3-
4-
#! Real kinds to be considered during templating
5-
#:set REAL_KINDS = ["sp", "dp", "qp"]
1+
#:include "common.fypp"
62

73
!! Licensing:
84
!!
@@ -95,7 +91,7 @@ contains
9591
! Allocate a buffer to use as scratch memory.
9692
array_size = size( array, kind=int_size )
9793
allocate( buf(0:array_size/2-1), stat=stat )
98-
if ( stat /= 0 ) error stop "Allocation of buffer failed."
94+
if ( stat /= 0 ) error stop "${k1}$_ord_sort: Allocation of buffer failed."
9995
call merge_sort( array, buf )
10096
end if
10197

@@ -436,7 +432,7 @@ contains
436432
! Allocate a buffer to use as scratch memory.
437433
array_size = size( array, kind=int_size )
438434
allocate( buf(0:array_size/2-1), stat=stat )
439-
if ( stat /= 0 ) error stop "Allocation of buffer failed."
435+
if ( stat /= 0 ) error stop "${k1}$_ord_sort: Allocation of buffer failed."
440436
call merge_sort( array, buf )
441437
end if
442438

@@ -776,7 +772,7 @@ contains
776772
array_size = size( array, kind=int_size )
777773
allocate( character(len=len(array)) :: buf(0:array_size/2-1), &
778774
stat=stat )
779-
if ( stat /= 0 ) error stop "Allocation of buffer failed."
775+
if ( stat /= 0 ) error stop "${k1}$_ord_sort: Allocation of buffer failed."
780776
call merge_sort( array, buf )
781777
end if
782778

@@ -1113,7 +1109,7 @@ contains
11131109
! Allocate a buffer to use as scratch memory.
11141110
array_size = size( array, kind=int_size )
11151111
allocate( buf(0:array_size/2-1), stat=stat )
1116-
if ( stat /= 0 ) error stop "Allocation of buffer failed."
1112+
if ( stat /= 0 ) error stop "${k1}$_ord_sort: Allocation of buffer failed."
11171113
call merge_sort( array, buf )
11181114
end if
11191115

src/stdlib_sorting_sort.fypp

+1-5
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,4 @@
1-
#! Integer kinds to be considered during templating
2-
#:set INT_KINDS = ["int8", "int16", "int32", "int64"]
3-
4-
#! Real kinds to be considered during templating
5-
#:set REAL_KINDS = ["sp", "dp", "qp"]
1+
#:include "common.fypp"
62

73
!! Licensing:
84
!!

src/stdlib_sorting_sort_index.fypp

+1-5
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,4 @@
1-
#! Integer kinds to be considered during templating
2-
#:set INT_KINDS = ["int8", "int16", "int32", "int64"]
3-
4-
#! Real kinds to be considered during templating
5-
#:set REAL_KINDS = ["sp", "dp", "qp"]
1+
#:include "common.fypp"
62

73
!! Licensing:
84
!!

0 commit comments

Comments
 (0)