module Data.Tensort.Utils.LogNat (getLnBytesize, getLn) where
import Data.Tensort.Utils.Types (Sortable (..))
getLnBytesize :: Sortable -> Int
getLnBytesize :: Sortable -> Int
getLnBytesize (SortBit [Int]
xs) = Int -> Int
getLn ([Int] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
xs)
getLnBytesize (SortRec [Record]
xs) = Int -> Int
getLn ([Record] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Record]
xs)
getLn :: Int -> Int
getLn :: Int -> Int
getLn Int
x = 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
x) :: Double)