|
1 | 1 | submodule(stdlib_system) stdlib_system_path
|
2 | 2 | use stdlib_ascii, only: reverse
|
3 | 3 | use stdlib_strings, only: chomp, find, join
|
| 4 | + use stdlib_string_type, only: string_type, char, assignment(=) |
4 | 5 | contains
|
5 |
| - module function join2(p1, p2) result(path) |
| 6 | + module function join2_char_char(p1, p2) result(path) |
6 | 7 | character(:), allocatable :: path
|
7 | 8 | character(*), intent(in) :: p1, p2
|
8 | 9 |
|
9 | 10 | path = trim(p1) // path_sep() // trim(p2)
|
10 |
| - end function join2 |
| 11 | + end function join2_char_char |
11 | 12 |
|
12 |
| - module function joinarr(p) result(path) |
| 13 | + module function join2_char_string(p1, p2) result(path) |
| 14 | + character(:), allocatable :: path |
| 15 | + character(*), intent(in) :: p1 |
| 16 | + type(string_type), intent(in) :: p2 |
| 17 | + |
| 18 | + path = join_path(p1, char(p2)) |
| 19 | + end function join2_char_string |
| 20 | + |
| 21 | + module function join2_string_char(p1, p2) result(path) |
| 22 | + type(string_type) :: path |
| 23 | + type(string_type), intent(in) :: p1 |
| 24 | + character(*), intent(in) :: p2 |
| 25 | + |
| 26 | + path = join_path(char(p1), p2) |
| 27 | + end function join2_string_char |
| 28 | + |
| 29 | + module function join2_string_string(p1, p2) result(path) |
| 30 | + type(string_type) :: path |
| 31 | + type(string_type), intent(in) :: p1, p2 |
| 32 | + |
| 33 | + path = join_path(char(p1), char(p2)) |
| 34 | + end function join2_string_string |
| 35 | + |
| 36 | + module function joinarr_char(p) result(path) |
13 | 37 | character(:), allocatable :: path
|
14 | 38 | character(*), intent(in) :: p(:)
|
15 | 39 |
|
16 | 40 | path = join(p, path_sep())
|
17 |
| - end function joinarr |
| 41 | + end function joinarr_char |
18 | 42 |
|
19 |
| - module function join_op(p1, p2) result(path) |
| 43 | + module function joinarr_string(p) result(path) |
| 44 | + type(string_type) :: path |
| 45 | + type(string_type), intent(in) :: p(:) |
| 46 | + |
| 47 | + path = join(p, path_sep()) |
| 48 | + end function joinarr_string |
| 49 | + |
| 50 | + module function join_op_char_char(p1, p2) result(path) |
20 | 51 | character(:), allocatable :: path
|
21 | 52 | character(*), intent(in) :: p1, p2
|
22 | 53 |
|
23 | 54 | path = join_path(p1, p2)
|
24 |
| - end function join_op |
| 55 | + end function join_op_char_char |
| 56 | + |
| 57 | + module function join_op_char_string(p1, p2) result(path) |
| 58 | + character(:), allocatable :: path |
| 59 | + character(*), intent(in) :: p1 |
| 60 | + type(string_type), intent(in) :: p2 |
| 61 | + |
| 62 | + path = join_path(p1, char(p2)) |
| 63 | + end function join_op_char_string |
| 64 | + |
| 65 | + module function join_op_string_char(p1, p2) result(path) |
| 66 | + type(string_type) :: path |
| 67 | + type(string_type), intent(in) :: p1 |
| 68 | + character(*), intent(in) :: p2 |
25 | 69 |
|
26 |
| - module subroutine split_path(p, head, tail) |
| 70 | + path = join_path(char(p1), p2) |
| 71 | + end function join_op_string_char |
| 72 | + |
| 73 | + module function join_op_string_string(p1, p2) result(path) |
| 74 | + type(string_type) :: path |
| 75 | + type(string_type), intent(in) :: p1, p2 |
| 76 | + |
| 77 | + path = join_path(char(p1), char(p2)) |
| 78 | + end function join_op_string_string |
| 79 | + |
| 80 | + module subroutine split_path_char(p, head, tail) |
27 | 81 | character(*), intent(in) :: p
|
28 | 82 | character(:), allocatable, intent(out) :: head, tail
|
29 | 83 | character(:), allocatable :: temp
|
@@ -64,19 +118,47 @@ module subroutine split_path(p, head, tail)
|
64 | 118 | end if
|
65 | 119 |
|
66 | 120 | tail = temp(len(temp)-i+2:)
|
67 |
| - end subroutine split_path |
| 121 | + end subroutine split_path_char |
| 122 | + |
| 123 | + module subroutine split_path_string(p, head, tail) |
| 124 | + type(string_type), intent(in) :: p |
| 125 | + type(string_type), intent(out) :: head, tail |
| 126 | + |
| 127 | + character(:), allocatable :: head_char, tail_char |
| 128 | + |
| 129 | + call split_path(char(p), head_char, tail_char) |
| 130 | + |
| 131 | + head = head_char |
| 132 | + tail = tail_char |
| 133 | + end subroutine split_path_string |
68 | 134 |
|
69 |
| - module function base_name(p) result(base) |
| 135 | + module function base_name_char(p) result(base) |
70 | 136 | character(:), allocatable :: base, temp
|
71 | 137 | character(*), intent(in) :: p
|
72 | 138 |
|
73 | 139 | call split_path(p, temp, base)
|
74 |
| - end function base_name |
| 140 | + end function base_name_char |
75 | 141 |
|
76 |
| - module function dir_name(p) result(dir) |
| 142 | + module function base_name_string(p) result(base) |
| 143 | + type(string_type) :: base |
| 144 | + type(string_type), intent(in) :: p |
| 145 | + type(string_type) :: temp |
| 146 | + |
| 147 | + call split_path(p, temp, base) |
| 148 | + end function base_name_string |
| 149 | + |
| 150 | + module function dir_name_char(p) result(dir) |
77 | 151 | character(:), allocatable :: dir, temp
|
78 | 152 | character(*), intent(in) :: p
|
79 | 153 |
|
80 | 154 | call split_path(p, dir, temp)
|
81 |
| - end function dir_name |
| 155 | + end function dir_name_char |
| 156 | + |
| 157 | + module function dir_name_string(p) result(dir) |
| 158 | + type(string_type) :: dir |
| 159 | + type(string_type), intent(in) :: p |
| 160 | + type(string_type) :: temp |
| 161 | + |
| 162 | + call split_path(p, dir, temp) |
| 163 | + end function dir_name_string |
82 | 164 | end submodule stdlib_system_path
|
0 commit comments