Skip to content

Commit

Permalink
Fix CI error: remove module keyword in submodule.
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha committed Nov 9, 2021
1 parent 4bae170 commit a6b9e3e
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 25 deletions.
6 changes: 3 additions & 3 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,7 @@ program demo_savetxt
end program demo_savetxt
```

## `disp` - display the value of the vairable
## `disp` - display the value of the variable

### Status

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

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

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

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

Expand Down
33 changes: 16 additions & 17 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -32,30 +32,29 @@ module stdlib_io

!> version: experimental
!>
!> Display a scalar, vector or matrix.
!> ([Specification](../page/specs/stdlib_io.html#disp-display-your-data))
#! Displays a scalar or array value nicely
!> Display a scalar, vector or matrix formatted.
!> ([Specification](../page/specs/stdlib_io.html#display-the-value-of-the-variable))
interface disp
#:set ALL_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES + LOG_KINDS_TYPES + STRING_KINDS_TYPES
module subroutine disp_char(x, header, unit, brief, format, width, sep)
character(*), intent(in), optional :: x
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
character(*), intent(in), optional :: x
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
end subroutine disp_char
#:for r1 in range(0, 3)
#:for k1, t1 in ALL_KINDS_TYPES
module subroutine disp_${r1}$_${t1[0]}$${k1}$(x, header, unit, brief, format, width, sep)
${t1}$, intent(in) :: x${ranksuffix(r1)}$
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
${t1}$, intent(in) :: x${ranksuffix(r1)}$
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
end subroutine disp_${r1}$_${t1[0]}$${k1}$
#:endfor
#:endfor
Expand Down
10 changes: 5 additions & 5 deletions src/stdlib_io_disp.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ contains
integer :: unit_, width_#{if r1 == 2}#, max_elem_len#{endif}#
logical :: brief_
character(len=:), allocatable :: format_, sep_
#{if r1 != 0 or (r1 == 1 and k1 != "string_type")}#integer :: i#{endif}#
#{if r1 != 0 and not(r1 == 1 and k1 == "string_type")}#integer :: i#{endif}#
#{if r1 == 2 and k1 != "string_type"}#integer :: j#{endif}#
#{if k1 != "string_type"}#type(string_type), allocatable :: x_str${ranksuffix(r1)}$#{endif}#
#{if r1 != 0}#type(string_type) :: array_info#{endif}#
Expand Down Expand Up @@ -146,7 +146,7 @@ contains
#:endfor

!> Format output string
pure module function format_output_string(x, width, brief, sep, max_elem_len) result(str)
pure function format_output_string(x, width, brief, sep, max_elem_len) result(str)

type(string_type), intent(in) :: x(:)
integer, intent(in) :: width
Expand Down Expand Up @@ -262,8 +262,8 @@ contains

end function format_output_string

!> Print array infomation
pure type(string_type) module function array_info_maker(m, n) result(info)
!> Print array information
pure type(string_type) function array_info_maker(m, n) result(info)
integer, intent(in) :: m
integer, intent(in), optional :: n

Expand All @@ -276,7 +276,7 @@ contains
end function array_info_maker

!> Display `character(*)` value.
module subroutine disp_char(x, header, unit, brief, format, width, sep)
subroutine disp_char(x, header, unit, brief, format, width, sep)

character(*), intent(in), optional :: x
character(len=*), intent(in), optional :: header
Expand Down

0 comments on commit a6b9e3e

Please sign in to comment.