File: string_30.f90

package info (click to toggle)
lfortran 0.58.0-6
  • 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: 37; javascript: 15
file content (109 lines) | stat: -rw-r--r-- 3,040 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
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
module stdlib_string_type
    implicit none
    private

    public :: string_type

    public :: operator(//)

    type :: string_type
        private
        character(len=:), allocatable :: raw
    end type string_type

    interface operator(//)
        module procedure :: concat_string_string
        module procedure :: concat_string_char
        module procedure :: concat_char_string
    end interface operator(//)

contains

    elemental function concat_string_string(lhs, rhs) result(string)
        type(string_type), intent(in) :: lhs
        type(string_type), intent(in) :: rhs
        type(string_type) :: string

    end function concat_string_string

    elemental function concat_string_char(lhs, rhs) result(string)
        type(string_type), intent(in) :: lhs
        character(len=*), intent(in) :: rhs
        type(string_type) :: string

    end function concat_string_char

    elemental function concat_char_string(lhs, rhs) result(string)
        character(len=*), intent(in) :: lhs
        type(string_type), intent(in) :: rhs
        type(string_type) :: string

    end function concat_char_string

end module stdlib_string_type

module stdlib_ansi
    use stdlib_string_type, only : string_type
    implicit none
    private

    public :: ansi_code

    public :: to_string, operator(//)

    public :: concat_left_str, concat_right_str

    type :: ansi_code
        private
        integer(1) :: style = -1_1
        integer(1) :: bg = -1_1
        integer(1) :: fg = -1_1
    end type ansi_code

    interface to_string
        pure module function to_string_ansi_code(code) result(str)
            type(ansi_code), intent(in) :: code
            character(len=:), allocatable :: str
        end function to_string_ansi_code
    end interface to_string

    interface operator(//)

        pure module function concat_left_str(lval, code) result(str)
            type(string_type), intent(in) :: lval
            type(ansi_code), intent(in) :: code
            type(string_type) :: str
        end function concat_left_str

        pure module function concat_right_str(code, rval) result(str)
            type(string_type), intent(in) :: rval
            type(ansi_code), intent(in) :: code
            type(string_type) :: str
        end function concat_right_str
    end interface operator(//)

end module stdlib_ansi

submodule (stdlib_ansi) stdlib_ansi_operator
    use stdlib_string_type, only : operator(//)
    implicit none

contains

    pure module function concat_left_str(lval, code) result(str)
        type(string_type), intent(in) :: lval
        type(ansi_code), intent(in) :: code
        type(string_type) :: str

        str = lval // to_string(code)
    end function concat_left_str

    pure module function concat_right_str(code, rval) result(str)
        type(string_type), intent(in) :: rval
        type(ansi_code), intent(in) :: code
        type(string_type) :: str

        str = to_string(code) // rval
    end function concat_right_str

end submodule stdlib_ansi_operator