Skip to content

Commit d8f8be7

Browse files
committed
Merge branch 'subprocess' of https://github.com/perazz/stdlib into subprocess
2 parents 33f81a3 + bb98188 commit d8f8be7

27 files changed

+279
-259
lines changed

doc/specs/stdlib_strings.md

Lines changed: 15 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -470,7 +470,7 @@ inserting a separator between each string (default: space). A user-defined separ
470470

471471
#### Syntax
472472

473-
`cmd = ` [[stdlib_strings(module):join(interface)]] ` (strings, separator)`
473+
`joined = ` [[stdlib_strings(module):join(interface)]] ` (strings, separator)`
474474

475475
#### Status
476476

@@ -484,7 +484,7 @@ Pure function
484484

485485
- `strings`: Array of strings (either `type(string_type)` or `character(len=*)`).
486486
This argument is `intent(in)`. It is an array of strings that will be concatenated together.
487-
- `separator`: Character scalar (optional).
487+
- `separator`: `character(len=*)` scalar (optional).
488488
This argument is `intent(in)`. It specifies the separator to be used between the strings. If not provided, the default separator (a space) is used.
489489

490490
#### Result value
@@ -494,13 +494,7 @@ The result is of the same type as the elements of `strings` (`type(string_type)`
494494
#### Example
495495

496496
```fortran
497-
! Example usage:
498-
program test_join
499-
type(string_type) :: result
500-
type(string_type), dimension(3) :: words = [string_type('hello'), string_type('world'), string_type('fortran')]
501-
result = join_string(words, ', ') ! Joins with comma and space
502-
print *, result ! Output: "hello, world, fortran"
503-
end program test_join
497+
{!example/strings/example_join.f90!}
504498
```
505499

506500
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
@@ -544,16 +538,16 @@ The result is an `allocatable` length `character` scalar with up to `128` cached
544538
```
545539

546540
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
547-
### `to_c_string`
541+
### `to_c_char`
548542

549543
#### Description
550544

551-
Convert a Fortran character string to a C character array.
552-
This function converts a Fortran string into a C-style string, ensuring proper null-termination for use in C functions or libraries.
545+
Convert a Fortran `character` string or a `type(string_type)` variable to a C character array.
546+
This function converts a Fortran string into a C-style array of characters, ensuring proper null-termination for use in C functions or libraries.
553547

554548
#### Syntax
555549

556-
`cstr = ` [[stdlib_strings(module):to_c_string(function)]] ` (value)`
550+
`cstr = ` [[stdlib_strings(module):to_c_char(function)]] ` (value)`
557551

558552
#### Status
559553

@@ -565,10 +559,15 @@ Pure function.
565559

566560
#### Argument
567561

568-
- `value`: Shall be a `character(len=*)` string.
569-
This is an `intent(in)` argument.
570-
The Fortran string that will be converted to a C character array.
562+
- `value`: Shall be a `character(len=*)` string or a `type(string_type)` variable. It is an `intent(in)` argument.
563+
This Fortran variable will be converted to a C character array.
571564

572565
#### Result value
573566

574567
The result is a `character(kind=c_char)` array with a dimension of `len(value) + 1` to accommodate the null terminator.
568+
569+
#### Example
570+
571+
```fortran
572+
{!example/strings/example_to_c_char.f90!}
573+
```

example/linalg/example_pseudoinverse.f90

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,6 @@ program example_pseudoinverse
55

66
real :: A(15,5), Am1(5,15)
77
type(linalg_state_type) :: state
8-
integer :: i, j
9-
real, parameter :: tol = sqrt(epsilon(0.0))
108

119
! Generate random matrix A (15x15)
1210
call random_number(A)

example/linalg/example_sparse_from_ijv.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ program example_sparse_from_ijv
3535
print *, 'ELL'
3636
print *, ' index | data'
3737
do i = 1, ELL%nrows
38-
print '(3I4,x,3f8.1)', ELL%index(i,:) , ELL%data(i,:)
38+
print '(3I4,1x,3f8.1)', ELL%index(i,:) , ELL%data(i,:)
3939
end do
4040

41-
end program example_sparse_from_ijv
41+
end program example_sparse_from_ijv

example/strings/CMakeLists.txt

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,15 @@ ADD_EXAMPLE(chomp)
22
ADD_EXAMPLE(count)
33
ADD_EXAMPLE(ends_with)
44
ADD_EXAMPLE(find)
5+
ADD_EXAMPLE(join)
56
ADD_EXAMPLE(padl)
67
ADD_EXAMPLE(padr)
78
ADD_EXAMPLE(replace_all)
89
ADD_EXAMPLE(slice)
910
ADD_EXAMPLE(starts_with)
1011
ADD_EXAMPLE(strip)
1112
ADD_EXAMPLE(to_string)
13+
ADD_EXAMPLE(to_c_char)
1214
ADD_EXAMPLE(zfill)
1315
ADD_EXAMPLE(string_to_number)
14-
ADD_EXAMPLE(stream_of_strings_to_numbers)
16+
ADD_EXAMPLE(stream_of_strings_to_numbers)

example/strings/example_join.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
program example_join
2+
use stdlib_strings, only: join
3+
implicit none
4+
5+
character(len=:), allocatable :: line
6+
character(*), parameter :: words(3) = [character(7) :: "Hello", "World", "Fortran"]
7+
8+
! Default separator (space)
9+
line = join(words)
10+
print *, "'" // line // "'" !! 'Hello World Fortran'
11+
12+
! Custom separator
13+
line = join(words, "_")
14+
print *, "'" // line // "'" !! 'Hello_World_Fortran'
15+
16+
! Custom 2-character separator
17+
line = join(words, ", ")
18+
print *, "'" // line // "'" !! 'Hello, World, Fortran'
19+
20+
end program example_join

example/strings/example_to_c_char.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
program example_to_c_char
2+
use stdlib_strings, only: to_c_char
3+
use stdlib_string_type, only: string_type
4+
use stdlib_kinds, only: c_char
5+
implicit none
6+
7+
character(kind=c_char), allocatable :: cstr(:),cstr2(:)
8+
character(*), parameter :: hello = "Hello, World!"
9+
10+
! Convert character array
11+
cstr = to_c_char(hello)
12+
13+
! Convert string type
14+
cstr2 = to_c_char(string_type(hello))
15+
16+
if (size(cstr)/=size(cstr2) .or. .not.all(cstr==cstr2)) then
17+
error stop 'String conversion error'
18+
end if
19+
20+
end program example_to_c_char

src/lapack/stdlib_lapack_auxiliary.fypp

Lines changed: 15 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -163,7 +163,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
163163
pure real(sp) module function stdlib${ii}$_slamc3( a, b )
164164
! -- lapack auxiliary routine --
165165
! univ. of tennessee, univ. of california berkeley and nag ltd..
166-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
167166
! Scalar Arguments
168167
real(sp), intent(in) :: a, b
169168
! =====================================================================
@@ -175,7 +174,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
175174
pure real(dp) module function stdlib${ii}$_dlamc3( a, b )
176175
! -- lapack auxiliary routine --
177176
! univ. of tennessee, univ. of california berkeley and nag ltd..
178-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
179177
! Scalar Arguments
180178
real(dp), intent(in) :: a, b
181179
! =====================================================================
@@ -189,7 +187,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
189187
pure real(${rk}$) module function stdlib${ii}$_${ri}$lamc3( a, b )
190188
! -- lapack auxiliary routine --
191189
! univ. of tennessee, univ. of california berkeley and nag ltd..
192-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
193190
! Scalar Arguments
194191
real(${rk}$), intent(in) :: a, b
195192
! =====================================================================
@@ -215,7 +212,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
215212
! -- lapack auxiliary routine --
216213
! -- lapack is a software package provided by univ. of tennessee, --
217214
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
218-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
219215
! Scalar Arguments
220216
real(sp), intent(inout) :: large, small
221217
! =====================================================================
@@ -242,7 +238,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
242238
! -- lapack auxiliary routine --
243239
! -- lapack is a software package provided by univ. of tennessee, --
244240
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
245-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
246241
! Scalar Arguments
247242
real(dp), intent(inout) :: large, small
248243
! =====================================================================
@@ -271,7 +266,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
271266
! -- lapack auxiliary routine --
272267
! -- lapack is a software package provided by univ. of tennessee, --
273268
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
274-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
275269
! Scalar Arguments
276270
real(${rk}$), intent(inout) :: large, small
277271
! =====================================================================
@@ -299,7 +293,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
299293
! -- lapack auxiliary routine --
300294
! -- lapack is a software package provided by univ. of tennessee, --
301295
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
302-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
296+
use stdlib_blas_constants_sp, only: zero
303297
! Scalar Arguments
304298
integer(${ik}$), intent(in) :: incx, n
305299
! Array Arguments
@@ -342,7 +336,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
342336
! -- lapack auxiliary routine --
343337
! -- lapack is a software package provided by univ. of tennessee, --
344338
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
345-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
339+
use stdlib_blas_constants_dp, only: zero
346340
! Scalar Arguments
347341
integer(${ik}$), intent(in) :: incx, n
348342
! Array Arguments
@@ -385,7 +379,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
385379
! -- lapack auxiliary routine --
386380
! -- lapack is a software package provided by univ. of tennessee, --
387381
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
388-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
382+
use stdlib_blas_constants_${rk}$, only: zero
389383
! Scalar Arguments
390384
integer(${ik}$), intent(in) :: incx, n
391385
! Array Arguments
@@ -429,7 +423,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
429423
! -- lapack auxiliary routine --
430424
! -- lapack is a software package provided by univ. of tennessee, --
431425
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
432-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
426+
use stdlib_blas_constants_sp, only: one
433427
! Scalar Arguments
434428
character, intent(out) :: equed
435429
character, intent(in) :: uplo
@@ -488,7 +482,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
488482
! -- lapack auxiliary routine --
489483
! -- lapack is a software package provided by univ. of tennessee, --
490484
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
491-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
485+
use stdlib_blas_constants_dp, only: one
492486
! Scalar Arguments
493487
character, intent(out) :: equed
494488
character, intent(in) :: uplo
@@ -549,7 +543,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
549543
! -- lapack auxiliary routine --
550544
! -- lapack is a software package provided by univ. of tennessee, --
551545
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
552-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
546+
use stdlib_blas_constants_${rk}$, only: one
553547
! Scalar Arguments
554548
character, intent(out) :: equed
555549
character, intent(in) :: uplo
@@ -611,7 +605,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
611605
! -- lapack auxiliary routine --
612606
! -- lapack is a software package provided by univ. of tennessee, --
613607
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
614-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
608+
use stdlib_blas_constants_sp, only: one
615609
! Scalar Arguments
616610
character, intent(out) :: equed
617611
character, intent(in) :: uplo
@@ -670,7 +664,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
670664
! -- lapack auxiliary routine --
671665
! -- lapack is a software package provided by univ. of tennessee, --
672666
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
673-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
667+
use stdlib_blas_constants_dp, only: one
674668
! Scalar Arguments
675669
character, intent(out) :: equed
676670
character, intent(in) :: uplo
@@ -731,7 +725,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
731725
! -- lapack auxiliary routine --
732726
! -- lapack is a software package provided by univ. of tennessee, --
733727
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
734-
use stdlib_blas_constants_${ck}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
728+
use stdlib_blas_constants_${ck}$, only: one
735729
! Scalar Arguments
736730
character, intent(out) :: equed
737731
character, intent(in) :: uplo
@@ -793,7 +787,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
793787
! -- lapack auxiliary routine --
794788
! -- lapack is a software package provided by univ. of tennessee, --
795789
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
796-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
790+
use stdlib_blas_constants_sp, only: one
797791
! Scalar Arguments
798792
real(sp), intent(inout) :: a
799793
real(sp), intent(in) :: b, c, d
@@ -815,7 +809,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
815809
! -- lapack auxiliary routine --
816810
! -- lapack is a software package provided by univ. of tennessee, --
817811
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
818-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
812+
use stdlib_blas_constants_dp, only: one
819813
! Scalar Arguments
820814
real(dp), intent(inout) :: a
821815
real(dp), intent(in) :: b, c, d
@@ -839,7 +833,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
839833
! -- lapack auxiliary routine --
840834
! -- lapack is a software package provided by univ. of tennessee, --
841835
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
842-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
836+
use stdlib_blas_constants_${rk}$, only: one
843837
! Scalar Arguments
844838
real(${rk}$), intent(inout) :: a
845839
real(${rk}$), intent(in) :: b, c, d
@@ -866,7 +860,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
866860
! -- lapack auxiliary routine --
867861
! -- lapack is a software package provided by univ. of tennessee, --
868862
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
869-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
863+
use stdlib_blas_constants_sp, only: zero
870864
! Scalar Arguments
871865
real(sp), intent(in) :: a, b, c, d, r, t
872866
! =====================================================================
@@ -891,7 +885,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
891885
! -- lapack auxiliary routine --
892886
! -- lapack is a software package provided by univ. of tennessee, --
893887
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
894-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
888+
use stdlib_blas_constants_dp, only: zero
895889
! Scalar Arguments
896890
real(dp), intent(in) :: a, b, c, d, r, t
897891
! =====================================================================
@@ -918,7 +912,7 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
918912
! -- lapack auxiliary routine --
919913
! -- lapack is a software package provided by univ. of tennessee, --
920914
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
921-
use stdlib_blas_constants_${rk}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
915+
use stdlib_blas_constants_${rk}$, only: zero
922916
! Scalar Arguments
923917
real(${rk}$), intent(in) :: a, b, c, d, r, t
924918
! =====================================================================
@@ -950,7 +944,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
950944
! -- lapack auxiliary routine --
951945
! -- lapack is a software package provided by univ. of tennessee, --
952946
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
953-
use stdlib_blas_constants_sp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
954947
! Scalar Arguments
955948
integer(${ik}$), intent(in) :: incx, incy, n
956949
real(sp), intent(in) :: c
@@ -994,7 +987,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
994987
! -- lapack auxiliary routine --
995988
! -- lapack is a software package provided by univ. of tennessee, --
996989
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
997-
use stdlib_blas_constants_dp, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
998990
! Scalar Arguments
999991
integer(${ik}$), intent(in) :: incx, incy, n
1000992
real(dp), intent(in) :: c
@@ -1040,7 +1032,6 @@ submodule(stdlib_lapack_base) stdlib_lapack_auxiliary
10401032
! -- lapack auxiliary routine --
10411033
! -- lapack is a software package provided by univ. of tennessee, --
10421034
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
1043-
use stdlib_blas_constants_${ck}$, only: negone, zero, half, one, two, three, four, eight, ten, czero, chalf, cone, cnegone
10441035
! Scalar Arguments
10451036
integer(${ik}$), intent(in) :: incx, incy, n
10461037
real(${ck}$), intent(in) :: c

0 commit comments

Comments
 (0)