module Ki.Internal.ByteCount
  ( ByteCount,
    kilobytes,
    megabytes,
    byteCountToInt64,
  )
where

import Ki.Internal.Prelude

-- | A number of bytes.
newtype ByteCount = ByteCount Int64
  deriving newtype (ByteCount -> ByteCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteCount -> ByteCount -> Bool
$c/= :: ByteCount -> ByteCount -> Bool
== :: ByteCount -> ByteCount -> Bool
$c== :: ByteCount -> ByteCount -> Bool
Eq, Eq ByteCount
ByteCount -> ByteCount -> Bool
ByteCount -> ByteCount -> Ordering
ByteCount -> ByteCount -> ByteCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ByteCount -> ByteCount -> ByteCount
$cmin :: ByteCount -> ByteCount -> ByteCount
max :: ByteCount -> ByteCount -> ByteCount
$cmax :: ByteCount -> ByteCount -> ByteCount
>= :: ByteCount -> ByteCount -> Bool
$c>= :: ByteCount -> ByteCount -> Bool
> :: ByteCount -> ByteCount -> Bool
$c> :: ByteCount -> ByteCount -> Bool
<= :: ByteCount -> ByteCount -> Bool
$c<= :: ByteCount -> ByteCount -> Bool
< :: ByteCount -> ByteCount -> Bool
$c< :: ByteCount -> ByteCount -> Bool
compare :: ByteCount -> ByteCount -> Ordering
$ccompare :: ByteCount -> ByteCount -> Ordering
Ord)

instance Show ByteCount where
  show :: ByteCount -> String
show (ByteCount Int64
b)
    | (Int64
mb, Int64
0) <- forall a. Integral a => a -> a -> (a, a)
quotRem Int64
b Int64
1048576, Int64
mb forall a. Ord a => a -> a -> Bool
> Int64
0 = String
"megabytes " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int64
mb
    | (Int64
kb, Int64
0) <- forall a. Integral a => a -> a -> (a, a)
quotRem Int64
b Int64
1024 = String
"kilobytes " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int64
kb
    | Bool
otherwise = forall a. HasCallStack => a
undefined

-- | A number of kilobytes.
kilobytes :: Natural -> ByteCount
kilobytes :: Natural -> ByteCount
kilobytes Natural
n =
  Int64 -> ByteCount
ByteCount (Natural -> Int64
snip (Natural
n forall a. Num a => a -> a -> a
* Natural
1024))

-- | A number of megabytes.
megabytes :: Natural -> ByteCount
megabytes :: Natural -> ByteCount
megabytes Natural
n =
  Int64 -> ByteCount
ByteCount (Natural -> Int64
snip (Natural
n forall a. Num a => a -> a -> a
* Natural
1048576))

byteCountToInt64 :: ByteCount -> Int64
byteCountToInt64 :: ByteCount -> Int64
byteCountToInt64 =
  coerce :: forall a b. Coercible a b => a -> b
coerce

snip :: Natural -> Int64
snip :: Natural -> Int64
snip Natural
n =
  forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Ord a => a -> a -> a
min (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bounded a => a
maxBound :: Int64)) Natural
n)