Skip to content

Commit 761dacf

Browse files
committed
Fix CI error: remove module keyword in submodule.
1 parent 4bae170 commit 761dacf

File tree

3 files changed

+24
-25
lines changed

3 files changed

+24
-25
lines changed

Diff for: doc/specs/stdlib_io.md

+3-3
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ program demo_savetxt
132132
end program demo_savetxt
133133
```
134134

135-
## `disp` - display the value of the vairable
135+
## `disp` - display the value of the variable
136136

137137
### Status
138138

@@ -163,15 +163,15 @@ This argument is `intent(in)` and `optional`.
163163
This argument is `intent(in)` and `optional`.<br>
164164
The default value is `output_unit` from `iso_fortran_env` module.
165165

166-
- `brief`: Shall be a `logical` scalar, controls an abridged version of the `x` array to be outputed.
166+
- `brief`: Shall be a `logical` scalar, controls an abridged version of the `x` array to be outputted.
167167
This argument is `intent(in)` and `optional`.<br>
168168
The default value is `.false.`
169169

170170
- `format`: Shall be a `character(len=*)` scalar.
171171
This argument is `intent(in)` and `optional`.<br>
172172
The default value is `g0.4`.
173173

174-
- `width`: Shall be an `integer` scalar, controls the outputed maximum width (`>=80`).
174+
- `width`: Shall be an `integer` scalar, controls the outputted maximum width (`>=80`).
175175
This argument is `intent(in)` and `optional`.<br>
176176
The default value is `80`.
177177

Diff for: src/stdlib_io.fypp

+16-17
Original file line numberDiff line numberDiff line change
@@ -32,30 +32,29 @@ module stdlib_io
3232

3333
!> version: experimental
3434
!>
35-
!> Display a scalar, vector or matrix.
36-
!> ([Specification](../page/specs/stdlib_io.html#disp-display-your-data))
37-
#! Displays a scalar or array value nicely
35+
!> Display a scalar, vector or matrix formatted.
36+
!> ([Specification](../page/specs/stdlib_io.html#display-the-value-of-the-variable))
3837
interface disp
3938
#:set ALL_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES + LOG_KINDS_TYPES + STRING_KINDS_TYPES
4039
module subroutine disp_char(x, header, unit, brief, format, width, sep)
41-
character(*), intent(in), optional :: x
42-
character(len=*), intent(in), optional :: header
43-
integer, intent(in), optional :: unit
44-
logical, intent(in), optional :: brief
45-
character(len=*), intent(in), optional :: format
46-
integer, intent(in), optional :: width
47-
character(len=*), intent(in), optional :: sep
40+
character(*), intent(in), optional :: x
41+
character(len=*), intent(in), optional :: header
42+
integer, intent(in), optional :: unit
43+
logical, intent(in), optional :: brief
44+
character(len=*), intent(in), optional :: format
45+
integer, intent(in), optional :: width
46+
character(len=*), intent(in), optional :: sep
4847
end subroutine disp_char
4948
#:for r1 in range(0, 3)
5049
#:for k1, t1 in ALL_KINDS_TYPES
5150
module subroutine disp_${r1}$_${t1[0]}$${k1}$(x, header, unit, brief, format, width, sep)
52-
${t1}$, intent(in) :: x${ranksuffix(r1)}$
53-
character(len=*), intent(in), optional :: header
54-
integer, intent(in), optional :: unit
55-
logical, intent(in), optional :: brief
56-
character(len=*), intent(in), optional :: format
57-
integer, intent(in), optional :: width
58-
character(len=*), intent(in), optional :: sep
51+
${t1}$, intent(in) :: x${ranksuffix(r1)}$
52+
character(len=*), intent(in), optional :: header
53+
integer, intent(in), optional :: unit
54+
logical, intent(in), optional :: brief
55+
character(len=*), intent(in), optional :: format
56+
integer, intent(in), optional :: width
57+
character(len=*), intent(in), optional :: sep
5958
end subroutine disp_${r1}$_${t1[0]}$${k1}$
6059
#:endfor
6160
#:endfor

Diff for: src/stdlib_io_disp.fypp

+5-5
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ contains
3232
integer :: unit_, width_#{if r1 == 2}#, max_elem_len#{endif}#
3333
logical :: brief_
3434
character(len=:), allocatable :: format_, sep_
35-
#{if r1 != 0 or (r1 == 1 and k1 != "string_type")}#integer :: i#{endif}#
35+
#{if r1 != 0 and not(r1 == 1 and k1 == "string_type")}#integer :: i#{endif}#
3636
#{if r1 == 2 and k1 != "string_type"}#integer :: j#{endif}#
3737
#{if k1 != "string_type"}#type(string_type), allocatable :: x_str${ranksuffix(r1)}$#{endif}#
3838
#{if r1 != 0}#type(string_type) :: array_info#{endif}#
@@ -146,7 +146,7 @@ contains
146146
#:endfor
147147

148148
!> Format output string
149-
pure module function format_output_string(x, width, brief, sep, max_elem_len) result(str)
149+
pure function format_output_string(x, width, brief, sep, max_elem_len) result(str)
150150

151151
type(string_type), intent(in) :: x(:)
152152
integer, intent(in) :: width
@@ -204,7 +204,7 @@ contains
204204
num1 = merge(width/elem_len, 1, elem_len <= width)
205205
num2 = size(x, 1)/num1
206206

207-
if (num2 > 1 .or. size(x, 1) /= 0) then
207+
if (num2 > 1 .or. size(x, 1) > 1) then
208208
allocate(str(merge(num2, num2 + 1, mod(size(x, 1), num1)==0)))
209209

210210
do i = 1, size(str) - 1
@@ -262,8 +262,8 @@ contains
262262

263263
end function format_output_string
264264

265-
!> Print array infomation
266-
pure type(string_type) module function array_info_maker(m, n) result(info)
265+
!> Print array information
266+
pure type(string_type) function array_info_maker(m, n) result(info)
267267
integer, intent(in) :: m
268268
integer, intent(in), optional :: n
269269

0 commit comments

Comments
 (0)