diff --git a/doc/specs/stdlib_ascii.md b/doc/specs/stdlib_ascii.md
index 5a6653337..fbc1b4982 100644
--- a/doc/specs/stdlib_ascii.md
+++ b/doc/specs/stdlib_ascii.md
@@ -169,3 +169,39 @@ program demo_reverse
     print'(a)', reverse("Hello, World!") ! returns "!dlroW ,olleH"
 end program demo_reverse
 ```
+
+### `sort`
+
+#### Status
+
+Experimental
+
+#### Description
+
+Sorts all the characters in the input character type according to their ascii values.
+
+#### Syntax
+
+`res = [[stdlib_ascii(module):sort(function)]] (string)`
+
+#### Class
+
+Pure function.
+
+#### Argument
+
+`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
+
+#### Result value
+
+The result is an intrinsic character type of the same length as `string`.
+
+#### Example
+
+```fortran
+program demo_sort
+    use stdlib_ascii, only : sort
+    implicit none
+    print'(a)', sort("Sort This String") ! returns "  SSTghiinorrstt"
+end program demo_sort
+```
\ No newline at end of file
diff --git a/doc/specs/stdlib_string_type.md b/doc/specs/stdlib_string_type.md
index 63c38ccf4..b5bf9a18e 100644
--- a/doc/specs/stdlib_string_type.md
+++ b/doc/specs/stdlib_string_type.md
@@ -1221,6 +1221,50 @@ program demo
 end program demo
 ```
 
+<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
+### Sort function
+
+#### Description
+
+Returns a new string_type instance which holds the sorted version of the character sequence hold by the input string.
+
+#### Syntax
+
+`sorted_string = [[stdlib_string_type(module): sort(interface)]] (string)`
+
+#### Status
+
+Experimental
+
+#### Class
+
+Elemental function.
+
+#### Argument
+
+`string`: Instance of `string_type`. This argument is `intent(in)`.
+
+#### Result Value
+
+The Result is a scalar `string_type` value.
+
+#### Example
+
+```fortran
+program demo
+  use stdlib_string_type
+  implicit none
+  type(string_type) :: string, sorted_string
+  
+  string = "Sort This String"
+  ! string <-- "Sort This String"
+
+  sorted_string = sort(string)
+  ! string <-- "Sort This String"
+  ! sorted_string <-- "  SSTghiinorrstt"
+end program demo
+```
+
 
 <!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
 ### Comparison operator greater
diff --git a/src/stdlib_ascii.f90 b/src/stdlib_ascii.f90
index e446f29e2..c7f5cfccc 100644
--- a/src/stdlib_ascii.f90
+++ b/src/stdlib_ascii.f90
@@ -16,7 +16,7 @@ module stdlib_ascii
     public :: is_lower, is_upper
 
     ! Character conversion functions
-    public :: to_lower, to_upper, to_title, reverse
+    public :: to_lower, to_upper, to_title, reverse, sort
 
     ! All control characters in the ASCII table (see www.asciitable.com).
     character(len=1), public, parameter :: NUL = achar(int(z'00')) !! Null
@@ -92,6 +92,13 @@ module stdlib_ascii
     interface reverse
         module procedure :: reverse
     end interface reverse
+
+    !> Returns a new character sequence which sorted version of
+    !> the input charater sequence
+    !> This method is pure and returns a character sequence
+    interface sort
+        module procedure :: sort
+    end interface sort
     
 
 contains
@@ -312,4 +319,30 @@ pure function reverse(string) result(reverse_string)
 
     end function reverse
 
+
+    !> Sort the character order in the input character variable
+    !> Version: experimental
+    pure function sort(string) result(sorted_string)
+        character(len=*), intent(in) :: string
+        character(len=len(string)) :: sorted_string
+        integer, dimension(128) :: count
+        integer :: i,j
+        !implementation
+        do i = 1, 128
+            count(i) = 0
+        end do
+
+        do i = 1, len(string)
+            count(iachar(string(i:i))) = count(iachar(string(i:i))) + 1
+        end do
+        j = 1
+        do i = 1, 128
+            do while (count(i)>0)
+                sorted_string(j:j) = achar(i)
+                j = j+1
+                count(i) = count(i) - 1;
+            end do
+        end do
+    end function sort
+
 end module stdlib_ascii
diff --git a/src/stdlib_string_type.f90 b/src/stdlib_string_type.f90
index 2b46a5de9..f2f28fe79 100644
--- a/src/stdlib_string_type.f90
+++ b/src/stdlib_string_type.f90
@@ -13,7 +13,7 @@
 !> The specification of this module is available [here](../page/specs/stdlib_string_type.html).
 module stdlib_string_type
     use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, &
-                            to_title_ => to_title, reverse_ => reverse
+                            to_title_ => to_title, reverse_ => reverse, sort_ => sort
 
     implicit none
     private
@@ -21,7 +21,7 @@ module stdlib_string_type
     public :: string_type
     public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl
     public :: lgt, lge, llt, lle, char, ichar, iachar
-    public :: to_lower, to_upper, to_title, reverse
+    public :: to_lower, to_upper, to_title, reverse, sort
     public :: assignment(=)
     public :: operator(>), operator(>=), operator(<), operator(<=)
     public :: operator(==), operator(/=), operator(//)
@@ -125,6 +125,14 @@ module stdlib_string_type
         module procedure :: reverse_string
     end interface reverse
 
+    !> Sorts the character sequence hold by the input string
+    !> 
+    !> This method is Elemental and returns a new string_type instance which holds this
+    !> sorted character sequence
+    interface sort
+        module procedure :: sort_string
+    end interface sort
+
     !> Return the character sequence represented by the string.
     !>
     !> This method is elemental and returns a scalar character value.
@@ -522,6 +530,14 @@ elemental function reverse_string(string) result(reversed_string)
 
     end function reverse_string
 
+    !> Sorts the character sequence hold by the input string
+    elemental function sort_string(string) result(sorted_string)
+        type(string_type), intent(in) :: string
+        type(string_type) :: sorted_string
+
+        sorted_string%raw = sort_(maybe(string))
+
+    end function sort_string
 
     !> Position of a sequence of character within a character sequence.
     !> In this version both character sequences are represented by a string.
diff --git a/src/tests/ascii/test_ascii.f90 b/src/tests/ascii/test_ascii.f90
index cfe4a938c..3623e9dac 100644
--- a/src/tests/ascii/test_ascii.f90
+++ b/src/tests/ascii/test_ascii.f90
@@ -6,7 +6,7 @@ program test_ascii
         whitespace, letters, is_alphanum, is_alpha, is_lower, is_upper, &
         is_digit, is_octal_digit, is_hex_digit, is_white, is_blank, &
         is_control, is_punctuation, is_graphical, is_printable, is_ascii, &
-        to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL
+        to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL, sort
 
     implicit none
 
@@ -72,6 +72,7 @@ program test_ascii
     call test_to_lower_string
     call test_to_title_string
     call test_reverse_string
+    call test_sort_string
 
 contains
 
@@ -613,4 +614,18 @@ subroutine test_reverse_string
         call check(trim(adjustl(dlc)) == "desrever")
     end subroutine test_reverse_string
 
+    subroutine test_sort_string
+        character(len=:), allocatable :: dlc
+        character(len=32), parameter :: input = "This is to be sorted"
+
+        dlc = sort("This is to be sorted")
+        call check(dlc == "    Tbdeehiioorssstt")
+
+        dlc = sort(input)
+        call check(len(dlc) == 32)
+        call check(len_trim(dlc) == 32)
+        call check(trim(dlc) == "                Tbdeehiioorssstt")
+        call check(trim(adjustl(dlc)) == "Tbdeehiioorssstt")
+    end subroutine test_sort_string
+
 end program test_ascii
diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90
index 4a8d516a8..669700a46 100644
--- a/src/tests/string/test_string_functions.f90
+++ b/src/tests/string/test_string_functions.f90
@@ -2,7 +2,7 @@
 module test_string_functions
     use stdlib_error, only : check
     use stdlib_string_type, only : string_type, assignment(=), operator(==), &
-                                    to_lower, to_upper, to_title, reverse
+                                    to_lower, to_upper, to_title, reverse, sort
     implicit none
 
 contains
@@ -43,6 +43,15 @@ subroutine test_reverse_string
 
     end subroutine test_reverse_string
 
+    subroutine test_sort_string
+        type(string_type) :: test_string, compare_string
+        test_string = "Sort my Life"
+        compare_string = "  LSefimorty"
+
+        call check(sort(test_string) == compare_string)
+
+    end subroutine test_sort_string
+
 end module test_string_functions
 
 
@@ -54,5 +63,6 @@ program tester
     call test_to_upper_string
     call test_to_title_string
     call test_reverse_string
+    call test_sort_string
 
 end program tester