Skip to content

Commit

Permalink
Add additional recursive robustsorts
Browse files Browse the repository at this point in the history
  • Loading branch information
kaBeech committed Aug 12, 2024
1 parent 6c9ae81 commit 8756354
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 6 deletions.
2 changes: 1 addition & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module Main where

import Data.Tensort.OtherSorts.Mergesort (mergesort)
import Data.Tensort.OtherSorts.Quicksort (quicksort)
import Data.Tensort.Robustsort (robustsortB, robustsortM, robustsortP, robustsortRM, robustsortRecursive)
import Data.Tensort.Robustsort (robustsortB, robustsortM, robustsortP, robustsortRM)
import Data.Tensort.Subalgorithms.Bubblesort (bubblesort)
import Data.Tensort.Tensort (tensortB4, tensortBL)
import Data.Tensort.Utils.RandomizeList (randomizeList)
Expand Down
40 changes: 35 additions & 5 deletions src/Data/Tensort/Robustsort.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@ module Data.Tensort.Robustsort
( robustsortP,
robustsortB,
robustsortM,
robustsortRecursive,
robustsortRCustom,
robustsortRP,
robustsortRB,
robustsortRM,
)
where
Expand All @@ -12,31 +14,59 @@ import Data.Tensort.Subalgorithms.Bubblesort (bubblesort)
import Data.Tensort.Subalgorithms.Exchangesort (exchangesort)
import Data.Tensort.Subalgorithms.Magicsort (magicsort)
import Data.Tensort.Subalgorithms.Permutationsort (permutationsort)
import Data.Tensort.Subalgorithms.Supersort (magicSuperStrat, mundaneSuperStrat, supersort)
import Data.Tensort.Subalgorithms.Supersort
( magicSuperStrat,
mundaneSuperStrat,
supersort,
)
import Data.Tensort.Tensort (tensort)
import Data.Tensort.Utils.MkTsProps (mkTsProps)
import Data.Tensort.Utils.Types (SortAlg, Sortable, fromSortBit)

robustsortRP :: Sortable -> Sortable
robustsortRP = robustsortRCustom robustsortP

robustsortP :: Sortable -> Sortable
robustsortP = tensort (mkTsProps 3 supersortP)

supersortP :: Sortable -> Sortable
supersortP = supersort (bubblesort, exchangesort, permutationsort, mundaneSuperStrat)
supersortP =
supersort
( bubblesort,
exchangesort,
permutationsort,
mundaneSuperStrat
)

robustsortRB :: Sortable -> Sortable
robustsortRB = robustsortRCustom robustsortB

robustsortB :: Sortable -> Sortable
robustsortB = tensort (mkTsProps 3 supersortB)

supersortB :: Sortable -> Sortable
supersortB = supersort (bubblesort, exchangesort, bogosort, mundaneSuperStrat)

robustsortRM :: Sortable -> Sortable
robustsortRM = robustsortRCustom robustsortM

robustsortM :: Sortable -> Sortable
robustsortM = tensort (mkTsProps 3 supersortM)

supersortM :: Sortable -> Sortable
supersortM = supersort (bubblesort, exchangesort, magicsort, magicSuperStrat)

robustsortRM :: Sortable -> Sortable
robustsortRM xs = tensort (mkTsProps (getLn (length (fromSortBit xs))) (robustsortRecursive (getLn (length (fromSortBit xs))) robustsortM)) xs
robustsortRCustom :: SortAlg -> Sortable -> Sortable
robustsortRCustom baseSortAlg xs =
tensort
( mkTsProps
(getLnBytesize xs)
(robustsortRecursive (getLnBytesize xs) baseSortAlg)
)
xs

getLnBytesize :: Sortable -> Int
getLnBytesize xs = getLn (length (fromSortBit xs))

getLn :: Int -> Int
getLn x = ceiling (log (fromIntegral x) :: Double)
Expand Down

0 comments on commit 8756354

Please sign in to comment.