File: submodule_13.f90

package info (click to toggle)
lfortran 0.58.0-4
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 54,512 kB
  • sloc: cpp: 162,179; f90: 68,251; python: 17,476; ansic: 6,278; yacc: 2,334; sh: 1,317; fortran: 892; makefile: 33; javascript: 15
file content (66 lines) | stat: -rw-r--r-- 1,938 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
module submodule_13_mod
  implicit none

  private
  public :: string_t
  public :: operator(.separatedBy.)

  type string_t
    private
    character(len=:), allocatable :: string_
  contains
    procedure :: bracket
  end type string_t

  interface string_t
    elemental module function from_default_integer(i) result(string)
      implicit none
      integer, intent(in) :: i
      type(string_t) :: string
    end function from_default_integer
  end interface

  interface
    elemental module function bracket(self, opening, closing) result(bracketed_self)
      implicit none
      class(string_t), intent(in) :: self
      character(len=*), intent(in), optional :: opening, closing
      type(string_t) :: bracketed_self
    end function bracket
  end interface

  contains

    elemental module function bracket(self, opening, closing) result(bracketed_self)
      class(string_t), intent(in) :: self
      character(len=*), intent(in), optional :: opening, closing
      type(string_t) :: bracketed_self

      if (present(opening) .and. present(closing)) then
          bracketed_self%string_ = opening // self%string_ // closing
      else
          bracketed_self%string_ = self%string_
      end if
    end function bracket

end module submodule_13_mod


program submodule_13
  use submodule_13_mod, only : string_t
  implicit none

contains

  pure function markdown_table(row_header, column_header, body_cells, side_borders) result(lines)
    integer, parameter :: first_body_row = 3
    type(string_t), intent(in) :: row_header(first_body_row:), column_header(:), body_cells(first_body_row:,:)
    logical, intent(in) :: side_borders
    character(len=1), parameter :: column_separator = "|"
    integer, parameter :: num_rule_lines = 1
    type(string_t) :: lines(size(body_cells,1) + num_rule_lines)

    if (side_borders) lines = lines%bracket(column_separator)
  end function markdown_table

end program submodule_13