{- |
Copyright:  (c) 2019-2020 Veronika Romashkina
License:    MPL-2.0
Maintainer: Veronika Romashkina <vrom911@gmail.com>

Lists size representation.
-}

module Slist.Size
    ( Size (..)
    , sizes
    ) where


{- | Data type that represents lists size/lengths.

+-----------+----------+------------+
| List      | @length@ | Size       |
+===========+==========+============+
| @[]@      | @0@      | @Size 0@   |
+-----------+----------+------------+
| @[1..10]@ | @10@     | @Size 10@  |
+-----------+----------+------------+
| @[1..]@   | /hangs/  | @Infinity@ |
+-----------+----------+------------+

Note, that size is not suppose to have negative value, so use
the 'Size' constructor carefully.
-}
data Size
    -- | Finite size
    = Size !Int
    -- | Infinite size.
    | Infinity
    deriving stock (Int -> Size -> ShowS
[Size] -> ShowS
Size -> String
(Int -> Size -> ShowS)
-> (Size -> String) -> ([Size] -> ShowS) -> Show Size
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Size] -> ShowS
$cshowList :: [Size] -> ShowS
show :: Size -> String
$cshow :: Size -> String
showsPrec :: Int -> Size -> ShowS
$cshowsPrec :: Int -> Size -> ShowS
Show, ReadPrec [Size]
ReadPrec Size
Int -> ReadS Size
ReadS [Size]
(Int -> ReadS Size)
-> ReadS [Size] -> ReadPrec Size -> ReadPrec [Size] -> Read Size
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Size]
$creadListPrec :: ReadPrec [Size]
readPrec :: ReadPrec Size
$creadPrec :: ReadPrec Size
readList :: ReadS [Size]
$creadList :: ReadS [Size]
readsPrec :: Int -> ReadS Size
$creadsPrec :: Int -> ReadS Size
Read, Size -> Size -> Bool
(Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Size -> Size -> Bool
$c/= :: Size -> Size -> Bool
== :: Size -> Size -> Bool
$c== :: Size -> Size -> Bool
Eq, Eq Size
Eq Size =>
(Size -> Size -> Ordering)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> Ord Size
Size -> Size -> Bool
Size -> Size -> Ordering
Size -> Size -> Size
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 :: Size -> Size -> Size
$cmin :: Size -> Size -> Size
max :: Size -> Size -> Size
$cmax :: Size -> Size -> Size
>= :: Size -> Size -> Bool
$c>= :: Size -> Size -> Bool
> :: Size -> Size -> Bool
$c> :: Size -> Size -> Bool
<= :: Size -> Size -> Bool
$c<= :: Size -> Size -> Bool
< :: Size -> Size -> Bool
$c< :: Size -> Size -> Bool
compare :: Size -> Size -> Ordering
$ccompare :: Size -> Size -> Ordering
$cp1Ord :: Eq Size
Ord)

{- | Efficient implementations of numeric operations with 'Size's.

Any operations with 'Infinity' size results into 'Infinity'.

TODO: checking on overflow when '+' or '*' sizes.
-}
instance Num Size where
    (+) :: Size -> Size -> Size
    Infinity + :: Size -> Size -> Size
+ _ = Size
Infinity
    _ + Infinity = Size
Infinity
    (Size x :: Int
x) + (Size y :: Int
y) = Int -> Size
Size (Int -> Size) -> Int -> Size
forall a b. (a -> b) -> a -> b
$ Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y
    {-# INLINE (+) #-}

    (-) :: Size -> Size -> Size
    Infinity - :: Size -> Size -> Size
- _ = Size
Infinity
    _ - Infinity = Size
Infinity
    (Size x :: Int
x) - (Size y :: Int
y) = Int -> Size
Size (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y)
    {-# INLINE (-) #-}

    (*) :: Size -> Size -> Size
    Infinity * :: Size -> Size -> Size
* _ = Size
Infinity
    _ * Infinity = Size
Infinity
    (Size x :: Int
x) * (Size y :: Int
y) = Int -> Size
Size (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
y)
    {-# INLINE (*) #-}

    abs :: Size -> Size
    abs :: Size -> Size
abs Infinity = Size
Infinity
    abs (Size x :: Int
x) = Int -> Size
Size (Int -> Size) -> Int -> Size
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Num a => a -> a
abs Int
x
    {-# INLINE abs #-}

    signum :: Size -> Size
    signum :: Size -> Size
signum Infinity = Size
Infinity
    signum (Size x :: Int
x) = Int -> Size
Size (Int -> Int
forall a. Num a => a -> a
signum Int
x)
    {-# INLINE signum #-}

    fromInteger :: Integer -> Size
    fromInteger :: Integer -> Size
fromInteger = Int -> Size
Size (Int -> Size) -> (Integer -> Int) -> Integer -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
    {-# INLINE fromInteger #-}

{- | The minimum possible size for the list is empty list: @Size 0@
The maximum possible size is 'Infinity'.
-}
instance Bounded Size where
    minBound :: Size
    minBound :: Size
minBound = Int -> Size
Size 0

    maxBound :: Size
    maxBound :: Size
maxBound = Size
Infinity

{- | Returns the list of sizes from zero to the given one (including).

>>> sizes $ Size 3
[Size 0,Size 1,Size 2,Size 3]

@
>> __sizes Infinity__
[Size 0, Size 1, ..., Size 'maxBound', Infinity]
@
-}
sizes :: Size -> [Size]
sizes :: Size -> [Size]
sizes (Size n :: Int
n) = (Int -> Size) -> [Int] -> [Size]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Size
Size [0..Int
n]
sizes Infinity = (Int -> Size) -> [Int] -> [Size]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Size
Size [0..Int
forall a. Bounded a => a
maxBound] [Size] -> [Size] -> [Size]
forall a. [a] -> [a] -> [a]
++ [Size
Infinity]