module Data.PrimitiveArray.Index.Unit where
import Control.Applicative (pure)
import Control.DeepSeq (NFData(..))
import Data.Aeson (FromJSON,FromJSONKey,ToJSON,ToJSONKey)
import Data.Binary (Binary)
import Data.Hashable (Hashable)
import Data.Serialize (Serialize)
import Data.Vector.Fusion.Stream.Monadic (Step(..), map)
import Data.Vector.Unboxed.Deriving
import GHC.Generics (Generic)
import Prelude hiding (map)
import Test.QuickCheck (Arbitrary(..), choose)
import Data.PrimitiveArray.Index.Class
data Unit t = Unit
deriving (Unit t -> Unit t -> Bool
(Unit t -> Unit t -> Bool)
-> (Unit t -> Unit t -> Bool) -> Eq (Unit t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (t :: k). Unit t -> Unit t -> Bool
/= :: Unit t -> Unit t -> Bool
$c/= :: forall k (t :: k). Unit t -> Unit t -> Bool
== :: Unit t -> Unit t -> Bool
$c== :: forall k (t :: k). Unit t -> Unit t -> Bool
Eq,Eq (Unit t)
Eq (Unit t)
-> (Unit t -> Unit t -> Ordering)
-> (Unit t -> Unit t -> Bool)
-> (Unit t -> Unit t -> Bool)
-> (Unit t -> Unit t -> Bool)
-> (Unit t -> Unit t -> Bool)
-> (Unit t -> Unit t -> Unit t)
-> (Unit t -> Unit t -> Unit t)
-> Ord (Unit t)
Unit t -> Unit t -> Bool
Unit t -> Unit t -> Ordering
Unit t -> Unit t -> Unit t
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
forall k (t :: k). Eq (Unit t)
forall k (t :: k). Unit t -> Unit t -> Bool
forall k (t :: k). Unit t -> Unit t -> Ordering
forall k (t :: k). Unit t -> Unit t -> Unit t
min :: Unit t -> Unit t -> Unit t
$cmin :: forall k (t :: k). Unit t -> Unit t -> Unit t
max :: Unit t -> Unit t -> Unit t
$cmax :: forall k (t :: k). Unit t -> Unit t -> Unit t
>= :: Unit t -> Unit t -> Bool
$c>= :: forall k (t :: k). Unit t -> Unit t -> Bool
> :: Unit t -> Unit t -> Bool
$c> :: forall k (t :: k). Unit t -> Unit t -> Bool
<= :: Unit t -> Unit t -> Bool
$c<= :: forall k (t :: k). Unit t -> Unit t -> Bool
< :: Unit t -> Unit t -> Bool
$c< :: forall k (t :: k). Unit t -> Unit t -> Bool
compare :: Unit t -> Unit t -> Ordering
$ccompare :: forall k (t :: k). Unit t -> Unit t -> Ordering
$cp1Ord :: forall k (t :: k). Eq (Unit t)
Ord,Int -> Unit t -> ShowS
[Unit t] -> ShowS
Unit t -> String
(Int -> Unit t -> ShowS)
-> (Unit t -> String) -> ([Unit t] -> ShowS) -> Show (Unit t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (t :: k). Int -> Unit t -> ShowS
forall k (t :: k). [Unit t] -> ShowS
forall k (t :: k). Unit t -> String
showList :: [Unit t] -> ShowS
$cshowList :: forall k (t :: k). [Unit t] -> ShowS
show :: Unit t -> String
$cshow :: forall k (t :: k). Unit t -> String
showsPrec :: Int -> Unit t -> ShowS
$cshowsPrec :: forall k (t :: k). Int -> Unit t -> ShowS
Show,(forall x. Unit t -> Rep (Unit t) x)
-> (forall x. Rep (Unit t) x -> Unit t) -> Generic (Unit t)
forall x. Rep (Unit t) x -> Unit t
forall x. Unit t -> Rep (Unit t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (t :: k) x. Rep (Unit t) x -> Unit t
forall k (t :: k) x. Unit t -> Rep (Unit t) x
$cto :: forall k (t :: k) x. Rep (Unit t) x -> Unit t
$cfrom :: forall k (t :: k) x. Unit t -> Rep (Unit t) x
Generic,ReadPrec [Unit t]
ReadPrec (Unit t)
Int -> ReadS (Unit t)
ReadS [Unit t]
(Int -> ReadS (Unit t))
-> ReadS [Unit t]
-> ReadPrec (Unit t)
-> ReadPrec [Unit t]
-> Read (Unit t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (t :: k). ReadPrec [Unit t]
forall k (t :: k). ReadPrec (Unit t)
forall k (t :: k). Int -> ReadS (Unit t)
forall k (t :: k). ReadS [Unit t]
readListPrec :: ReadPrec [Unit t]
$creadListPrec :: forall k (t :: k). ReadPrec [Unit t]
readPrec :: ReadPrec (Unit t)
$creadPrec :: forall k (t :: k). ReadPrec (Unit t)
readList :: ReadS [Unit t]
$creadList :: forall k (t :: k). ReadS [Unit t]
readsPrec :: Int -> ReadS (Unit t)
$creadsPrec :: forall k (t :: k). Int -> ReadS (Unit t)
Read)
derivingUnbox "Unit"
[t| forall t . Unit t -> () |]
[| \ Unit -> () |]
[| \ () -> Unit |]
instance Binary (Unit t)
instance Serialize (Unit t)
instance FromJSON (Unit t)
instance FromJSONKey (Unit t)
instance ToJSON (Unit t)
instance ToJSONKey (Unit t)
instance Hashable (Unit t)
instance NFData (Unit t) where
rnf :: Unit t -> ()
rnf Unit t
Unit = ()
{-# Inline rnf #-}
instance Index (Unit t) where
data LimitType (Unit t) = LtUnit
linearIndex :: LimitType (Unit t) -> Unit t -> Int
linearIndex LimitType (Unit t)
_ Unit t
_ = Int
0
{-# Inline linearIndex #-}
size :: LimitType (Unit t) -> Int
size LimitType (Unit t)
_ = Int
1
{-# Inline size #-}
inBounds :: LimitType (Unit t) -> Unit t -> Bool
inBounds LimitType (Unit t)
_ Unit t
_ = Bool
True
{-# Inline inBounds #-}
zeroBound :: Unit t
zeroBound = Unit t
forall k (t :: k). Unit t
Unit
{-# Inline zeroBound #-}
zeroBound' :: LimitType (Unit t)
zeroBound' = LimitType (Unit t)
forall k (t :: k). LimitType (Unit t)
LtUnit
{-# Inline zeroBound' #-}
totalSize :: LimitType (Unit t) -> [Integer]
totalSize LimitType (Unit t)
LtUnit = Integer -> [Integer]
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
1
{-# Inline [0] totalSize #-}
fromLinearIndex :: LimitType (Unit t) -> Int -> Unit t
fromLinearIndex LimitType (Unit t)
_ Int
_ = Unit t
forall k (t :: k). Unit t
Unit
{-# Inline fromLinearIndex #-}
showBound :: LimitType (Unit t) -> [String]
showBound LimitType (Unit t)
_ = [String
"LtUnit"]
showIndex :: Unit t -> [String]
showIndex Unit t
_ = [String
"Unit"]
deriving instance Eq (LimitType (Unit t))
deriving instance Generic (LimitType (Unit t))
deriving instance Read (LimitType (Unit t))
deriving instance Show (LimitType (Unit t))
instance IndexStream z => IndexStream (z:.Unit t) where
streamUp :: LimitType (z :. Unit t)
-> LimitType (z :. Unit t) -> Stream m (z :. Unit t)
streamUp (ls:..LtUnit) (hs:..LtUnit) = (z -> z :. Unit t) -> Stream m z -> Stream m (z :. Unit t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
map (\z
z -> z
zz -> Unit t -> z :. Unit t
forall a b. a -> b -> a :. b
:.Unit t
forall k (t :: k). Unit t
Unit) (Stream m z -> Stream m (z :. Unit t))
-> Stream m z -> Stream m (z :. Unit t)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
{-# Inline streamUp #-}
streamDown :: LimitType (z :. Unit t)
-> LimitType (z :. Unit t) -> Stream m (z :. Unit t)
streamDown (ls:..LtUnit) (hs:..LtUnit) = (z -> z :. Unit t) -> Stream m z -> Stream m (z :. Unit t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
map (\z
z -> z
zz -> Unit t -> z :. Unit t
forall a b. a -> b -> a :. b
:.Unit t
forall k (t :: k). Unit t
Unit) (Stream m z -> Stream m (z :. Unit t))
-> Stream m z -> Stream m (z :. Unit t)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline streamDown #-}
instance (IndexStream (Z:.Unit t)) => IndexStream (Unit t) where
streamUp :: LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t)
streamUp LimitType (Unit t)
l LimitType (Unit t)
h = ((Z :. Unit t) -> Unit t)
-> Stream m (Z :. Unit t) -> Stream m (Unit t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
map (\(Z
Z:.Unit t
i) -> Unit t
i) (Stream m (Z :. Unit t) -> Stream m (Unit t))
-> Stream m (Z :. Unit t) -> Stream m (Unit t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. Unit t)
-> LimitType (Z :. Unit t) -> Stream m (Z :. Unit t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp (LimitType Z
ZZLimitType Z -> LimitType (Unit t) -> LimitType (Z :. Unit t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Unit t)
l) (LimitType Z
ZZLimitType Z -> LimitType (Unit t) -> LimitType (Z :. Unit t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Unit t)
h)
{-# INLINE streamUp #-}
streamDown :: LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t)
streamDown LimitType (Unit t)
l LimitType (Unit t)
h = ((Z :. Unit t) -> Unit t)
-> Stream m (Z :. Unit t) -> Stream m (Unit t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
map (\(Z
Z:.Unit t
i) -> Unit t
i) (Stream m (Z :. Unit t) -> Stream m (Unit t))
-> Stream m (Z :. Unit t) -> Stream m (Unit t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. Unit t)
-> LimitType (Z :. Unit t) -> Stream m (Z :. Unit t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown (LimitType Z
ZZLimitType Z -> LimitType (Unit t) -> LimitType (Z :. Unit t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Unit t)
l) (LimitType Z
ZZLimitType Z -> LimitType (Unit t) -> LimitType (Z :. Unit t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Unit t)
h)
{-# INLINE streamDown #-}
instance Arbitrary (Unit t) where
arbitrary :: Gen (Unit t)
arbitrary = Unit t -> Gen (Unit t)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Unit t
forall k (t :: k). Unit t
Unit
shrink :: Unit t -> [Unit t]
shrink Unit t
Unit = []