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.LogNat (getLnBytesize)
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 []) = [Bit] -> Sortable
SortBit []
tensort TensortProps
_ (SortBit [Bit
x]) = [Bit] -> Sortable
SortBit [Bit
x]
tensort TensortProps
tsProps (SortBit [Bit
x, Bit
y]) = TensortProps -> Sortable -> Sortable
subAlgorithm TensortProps
tsProps ([Bit] -> Sortable
SortBit [Bit
x, Bit
y])
tensort TensortProps
tsProps (SortBit [Bit]
xs) = do
let bits :: Sortable
bits = Bit -> Sortable -> Sortable
randomizeList Bit
143 ([Bit] -> Sortable
SortBit [Bit]
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 = Bit -> Sortable -> Sortable
randomizeList Bit
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 (Bit -> (Sortable -> Sortable) -> TensortProps
mkTsProps Bit
4 Sortable -> Sortable
bubblesort)
tensortBN :: Int -> Sortable -> Sortable
tensortBN :: Bit -> Sortable -> Sortable
tensortBN Bit
n = TensortProps -> Sortable -> Sortable
tensort (Bit -> (Sortable -> Sortable) -> TensortProps
mkTsProps Bit
n Sortable -> Sortable
bubblesort)
tensortBL :: Sortable -> Sortable
tensortBL :: Sortable -> Sortable
tensortBL Sortable
xs = TensortProps -> Sortable -> Sortable
tensort (Bit -> (Sortable -> Sortable) -> TensortProps
mkTsProps (Sortable -> Bit
getLnBytesize Sortable
xs) Sortable -> Sortable
bubblesort) Sortable
xs