{-# LANGUAGE RoleAnnotations #-}
module Covenant.Index
( Index,
Count,
intIndex,
intCount,
ix0,
count0,
ix1,
count1,
ix2,
count2,
ix3,
count3,
)
where
import Data.Bits (toIntegralSized)
import Data.Coerce (coerce)
import Data.List.NonEmpty (NonEmpty)
import Data.Semigroup (Semigroup (sconcat, stimes), Sum (Sum))
import Data.Word (Word32)
import GHC.TypeLits (Symbol)
import Optics.Prism (Prism', prism)
import Test.QuickCheck (Arbitrary)
newtype Index (ofWhat :: Symbol) = Index Word32
deriving
(
Index ofWhat -> Index ofWhat -> Bool
(Index ofWhat -> Index ofWhat -> Bool)
-> (Index ofWhat -> Index ofWhat -> Bool) -> Eq (Index ofWhat)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
$c== :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
== :: Index ofWhat -> Index ofWhat -> Bool
$c/= :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
/= :: Index ofWhat -> Index ofWhat -> Bool
Eq,
Eq (Index ofWhat)
Eq (Index ofWhat) =>
(Index ofWhat -> Index ofWhat -> Ordering)
-> (Index ofWhat -> Index ofWhat -> Bool)
-> (Index ofWhat -> Index ofWhat -> Bool)
-> (Index ofWhat -> Index ofWhat -> Bool)
-> (Index ofWhat -> Index ofWhat -> Bool)
-> (Index ofWhat -> Index ofWhat -> Index ofWhat)
-> (Index ofWhat -> Index ofWhat -> Index ofWhat)
-> Ord (Index ofWhat)
Index ofWhat -> Index ofWhat -> Bool
Index ofWhat -> Index ofWhat -> Ordering
Index ofWhat -> Index ofWhat -> Index ofWhat
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 (ofWhat :: Symbol). Eq (Index ofWhat)
forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Ordering
forall (ofWhat :: Symbol).
Index ofWhat -> Index ofWhat -> Index ofWhat
$ccompare :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Ordering
compare :: Index ofWhat -> Index ofWhat -> Ordering
$c< :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
< :: Index ofWhat -> Index ofWhat -> Bool
$c<= :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
<= :: Index ofWhat -> Index ofWhat -> Bool
$c> :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
> :: Index ofWhat -> Index ofWhat -> Bool
$c>= :: forall (ofWhat :: Symbol). Index ofWhat -> Index ofWhat -> Bool
>= :: Index ofWhat -> Index ofWhat -> Bool
$cmax :: forall (ofWhat :: Symbol).
Index ofWhat -> Index ofWhat -> Index ofWhat
max :: Index ofWhat -> Index ofWhat -> Index ofWhat
$cmin :: forall (ofWhat :: Symbol).
Index ofWhat -> Index ofWhat -> Index ofWhat
min :: Index ofWhat -> Index ofWhat -> Index ofWhat
Ord,
Gen (Index ofWhat)
Gen (Index ofWhat)
-> (Index ofWhat -> [Index ofWhat]) -> Arbitrary (Index ofWhat)
Index ofWhat -> [Index ofWhat]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
forall (ofWhat :: Symbol). Gen (Index ofWhat)
forall (ofWhat :: Symbol). Index ofWhat -> [Index ofWhat]
$carbitrary :: forall (ofWhat :: Symbol). Gen (Index ofWhat)
arbitrary :: Gen (Index ofWhat)
$cshrink :: forall (ofWhat :: Symbol). Index ofWhat -> [Index ofWhat]
shrink :: Index ofWhat -> [Index ofWhat]
Arbitrary
)
via Word32
deriving stock
(
Int -> Index ofWhat -> ShowS
[Index ofWhat] -> ShowS
Index ofWhat -> String
(Int -> Index ofWhat -> ShowS)
-> (Index ofWhat -> String)
-> ([Index ofWhat] -> ShowS)
-> Show (Index ofWhat)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (ofWhat :: Symbol). Int -> Index ofWhat -> ShowS
forall (ofWhat :: Symbol). [Index ofWhat] -> ShowS
forall (ofWhat :: Symbol). Index ofWhat -> String
$cshowsPrec :: forall (ofWhat :: Symbol). Int -> Index ofWhat -> ShowS
showsPrec :: Int -> Index ofWhat -> ShowS
$cshow :: forall (ofWhat :: Symbol). Index ofWhat -> String
show :: Index ofWhat -> String
$cshowList :: forall (ofWhat :: Symbol). [Index ofWhat] -> ShowS
showList :: [Index ofWhat] -> ShowS
Show
)
type role Index nominal
instance Semigroup (Index ofWhat) where
{-# INLINEABLE (<>) #-}
Index Word32
x <> :: Index ofWhat -> Index ofWhat -> Index ofWhat
<> Index Word32
y = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index (Word32
x Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
y)
{-# INLINEABLE sconcat #-}
sconcat :: NonEmpty (Index ofWhat) -> Index ofWhat
sconcat = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index (Word32 -> Index ofWhat)
-> (NonEmpty (Index ofWhat) -> Word32)
-> NonEmpty (Index ofWhat)
-> Index ofWhat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Word32 -> Word32
forall a. Num a => NonEmpty a -> a
forall (t :: Type -> Type) a. (Foldable t, Num a) => t a -> a
sum (NonEmpty Word32 -> Word32)
-> (NonEmpty (Index ofWhat) -> NonEmpty Word32)
-> NonEmpty (Index ofWhat)
-> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(NonEmpty (Index ofWhat)) @(NonEmpty Word32)
{-# INLINEABLE stimes #-}
stimes :: forall b. Integral b => b -> Index ofWhat -> Index ofWhat
stimes b
b = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index (Word32 -> Index ofWhat)
-> (Index ofWhat -> Word32) -> Index ofWhat -> Index ofWhat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum Word32 -> Word32
forall a b. Coercible a b => a -> b
coerce (Sum Word32 -> Word32)
-> (Index ofWhat -> Sum Word32) -> Index ofWhat -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Sum Word32 -> Sum Word32
forall b. Integral b => b -> Sum Word32 -> Sum Word32
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
b (Sum Word32 -> Sum Word32)
-> (Index ofWhat -> Sum Word32) -> Index ofWhat -> Sum Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @_ @(Sum Word32)
instance Monoid (Index ofWhat) where
{-# INLINEABLE mempty #-}
mempty :: Index ofWhat
mempty = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index Word32
0
intIndex :: forall (ofWhat :: Symbol). Prism' Int (Index ofWhat)
intIndex :: forall (ofWhat :: Symbol). Prism' Int (Index ofWhat)
intIndex =
(Index ofWhat -> Int)
-> (Int -> Either Int (Index ofWhat))
-> Prism Int Int (Index ofWhat) (Index ofWhat)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> (Index ofWhat -> Word32) -> Index ofWhat -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @_ @Word32)
(\Int
i -> Either Int (Index ofWhat)
-> (Word32 -> Either Int (Index ofWhat))
-> Maybe Word32
-> Either Int (Index ofWhat)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> Either Int (Index ofWhat)
forall a b. a -> Either a b
Left Int
i) (Index ofWhat -> Either Int (Index ofWhat)
forall a b. b -> Either a b
Right (Index ofWhat -> Either Int (Index ofWhat))
-> (Word32 -> Index ofWhat) -> Word32 -> Either Int (Index ofWhat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index) (Maybe Word32 -> Either Int (Index ofWhat))
-> (Int -> Maybe Word32) -> Int -> Either Int (Index ofWhat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
toIntegralSized (Int -> Either Int (Index ofWhat))
-> Int -> Either Int (Index ofWhat)
forall a b. (a -> b) -> a -> b
$ Int
i)
ix0 :: forall (ofWhat :: Symbol). Index ofWhat
ix0 :: forall (ofWhat :: Symbol). Index ofWhat
ix0 = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index Word32
0
ix1 :: forall (ofWhat :: Symbol). Index ofWhat
ix1 :: forall (ofWhat :: Symbol). Index ofWhat
ix1 = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index Word32
1
ix2 :: forall (ofWhat :: Symbol). Index ofWhat
ix2 :: forall (ofWhat :: Symbol). Index ofWhat
ix2 = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index Word32
2
ix3 :: forall (ofWhat :: Symbol). Index ofWhat
ix3 :: forall (ofWhat :: Symbol). Index ofWhat
ix3 = Word32 -> Index ofWhat
forall (ofWhat :: Symbol). Word32 -> Index ofWhat
Index Word32
3
newtype Count (ofWhat :: Symbol) = Count Word32
deriving
(
Count ofWhat -> Count ofWhat -> Bool
(Count ofWhat -> Count ofWhat -> Bool)
-> (Count ofWhat -> Count ofWhat -> Bool) -> Eq (Count ofWhat)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
$c== :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
== :: Count ofWhat -> Count ofWhat -> Bool
$c/= :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
/= :: Count ofWhat -> Count ofWhat -> Bool
Eq,
Eq (Count ofWhat)
Eq (Count ofWhat) =>
(Count ofWhat -> Count ofWhat -> Ordering)
-> (Count ofWhat -> Count ofWhat -> Bool)
-> (Count ofWhat -> Count ofWhat -> Bool)
-> (Count ofWhat -> Count ofWhat -> Bool)
-> (Count ofWhat -> Count ofWhat -> Bool)
-> (Count ofWhat -> Count ofWhat -> Count ofWhat)
-> (Count ofWhat -> Count ofWhat -> Count ofWhat)
-> Ord (Count ofWhat)
Count ofWhat -> Count ofWhat -> Bool
Count ofWhat -> Count ofWhat -> Ordering
Count ofWhat -> Count ofWhat -> Count ofWhat
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 (ofWhat :: Symbol). Eq (Count ofWhat)
forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Ordering
forall (ofWhat :: Symbol).
Count ofWhat -> Count ofWhat -> Count ofWhat
$ccompare :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Ordering
compare :: Count ofWhat -> Count ofWhat -> Ordering
$c< :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
< :: Count ofWhat -> Count ofWhat -> Bool
$c<= :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
<= :: Count ofWhat -> Count ofWhat -> Bool
$c> :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
> :: Count ofWhat -> Count ofWhat -> Bool
$c>= :: forall (ofWhat :: Symbol). Count ofWhat -> Count ofWhat -> Bool
>= :: Count ofWhat -> Count ofWhat -> Bool
$cmax :: forall (ofWhat :: Symbol).
Count ofWhat -> Count ofWhat -> Count ofWhat
max :: Count ofWhat -> Count ofWhat -> Count ofWhat
$cmin :: forall (ofWhat :: Symbol).
Count ofWhat -> Count ofWhat -> Count ofWhat
min :: Count ofWhat -> Count ofWhat -> Count ofWhat
Ord
)
via Word32
deriving stock
(
Int -> Count ofWhat -> ShowS
[Count ofWhat] -> ShowS
Count ofWhat -> String
(Int -> Count ofWhat -> ShowS)
-> (Count ofWhat -> String)
-> ([Count ofWhat] -> ShowS)
-> Show (Count ofWhat)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (ofWhat :: Symbol). Int -> Count ofWhat -> ShowS
forall (ofWhat :: Symbol). [Count ofWhat] -> ShowS
forall (ofWhat :: Symbol). Count ofWhat -> String
$cshowsPrec :: forall (ofWhat :: Symbol). Int -> Count ofWhat -> ShowS
showsPrec :: Int -> Count ofWhat -> ShowS
$cshow :: forall (ofWhat :: Symbol). Count ofWhat -> String
show :: Count ofWhat -> String
$cshowList :: forall (ofWhat :: Symbol). [Count ofWhat] -> ShowS
showList :: [Count ofWhat] -> ShowS
Show
)
type role Count nominal
intCount :: forall (ofWhat :: Symbol). Prism' Int (Count ofWhat)
intCount :: forall (ofWhat :: Symbol). Prism' Int (Count ofWhat)
intCount =
(Count ofWhat -> Int)
-> (Int -> Either Int (Count ofWhat))
-> Prism Int Int (Count ofWhat) (Count ofWhat)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> (Count ofWhat -> Word32) -> Count ofWhat -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @_ @Word32)
(\Int
i -> Either Int (Count ofWhat)
-> (Word32 -> Either Int (Count ofWhat))
-> Maybe Word32
-> Either Int (Count ofWhat)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> Either Int (Count ofWhat)
forall a b. a -> Either a b
Left Int
i) (Count ofWhat -> Either Int (Count ofWhat)
forall a b. b -> Either a b
Right (Count ofWhat -> Either Int (Count ofWhat))
-> (Word32 -> Count ofWhat) -> Word32 -> Either Int (Count ofWhat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Count ofWhat
forall (ofWhat :: Symbol). Word32 -> Count ofWhat
Count) (Maybe Word32 -> Either Int (Count ofWhat))
-> (Int -> Maybe Word32) -> Int -> Either Int (Count ofWhat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
toIntegralSized (Int -> Either Int (Count ofWhat))
-> Int -> Either Int (Count ofWhat)
forall a b. (a -> b) -> a -> b
$ Int
i)
count0 :: forall (ofWhat :: Symbol). Count ofWhat
count0 :: forall (ofWhat :: Symbol). Count ofWhat
count0 = Word32 -> Count ofWhat
forall (ofWhat :: Symbol). Word32 -> Count ofWhat
Count Word32
0
count1 :: forall (ofWhat :: Symbol). Count ofWhat
count1 :: forall (ofWhat :: Symbol). Count ofWhat
count1 = Word32 -> Count ofWhat
forall (ofWhat :: Symbol). Word32 -> Count ofWhat
Count Word32
1
count2 :: forall (ofWhat :: Symbol). Count ofWhat
count2 :: forall (ofWhat :: Symbol). Count ofWhat
count2 = Word32 -> Count ofWhat
forall (ofWhat :: Symbol). Word32 -> Count ofWhat
Count Word32
2
count3 :: forall (ofWhat :: Symbol). Count ofWhat
count3 :: forall (ofWhat :: Symbol). Count ofWhat
count3 = Word32 -> Count ofWhat
forall (ofWhat :: Symbol). Word32 -> Count ofWhat
Count Word32
3