module Data.Tensort.Tensort
( tensort,
tensortB4,
tensortBN,
tensortBL,
)
where
import Data.Tensort.Subalgorithms.Bubblesort (bubblesort)
import Data.Tensort.Utils.Compose (createInitialTensors)
import Data.Tensort.Utils.Convert (rawToBytes)
import Data.Tensort.Utils.MkTsProps (mkTsProps)
import Data.Tensort.Utils.RandomizeList (randomizeList)
import Data.Tensort.Utils.Reduce (reduceTensorStacks)
import Data.Tensort.Utils.Render (getSortedBitsFromTensor)
import Data.Tensort.Utils.Types (Sortable (..), TensortProps (..), fromSBitBits, fromSBitRecs)
tensort :: TensortProps -> Sortable -> Sortable
tensort :: TensortProps -> Sortable -> Sortable
tensort TensortProps
_ (SortBit []) = [Int] -> Sortable
SortBit []
tensort TensortProps
_ (SortBit [Int
x]) = [Int] -> Sortable
SortBit [Int
x]
tensort TensortProps
tsProps (SortBit [Int
x, Int
y]) = TensortProps -> Sortable -> Sortable
subAlgorithm TensortProps
tsProps ([Int] -> Sortable
SortBit [Int
x, Int
y])
tensort TensortProps
tsProps (SortBit [Int]
xs) = do
let bits :: Sortable
bits = Int -> Sortable -> Sortable
randomizeList Int
143 ([Int] -> Sortable
SortBit [Int]
xs)
let bytes :: SBytes
bytes = TensortProps -> Sortable -> SBytes
rawToBytes TensortProps
tsProps Sortable
bits
let tensorStacks :: STensors
tensorStacks = TensortProps -> SBytes -> STensors
createInitialTensors TensortProps
tsProps SBytes
bytes
let topTensor :: STensorStack
topTensor = TensortProps -> STensors -> STensorStack
reduceTensorStacks TensortProps
tsProps STensors
tensorStacks
[SBit] -> Sortable
fromSBitBits ((Sortable -> Sortable) -> STensorStack -> [SBit]
getSortedBitsFromTensor (TensortProps -> Sortable -> Sortable
subAlgorithm TensortProps
tsProps) STensorStack
topTensor)
tensort TensortProps
_ (SortRec []) = [Record] -> Sortable
SortRec []
tensort TensortProps
_ (SortRec [Record
x]) = [Record] -> Sortable
SortRec [Record
x]
tensort TensortProps
tsProps (SortRec [Record
x, Record
y]) = TensortProps -> Sortable -> Sortable
subAlgorithm TensortProps
tsProps ([Record] -> Sortable
SortRec [Record
x, Record
y])
tensort TensortProps
tsProps (SortRec [Record]
xs) = do
let recs :: Sortable
recs = Int -> Sortable -> Sortable
randomizeList Int
143 ([Record] -> Sortable
SortRec [Record]
xs)
let bytes :: SBytes
bytes = TensortProps -> Sortable -> SBytes
rawToBytes TensortProps
tsProps Sortable
recs
let tensorStacks :: STensors
tensorStacks = TensortProps -> SBytes -> STensors
createInitialTensors TensortProps
tsProps SBytes
bytes
let topTensor :: STensorStack
topTensor = TensortProps -> STensors -> STensorStack
reduceTensorStacks TensortProps
tsProps STensors
tensorStacks
[SBit] -> Sortable
fromSBitRecs ((Sortable -> Sortable) -> STensorStack -> [SBit]
getSortedBitsFromTensor (TensortProps -> Sortable -> Sortable
subAlgorithm TensortProps
tsProps) STensorStack
topTensor)
tensortB4 :: Sortable -> Sortable
tensortB4 :: Sortable -> Sortable
tensortB4 = TensortProps -> Sortable -> Sortable
tensort (Int -> (Sortable -> Sortable) -> TensortProps
mkTsProps Int
4 Sortable -> Sortable
bubblesort)
tensortBN :: Int -> Sortable -> Sortable
tensortBN :: Int -> Sortable -> Sortable
tensortBN Int
n = TensortProps -> Sortable -> Sortable
tensort (Int -> (Sortable -> Sortable) -> TensortProps
mkTsProps Int
n Sortable -> Sortable
bubblesort)
tensortBL :: Sortable -> Sortable
tensortBL :: Sortable -> Sortable
tensortBL Sortable
xs = TensortProps -> Sortable -> Sortable
tensort (Int -> (Sortable -> Sortable) -> TensortProps
mkTsProps (Sortable -> Int
calculateBytesize Sortable
xs) Sortable -> Sortable
bubblesort) Sortable
xs
calculateBytesize :: Sortable -> Int
calculateBytesize :: Sortable -> Int
calculateBytesize (SortBit [Int]
xs) =
Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double -> Double
forall a. Floating a => a -> a
log (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
xs)) :: Double)
calculateBytesize (SortRec [Record]
xs) =
Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double -> Double
forall a. Floating a => a -> a
log (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Record] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Record]
xs)) :: Double)