11{-# LANGUAGE LinearTypes #-}
22{-# LANGUAGE NoImplicitPrelude #-}
33
4+ -- Uncomment the line below to observe the generated (optimised) Core. It will
5+ -- land in a file named “Quicksort.dump-simpl”
6+ -- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dsuppress-all -dsuppress-uniques #-}
7+
48-- | This module implements quicksort with mutable arrays from linear-base
59module Simple.Quicksort where
610
@@ -13,15 +17,22 @@ import Prelude.Linear hiding (partition)
1317-- # Quicksort
1418-------------------------------------------------------------------------------
1519
16- quickSort :: [Int ] -> [Int ]
17- quickSort xs = unur $ Array. fromList xs $ Array. toList . arrQuicksort
20+ quicksortUsingList :: (Ord a ) => [a ] -> [a ]
21+ quicksortUsingList [] = []
22+ quicksortUsingList (x : xs) = quicksortUsingList ltx ++ x : quicksortUsingList gex
23+ where
24+ ltx = [y | y <- xs, y < x]
25+ gex = [y | y <- xs, y >= x]
26+
27+ quicksortUsingArray :: (Ord a ) => [a ] -> [a ]
28+ quicksortUsingArray xs = unur $ Array. fromList xs $ Array. toList . quicksortArray
1829
19- arrQuicksort :: Array Int % 1 -> Array Int
20- arrQuicksort arr =
30+ quicksortArray :: ( Ord a ) => Array a % 1 -> Array a
31+ quicksortArray arr =
2132 Array. size arr
2233 & \ (Ur len, arr1) -> go 0 (len - 1 ) arr1
2334
24- go :: Int -> Int -> Array Int % 1 -> Array Int
35+ go :: ( Ord a ) => Int -> Int -> Array a % 1 -> Array a
2536go lo hi arr
2637 | lo >= hi = arr
2738 | otherwise =
@@ -39,23 +50,23 @@ go lo hi arr
3950-- @arr'[j] > pivot@ for @ix < j <= hi@,
4051-- @arr'[k] = arr[k]@ for @k < lo@ and @k > hi@, and
4152-- @arr'@ is a permutation of @arr@.
42- partition :: Array Int % 1 -> Int -> Int -> Int -> (Array Int , Ur Int )
43- partition arr pivot lx rx
44- | (rx < lx ) = (arr, Ur (lx - 1 ))
53+ partition :: ( Ord a ) => Array a % 1 -> a -> Int -> Int -> (Array a , Ur Int )
54+ partition arr pivot lo hi
55+ | (hi < lo ) = (arr, Ur (lo - 1 ))
4556 | otherwise =
46- Array. read arr lx
57+ Array. read arr lo
4758 & \ (Ur lVal, arr1) ->
48- Array. read arr1 rx
59+ Array. read arr1 hi
4960 & \ (Ur rVal, arr2) -> case (lVal <= pivot, pivot < rVal) of
50- (True , True ) -> partition arr2 pivot (lx + 1 ) (rx - 1 )
51- (True , False ) -> partition arr2 pivot (lx + 1 ) rx
52- (False , True ) -> partition arr2 pivot lx (rx - 1 )
61+ (True , True ) -> partition arr2 pivot (lo + 1 ) (hi - 1 )
62+ (True , False ) -> partition arr2 pivot (lo + 1 ) hi
63+ (False , True ) -> partition arr2 pivot lo (hi - 1 )
5364 (False , False ) ->
54- swap arr2 lx rx
55- & \ arr3 -> partition arr3 pivot (lx + 1 ) (rx - 1 )
65+ swap arr2 lo hi
66+ & \ arr3 -> partition arr3 pivot (lo + 1 ) (hi - 1 )
5667
5768-- | @swap a i j@ exchanges the positions of values at @i@ and @j@ of @a@.
58- swap :: (HasCallStack ) => Array Int % 1 -> Int -> Int -> Array Int
69+ swap :: (HasCallStack ) => Array a % 1 -> Int -> Int -> Array a
5970swap arr i j =
6071 Array. read arr i
6172 & \ (Ur ival, arr1) ->
0 commit comments