11submodule(stdlib_system) stdlib_system_path
22 use stdlib_ascii, only: reverse
33 use stdlib_strings, only: chomp, find, join
4- use stdlib_string_type, only: string_type, char, assignment ( = )
4+ use stdlib_string_type, only: string_type, char, move
55contains
66 module function join2_char_char (p1 , p2 ) result(path)
77 character (:), allocatable :: path
@@ -22,15 +22,21 @@ module function join2_string_char(p1, p2) result(path)
2222 type (string_type) :: path
2323 type (string_type), intent (in ) :: p1
2424 character (* ), intent (in ) :: p2
25+ character (:), allocatable :: join_char
2526
26- path = join_path(char (p1), p2)
27+ join_char = join_path(char (p1), p2)
28+
29+ call move(join_char, path)
2730 end function join2_string_char
2831
2932 module function join2_string_string (p1 , p2 ) result(path)
3033 type (string_type) :: path
3134 type (string_type), intent (in ) :: p1, p2
35+ character (:), allocatable :: join_char
36+
37+ join_char = join_path(char (p1), char (p2))
3238
33- path = join_path( char (p1), char (p2) )
39+ call move(join_char, path )
3440 end function join2_string_string
3541
3642 module function joinarr_char (p ) result(path)
@@ -59,22 +65,22 @@ module function join_op_char_string(p1, p2) result(path)
5965 character (* ), intent (in ) :: p1
6066 type (string_type), intent (in ) :: p2
6167
62- path = join_path(p1, char (p2) )
68+ path = join_path(p1, p2 )
6369 end function join_op_char_string
6470
6571 module function join_op_string_char (p1 , p2 ) result(path)
6672 type (string_type) :: path
6773 type (string_type), intent (in ) :: p1
6874 character (* ), intent (in ) :: p2
6975
70- path = join_path(char (p1) , p2)
76+ path = join_path(p1 , p2)
7177 end function join_op_string_char
7278
7379 module function join_op_string_string (p1 , p2 ) result(path)
7480 type (string_type) :: path
7581 type (string_type), intent (in ) :: p1, p2
7682
77- path = join_path(char (p1), char (p2) )
83+ path = join_path(p1, p2 )
7884 end function join_op_string_string
7985
8086 module subroutine split_path_char (p , head , tail )
@@ -128,8 +134,8 @@ module subroutine split_path_string(p, head, tail)
128134
129135 call split_path(char (p), head_char, tail_char)
130136
131- head = head_char
132- tail = tail_char
137+ call move( head_char, head)
138+ call move( tail_char, tail)
133139 end subroutine split_path_string
134140
135141 module function base_name_char (p ) result(base)
0 commit comments