@@ -3,6 +3,7 @@ module stdlib_system
33 c_f_pointer
44use stdlib_kinds, only: int64, dp, c_bool, c_char
55use stdlib_strings, only: to_c_char
6+ use stdlib_string_type, only: string_type
67use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
78implicit none
89private
@@ -565,15 +566,37 @@ end function process_get_ID
565566 ! ! join the paths provided according to the OS-specific path-separator
566567 ! ! ([Specification](../page/specs/stdlib_system.html#join_path))
567568 ! !
568- module function join2 (p1 , p2 ) result(path)
569+ module function join2_char_char (p1 , p2 ) result(path)
569570 character (:), allocatable :: path
570571 character (* ), intent (in ) :: p1, p2
571- end function join2
572+ end function join2_char_char
572573
573- module function joinarr (p ) result(path)
574+ module function join2_char_string (p1 , p2 ) result(path)
575+ character (:), allocatable :: path
576+ character (* ), intent (in ) :: p1
577+ type (string_type), intent (in ) :: p2
578+ end function join2_char_string
579+
580+ module function join2_string_char (p1 , p2 ) result(path)
581+ type (string_type) :: path
582+ type (string_type), intent (in ) :: p1
583+ character (* ), intent (in ) :: p2
584+ end function join2_string_char
585+
586+ module function join2_string_string (p1 , p2 ) result(path)
587+ type (string_type) :: path
588+ type (string_type), intent (in ) :: p1, p2
589+ end function join2_string_string
590+
591+ module function joinarr_char (p ) result(path)
574592 character (:), allocatable :: path
575593 character (* ), intent (in ) :: p(:)
576- end function joinarr
594+ end function joinarr_char
595+
596+ module function joinarr_string (p ) result(path)
597+ type (string_type) :: path
598+ type (string_type), intent (in ) :: p(:)
599+ end function joinarr_string
577600end interface join_path
578601
579602interface operator (/ )
@@ -583,10 +606,27 @@ end function joinarr
583606 ! ! A binary operator to join the paths provided according to the OS-specific path-separator
584607 ! ! ([Specification](../page/specs/stdlib_system.html#operator(/)))
585608 ! !
586- module function join_op (p1 , p2 ) result(path)
609+ module function join_op_char_char (p1 , p2 ) result(path)
587610 character (:), allocatable :: path
588611 character (* ), intent (in ) :: p1, p2
589- end function join_op
612+ end function join_op_char_char
613+
614+ module function join_op_char_string (p1 , p2 ) result(path)
615+ character (:), allocatable :: path
616+ character (* ), intent (in ) :: p1
617+ type (string_type), intent (in ) :: p2
618+ end function join_op_char_string
619+
620+ module function join_op_string_char (p1 , p2 ) result(path)
621+ type (string_type) :: path
622+ type (string_type), intent (in ) :: p1
623+ character (* ), intent (in ) :: p2
624+ end function join_op_string_char
625+
626+ module function join_op_string_string (p1 , p2 ) result(path)
627+ type (string_type) :: path
628+ type (string_type), intent (in ) :: p1, p2
629+ end function join_op_string_string
590630end interface operator (/ )
591631
592632interface split_path
@@ -602,10 +642,15 @@ end function join_op
602642 ! ! If the path only consists of separators, `head` is set to the separator and tail is empty
603643 ! ! If the path is a root directory, `head` is set to that directory and tail is empty
604644 ! ! `head` ends with a path-separator iff the path appears to be a root directory or a child of the root directory
605- module subroutine split_path (p , head , tail )
645+ module subroutine split_path_char (p , head , tail )
606646 character (* ), intent (in ) :: p
607647 character (:), allocatable , intent (out ) :: head, tail
608- end subroutine split_path
648+ end subroutine split_path_char
649+
650+ module subroutine split_path_string (p , head , tail )
651+ type (string_type), intent (in ) :: p
652+ type (string_type), intent (out ) :: head, tail
653+ end subroutine split_path_string
609654end interface split_path
610655
611656interface base_name
@@ -617,10 +662,15 @@ end subroutine split_path
617662 ! !
618663 ! !### Description
619664 ! ! The value returned is the `tail` of the interface `split_path`
620- module function base_name (p ) result(base)
665+ module function base_name_char (p ) result(base)
621666 character (:), allocatable :: base
622667 character (* ), intent (in ) :: p
623- end function base_name
668+ end function base_name_char
669+
670+ module function base_name_string (p ) result(base)
671+ type (string_type) :: base
672+ type (string_type), intent (in ) :: p
673+ end function base_name_string
624674end interface base_name
625675
626676interface dir_name
@@ -632,10 +682,15 @@ end function base_name
632682 ! !
633683 ! !### Description
634684 ! ! The value returned is the `head` of the interface `split_path`
635- module function dir_name (p ) result(base )
636- character (:), allocatable :: base
685+ module function dir_name_char (p ) result(dir )
686+ character (:), allocatable :: dir
637687 character (* ), intent (in ) :: p
638- end function dir_name
688+ end function dir_name_char
689+
690+ module function dir_name_string (p ) result(dir)
691+ type (string_type) :: dir
692+ type (string_type), intent (in ) :: p
693+ end function dir_name_string
639694end interface dir_name
640695
641696
0 commit comments