{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

module Byron.Spec.Ledger.Core where

import Cardano.Ledger.Binary (DecCBOR, EncCBOR, FromCBOR, ToCBOR (..), toByronCBOR)
import Data.AbstractSize
import Data.Bimap (Bimap)
import qualified Data.Bimap as Bimap
import Data.Data (Data, Typeable)
import Data.Foldable (toList)
import Data.Hashable (Hashable)
import qualified Data.Hashable as H
import Data.Int (Int64)
import Data.Kind (Type)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (isJust)
import Data.Monoid (Sum (..))
import qualified Data.Sequence as Seq
import Data.Set (Set, intersection, isSubsetOf)
import qualified Data.Set as Set
import Data.Typeable (typeOf)
import Data.Word (Word64, Word8)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
import Numeric.Natural (Natural)

-- | An encoded hash of part of the system.
--
-- 'Nothing' is used to signal to the elaborators (i.e. the algorithms that
-- translate abstract data into data concrete) that they should produce an
-- invalid concrete hash.
newtype Hash = Hash
  { Hash -> Maybe Int
unHash :: Maybe Int
  }
  deriving stock (Int -> Hash -> ShowS
[Hash] -> ShowS
Hash -> String
(Int -> Hash -> ShowS)
-> (Hash -> String) -> ([Hash] -> ShowS) -> Show Hash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash -> ShowS
showsPrec :: Int -> Hash -> ShowS
$cshow :: Hash -> String
show :: Hash -> String
$cshowList :: [Hash] -> ShowS
showList :: [Hash] -> ShowS
Show, (forall x. Hash -> Rep Hash x)
-> (forall x. Rep Hash x -> Hash) -> Generic Hash
forall x. Rep Hash x -> Hash
forall x. Hash -> Rep Hash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Hash -> Rep Hash x
from :: forall x. Hash -> Rep Hash x
$cto :: forall x. Rep Hash x -> Hash
to :: forall x. Rep Hash x -> Hash
Generic, Typeable Hash
Typeable Hash =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Hash -> c Hash)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Hash)
-> (Hash -> Constr)
-> (Hash -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Hash))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hash))
-> ((forall b. Data b => b -> b) -> Hash -> Hash)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r)
-> (forall u. (forall d. Data d => d -> u) -> Hash -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Hash -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Hash -> m Hash)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Hash -> m Hash)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Hash -> m Hash)
-> Data Hash
Hash -> Constr
Hash -> DataType
(forall b. Data b => b -> b) -> Hash -> Hash
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Hash -> u
forall u. (forall d. Data d => d -> u) -> Hash -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Hash
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hash -> c Hash
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Hash)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hash)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hash -> c Hash
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hash -> c Hash
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Hash
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Hash
$ctoConstr :: Hash -> Constr
toConstr :: Hash -> Constr
$cdataTypeOf :: Hash -> DataType
dataTypeOf :: Hash -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Hash)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Hash)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hash)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hash)
$cgmapT :: (forall b. Data b => b -> b) -> Hash -> Hash
gmapT :: (forall b. Data b => b -> b) -> Hash -> Hash
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Hash -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Hash -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Hash -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Hash -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hash -> m Hash
Data)
  deriving newtype (Hash -> Hash -> Bool
(Hash -> Hash -> Bool) -> (Hash -> Hash -> Bool) -> Eq Hash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash -> Hash -> Bool
== :: Hash -> Hash -> Bool
$c/= :: Hash -> Hash -> Bool
/= :: Hash -> Hash -> Bool
Eq, Eq Hash
Eq Hash =>
(Hash -> Hash -> Ordering)
-> (Hash -> Hash -> Bool)
-> (Hash -> Hash -> Bool)
-> (Hash -> Hash -> Bool)
-> (Hash -> Hash -> Bool)
-> (Hash -> Hash -> Hash)
-> (Hash -> Hash -> Hash)
-> Ord Hash
Hash -> Hash -> Bool
Hash -> Hash -> Ordering
Hash -> Hash -> Hash
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
$ccompare :: Hash -> Hash -> Ordering
compare :: Hash -> Hash -> Ordering
$c< :: Hash -> Hash -> Bool
< :: Hash -> Hash -> Bool
$c<= :: Hash -> Hash -> Bool
<= :: Hash -> Hash -> Bool
$c> :: Hash -> Hash -> Bool
> :: Hash -> Hash -> Bool
$c>= :: Hash -> Hash -> Bool
>= :: Hash -> Hash -> Bool
$cmax :: Hash -> Hash -> Hash
max :: Hash -> Hash -> Hash
$cmin :: Hash -> Hash -> Hash
min :: Hash -> Hash -> Hash
Ord, Eq Hash
Eq Hash => (Int -> Hash -> Int) -> (Hash -> Int) -> Hashable Hash
Int -> Hash -> Int
Hash -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Hash -> Int
hashWithSalt :: Int -> Hash -> Int
$chash :: Hash -> Int
hash :: Hash -> Int
Hashable, Typeable Hash
Typeable Hash =>
(Hash -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Hash -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Hash] -> Size)
-> EncCBOR Hash
Hash -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Hash] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Hash -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Hash -> Encoding
encCBOR :: Hash -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Hash -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Hash -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Hash] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Hash] -> Size
EncCBOR, Context -> Hash -> IO (Maybe ThunkInfo)
Proxy Hash -> String
(Context -> Hash -> IO (Maybe ThunkInfo))
-> (Context -> Hash -> IO (Maybe ThunkInfo))
-> (Proxy Hash -> String)
-> NoThunks Hash
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Hash -> IO (Maybe ThunkInfo)
noThunks :: Context -> Hash -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Hash -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Hash -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Hash -> String
showTypeOf :: Proxy Hash -> String
NoThunks)
  deriving anyclass (Hash -> Seq TypeRep
(Hash -> Seq TypeRep) -> HasTypeReps Hash
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Hash -> Seq TypeRep
typeReps :: Hash -> Seq TypeRep
HasTypeReps)

instance ToCBOR Hash where
  toCBOR :: Hash -> Encoding
toCBOR = Hash -> Encoding
forall a. EncCBOR a => a -> Encoding
toByronCBOR

isValid :: Hash -> Bool
isValid :: Hash -> Bool
isValid = Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Int -> Bool) -> (Hash -> Maybe Int) -> Hash -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash -> Maybe Int
unHash

-- | Hash part of the ledger payload
class HasHash a where
  hash :: a -> Hash

---------------------------------------------------------------------------------
-- Signing and verification
---------------------------------------------------------------------------------

-- | Representation of the owner of key pair.
newtype Owner = Owner
  { Owner -> Natural
unOwner :: Natural
  }
  deriving stock (Int -> Owner -> ShowS
[Owner] -> ShowS
Owner -> String
(Int -> Owner -> ShowS)
-> (Owner -> String) -> ([Owner] -> ShowS) -> Show Owner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Owner -> ShowS
showsPrec :: Int -> Owner -> ShowS
$cshow :: Owner -> String
show :: Owner -> String
$cshowList :: [Owner] -> ShowS
showList :: [Owner] -> ShowS
Show, (forall x. Owner -> Rep Owner x)
-> (forall x. Rep Owner x -> Owner) -> Generic Owner
forall x. Rep Owner x -> Owner
forall x. Owner -> Rep Owner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Owner -> Rep Owner x
from :: forall x. Owner -> Rep Owner x
$cto :: forall x. Rep Owner x -> Owner
to :: forall x. Rep Owner x -> Owner
Generic, Typeable Owner
Typeable Owner =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Owner -> c Owner)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Owner)
-> (Owner -> Constr)
-> (Owner -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Owner))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner))
-> ((forall b. Data b => b -> b) -> Owner -> Owner)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r)
-> (forall u. (forall d. Data d => d -> u) -> Owner -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Owner -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Owner -> m Owner)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Owner -> m Owner)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Owner -> m Owner)
-> Data Owner
Owner -> Constr
Owner -> DataType
(forall b. Data b => b -> b) -> Owner -> Owner
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Owner -> u
forall u. (forall d. Data d => d -> u) -> Owner -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Owner
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Owner -> c Owner
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Owner)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Owner -> c Owner
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Owner -> c Owner
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Owner
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Owner
$ctoConstr :: Owner -> Constr
toConstr :: Owner -> Constr
$cdataTypeOf :: Owner -> DataType
dataTypeOf :: Owner -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Owner)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Owner)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner)
$cgmapT :: (forall b. Data b => b -> b) -> Owner -> Owner
gmapT :: (forall b. Data b => b -> b) -> Owner -> Owner
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Owner -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Owner -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Owner -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Owner -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Owner -> m Owner
Data)
  deriving newtype (Owner -> Owner -> Bool
(Owner -> Owner -> Bool) -> (Owner -> Owner -> Bool) -> Eq Owner
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Owner -> Owner -> Bool
== :: Owner -> Owner -> Bool
$c/= :: Owner -> Owner -> Bool
/= :: Owner -> Owner -> Bool
Eq, Eq Owner
Eq Owner =>
(Owner -> Owner -> Ordering)
-> (Owner -> Owner -> Bool)
-> (Owner -> Owner -> Bool)
-> (Owner -> Owner -> Bool)
-> (Owner -> Owner -> Bool)
-> (Owner -> Owner -> Owner)
-> (Owner -> Owner -> Owner)
-> Ord Owner
Owner -> Owner -> Bool
Owner -> Owner -> Ordering
Owner -> Owner -> Owner
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
$ccompare :: Owner -> Owner -> Ordering
compare :: Owner -> Owner -> Ordering
$c< :: Owner -> Owner -> Bool
< :: Owner -> Owner -> Bool
$c<= :: Owner -> Owner -> Bool
<= :: Owner -> Owner -> Bool
$c> :: Owner -> Owner -> Bool
> :: Owner -> Owner -> Bool
$c>= :: Owner -> Owner -> Bool
>= :: Owner -> Owner -> Bool
$cmax :: Owner -> Owner -> Owner
max :: Owner -> Owner -> Owner
$cmin :: Owner -> Owner -> Owner
min :: Owner -> Owner -> Owner
Ord, Eq Owner
Eq Owner =>
(Int -> Owner -> Int) -> (Owner -> Int) -> Hashable Owner
Int -> Owner -> Int
Owner -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Owner -> Int
hashWithSalt :: Int -> Owner -> Int
$chash :: Owner -> Int
hash :: Owner -> Int
Hashable, Typeable Owner
Typeable Owner =>
(forall s. Decoder s Owner)
-> (forall s. Proxy Owner -> Decoder s ())
-> (Proxy Owner -> Text)
-> DecCBOR Owner
Proxy Owner -> Text
forall s. Decoder s Owner
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy Owner -> Decoder s ()
$cdecCBOR :: forall s. Decoder s Owner
decCBOR :: forall s. Decoder s Owner
$cdropCBOR :: forall s. Proxy Owner -> Decoder s ()
dropCBOR :: forall s. Proxy Owner -> Decoder s ()
$clabel :: Proxy Owner -> Text
label :: Proxy Owner -> Text
DecCBOR, Typeable Owner
Typeable Owner =>
(Owner -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy Owner -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Owner] -> Size)
-> EncCBOR Owner
Owner -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Owner -> Encoding
encCBOR :: Owner -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
EncCBOR, Typeable Owner
Typeable Owner =>
(forall s. Decoder s Owner)
-> (Proxy Owner -> Text) -> FromCBOR Owner
Proxy Owner -> Text
forall s. Decoder s Owner
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s Owner
fromCBOR :: forall s. Decoder s Owner
$clabel :: Proxy Owner -> Text
label :: Proxy Owner -> Text
FromCBOR, Typeable Owner
Typeable Owner =>
(Owner -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Owner -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Owner] -> Size)
-> ToCBOR Owner
Owner -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Owner -> Encoding
toCBOR :: Owner -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Owner -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Owner] -> Size
ToCBOR, Context -> Owner -> IO (Maybe ThunkInfo)
Proxy Owner -> String
(Context -> Owner -> IO (Maybe ThunkInfo))
-> (Context -> Owner -> IO (Maybe ThunkInfo))
-> (Proxy Owner -> String)
-> NoThunks Owner
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Owner -> IO (Maybe ThunkInfo)
noThunks :: Context -> Owner -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Owner -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Owner -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Owner -> String
showTypeOf :: Proxy Owner -> String
NoThunks)
  deriving anyclass (Owner -> Seq TypeRep
(Owner -> Seq TypeRep) -> HasTypeReps Owner
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Owner -> Seq TypeRep
typeReps :: Owner -> Seq TypeRep
HasTypeReps)

class HasOwner a where
  owner :: a -> Owner

-- | Signing Key.
newtype SKey = SKey Owner
  deriving stock (Int -> SKey -> ShowS
[SKey] -> ShowS
SKey -> String
(Int -> SKey -> ShowS)
-> (SKey -> String) -> ([SKey] -> ShowS) -> Show SKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SKey -> ShowS
showsPrec :: Int -> SKey -> ShowS
$cshow :: SKey -> String
show :: SKey -> String
$cshowList :: [SKey] -> ShowS
showList :: [SKey] -> ShowS
Show, (forall x. SKey -> Rep SKey x)
-> (forall x. Rep SKey x -> SKey) -> Generic SKey
forall x. Rep SKey x -> SKey
forall x. SKey -> Rep SKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SKey -> Rep SKey x
from :: forall x. SKey -> Rep SKey x
$cto :: forall x. Rep SKey x -> SKey
to :: forall x. Rep SKey x -> SKey
Generic, Typeable SKey
Typeable SKey =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SKey -> c SKey)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SKey)
-> (SKey -> Constr)
-> (SKey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SKey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SKey))
-> ((forall b. Data b => b -> b) -> SKey -> SKey)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r)
-> (forall u. (forall d. Data d => d -> u) -> SKey -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> SKey -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SKey -> m SKey)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SKey -> m SKey)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SKey -> m SKey)
-> Data SKey
SKey -> Constr
SKey -> DataType
(forall b. Data b => b -> b) -> SKey -> SKey
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SKey -> u
forall u. (forall d. Data d => d -> u) -> SKey -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SKey -> c SKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SKey)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SKey -> c SKey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SKey -> c SKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SKey
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SKey
$ctoConstr :: SKey -> Constr
toConstr :: SKey -> Constr
$cdataTypeOf :: SKey -> DataType
dataTypeOf :: SKey -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SKey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SKey)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SKey)
$cgmapT :: (forall b. Data b => b -> b) -> SKey -> SKey
gmapT :: (forall b. Data b => b -> b) -> SKey -> SKey
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SKey -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SKey -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SKey -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SKey -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SKey -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SKey -> m SKey
Data)
  deriving newtype (SKey -> SKey -> Bool
(SKey -> SKey -> Bool) -> (SKey -> SKey -> Bool) -> Eq SKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SKey -> SKey -> Bool
== :: SKey -> SKey -> Bool
$c/= :: SKey -> SKey -> Bool
/= :: SKey -> SKey -> Bool
Eq, Eq SKey
Eq SKey =>
(SKey -> SKey -> Ordering)
-> (SKey -> SKey -> Bool)
-> (SKey -> SKey -> Bool)
-> (SKey -> SKey -> Bool)
-> (SKey -> SKey -> Bool)
-> (SKey -> SKey -> SKey)
-> (SKey -> SKey -> SKey)
-> Ord SKey
SKey -> SKey -> Bool
SKey -> SKey -> Ordering
SKey -> SKey -> SKey
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
$ccompare :: SKey -> SKey -> Ordering
compare :: SKey -> SKey -> Ordering
$c< :: SKey -> SKey -> Bool
< :: SKey -> SKey -> Bool
$c<= :: SKey -> SKey -> Bool
<= :: SKey -> SKey -> Bool
$c> :: SKey -> SKey -> Bool
> :: SKey -> SKey -> Bool
$c>= :: SKey -> SKey -> Bool
>= :: SKey -> SKey -> Bool
$cmax :: SKey -> SKey -> SKey
max :: SKey -> SKey -> SKey
$cmin :: SKey -> SKey -> SKey
min :: SKey -> SKey -> SKey
Ord, Typeable SKey
Typeable SKey =>
(SKey -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy SKey -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [SKey] -> Size)
-> EncCBOR SKey
SKey -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: SKey -> Encoding
encCBOR :: SKey -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
EncCBOR, Typeable SKey
Typeable SKey =>
(SKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy SKey -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SKey] -> Size)
-> ToCBOR SKey
SKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SKey -> Encoding
toCBOR :: SKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SKey -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SKey] -> Size
ToCBOR, Context -> SKey -> IO (Maybe ThunkInfo)
Proxy SKey -> String
(Context -> SKey -> IO (Maybe ThunkInfo))
-> (Context -> SKey -> IO (Maybe ThunkInfo))
-> (Proxy SKey -> String)
-> NoThunks SKey
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> SKey -> IO (Maybe ThunkInfo)
noThunks :: Context -> SKey -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SKey -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> SKey -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy SKey -> String
showTypeOf :: Proxy SKey -> String
NoThunks)
  deriving anyclass (SKey -> Seq TypeRep
(SKey -> Seq TypeRep) -> HasTypeReps SKey
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: SKey -> Seq TypeRep
typeReps :: SKey -> Seq TypeRep
HasTypeReps)

instance HasOwner SKey where
  owner :: SKey -> Owner
owner (SKey Owner
o) = Owner
o

-- | Verification Key.
newtype VKey = VKey Owner
  deriving stock (Int -> VKey -> ShowS
[VKey] -> ShowS
VKey -> String
(Int -> VKey -> ShowS)
-> (VKey -> String) -> ([VKey] -> ShowS) -> Show VKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VKey -> ShowS
showsPrec :: Int -> VKey -> ShowS
$cshow :: VKey -> String
show :: VKey -> String
$cshowList :: [VKey] -> ShowS
showList :: [VKey] -> ShowS
Show, (forall x. VKey -> Rep VKey x)
-> (forall x. Rep VKey x -> VKey) -> Generic VKey
forall x. Rep VKey x -> VKey
forall x. VKey -> Rep VKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VKey -> Rep VKey x
from :: forall x. VKey -> Rep VKey x
$cto :: forall x. Rep VKey x -> VKey
to :: forall x. Rep VKey x -> VKey
Generic, Typeable VKey
Typeable VKey =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> VKey -> c VKey)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VKey)
-> (VKey -> Constr)
-> (VKey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VKey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VKey))
-> ((forall b. Data b => b -> b) -> VKey -> VKey)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r)
-> (forall u. (forall d. Data d => d -> u) -> VKey -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> VKey -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> VKey -> m VKey)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VKey -> m VKey)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VKey -> m VKey)
-> Data VKey
VKey -> Constr
VKey -> DataType
(forall b. Data b => b -> b) -> VKey -> VKey
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VKey -> u
forall u. (forall d. Data d => d -> u) -> VKey -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKey -> c VKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VKey)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKey -> c VKey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKey -> c VKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKey
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKey
$ctoConstr :: VKey -> Constr
toConstr :: VKey -> Constr
$cdataTypeOf :: VKey -> DataType
dataTypeOf :: VKey -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VKey)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VKey)
$cgmapT :: (forall b. Data b => b -> b) -> VKey -> VKey
gmapT :: (forall b. Data b => b -> b) -> VKey -> VKey
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VKey -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VKey -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> VKey -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VKey -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VKey -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKey -> m VKey
Data)
  deriving newtype (VKey -> VKey -> Bool
(VKey -> VKey -> Bool) -> (VKey -> VKey -> Bool) -> Eq VKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VKey -> VKey -> Bool
== :: VKey -> VKey -> Bool
$c/= :: VKey -> VKey -> Bool
/= :: VKey -> VKey -> Bool
Eq, Eq VKey
Eq VKey =>
(VKey -> VKey -> Ordering)
-> (VKey -> VKey -> Bool)
-> (VKey -> VKey -> Bool)
-> (VKey -> VKey -> Bool)
-> (VKey -> VKey -> Bool)
-> (VKey -> VKey -> VKey)
-> (VKey -> VKey -> VKey)
-> Ord VKey
VKey -> VKey -> Bool
VKey -> VKey -> Ordering
VKey -> VKey -> VKey
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
$ccompare :: VKey -> VKey -> Ordering
compare :: VKey -> VKey -> Ordering
$c< :: VKey -> VKey -> Bool
< :: VKey -> VKey -> Bool
$c<= :: VKey -> VKey -> Bool
<= :: VKey -> VKey -> Bool
$c> :: VKey -> VKey -> Bool
> :: VKey -> VKey -> Bool
$c>= :: VKey -> VKey -> Bool
>= :: VKey -> VKey -> Bool
$cmax :: VKey -> VKey -> VKey
max :: VKey -> VKey -> VKey
$cmin :: VKey -> VKey -> VKey
min :: VKey -> VKey -> VKey
Ord, Eq VKey
Eq VKey => (Int -> VKey -> Int) -> (VKey -> Int) -> Hashable VKey
Int -> VKey -> Int
VKey -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> VKey -> Int
hashWithSalt :: Int -> VKey -> Int
$chash :: VKey -> Int
hash :: VKey -> Int
Hashable, Typeable VKey
Typeable VKey =>
(forall s. Decoder s VKey)
-> (forall s. Proxy VKey -> Decoder s ())
-> (Proxy VKey -> Text)
-> DecCBOR VKey
Proxy VKey -> Text
forall s. Decoder s VKey
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy VKey -> Decoder s ()
$cdecCBOR :: forall s. Decoder s VKey
decCBOR :: forall s. Decoder s VKey
$cdropCBOR :: forall s. Proxy VKey -> Decoder s ()
dropCBOR :: forall s. Proxy VKey -> Decoder s ()
$clabel :: Proxy VKey -> Text
label :: Proxy VKey -> Text
DecCBOR, Typeable VKey
Typeable VKey =>
(VKey -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy VKey -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [VKey] -> Size)
-> EncCBOR VKey
VKey -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: VKey -> Encoding
encCBOR :: VKey -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
EncCBOR, Typeable VKey
Typeable VKey =>
(forall s. Decoder s VKey) -> (Proxy VKey -> Text) -> FromCBOR VKey
Proxy VKey -> Text
forall s. Decoder s VKey
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s VKey
fromCBOR :: forall s. Decoder s VKey
$clabel :: Proxy VKey -> Text
label :: Proxy VKey -> Text
FromCBOR, Typeable VKey
Typeable VKey =>
(VKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy VKey -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VKey] -> Size)
-> ToCBOR VKey
VKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VKey -> Encoding
toCBOR :: VKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy VKey -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VKey] -> Size
ToCBOR, Context -> VKey -> IO (Maybe ThunkInfo)
Proxy VKey -> String
(Context -> VKey -> IO (Maybe ThunkInfo))
-> (Context -> VKey -> IO (Maybe ThunkInfo))
-> (Proxy VKey -> String)
-> NoThunks VKey
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> VKey -> IO (Maybe ThunkInfo)
noThunks :: Context -> VKey -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> VKey -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> VKey -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy VKey -> String
showTypeOf :: Proxy VKey -> String
NoThunks)
  deriving anyclass (VKey -> Seq TypeRep
(VKey -> Seq TypeRep) -> HasTypeReps VKey
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: VKey -> Seq TypeRep
typeReps :: VKey -> Seq TypeRep
HasTypeReps)

instance HasHash VKey where
  hash :: VKey -> Hash
hash = Maybe Int -> Hash
Hash (Maybe Int -> Hash) -> (VKey -> Maybe Int) -> VKey -> Hash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (VKey -> Int) -> VKey -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VKey -> Int
forall a. Hashable a => a -> Int
H.hash

instance HasOwner VKey where
  owner :: VKey -> Owner
owner (VKey Owner
o) = Owner
o

-- | A genesis key is a specialisation of a generic VKey.
newtype VKeyGenesis = VKeyGenesis {VKeyGenesis -> VKey
unVKeyGenesis :: VKey}
  deriving stock (Int -> VKeyGenesis -> ShowS
[VKeyGenesis] -> ShowS
VKeyGenesis -> String
(Int -> VKeyGenesis -> ShowS)
-> (VKeyGenesis -> String)
-> ([VKeyGenesis] -> ShowS)
-> Show VKeyGenesis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VKeyGenesis -> ShowS
showsPrec :: Int -> VKeyGenesis -> ShowS
$cshow :: VKeyGenesis -> String
show :: VKeyGenesis -> String
$cshowList :: [VKeyGenesis] -> ShowS
showList :: [VKeyGenesis] -> ShowS
Show, (forall x. VKeyGenesis -> Rep VKeyGenesis x)
-> (forall x. Rep VKeyGenesis x -> VKeyGenesis)
-> Generic VKeyGenesis
forall x. Rep VKeyGenesis x -> VKeyGenesis
forall x. VKeyGenesis -> Rep VKeyGenesis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VKeyGenesis -> Rep VKeyGenesis x
from :: forall x. VKeyGenesis -> Rep VKeyGenesis x
$cto :: forall x. Rep VKeyGenesis x -> VKeyGenesis
to :: forall x. Rep VKeyGenesis x -> VKeyGenesis
Generic, Typeable VKeyGenesis
Typeable VKeyGenesis =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> VKeyGenesis -> c VKeyGenesis)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VKeyGenesis)
-> (VKeyGenesis -> Constr)
-> (VKeyGenesis -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VKeyGenesis))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VKeyGenesis))
-> ((forall b. Data b => b -> b) -> VKeyGenesis -> VKeyGenesis)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r)
-> (forall u. (forall d. Data d => d -> u) -> VKeyGenesis -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VKeyGenesis -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis)
-> Data VKeyGenesis
VKeyGenesis -> Constr
VKeyGenesis -> DataType
(forall b. Data b => b -> b) -> VKeyGenesis -> VKeyGenesis
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VKeyGenesis -> u
forall u. (forall d. Data d => d -> u) -> VKeyGenesis -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKeyGenesis
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKeyGenesis -> c VKeyGenesis
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKeyGenesis)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VKeyGenesis)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKeyGenesis -> c VKeyGenesis
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VKeyGenesis -> c VKeyGenesis
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKeyGenesis
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VKeyGenesis
$ctoConstr :: VKeyGenesis -> Constr
toConstr :: VKeyGenesis -> Constr
$cdataTypeOf :: VKeyGenesis -> DataType
dataTypeOf :: VKeyGenesis -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKeyGenesis)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VKeyGenesis)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VKeyGenesis)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VKeyGenesis)
$cgmapT :: (forall b. Data b => b -> b) -> VKeyGenesis -> VKeyGenesis
gmapT :: (forall b. Data b => b -> b) -> VKeyGenesis -> VKeyGenesis
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VKeyGenesis -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VKeyGenesis -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> VKeyGenesis -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VKeyGenesis -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VKeyGenesis -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VKeyGenesis -> m VKeyGenesis
Data)
  deriving newtype (VKeyGenesis -> VKeyGenesis -> Bool
(VKeyGenesis -> VKeyGenesis -> Bool)
-> (VKeyGenesis -> VKeyGenesis -> Bool) -> Eq VKeyGenesis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VKeyGenesis -> VKeyGenesis -> Bool
== :: VKeyGenesis -> VKeyGenesis -> Bool
$c/= :: VKeyGenesis -> VKeyGenesis -> Bool
/= :: VKeyGenesis -> VKeyGenesis -> Bool
Eq, Eq VKeyGenesis
Eq VKeyGenesis =>
(VKeyGenesis -> VKeyGenesis -> Ordering)
-> (VKeyGenesis -> VKeyGenesis -> Bool)
-> (VKeyGenesis -> VKeyGenesis -> Bool)
-> (VKeyGenesis -> VKeyGenesis -> Bool)
-> (VKeyGenesis -> VKeyGenesis -> Bool)
-> (VKeyGenesis -> VKeyGenesis -> VKeyGenesis)
-> (VKeyGenesis -> VKeyGenesis -> VKeyGenesis)
-> Ord VKeyGenesis
VKeyGenesis -> VKeyGenesis -> Bool
VKeyGenesis -> VKeyGenesis -> Ordering
VKeyGenesis -> VKeyGenesis -> VKeyGenesis
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
$ccompare :: VKeyGenesis -> VKeyGenesis -> Ordering
compare :: VKeyGenesis -> VKeyGenesis -> Ordering
$c< :: VKeyGenesis -> VKeyGenesis -> Bool
< :: VKeyGenesis -> VKeyGenesis -> Bool
$c<= :: VKeyGenesis -> VKeyGenesis -> Bool
<= :: VKeyGenesis -> VKeyGenesis -> Bool
$c> :: VKeyGenesis -> VKeyGenesis -> Bool
> :: VKeyGenesis -> VKeyGenesis -> Bool
$c>= :: VKeyGenesis -> VKeyGenesis -> Bool
>= :: VKeyGenesis -> VKeyGenesis -> Bool
$cmax :: VKeyGenesis -> VKeyGenesis -> VKeyGenesis
max :: VKeyGenesis -> VKeyGenesis -> VKeyGenesis
$cmin :: VKeyGenesis -> VKeyGenesis -> VKeyGenesis
min :: VKeyGenesis -> VKeyGenesis -> VKeyGenesis
Ord, Eq VKeyGenesis
Eq VKeyGenesis =>
(Int -> VKeyGenesis -> Int)
-> (VKeyGenesis -> Int) -> Hashable VKeyGenesis
Int -> VKeyGenesis -> Int
VKeyGenesis -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> VKeyGenesis -> Int
hashWithSalt :: Int -> VKeyGenesis -> Int
$chash :: VKeyGenesis -> Int
hash :: VKeyGenesis -> Int
Hashable, VKeyGenesis -> Hash
(VKeyGenesis -> Hash) -> HasHash VKeyGenesis
forall a. (a -> Hash) -> HasHash a
$chash :: VKeyGenesis -> Hash
hash :: VKeyGenesis -> Hash
HasHash, Typeable VKeyGenesis
Typeable VKeyGenesis =>
(forall s. Decoder s VKeyGenesis)
-> (forall s. Proxy VKeyGenesis -> Decoder s ())
-> (Proxy VKeyGenesis -> Text)
-> DecCBOR VKeyGenesis
Proxy VKeyGenesis -> Text
forall s. Decoder s VKeyGenesis
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy VKeyGenesis -> Decoder s ()
$cdecCBOR :: forall s. Decoder s VKeyGenesis
decCBOR :: forall s. Decoder s VKeyGenesis
$cdropCBOR :: forall s. Proxy VKeyGenesis -> Decoder s ()
dropCBOR :: forall s. Proxy VKeyGenesis -> Decoder s ()
$clabel :: Proxy VKeyGenesis -> Text
label :: Proxy VKeyGenesis -> Text
DecCBOR, Typeable VKeyGenesis
Typeable VKeyGenesis =>
(VKeyGenesis -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy VKeyGenesis -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [VKeyGenesis] -> Size)
-> EncCBOR VKeyGenesis
VKeyGenesis -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: VKeyGenesis -> Encoding
encCBOR :: VKeyGenesis -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
EncCBOR, Typeable VKeyGenesis
Typeable VKeyGenesis =>
(forall s. Decoder s VKeyGenesis)
-> (Proxy VKeyGenesis -> Text) -> FromCBOR VKeyGenesis
Proxy VKeyGenesis -> Text
forall s. Decoder s VKeyGenesis
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s VKeyGenesis
fromCBOR :: forall s. Decoder s VKeyGenesis
$clabel :: Proxy VKeyGenesis -> Text
label :: Proxy VKeyGenesis -> Text
FromCBOR, Typeable VKeyGenesis
Typeable VKeyGenesis =>
(VKeyGenesis -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy VKeyGenesis -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VKeyGenesis] -> Size)
-> ToCBOR VKeyGenesis
VKeyGenesis -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VKeyGenesis -> Encoding
toCBOR :: VKeyGenesis -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy VKeyGenesis -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VKeyGenesis] -> Size
ToCBOR, Context -> VKeyGenesis -> IO (Maybe ThunkInfo)
Proxy VKeyGenesis -> String
(Context -> VKeyGenesis -> IO (Maybe ThunkInfo))
-> (Context -> VKeyGenesis -> IO (Maybe ThunkInfo))
-> (Proxy VKeyGenesis -> String)
-> NoThunks VKeyGenesis
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> VKeyGenesis -> IO (Maybe ThunkInfo)
noThunks :: Context -> VKeyGenesis -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> VKeyGenesis -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> VKeyGenesis -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy VKeyGenesis -> String
showTypeOf :: Proxy VKeyGenesis -> String
NoThunks)
  deriving anyclass (VKeyGenesis -> Seq TypeRep
(VKeyGenesis -> Seq TypeRep) -> HasTypeReps VKeyGenesis
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: VKeyGenesis -> Seq TypeRep
typeReps :: VKeyGenesis -> Seq TypeRep
HasTypeReps)

instance HasOwner VKeyGenesis where
  owner :: VKeyGenesis -> Owner
owner (VKeyGenesis VKey
vk) = VKey -> Owner
forall a. HasOwner a => a -> Owner
owner VKey
vk

mkVKeyGenesis :: Natural -> VKeyGenesis
mkVKeyGenesis :: Natural -> VKeyGenesis
mkVKeyGenesis = VKey -> VKeyGenesis
VKeyGenesis (VKey -> VKeyGenesis)
-> (Natural -> VKey) -> Natural -> VKeyGenesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Owner -> VKey
VKey (Owner -> VKey) -> (Natural -> Owner) -> Natural -> VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Owner
Owner

-- | Make a set of genesis keys. The genesis keys are continuously numbered from 0 to the given
-- number of genesis keys minus 1.
mkVkGenesisSet ::
  -- | Number of genesis keys
  Word8 ->
  Set VKeyGenesis
mkVkGenesisSet :: Word8 -> Set VKeyGenesis
mkVkGenesisSet Word8
ngk = [VKeyGenesis] -> Set VKeyGenesis
forall a. Eq a => [a] -> Set a
Set.fromAscList ([VKeyGenesis] -> Set VKeyGenesis)
-> [VKeyGenesis] -> Set VKeyGenesis
forall a b. (a -> b) -> a -> b
$ Natural -> VKeyGenesis
mkVKeyGenesis (Natural -> VKeyGenesis) -> [Natural] -> [VKeyGenesis]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Natural
0 .. (Word8 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
ngk Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
1)]

-- | Key Pair.
data KeyPair = KeyPair
  { KeyPair -> SKey
sKey :: SKey
  , KeyPair -> VKey
vKey :: VKey
  }
  deriving (KeyPair -> KeyPair -> Bool
(KeyPair -> KeyPair -> Bool)
-> (KeyPair -> KeyPair -> Bool) -> Eq KeyPair
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyPair -> KeyPair -> Bool
== :: KeyPair -> KeyPair -> Bool
$c/= :: KeyPair -> KeyPair -> Bool
/= :: KeyPair -> KeyPair -> Bool
Eq, Eq KeyPair
Eq KeyPair =>
(KeyPair -> KeyPair -> Ordering)
-> (KeyPair -> KeyPair -> Bool)
-> (KeyPair -> KeyPair -> Bool)
-> (KeyPair -> KeyPair -> Bool)
-> (KeyPair -> KeyPair -> Bool)
-> (KeyPair -> KeyPair -> KeyPair)
-> (KeyPair -> KeyPair -> KeyPair)
-> Ord KeyPair
KeyPair -> KeyPair -> Bool
KeyPair -> KeyPair -> Ordering
KeyPair -> KeyPair -> KeyPair
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
$ccompare :: KeyPair -> KeyPair -> Ordering
compare :: KeyPair -> KeyPair -> Ordering
$c< :: KeyPair -> KeyPair -> Bool
< :: KeyPair -> KeyPair -> Bool
$c<= :: KeyPair -> KeyPair -> Bool
<= :: KeyPair -> KeyPair -> Bool
$c> :: KeyPair -> KeyPair -> Bool
> :: KeyPair -> KeyPair -> Bool
$c>= :: KeyPair -> KeyPair -> Bool
>= :: KeyPair -> KeyPair -> Bool
$cmax :: KeyPair -> KeyPair -> KeyPair
max :: KeyPair -> KeyPair -> KeyPair
$cmin :: KeyPair -> KeyPair -> KeyPair
min :: KeyPair -> KeyPair -> KeyPair
Ord, Int -> KeyPair -> ShowS
[KeyPair] -> ShowS
KeyPair -> String
(Int -> KeyPair -> ShowS)
-> (KeyPair -> String) -> ([KeyPair] -> ShowS) -> Show KeyPair
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyPair -> ShowS
showsPrec :: Int -> KeyPair -> ShowS
$cshow :: KeyPair -> String
show :: KeyPair -> String
$cshowList :: [KeyPair] -> ShowS
showList :: [KeyPair] -> ShowS
Show, (forall x. KeyPair -> Rep KeyPair x)
-> (forall x. Rep KeyPair x -> KeyPair) -> Generic KeyPair
forall x. Rep KeyPair x -> KeyPair
forall x. KeyPair -> Rep KeyPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. KeyPair -> Rep KeyPair x
from :: forall x. KeyPair -> Rep KeyPair x
$cto :: forall x. Rep KeyPair x -> KeyPair
to :: forall x. Rep KeyPair x -> KeyPair
Generic, Context -> KeyPair -> IO (Maybe ThunkInfo)
Proxy KeyPair -> String
(Context -> KeyPair -> IO (Maybe ThunkInfo))
-> (Context -> KeyPair -> IO (Maybe ThunkInfo))
-> (Proxy KeyPair -> String)
-> NoThunks KeyPair
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> KeyPair -> IO (Maybe ThunkInfo)
noThunks :: Context -> KeyPair -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> KeyPair -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> KeyPair -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy KeyPair -> String
showTypeOf :: Proxy KeyPair -> String
NoThunks)

instance HasTypeReps KeyPair

-- | Return a key pair for a given owner.
keyPair :: Owner -> KeyPair
keyPair :: Owner -> KeyPair
keyPair Owner
o = SKey -> VKey -> KeyPair
KeyPair (Owner -> SKey
SKey Owner
o) (Owner -> VKey
VKey Owner
o)

-- | A digital signature.
data Sig a = Sig a Owner
  deriving (Int -> Sig a -> ShowS
[Sig a] -> ShowS
Sig a -> String
(Int -> Sig a -> ShowS)
-> (Sig a -> String) -> ([Sig a] -> ShowS) -> Show (Sig a)
forall a. Show a => Int -> Sig a -> ShowS
forall a. Show a => [Sig a] -> ShowS
forall a. Show a => Sig a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Sig a -> ShowS
showsPrec :: Int -> Sig a -> ShowS
$cshow :: forall a. Show a => Sig a -> String
show :: Sig a -> String
$cshowList :: forall a. Show a => [Sig a] -> ShowS
showList :: [Sig a] -> ShowS
Show, Sig a -> Sig a -> Bool
(Sig a -> Sig a -> Bool) -> (Sig a -> Sig a -> Bool) -> Eq (Sig a)
forall a. Eq a => Sig a -> Sig a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Sig a -> Sig a -> Bool
== :: Sig a -> Sig a -> Bool
$c/= :: forall a. Eq a => Sig a -> Sig a -> Bool
/= :: Sig a -> Sig a -> Bool
Eq, Eq (Sig a)
Eq (Sig a) =>
(Sig a -> Sig a -> Ordering)
-> (Sig a -> Sig a -> Bool)
-> (Sig a -> Sig a -> Bool)
-> (Sig a -> Sig a -> Bool)
-> (Sig a -> Sig a -> Bool)
-> (Sig a -> Sig a -> Sig a)
-> (Sig a -> Sig a -> Sig a)
-> Ord (Sig a)
Sig a -> Sig a -> Bool
Sig a -> Sig a -> Ordering
Sig a -> Sig a -> Sig a
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 a. Ord a => Eq (Sig a)
forall a. Ord a => Sig a -> Sig a -> Bool
forall a. Ord a => Sig a -> Sig a -> Ordering
forall a. Ord a => Sig a -> Sig a -> Sig a
$ccompare :: forall a. Ord a => Sig a -> Sig a -> Ordering
compare :: Sig a -> Sig a -> Ordering
$c< :: forall a. Ord a => Sig a -> Sig a -> Bool
< :: Sig a -> Sig a -> Bool
$c<= :: forall a. Ord a => Sig a -> Sig a -> Bool
<= :: Sig a -> Sig a -> Bool
$c> :: forall a. Ord a => Sig a -> Sig a -> Bool
> :: Sig a -> Sig a -> Bool
$c>= :: forall a. Ord a => Sig a -> Sig a -> Bool
>= :: Sig a -> Sig a -> Bool
$cmax :: forall a. Ord a => Sig a -> Sig a -> Sig a
max :: Sig a -> Sig a -> Sig a
$cmin :: forall a. Ord a => Sig a -> Sig a -> Sig a
min :: Sig a -> Sig a -> Sig a
Ord, (forall x. Sig a -> Rep (Sig a) x)
-> (forall x. Rep (Sig a) x -> Sig a) -> Generic (Sig a)
forall x. Rep (Sig a) x -> Sig a
forall x. Sig a -> Rep (Sig a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Sig a) x -> Sig a
forall a x. Sig a -> Rep (Sig a) x
$cfrom :: forall a x. Sig a -> Rep (Sig a) x
from :: forall x. Sig a -> Rep (Sig a) x
$cto :: forall a x. Rep (Sig a) x -> Sig a
to :: forall x. Rep (Sig a) x -> Sig a
Generic, Eq (Sig a)
Eq (Sig a) =>
(Int -> Sig a -> Int) -> (Sig a -> Int) -> Hashable (Sig a)
Int -> Sig a -> Int
Sig a -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall a. Hashable a => Eq (Sig a)
forall a. Hashable a => Int -> Sig a -> Int
forall a. Hashable a => Sig a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> Sig a -> Int
hashWithSalt :: Int -> Sig a -> Int
$chash :: forall a. Hashable a => Sig a -> Int
hash :: Sig a -> Int
Hashable, Typeable (Sig a)
Typeable (Sig a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Sig a -> c (Sig a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Sig a))
-> (Sig a -> Constr)
-> (Sig a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Sig a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig a)))
-> ((forall b. Data b => b -> b) -> Sig a -> Sig a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Sig a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Sig a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Sig a -> m (Sig a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Sig a -> m (Sig a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Sig a -> m (Sig a))
-> Data (Sig a)
Sig a -> Constr
Sig a -> DataType
(forall b. Data b => b -> b) -> Sig a -> Sig a
forall a. Data a => Typeable (Sig a)
forall a. Data a => Sig a -> Constr
forall a. Data a => Sig a -> DataType
forall a. Data a => (forall b. Data b => b -> b) -> Sig a -> Sig a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Sig a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Sig a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Sig a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sig a -> c (Sig a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Sig a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Sig a -> u
forall u. (forall d. Data d => d -> u) -> Sig a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Sig a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sig a -> c (Sig a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Sig a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sig a -> c (Sig a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sig a -> c (Sig a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Sig a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Sig a)
$ctoConstr :: forall a. Data a => Sig a -> Constr
toConstr :: Sig a -> Constr
$cdataTypeOf :: forall a. Data a => Sig a -> DataType
dataTypeOf :: Sig a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Sig a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Sig a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig a))
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> Sig a -> Sig a
gmapT :: (forall b. Data b => b -> b) -> Sig a -> Sig a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig a -> r
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Sig a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Sig a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Sig a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Sig a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sig a -> m (Sig a)
Data, Context -> Sig a -> IO (Maybe ThunkInfo)
Proxy (Sig a) -> String
(Context -> Sig a -> IO (Maybe ThunkInfo))
-> (Context -> Sig a -> IO (Maybe ThunkInfo))
-> (Proxy (Sig a) -> String)
-> NoThunks (Sig a)
forall a. NoThunks a => Context -> Sig a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Proxy (Sig a) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: forall a. NoThunks a => Context -> Sig a -> IO (Maybe ThunkInfo)
noThunks :: Context -> Sig a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall a. NoThunks a => Context -> Sig a -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Sig a -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall a. NoThunks a => Proxy (Sig a) -> String
showTypeOf :: Proxy (Sig a) -> String
NoThunks)

-- | We need a custom instance here that returns only the top level type.
--   A generic instance would have recursed into type 'a' and since we use
--   'typeReps' to compute 'abstractSize', this would mean the size of
--   'Sig a' would include the size of 'a' (e.g. 'Tx'). This would create an
--   artificial coupling between the size of a type and it's "signature".
instance Typeable a => HasTypeReps (Sig a) where
  typeReps :: Sig a -> Seq TypeRep
typeReps Sig a
x = Sig a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf Sig a
x TypeRep -> Seq TypeRep -> Seq TypeRep
forall a. a -> Seq a -> Seq a
Seq.<| Seq TypeRep
forall a. Seq a
Seq.empty

-- | Produce a digital signature
sign :: SKey -> a -> Sig a
sign :: forall a. SKey -> a -> Sig a
sign (SKey Owner
k) a
d = a -> Owner -> Sig a
forall a. a -> Owner -> Sig a
Sig a
d Owner
k

-- | Verify a digital signature
verify :: Eq a => VKey -> a -> Sig a -> Bool
verify :: forall a. Eq a => VKey -> a -> Sig a -> Bool
verify (VKey Owner
vk) a
vd (Sig a
sd Owner
sk) = Owner
vk Owner -> Owner -> Bool
forall a. Eq a => a -> a -> Bool
== Owner
sk Bool -> Bool -> Bool
&& a
vd a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
sd

---------------------------------------------------------------------------------
-- Slots and Epochs
---------------------------------------------------------------------------------

newtype Epoch = Epoch {Epoch -> Word64
unEpoch :: Word64}
  deriving stock (Int -> Epoch -> ShowS
[Epoch] -> ShowS
Epoch -> String
(Int -> Epoch -> ShowS)
-> (Epoch -> String) -> ([Epoch] -> ShowS) -> Show Epoch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Epoch -> ShowS
showsPrec :: Int -> Epoch -> ShowS
$cshow :: Epoch -> String
show :: Epoch -> String
$cshowList :: [Epoch] -> ShowS
showList :: [Epoch] -> ShowS
Show, (forall x. Epoch -> Rep Epoch x)
-> (forall x. Rep Epoch x -> Epoch) -> Generic Epoch
forall x. Rep Epoch x -> Epoch
forall x. Epoch -> Rep Epoch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Epoch -> Rep Epoch x
from :: forall x. Epoch -> Rep Epoch x
$cto :: forall x. Rep Epoch x -> Epoch
to :: forall x. Rep Epoch x -> Epoch
Generic, Typeable Epoch
Typeable Epoch =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Epoch -> c Epoch)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Epoch)
-> (Epoch -> Constr)
-> (Epoch -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Epoch))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Epoch))
-> ((forall b. Data b => b -> b) -> Epoch -> Epoch)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r)
-> (forall u. (forall d. Data d => d -> u) -> Epoch -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Epoch -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Epoch -> m Epoch)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Epoch -> m Epoch)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Epoch -> m Epoch)
-> Data Epoch
Epoch -> Constr
Epoch -> DataType
(forall b. Data b => b -> b) -> Epoch -> Epoch
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Epoch -> u
forall u. (forall d. Data d => d -> u) -> Epoch -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Epoch
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Epoch -> c Epoch
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Epoch)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Epoch)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Epoch -> c Epoch
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Epoch -> c Epoch
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Epoch
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Epoch
$ctoConstr :: Epoch -> Constr
toConstr :: Epoch -> Constr
$cdataTypeOf :: Epoch -> DataType
dataTypeOf :: Epoch -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Epoch)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Epoch)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Epoch)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Epoch)
$cgmapT :: (forall b. Data b => b -> b) -> Epoch -> Epoch
gmapT :: (forall b. Data b => b -> b) -> Epoch -> Epoch
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Epoch -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Epoch -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Epoch -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Epoch -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Epoch -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Epoch -> m Epoch
Data)
  deriving newtype (Epoch -> Epoch -> Bool
(Epoch -> Epoch -> Bool) -> (Epoch -> Epoch -> Bool) -> Eq Epoch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Epoch -> Epoch -> Bool
== :: Epoch -> Epoch -> Bool
$c/= :: Epoch -> Epoch -> Bool
/= :: Epoch -> Epoch -> Bool
Eq, Eq Epoch
Eq Epoch =>
(Epoch -> Epoch -> Ordering)
-> (Epoch -> Epoch -> Bool)
-> (Epoch -> Epoch -> Bool)
-> (Epoch -> Epoch -> Bool)
-> (Epoch -> Epoch -> Bool)
-> (Epoch -> Epoch -> Epoch)
-> (Epoch -> Epoch -> Epoch)
-> Ord Epoch
Epoch -> Epoch -> Bool
Epoch -> Epoch -> Ordering
Epoch -> Epoch -> Epoch
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
$ccompare :: Epoch -> Epoch -> Ordering
compare :: Epoch -> Epoch -> Ordering
$c< :: Epoch -> Epoch -> Bool
< :: Epoch -> Epoch -> Bool
$c<= :: Epoch -> Epoch -> Bool
<= :: Epoch -> Epoch -> Bool
$c> :: Epoch -> Epoch -> Bool
> :: Epoch -> Epoch -> Bool
$c>= :: Epoch -> Epoch -> Bool
>= :: Epoch -> Epoch -> Bool
$cmax :: Epoch -> Epoch -> Epoch
max :: Epoch -> Epoch -> Epoch
$cmin :: Epoch -> Epoch -> Epoch
min :: Epoch -> Epoch -> Epoch
Ord, Eq Epoch
Eq Epoch =>
(Int -> Epoch -> Int) -> (Epoch -> Int) -> Hashable Epoch
Int -> Epoch -> Int
Epoch -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Epoch -> Int
hashWithSalt :: Int -> Epoch -> Int
$chash :: Epoch -> Int
hash :: Epoch -> Int
Hashable, Integer -> Epoch
Epoch -> Epoch
Epoch -> Epoch -> Epoch
(Epoch -> Epoch -> Epoch)
-> (Epoch -> Epoch -> Epoch)
-> (Epoch -> Epoch -> Epoch)
-> (Epoch -> Epoch)
-> (Epoch -> Epoch)
-> (Epoch -> Epoch)
-> (Integer -> Epoch)
-> Num Epoch
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Epoch -> Epoch -> Epoch
+ :: Epoch -> Epoch -> Epoch
$c- :: Epoch -> Epoch -> Epoch
- :: Epoch -> Epoch -> Epoch
$c* :: Epoch -> Epoch -> Epoch
* :: Epoch -> Epoch -> Epoch
$cnegate :: Epoch -> Epoch
negate :: Epoch -> Epoch
$cabs :: Epoch -> Epoch
abs :: Epoch -> Epoch
$csignum :: Epoch -> Epoch
signum :: Epoch -> Epoch
$cfromInteger :: Integer -> Epoch
fromInteger :: Integer -> Epoch
Num, Typeable Epoch
Typeable Epoch =>
(Epoch -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy Epoch -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Epoch] -> Size)
-> EncCBOR Epoch
Epoch -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Epoch -> Encoding
encCBOR :: Epoch -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
EncCBOR, Typeable Epoch
Typeable Epoch =>
(Epoch -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Epoch] -> Size)
-> ToCBOR Epoch
Epoch -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Epoch -> Encoding
toCBOR :: Epoch -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Epoch -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Epoch] -> Size
ToCBOR, Context -> Epoch -> IO (Maybe ThunkInfo)
Proxy Epoch -> String
(Context -> Epoch -> IO (Maybe ThunkInfo))
-> (Context -> Epoch -> IO (Maybe ThunkInfo))
-> (Proxy Epoch -> String)
-> NoThunks Epoch
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Epoch -> IO (Maybe ThunkInfo)
noThunks :: Context -> Epoch -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Epoch -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Epoch -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Epoch -> String
showTypeOf :: Proxy Epoch -> String
NoThunks)
  deriving anyclass (Epoch -> Seq TypeRep
(Epoch -> Seq TypeRep) -> HasTypeReps Epoch
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Epoch -> Seq TypeRep
typeReps :: Epoch -> Seq TypeRep
HasTypeReps)

newtype Slot = Slot {Slot -> Word64
unSlot :: Word64}
  deriving stock (Int -> Slot -> ShowS
[Slot] -> ShowS
Slot -> String
(Int -> Slot -> ShowS)
-> (Slot -> String) -> ([Slot] -> ShowS) -> Show Slot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Slot -> ShowS
showsPrec :: Int -> Slot -> ShowS
$cshow :: Slot -> String
show :: Slot -> String
$cshowList :: [Slot] -> ShowS
showList :: [Slot] -> ShowS
Show, (forall x. Slot -> Rep Slot x)
-> (forall x. Rep Slot x -> Slot) -> Generic Slot
forall x. Rep Slot x -> Slot
forall x. Slot -> Rep Slot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Slot -> Rep Slot x
from :: forall x. Slot -> Rep Slot x
$cto :: forall x. Rep Slot x -> Slot
to :: forall x. Rep Slot x -> Slot
Generic, Typeable Slot
Typeable Slot =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Slot -> c Slot)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Slot)
-> (Slot -> Constr)
-> (Slot -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Slot))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot))
-> ((forall b. Data b => b -> b) -> Slot -> Slot)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r)
-> (forall u. (forall d. Data d => d -> u) -> Slot -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Slot -> m Slot)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Slot -> m Slot)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Slot -> m Slot)
-> Data Slot
Slot -> Constr
Slot -> DataType
(forall b. Data b => b -> b) -> Slot -> Slot
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u
forall u. (forall d. Data d => d -> u) -> Slot -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
$ctoConstr :: Slot -> Constr
toConstr :: Slot -> Constr
$cdataTypeOf :: Slot -> DataType
dataTypeOf :: Slot -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
$cgmapT :: (forall b. Data b => b -> b) -> Slot -> Slot
gmapT :: (forall b. Data b => b -> b) -> Slot -> Slot
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Slot -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Slot -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
Data)
  deriving newtype (Slot -> Slot -> Bool
(Slot -> Slot -> Bool) -> (Slot -> Slot -> Bool) -> Eq Slot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Slot -> Slot -> Bool
== :: Slot -> Slot -> Bool
$c/= :: Slot -> Slot -> Bool
/= :: Slot -> Slot -> Bool
Eq, Eq Slot
Eq Slot =>
(Slot -> Slot -> Ordering)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Slot)
-> (Slot -> Slot -> Slot)
-> Ord Slot
Slot -> Slot -> Bool
Slot -> Slot -> Ordering
Slot -> Slot -> Slot
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
$ccompare :: Slot -> Slot -> Ordering
compare :: Slot -> Slot -> Ordering
$c< :: Slot -> Slot -> Bool
< :: Slot -> Slot -> Bool
$c<= :: Slot -> Slot -> Bool
<= :: Slot -> Slot -> Bool
$c> :: Slot -> Slot -> Bool
> :: Slot -> Slot -> Bool
$c>= :: Slot -> Slot -> Bool
>= :: Slot -> Slot -> Bool
$cmax :: Slot -> Slot -> Slot
max :: Slot -> Slot -> Slot
$cmin :: Slot -> Slot -> Slot
min :: Slot -> Slot -> Slot
Ord, Eq Slot
Eq Slot => (Int -> Slot -> Int) -> (Slot -> Int) -> Hashable Slot
Int -> Slot -> Int
Slot -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Slot -> Int
hashWithSalt :: Int -> Slot -> Int
$chash :: Slot -> Int
hash :: Slot -> Int
Hashable, Typeable Slot
Typeable Slot =>
(Slot -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Slot -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Slot] -> Size)
-> EncCBOR Slot
Slot -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Slot -> Encoding
encCBOR :: Slot -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
EncCBOR, Typeable Slot
Typeable Slot =>
(Slot -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Slot -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Slot] -> Size)
-> ToCBOR Slot
Slot -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Slot -> Encoding
toCBOR :: Slot -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Slot -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Slot] -> Size
ToCBOR, Context -> Slot -> IO (Maybe ThunkInfo)
Proxy Slot -> String
(Context -> Slot -> IO (Maybe ThunkInfo))
-> (Context -> Slot -> IO (Maybe ThunkInfo))
-> (Proxy Slot -> String)
-> NoThunks Slot
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Slot -> IO (Maybe ThunkInfo)
noThunks :: Context -> Slot -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Slot -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Slot -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Slot -> String
showTypeOf :: Proxy Slot -> String
NoThunks)
  deriving anyclass (Slot -> Seq TypeRep
(Slot -> Seq TypeRep) -> HasTypeReps Slot
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Slot -> Seq TypeRep
typeReps :: Slot -> Seq TypeRep
HasTypeReps)

-- | A number of slots.
--
--  We use this newtype to distinguish between a cardinal slot and a relative
--  period of slots, and also to distinguish between number of slots and number
--  of blocks.
newtype SlotCount = SlotCount {SlotCount -> Word64
unSlotCount :: Word64}
  deriving stock ((forall x. SlotCount -> Rep SlotCount x)
-> (forall x. Rep SlotCount x -> SlotCount) -> Generic SlotCount
forall x. Rep SlotCount x -> SlotCount
forall x. SlotCount -> Rep SlotCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SlotCount -> Rep SlotCount x
from :: forall x. SlotCount -> Rep SlotCount x
$cto :: forall x. Rep SlotCount x -> SlotCount
to :: forall x. Rep SlotCount x -> SlotCount
Generic, Int -> SlotCount -> ShowS
[SlotCount] -> ShowS
SlotCount -> String
(Int -> SlotCount -> ShowS)
-> (SlotCount -> String)
-> ([SlotCount] -> ShowS)
-> Show SlotCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SlotCount -> ShowS
showsPrec :: Int -> SlotCount -> ShowS
$cshow :: SlotCount -> String
show :: SlotCount -> String
$cshowList :: [SlotCount] -> ShowS
showList :: [SlotCount] -> ShowS
Show, Typeable SlotCount
Typeable SlotCount =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SlotCount -> c SlotCount)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SlotCount)
-> (SlotCount -> Constr)
-> (SlotCount -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SlotCount))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SlotCount))
-> ((forall b. Data b => b -> b) -> SlotCount -> SlotCount)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SlotCount -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SlotCount -> r)
-> (forall u. (forall d. Data d => d -> u) -> SlotCount -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SlotCount -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SlotCount -> m SlotCount)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SlotCount -> m SlotCount)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SlotCount -> m SlotCount)
-> Data SlotCount
SlotCount -> Constr
SlotCount -> DataType
(forall b. Data b => b -> b) -> SlotCount -> SlotCount
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SlotCount -> u
forall u. (forall d. Data d => d -> u) -> SlotCount -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SlotCount
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SlotCount -> c SlotCount
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SlotCount)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SlotCount)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SlotCount -> c SlotCount
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SlotCount -> c SlotCount
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SlotCount
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SlotCount
$ctoConstr :: SlotCount -> Constr
toConstr :: SlotCount -> Constr
$cdataTypeOf :: SlotCount -> DataType
dataTypeOf :: SlotCount -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SlotCount)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SlotCount)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SlotCount)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SlotCount)
$cgmapT :: (forall b. Data b => b -> b) -> SlotCount -> SlotCount
gmapT :: (forall b. Data b => b -> b) -> SlotCount -> SlotCount
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SlotCount -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SlotCount -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SlotCount -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SlotCount -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SlotCount -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SlotCount -> m SlotCount
Data)
  deriving newtype (SlotCount -> SlotCount -> Bool
(SlotCount -> SlotCount -> Bool)
-> (SlotCount -> SlotCount -> Bool) -> Eq SlotCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SlotCount -> SlotCount -> Bool
== :: SlotCount -> SlotCount -> Bool
$c/= :: SlotCount -> SlotCount -> Bool
/= :: SlotCount -> SlotCount -> Bool
Eq, Eq SlotCount
Eq SlotCount =>
(SlotCount -> SlotCount -> Ordering)
-> (SlotCount -> SlotCount -> Bool)
-> (SlotCount -> SlotCount -> Bool)
-> (SlotCount -> SlotCount -> Bool)
-> (SlotCount -> SlotCount -> Bool)
-> (SlotCount -> SlotCount -> SlotCount)
-> (SlotCount -> SlotCount -> SlotCount)
-> Ord SlotCount
SlotCount -> SlotCount -> Bool
SlotCount -> SlotCount -> Ordering
SlotCount -> SlotCount -> SlotCount
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
$ccompare :: SlotCount -> SlotCount -> Ordering
compare :: SlotCount -> SlotCount -> Ordering
$c< :: SlotCount -> SlotCount -> Bool
< :: SlotCount -> SlotCount -> Bool
$c<= :: SlotCount -> SlotCount -> Bool
<= :: SlotCount -> SlotCount -> Bool
$c> :: SlotCount -> SlotCount -> Bool
> :: SlotCount -> SlotCount -> Bool
$c>= :: SlotCount -> SlotCount -> Bool
>= :: SlotCount -> SlotCount -> Bool
$cmax :: SlotCount -> SlotCount -> SlotCount
max :: SlotCount -> SlotCount -> SlotCount
$cmin :: SlotCount -> SlotCount -> SlotCount
min :: SlotCount -> SlotCount -> SlotCount
Ord, Integer -> SlotCount
SlotCount -> SlotCount
SlotCount -> SlotCount -> SlotCount
(SlotCount -> SlotCount -> SlotCount)
-> (SlotCount -> SlotCount -> SlotCount)
-> (SlotCount -> SlotCount -> SlotCount)
-> (SlotCount -> SlotCount)
-> (SlotCount -> SlotCount)
-> (SlotCount -> SlotCount)
-> (Integer -> SlotCount)
-> Num SlotCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: SlotCount -> SlotCount -> SlotCount
+ :: SlotCount -> SlotCount -> SlotCount
$c- :: SlotCount -> SlotCount -> SlotCount
- :: SlotCount -> SlotCount -> SlotCount
$c* :: SlotCount -> SlotCount -> SlotCount
* :: SlotCount -> SlotCount -> SlotCount
$cnegate :: SlotCount -> SlotCount
negate :: SlotCount -> SlotCount
$cabs :: SlotCount -> SlotCount
abs :: SlotCount -> SlotCount
$csignum :: SlotCount -> SlotCount
signum :: SlotCount -> SlotCount
$cfromInteger :: Integer -> SlotCount
fromInteger :: Integer -> SlotCount
Num, Eq SlotCount
Eq SlotCount =>
(Int -> SlotCount -> Int)
-> (SlotCount -> Int) -> Hashable SlotCount
Int -> SlotCount -> Int
SlotCount -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> SlotCount -> Int
hashWithSalt :: Int -> SlotCount -> Int
$chash :: SlotCount -> Int
hash :: SlotCount -> Int
Hashable, Typeable SlotCount
Typeable SlotCount =>
(SlotCount -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy SlotCount -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [SlotCount] -> Size)
-> EncCBOR SlotCount
SlotCount -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: SlotCount -> Encoding
encCBOR :: SlotCount -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
EncCBOR, Typeable SlotCount
Typeable SlotCount =>
(SlotCount -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy SlotCount -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SlotCount] -> Size)
-> ToCBOR SlotCount
SlotCount -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SlotCount -> Encoding
toCBOR :: SlotCount -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SlotCount] -> Size
ToCBOR, Context -> SlotCount -> IO (Maybe ThunkInfo)
Proxy SlotCount -> String
(Context -> SlotCount -> IO (Maybe ThunkInfo))
-> (Context -> SlotCount -> IO (Maybe ThunkInfo))
-> (Proxy SlotCount -> String)
-> NoThunks SlotCount
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> SlotCount -> IO (Maybe ThunkInfo)
noThunks :: Context -> SlotCount -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SlotCount -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> SlotCount -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy SlotCount -> String
showTypeOf :: Proxy SlotCount -> String
NoThunks)

instance HasTypeReps SlotCount

-- | Add a slot count to a slot.
addSlot :: Slot -> SlotCount -> Slot
addSlot :: Slot -> SlotCount -> Slot
addSlot (Slot Word64
n) (SlotCount Word64
m) = Word64 -> Slot
Slot (Word64 -> Slot) -> Word64 -> Slot
forall a b. (a -> b) -> a -> b
$ Word64
m Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
n

-- | An alias for 'addSlot'
(+.) :: Slot -> SlotCount -> Slot
+. :: Slot -> SlotCount -> Slot
(+.) = Slot -> SlotCount -> Slot
addSlot

infixl 6 +.

-- | Subtract a slot count from a slot.
--
--   This is bounded below by 0.
minusSlot :: Slot -> SlotCount -> Slot
minusSlot :: Slot -> SlotCount -> Slot
minusSlot (Slot Word64
m) (SlotCount Word64
n)
  | Word64
m Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
n = Word64 -> Slot
Slot Word64
0
  | Bool
otherwise = Word64 -> Slot
Slot (Word64 -> Slot) -> Word64 -> Slot
forall a b. (a -> b) -> a -> b
$ Word64
m Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
n

-- | An alias for 'minusSlot'
(-.) :: Slot -> SlotCount -> Slot
-. :: Slot -> SlotCount -> Slot
(-.) = Slot -> SlotCount -> Slot
minusSlot

infixl 6 -.

-- | Multiply the block count by the given constant. This function does not
-- check for overflow.
(*.) :: Word64 -> BlockCount -> SlotCount
Word64
n *. :: Word64 -> BlockCount -> SlotCount
*. (BlockCount Word64
c) = Word64 -> SlotCount
SlotCount (Word64 -> SlotCount) -> Word64 -> SlotCount
forall a b. (a -> b) -> a -> b
$ Word64
n Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
c

infixl 7 *.

-- | Subtract a slot count from a slot.
--
-- In case the slot count is greater than the slot's index, it returns
-- Nothing.
minusSlotMaybe :: Slot -> SlotCount -> Maybe Slot
minusSlotMaybe :: Slot -> SlotCount -> Maybe Slot
minusSlotMaybe (Slot Word64
m) (SlotCount Word64
n)
  | Word64
m Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
n = Maybe Slot
forall a. Maybe a
Nothing
  | Bool
otherwise = Slot -> Maybe Slot
forall a. a -> Maybe a
Just (Slot -> Maybe Slot) -> (Word64 -> Slot) -> Word64 -> Maybe Slot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Slot
Slot (Word64 -> Maybe Slot) -> Word64 -> Maybe Slot
forall a b. (a -> b) -> a -> b
$ Word64
m Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
n

newtype BlockCount = BlockCount {BlockCount -> Word64
unBlockCount :: Word64}
  deriving stock ((forall x. BlockCount -> Rep BlockCount x)
-> (forall x. Rep BlockCount x -> BlockCount) -> Generic BlockCount
forall x. Rep BlockCount x -> BlockCount
forall x. BlockCount -> Rep BlockCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BlockCount -> Rep BlockCount x
from :: forall x. BlockCount -> Rep BlockCount x
$cto :: forall x. Rep BlockCount x -> BlockCount
to :: forall x. Rep BlockCount x -> BlockCount
Generic, Int -> BlockCount -> ShowS
[BlockCount] -> ShowS
BlockCount -> String
(Int -> BlockCount -> ShowS)
-> (BlockCount -> String)
-> ([BlockCount] -> ShowS)
-> Show BlockCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlockCount -> ShowS
showsPrec :: Int -> BlockCount -> ShowS
$cshow :: BlockCount -> String
show :: BlockCount -> String
$cshowList :: [BlockCount] -> ShowS
showList :: [BlockCount] -> ShowS
Show)
  deriving newtype (BlockCount -> BlockCount -> Bool
(BlockCount -> BlockCount -> Bool)
-> (BlockCount -> BlockCount -> Bool) -> Eq BlockCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockCount -> BlockCount -> Bool
== :: BlockCount -> BlockCount -> Bool
$c/= :: BlockCount -> BlockCount -> Bool
/= :: BlockCount -> BlockCount -> Bool
Eq, Eq BlockCount
Eq BlockCount =>
(BlockCount -> BlockCount -> Ordering)
-> (BlockCount -> BlockCount -> Bool)
-> (BlockCount -> BlockCount -> Bool)
-> (BlockCount -> BlockCount -> Bool)
-> (BlockCount -> BlockCount -> Bool)
-> (BlockCount -> BlockCount -> BlockCount)
-> (BlockCount -> BlockCount -> BlockCount)
-> Ord BlockCount
BlockCount -> BlockCount -> Bool
BlockCount -> BlockCount -> Ordering
BlockCount -> BlockCount -> BlockCount
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
$ccompare :: BlockCount -> BlockCount -> Ordering
compare :: BlockCount -> BlockCount -> Ordering
$c< :: BlockCount -> BlockCount -> Bool
< :: BlockCount -> BlockCount -> Bool
$c<= :: BlockCount -> BlockCount -> Bool
<= :: BlockCount -> BlockCount -> Bool
$c> :: BlockCount -> BlockCount -> Bool
> :: BlockCount -> BlockCount -> Bool
$c>= :: BlockCount -> BlockCount -> Bool
>= :: BlockCount -> BlockCount -> Bool
$cmax :: BlockCount -> BlockCount -> BlockCount
max :: BlockCount -> BlockCount -> BlockCount
$cmin :: BlockCount -> BlockCount -> BlockCount
min :: BlockCount -> BlockCount -> BlockCount
Ord, Integer -> BlockCount
BlockCount -> BlockCount
BlockCount -> BlockCount -> BlockCount
(BlockCount -> BlockCount -> BlockCount)
-> (BlockCount -> BlockCount -> BlockCount)
-> (BlockCount -> BlockCount -> BlockCount)
-> (BlockCount -> BlockCount)
-> (BlockCount -> BlockCount)
-> (BlockCount -> BlockCount)
-> (Integer -> BlockCount)
-> Num BlockCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: BlockCount -> BlockCount -> BlockCount
+ :: BlockCount -> BlockCount -> BlockCount
$c- :: BlockCount -> BlockCount -> BlockCount
- :: BlockCount -> BlockCount -> BlockCount
$c* :: BlockCount -> BlockCount -> BlockCount
* :: BlockCount -> BlockCount -> BlockCount
$cnegate :: BlockCount -> BlockCount
negate :: BlockCount -> BlockCount
$cabs :: BlockCount -> BlockCount
abs :: BlockCount -> BlockCount
$csignum :: BlockCount -> BlockCount
signum :: BlockCount -> BlockCount
$cfromInteger :: Integer -> BlockCount
fromInteger :: Integer -> BlockCount
Num, Eq BlockCount
Eq BlockCount =>
(Int -> BlockCount -> Int)
-> (BlockCount -> Int) -> Hashable BlockCount
Int -> BlockCount -> Int
BlockCount -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> BlockCount -> Int
hashWithSalt :: Int -> BlockCount -> Int
$chash :: BlockCount -> Int
hash :: BlockCount -> Int
Hashable, Context -> BlockCount -> IO (Maybe ThunkInfo)
Proxy BlockCount -> String
(Context -> BlockCount -> IO (Maybe ThunkInfo))
-> (Context -> BlockCount -> IO (Maybe ThunkInfo))
-> (Proxy BlockCount -> String)
-> NoThunks BlockCount
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> BlockCount -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlockCount -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> BlockCount -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> BlockCount -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy BlockCount -> String
showTypeOf :: Proxy BlockCount -> String
NoThunks, Typeable BlockCount
Typeable BlockCount =>
(forall s. Decoder s BlockCount)
-> (forall s. Proxy BlockCount -> Decoder s ())
-> (Proxy BlockCount -> Text)
-> DecCBOR BlockCount
Proxy BlockCount -> Text
forall s. Decoder s BlockCount
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy BlockCount -> Decoder s ()
$cdecCBOR :: forall s. Decoder s BlockCount
decCBOR :: forall s. Decoder s BlockCount
$cdropCBOR :: forall s. Proxy BlockCount -> Decoder s ()
dropCBOR :: forall s. Proxy BlockCount -> Decoder s ()
$clabel :: Proxy BlockCount -> Text
label :: Proxy BlockCount -> Text
DecCBOR, Typeable BlockCount
Typeable BlockCount =>
(BlockCount -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy BlockCount -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [BlockCount] -> Size)
-> EncCBOR BlockCount
BlockCount -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlockCount -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: BlockCount -> Encoding
encCBOR :: BlockCount -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlockCount -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlockCount -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
EncCBOR, Typeable BlockCount
Typeable BlockCount =>
(forall s. Decoder s BlockCount)
-> (Proxy BlockCount -> Text) -> FromCBOR BlockCount
Proxy BlockCount -> Text
forall s. Decoder s BlockCount
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s BlockCount
fromCBOR :: forall s. Decoder s BlockCount
$clabel :: Proxy BlockCount -> Text
label :: Proxy BlockCount -> Text
FromCBOR, Typeable BlockCount
Typeable BlockCount =>
(BlockCount -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy BlockCount -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [BlockCount] -> Size)
-> ToCBOR BlockCount
BlockCount -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockCount -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: BlockCount -> Encoding
toCBOR :: BlockCount -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockCount -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockCount -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlockCount] -> Size
ToCBOR)

instance HasTypeReps BlockCount

---------------------------------------------------------------------------------
-- Transactions
---------------------------------------------------------------------------------

-- | The address of a transaction output, used to identify the owner.
newtype Addr = Addr VKey
  deriving stock (Int -> Addr -> ShowS
[Addr] -> ShowS
Addr -> String
(Int -> Addr -> ShowS)
-> (Addr -> String) -> ([Addr] -> ShowS) -> Show Addr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Addr -> ShowS
showsPrec :: Int -> Addr -> ShowS
$cshow :: Addr -> String
show :: Addr -> String
$cshowList :: [Addr] -> ShowS
showList :: [Addr] -> ShowS
Show, (forall x. Addr -> Rep Addr x)
-> (forall x. Rep Addr x -> Addr) -> Generic Addr
forall x. Rep Addr x -> Addr
forall x. Addr -> Rep Addr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Addr -> Rep Addr x
from :: forall x. Addr -> Rep Addr x
$cto :: forall x. Rep Addr x -> Addr
to :: forall x. Rep Addr x -> Addr
Generic, Typeable Addr
Typeable Addr =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Addr -> c Addr)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Addr)
-> (Addr -> Constr)
-> (Addr -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Addr))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr))
-> ((forall b. Data b => b -> b) -> Addr -> Addr)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r)
-> (forall u. (forall d. Data d => d -> u) -> Addr -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Addr -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Addr -> m Addr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Addr -> m Addr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Addr -> m Addr)
-> Data Addr
Addr -> Constr
Addr -> DataType
(forall b. Data b => b -> b) -> Addr -> Addr
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Addr -> u
forall u. (forall d. Data d => d -> u) -> Addr -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Addr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Addr -> c Addr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Addr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Addr -> c Addr
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Addr -> c Addr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Addr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Addr
$ctoConstr :: Addr -> Constr
toConstr :: Addr -> Constr
$cdataTypeOf :: Addr -> DataType
dataTypeOf :: Addr -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Addr)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Addr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr)
$cgmapT :: (forall b. Data b => b -> b) -> Addr -> Addr
gmapT :: (forall b. Data b => b -> b) -> Addr -> Addr
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Addr -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Addr -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Addr -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Addr -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Addr -> m Addr
Data)
  deriving newtype (Addr -> Addr -> Bool
(Addr -> Addr -> Bool) -> (Addr -> Addr -> Bool) -> Eq Addr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Addr -> Addr -> Bool
== :: Addr -> Addr -> Bool
$c/= :: Addr -> Addr -> Bool
/= :: Addr -> Addr -> Bool
Eq, Eq Addr
Eq Addr =>
(Addr -> Addr -> Ordering)
-> (Addr -> Addr -> Bool)
-> (Addr -> Addr -> Bool)
-> (Addr -> Addr -> Bool)
-> (Addr -> Addr -> Bool)
-> (Addr -> Addr -> Addr)
-> (Addr -> Addr -> Addr)
-> Ord Addr
Addr -> Addr -> Bool
Addr -> Addr -> Ordering
Addr -> Addr -> Addr
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
$ccompare :: Addr -> Addr -> Ordering
compare :: Addr -> Addr -> Ordering
$c< :: Addr -> Addr -> Bool
< :: Addr -> Addr -> Bool
$c<= :: Addr -> Addr -> Bool
<= :: Addr -> Addr -> Bool
$c> :: Addr -> Addr -> Bool
> :: Addr -> Addr -> Bool
$c>= :: Addr -> Addr -> Bool
>= :: Addr -> Addr -> Bool
$cmax :: Addr -> Addr -> Addr
max :: Addr -> Addr -> Addr
$cmin :: Addr -> Addr -> Addr
min :: Addr -> Addr -> Addr
Ord, Eq Addr
Eq Addr => (Int -> Addr -> Int) -> (Addr -> Int) -> Hashable Addr
Int -> Addr -> Int
Addr -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Addr -> Int
hashWithSalt :: Int -> Addr -> Int
$chash :: Addr -> Int
hash :: Addr -> Int
Hashable, Addr -> Owner
(Addr -> Owner) -> HasOwner Addr
forall a. (a -> Owner) -> HasOwner a
$cowner :: Addr -> Owner
owner :: Addr -> Owner
HasOwner, Typeable Addr
Typeable Addr =>
(Addr -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Addr -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Addr] -> Size)
-> EncCBOR Addr
Addr -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Addr -> Encoding
encCBOR :: Addr -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
EncCBOR, Typeable Addr
Typeable Addr =>
(Addr -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Addr -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Addr] -> Size)
-> ToCBOR Addr
Addr -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Addr -> Encoding
toCBOR :: Addr -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Addr -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Addr] -> Size
ToCBOR, Context -> Addr -> IO (Maybe ThunkInfo)
Proxy Addr -> String
(Context -> Addr -> IO (Maybe ThunkInfo))
-> (Context -> Addr -> IO (Maybe ThunkInfo))
-> (Proxy Addr -> String)
-> NoThunks Addr
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Addr -> IO (Maybe ThunkInfo)
noThunks :: Context -> Addr -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Addr -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Addr -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Addr -> String
showTypeOf :: Proxy Addr -> String
NoThunks)
  deriving anyclass (Addr -> Seq TypeRep
(Addr -> Seq TypeRep) -> HasTypeReps Addr
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Addr -> Seq TypeRep
typeReps :: Addr -> Seq TypeRep
HasTypeReps)

-- | Create an address from a number.
mkAddr :: Natural -> Addr
mkAddr :: Natural -> Addr
mkAddr = VKey -> Addr
Addr (VKey -> Addr) -> (Natural -> VKey) -> Natural -> Addr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Owner -> VKey
VKey (Owner -> VKey) -> (Natural -> Owner) -> Natural -> VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Owner
Owner

instance HasHash Addr where
  hash :: Addr -> Hash
hash = Maybe Int -> Hash
Hash (Maybe Int -> Hash) -> (Addr -> Maybe Int) -> Addr -> Hash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Addr -> Int) -> Addr -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr -> Int
forall a. Hashable a => a -> Int
H.hash

-- | A unit of value held by a UTxO.
newtype Lovelace = Lovelace
  { Lovelace -> Integer
unLovelace :: Integer
  }
  deriving stock (Int -> Lovelace -> ShowS
[Lovelace] -> ShowS
Lovelace -> String
(Int -> Lovelace -> ShowS)
-> (Lovelace -> String) -> ([Lovelace] -> ShowS) -> Show Lovelace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Lovelace -> ShowS
showsPrec :: Int -> Lovelace -> ShowS
$cshow :: Lovelace -> String
show :: Lovelace -> String
$cshowList :: [Lovelace] -> ShowS
showList :: [Lovelace] -> ShowS
Show, (forall x. Lovelace -> Rep Lovelace x)
-> (forall x. Rep Lovelace x -> Lovelace) -> Generic Lovelace
forall x. Rep Lovelace x -> Lovelace
forall x. Lovelace -> Rep Lovelace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Lovelace -> Rep Lovelace x
from :: forall x. Lovelace -> Rep Lovelace x
$cto :: forall x. Rep Lovelace x -> Lovelace
to :: forall x. Rep Lovelace x -> Lovelace
Generic, Typeable Lovelace
Typeable Lovelace =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Lovelace -> c Lovelace)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Lovelace)
-> (Lovelace -> Constr)
-> (Lovelace -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Lovelace))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lovelace))
-> ((forall b. Data b => b -> b) -> Lovelace -> Lovelace)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Lovelace -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Lovelace -> r)
-> (forall u. (forall d. Data d => d -> u) -> Lovelace -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Lovelace -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Lovelace -> m Lovelace)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Lovelace -> m Lovelace)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Lovelace -> m Lovelace)
-> Data Lovelace
Lovelace -> Constr
Lovelace -> DataType
(forall b. Data b => b -> b) -> Lovelace -> Lovelace
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Lovelace -> u
forall u. (forall d. Data d => d -> u) -> Lovelace -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lovelace
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lovelace -> c Lovelace
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lovelace)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lovelace)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lovelace -> c Lovelace
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lovelace -> c Lovelace
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lovelace
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lovelace
$ctoConstr :: Lovelace -> Constr
toConstr :: Lovelace -> Constr
$cdataTypeOf :: Lovelace -> DataType
dataTypeOf :: Lovelace -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lovelace)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lovelace)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lovelace)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lovelace)
$cgmapT :: (forall b. Data b => b -> b) -> Lovelace -> Lovelace
gmapT :: (forall b. Data b => b -> b) -> Lovelace -> Lovelace
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Lovelace -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Lovelace -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Lovelace -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Lovelace -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Lovelace -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lovelace -> m Lovelace
Data)
  deriving newtype (Lovelace -> Lovelace -> Bool
(Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool) -> Eq Lovelace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Lovelace -> Lovelace -> Bool
== :: Lovelace -> Lovelace -> Bool
$c/= :: Lovelace -> Lovelace -> Bool
/= :: Lovelace -> Lovelace -> Bool
Eq, Eq Lovelace
Eq Lovelace =>
(Lovelace -> Lovelace -> Ordering)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> Ord Lovelace
Lovelace -> Lovelace -> Bool
Lovelace -> Lovelace -> Ordering
Lovelace -> Lovelace -> Lovelace
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
$ccompare :: Lovelace -> Lovelace -> Ordering
compare :: Lovelace -> Lovelace -> Ordering
$c< :: Lovelace -> Lovelace -> Bool
< :: Lovelace -> Lovelace -> Bool
$c<= :: Lovelace -> Lovelace -> Bool
<= :: Lovelace -> Lovelace -> Bool
$c> :: Lovelace -> Lovelace -> Bool
> :: Lovelace -> Lovelace -> Bool
$c>= :: Lovelace -> Lovelace -> Bool
>= :: Lovelace -> Lovelace -> Bool
$cmax :: Lovelace -> Lovelace -> Lovelace
max :: Lovelace -> Lovelace -> Lovelace
$cmin :: Lovelace -> Lovelace -> Lovelace
min :: Lovelace -> Lovelace -> Lovelace
Ord, Integer -> Lovelace
Lovelace -> Lovelace
Lovelace -> Lovelace -> Lovelace
(Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Integer -> Lovelace)
-> Num Lovelace
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Lovelace -> Lovelace -> Lovelace
+ :: Lovelace -> Lovelace -> Lovelace
$c- :: Lovelace -> Lovelace -> Lovelace
- :: Lovelace -> Lovelace -> Lovelace
$c* :: Lovelace -> Lovelace -> Lovelace
* :: Lovelace -> Lovelace -> Lovelace
$cnegate :: Lovelace -> Lovelace
negate :: Lovelace -> Lovelace
$cabs :: Lovelace -> Lovelace
abs :: Lovelace -> Lovelace
$csignum :: Lovelace -> Lovelace
signum :: Lovelace -> Lovelace
$cfromInteger :: Integer -> Lovelace
fromInteger :: Integer -> Lovelace
Num, Eq Lovelace
Eq Lovelace =>
(Int -> Lovelace -> Int) -> (Lovelace -> Int) -> Hashable Lovelace
Int -> Lovelace -> Int
Lovelace -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Lovelace -> Int
hashWithSalt :: Int -> Lovelace -> Int
$chash :: Lovelace -> Int
hash :: Lovelace -> Int
Hashable, Int -> Lovelace
Lovelace -> Int
Lovelace -> [Lovelace]
Lovelace -> Lovelace
Lovelace -> Lovelace -> [Lovelace]
Lovelace -> Lovelace -> Lovelace -> [Lovelace]
(Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Int -> Lovelace)
-> (Lovelace -> Int)
-> (Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> Lovelace -> [Lovelace])
-> Enum Lovelace
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Lovelace -> Lovelace
succ :: Lovelace -> Lovelace
$cpred :: Lovelace -> Lovelace
pred :: Lovelace -> Lovelace
$ctoEnum :: Int -> Lovelace
toEnum :: Int -> Lovelace
$cfromEnum :: Lovelace -> Int
fromEnum :: Lovelace -> Int
$cenumFrom :: Lovelace -> [Lovelace]
enumFrom :: Lovelace -> [Lovelace]
$cenumFromThen :: Lovelace -> Lovelace -> [Lovelace]
enumFromThen :: Lovelace -> Lovelace -> [Lovelace]
$cenumFromTo :: Lovelace -> Lovelace -> [Lovelace]
enumFromTo :: Lovelace -> Lovelace -> [Lovelace]
$cenumFromThenTo :: Lovelace -> Lovelace -> Lovelace -> [Lovelace]
enumFromThenTo :: Lovelace -> Lovelace -> Lovelace -> [Lovelace]
Enum, Num Lovelace
Ord Lovelace
(Num Lovelace, Ord Lovelace) =>
(Lovelace -> Rational) -> Real Lovelace
Lovelace -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Lovelace -> Rational
toRational :: Lovelace -> Rational
Real, Enum Lovelace
Real Lovelace
(Real Lovelace, Enum Lovelace) =>
(Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> (Lovelace, Lovelace))
-> (Lovelace -> Lovelace -> (Lovelace, Lovelace))
-> (Lovelace -> Integer)
-> Integral Lovelace
Lovelace -> Integer
Lovelace -> Lovelace -> (Lovelace, Lovelace)
Lovelace -> Lovelace -> Lovelace
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Lovelace -> Lovelace -> Lovelace
quot :: Lovelace -> Lovelace -> Lovelace
$crem :: Lovelace -> Lovelace -> Lovelace
rem :: Lovelace -> Lovelace -> Lovelace
$cdiv :: Lovelace -> Lovelace -> Lovelace
div :: Lovelace -> Lovelace -> Lovelace
$cmod :: Lovelace -> Lovelace -> Lovelace
mod :: Lovelace -> Lovelace -> Lovelace
$cquotRem :: Lovelace -> Lovelace -> (Lovelace, Lovelace)
quotRem :: Lovelace -> Lovelace -> (Lovelace, Lovelace)
$cdivMod :: Lovelace -> Lovelace -> (Lovelace, Lovelace)
divMod :: Lovelace -> Lovelace -> (Lovelace, Lovelace)
$ctoInteger :: Lovelace -> Integer
toInteger :: Lovelace -> Integer
Integral, Typeable Lovelace
Typeable Lovelace =>
(Lovelace -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy Lovelace -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Lovelace] -> Size)
-> EncCBOR Lovelace
Lovelace -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [Lovelace] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: Lovelace -> Encoding
encCBOR :: Lovelace -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [Lovelace] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [Lovelace] -> Size
EncCBOR, Typeable Lovelace
Typeable Lovelace =>
(Lovelace -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy Lovelace -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Lovelace] -> Size)
-> ToCBOR Lovelace
Lovelace -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Lovelace] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Lovelace -> Encoding
toCBOR :: Lovelace -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Lovelace] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Lovelace] -> Size
ToCBOR, Context -> Lovelace -> IO (Maybe ThunkInfo)
Proxy Lovelace -> String
(Context -> Lovelace -> IO (Maybe ThunkInfo))
-> (Context -> Lovelace -> IO (Maybe ThunkInfo))
-> (Proxy Lovelace -> String)
-> NoThunks Lovelace
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Lovelace -> IO (Maybe ThunkInfo)
noThunks :: Context -> Lovelace -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Lovelace -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Lovelace -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Lovelace -> String
showTypeOf :: Proxy Lovelace -> String
NoThunks)
  deriving (NonEmpty Lovelace -> Lovelace
Lovelace -> Lovelace -> Lovelace
(Lovelace -> Lovelace -> Lovelace)
-> (NonEmpty Lovelace -> Lovelace)
-> (forall b. Integral b => b -> Lovelace -> Lovelace)
-> Semigroup Lovelace
forall b. Integral b => b -> Lovelace -> Lovelace
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Lovelace -> Lovelace -> Lovelace
<> :: Lovelace -> Lovelace -> Lovelace
$csconcat :: NonEmpty Lovelace -> Lovelace
sconcat :: NonEmpty Lovelace -> Lovelace
$cstimes :: forall b. Integral b => b -> Lovelace -> Lovelace
stimes :: forall b. Integral b => b -> Lovelace -> Lovelace
Semigroup, Semigroup Lovelace
Lovelace
Semigroup Lovelace =>
Lovelace
-> (Lovelace -> Lovelace -> Lovelace)
-> ([Lovelace] -> Lovelace)
-> Monoid Lovelace
[Lovelace] -> Lovelace
Lovelace -> Lovelace -> Lovelace
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Lovelace
mempty :: Lovelace
$cmappend :: Lovelace -> Lovelace -> Lovelace
mappend :: Lovelace -> Lovelace -> Lovelace
$cmconcat :: [Lovelace] -> Lovelace
mconcat :: [Lovelace] -> Lovelace
Monoid) via (Sum Integer)
  deriving anyclass (Lovelace -> Seq TypeRep
(Lovelace -> Seq TypeRep) -> HasTypeReps Lovelace
forall a. (a -> Seq TypeRep) -> HasTypeReps a
$ctypeReps :: Lovelace -> Seq TypeRep
typeReps :: Lovelace -> Seq TypeRep
HasTypeReps)

-- | Constant amount of Lovelace in the system.
lovelaceCap :: Lovelace
lovelaceCap :: Lovelace
lovelaceCap = Integer -> Lovelace
Lovelace (Integer -> Lovelace) -> Integer -> Lovelace
forall a b. (a -> b) -> a -> b
$ Integer
45 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int64
10 :: Int64) Int64 -> Int64 -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int64
15 :: Int64))

---------------------------------------------------------------------------------
-- Domain restriction and exclusion
---------------------------------------------------------------------------------

class Relation m where
  type Domain m :: Type
  type Range m :: Type

  singleton :: Domain m -> Range m -> m

  -- | Domain
  dom :: Ord (Domain m) => m -> Set (Domain m)

  -- | Range
  range :: Ord (Range m) => m -> Set (Range m)

  -- | Domain restriction
  --
  -- Unicode: 25c1
  (◁), (<|) :: (Ord (Domain m), Foldable f) => f (Domain m) -> m -> m
  f (Domain m)
s <| m
r = f (Domain m)
s f (Domain m) -> m -> m
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
forall (f :: * -> *).
(Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
 m
r

  -- | Domain exclusion
  --
  -- Unicode: 22ea
  (⋪), (</|) :: (Ord (Domain m), Foldable f) => f (Domain m) -> m -> m
  f (Domain m)
s </| m
r = f (Domain m)
s f (Domain m) -> m -> m
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
forall (f :: * -> *).
(Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
 m
r

  -- | Range restriction
  --
  -- Unicode: 25b7
  (▷), (|>) :: Ord (Range m) => m -> Set (Range m) -> m
  m
s |> Set (Range m)
r = m
s m -> Set (Range m) -> m
forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
 Set (Range m)
r

  -- | Range exclusion
  --
  -- Unicode: 22eb
  (⋫), (|/>) :: Ord (Range m) => m -> Set (Range m) -> m
  m
s |/> Set (Range m)
r = m
s m -> Set (Range m) -> m
forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
 Set (Range m)
r

  -- | Union
  (∪) :: (Ord (Domain m), Ord (Range m)) => m -> m -> m

  -- | Union Override Right
  (⨃) :: (Ord (Domain m), Ord (Range m), Foldable f) => m -> f (Domain m, Range m) -> m

  -- | Restrict domain to values less or equal than the given value.
  --
  -- Unicode: 25c1
  (<=◁) :: Ord (Domain m) => Domain m -> m -> m

  infixl 5 <=◁

  -- | Restrict range to values less or equal than the given value
  --
  -- Unicode: 25b7
  (▷<=) :: Ord (Range m) => m -> Range m -> m

  infixl 5 ▷<=

  -- | Restrict range to values greater or equal than the given value
  --
  -- Unicode: 25b7
  (▷>=) :: Ord (Range m) => m -> Range m -> m

  infixl 5 ▷>=

  -- | Size of the relation
  size :: Integral n => m -> n

-- | Alias for 'elem'.
--
-- Unicode: 2208
(∈) :: (Eq a, Foldable f) => a -> f a -> Bool
a
a ∈ :: forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
 f a
f = a -> f a -> Bool
forall a. Eq a => a -> f a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
a f a
f

-- | Alias for not 'elem'.
--
-- Unicode: 2209
(∉) :: (Eq a, Foldable f) => a -> f a -> Bool
a
a ∉ :: forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
 f a
f = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ a -> f a -> Bool
forall a. Eq a => a -> f a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
a f a
f

infixl 4 

instance (Ord k, Ord v) => Relation (Bimap k v) where
  type Domain (Bimap k v) = k
  type Range (Bimap k v) = v

  singleton :: Domain (Bimap k v) -> Range (Bimap k v) -> Bimap k v
singleton = k -> v -> Bimap k v
Domain (Bimap k v) -> Range (Bimap k v) -> Bimap k v
forall a b. a -> b -> Bimap a b
Bimap.singleton

  dom :: Ord (Domain (Bimap k v)) => Bimap k v -> Set (Domain (Bimap k v))
dom = [k] -> Set k
forall a. Ord a => [a] -> Set a
Set.fromList ([k] -> Set k) -> (Bimap k v -> [k]) -> Bimap k v -> Set k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap k v -> [k]
forall a b. Bimap a b -> [a]
Bimap.keys
  range :: Ord (Range (Bimap k v)) => Bimap k v -> Set (Range (Bimap k v))
range = [v] -> Set v
forall a. Ord a => [a] -> Set a
Set.fromList ([v] -> Set v) -> (Bimap k v -> [v]) -> Bimap k v -> Set v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap k v -> [v]
forall a b. Bimap a b -> [b]
Bimap.elems

  f (Domain (Bimap k v))
s ◁ :: forall (f :: * -> *).
(Ord (Domain (Bimap k v)), Foldable f) =>
f (Domain (Bimap k v)) -> Bimap k v -> Bimap k v
 Bimap k v
r = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
k v
_ -> k
k k -> Set k -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` f k -> Set k
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f k
f (Domain (Bimap k v))
s) Bimap k v
r

  f (Domain (Bimap k v))
s ⋪ :: forall (f :: * -> *).
(Ord (Domain (Bimap k v)), Foldable f) =>
f (Domain (Bimap k v)) -> Bimap k v -> Bimap k v
 Bimap k v
r = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
k v
_ -> k
k k -> Set k -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` f k -> Set k
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f k
f (Domain (Bimap k v))
s) Bimap k v
r

  Bimap k v
r ▷ :: Ord (Range (Bimap k v)) =>
Bimap k v -> Set (Range (Bimap k v)) -> Bimap k v
 Set (Range (Bimap k v))
s = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v -> Set v -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member v
v Set v
Set (Range (Bimap k v))
s) Bimap k v
r

  Bimap k v
r ⋫ :: Ord (Range (Bimap k v)) =>
Bimap k v -> Set (Range (Bimap k v)) -> Bimap k v
 Set (Range (Bimap k v))
s = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v -> Set v -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember v
v Set v
Set (Range (Bimap k v))
s) Bimap k v
r

  Bimap k v
d0 ∪ :: (Ord (Domain (Bimap k v)), Ord (Range (Bimap k v))) =>
Bimap k v -> Bimap k v -> Bimap k v
 Bimap k v
d1 = (k -> v -> Bimap k v -> Bimap k v)
-> Bimap k v -> Bimap k v -> Bimap k v
forall a b c. (a -> b -> c -> c) -> c -> Bimap a b -> c
Bimap.fold k -> v -> Bimap k v -> Bimap k v
forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
Bimap.insert Bimap k v
d0 Bimap k v
d1
  Bimap k v
d0 ⨃ :: forall (f :: * -> *).
(Ord (Domain (Bimap k v)), Ord (Range (Bimap k v)), Foldable f) =>
Bimap k v -> f (Domain (Bimap k v), Range (Bimap k v)) -> Bimap k v
 f (Domain (Bimap k v), Range (Bimap k v))
d1 = ((k, v) -> Bimap k v -> Bimap k v)
-> Bimap k v -> [(k, v)] -> Bimap k v
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((k -> v -> Bimap k v -> Bimap k v)
-> (k, v) -> Bimap k v -> Bimap k v
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry k -> v -> Bimap k v -> Bimap k v
forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
Bimap.insert) Bimap k v
d0 (f (k, v) -> [(k, v)]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (k, v)
f (Domain (Bimap k v), Range (Bimap k v))
d1)

  Domain (Bimap k v)
vmax <=◁ :: Ord (Domain (Bimap k v)) =>
Domain (Bimap k v) -> Bimap k v -> Bimap k v
<=◁ Bimap k v
r = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
v v
_ -> k
v k -> k -> Bool
forall a. Ord a => a -> a -> Bool
<= k
Domain (Bimap k v)
vmax) Bimap k v
r

  Bimap k v
r ▷<= :: Ord (Range (Bimap k v)) =>
Bimap k v -> Range (Bimap k v) -> Bimap k v
▷<= Range (Bimap k v)
vmax = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v
v v -> v -> Bool
forall a. Ord a => a -> a -> Bool
<= v
Range (Bimap k v)
vmax) Bimap k v
r

  Bimap k v
r ▷>= :: Ord (Range (Bimap k v)) =>
Bimap k v -> Range (Bimap k v) -> Bimap k v
▷>= Range (Bimap k v)
vmin = (k -> v -> Bool) -> Bimap k v -> Bimap k v
forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v
v v -> v -> Bool
forall a. Ord a => a -> a -> Bool
>= v
Range (Bimap k v)
vmin) Bimap k v
r

  size :: forall n. Integral n => Bimap k v -> n
size = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> n) -> (Bimap k v -> Int) -> Bimap k v -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap k v -> Int
forall a b. Bimap a b -> Int
Bimap.size

instance Relation (Map k v) where
  type Domain (Map k v) = k
  type Range (Map k v) = v

  singleton :: Domain (Map k v) -> Range (Map k v) -> Map k v
singleton = k -> v -> Map k v
Domain (Map k v) -> Range (Map k v) -> Map k v
forall k a. k -> a -> Map k a
Map.singleton

  dom :: Ord (Domain (Map k v)) => Map k v -> Set (Domain (Map k v))
dom = Map k v -> Set k
Map k v -> Set (Domain (Map k v))
forall k a. Map k a -> Set k
Map.keysSet
  range :: Ord (Range (Map k v)) => Map k v -> Set (Range (Map k v))
range = [v] -> Set v
forall a. Ord a => [a] -> Set a
Set.fromList ([v] -> Set v) -> (Map k v -> [v]) -> Map k v -> Set v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map k v -> [v]
forall k a. Map k a -> [a]
Map.elems

  f (Domain (Map k v))
s ◁ :: forall (f :: * -> *).
(Ord (Domain (Map k v)), Foldable f) =>
f (Domain (Map k v)) -> Map k v -> Map k v
 Map k v
r = (k -> v -> Bool) -> Map k v -> Map k v
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k k -> Set k -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` f k -> Set k
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f k
f (Domain (Map k v))
s) Map k v
r

  f (Domain (Map k v))
s ⋪ :: forall (f :: * -> *).
(Ord (Domain (Map k v)), Foldable f) =>
f (Domain (Map k v)) -> Map k v -> Map k v
 Map k v
r = (k -> v -> Bool) -> Map k v -> Map k v
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k k -> Set k -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` f k -> Set k
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f k
f (Domain (Map k v))
s) Map k v
r

  Map k v
r ▷ :: Ord (Range (Map k v)) =>
Map k v -> Set (Range (Map k v)) -> Map k v
 Set (Range (Map k v))
s = (v -> Bool) -> Map k v -> Map k v
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter ((v -> Set v -> Bool) -> Set v -> v -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip v -> Set v -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Set v
Set (Range (Map k v))
s) Map k v
r

  Map k v
r ⋫ :: Ord (Range (Map k v)) =>
Map k v -> Set (Range (Map k v)) -> Map k v
 Set (Range (Map k v))
s = (v -> Bool) -> Map k v -> Map k v
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter ((v -> Set v -> Bool) -> Set v -> v -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip v -> Set v -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember Set v
Set (Range (Map k v))
s) Map k v
r

  Map k v
d0 ∪ :: (Ord (Domain (Map k v)), Ord (Range (Map k v))) =>
Map k v -> Map k v -> Map k v
 Map k v
d1 = Map k v -> Map k v -> Map k v
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map k v
d0 Map k v
d1

  -- For union override we pass @d1@ as first argument, since 'Map.union' is
  -- left biased.
  Map k v
d0 ⨃ :: forall (f :: * -> *).
(Ord (Domain (Map k v)), Ord (Range (Map k v)), Foldable f) =>
Map k v -> f (Domain (Map k v), Range (Map k v)) -> Map k v
 f (Domain (Map k v), Range (Map k v))
d1 = Map k v -> Map k v -> Map k v
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union ([(k, v)] -> Map k v
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(k, v)] -> Map k v)
-> (f (Domain (Map k v), Range (Map k v)) -> [(k, v)])
-> f (Domain (Map k v), Range (Map k v))
-> Map k v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f (k, v) -> [(k, v)]
f (Domain (Map k v), Range (Map k v)) -> [(k, v)]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (f (Domain (Map k v), Range (Map k v)) -> Map k v)
-> f (Domain (Map k v), Range (Map k v)) -> Map k v
forall a b. (a -> b) -> a -> b
$ f (Domain (Map k v), Range (Map k v))
d1) Map k v
d0

  Domain (Map k v)
vmax <=◁ :: Ord (Domain (Map k v)) => Domain (Map k v) -> Map k v -> Map k v
<=◁ Map k v
r = (k -> v -> Bool) -> Map k v -> Map k v
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k k -> k -> Bool
forall a. Ord a => a -> a -> Bool
<= k
Domain (Map k v)
vmax) Map k v
r

  Map k v
r ▷<= :: Ord (Range (Map k v)) => Map k v -> Range (Map k v) -> Map k v
▷<= Range (Map k v)
vmax = (v -> Bool) -> Map k v -> Map k v
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Range (Map k v) -> Range (Map k v) -> Bool
forall a. Ord a => a -> a -> Bool
<= Range (Map k v)
vmax) Map k v
r

  Map k v
r ▷>= :: Ord (Range (Map k v)) => Map k v -> Range (Map k v) -> Map k v
▷>= Range (Map k v)
vmin = (v -> Bool) -> Map k v -> Map k v
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Range (Map k v) -> Range (Map k v) -> Bool
forall a. Ord a => a -> a -> Bool
>= Range (Map k v)
vmin) Map k v
r

  size :: forall n. Integral n => Map k v -> n
size = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> n) -> (Map k v -> Int) -> Map k v -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map k v -> Int
forall k a. Map k a -> Int
Map.size

-- | Union override plus is (A\B)∪(B\A)∪{k|->v1+v2 | k|->v1 : A /\ k|->v2 : B}
(∪+) :: (Ord a, Ord b, Num b) => Map a b -> Map a b -> Map a b
Map a b
a ∪+ :: forall a b. (Ord a, Ord b, Num b) => Map a b -> Map a b -> Map a b
∪+ Map a b
b = ((Map a b -> Set (Domain (Map a b))
forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map a b
a) Set (Domain (Map a b)) -> Map a b -> Map a b
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
forall (f :: * -> *).
(Ord (Domain (Map a b)), Foldable f) =>
f (Domain (Map a b)) -> Map a b -> Map a b
 Map a b
b) Map a b -> Map a b -> Map a b
forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 ((Map a b -> Set (Domain (Map a b))
forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map a b
b) Set (Domain (Map a b)) -> Map a b -> Map a b
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
forall (f :: * -> *).
(Ord (Domain (Map a b)), Foldable f) =>
f (Domain (Map a b)) -> Map a b -> Map a b
 Map a b
a) Map a b -> Map a b -> Map a b
forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 ((b -> b -> b) -> Map a b -> Map a b -> Map a b
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith b -> b -> b
forall a. Num a => a -> a -> a
(+) Map a b
a Map a b
b)

instance Relation (Set (a, b)) where
  type Domain (Set (a, b)) = a
  type Range (Set (a, b)) = b

  singleton :: Domain (Set (a, b)) -> Range (Set (a, b)) -> Set (a, b)
singleton Domain (Set (a, b))
a Range (Set (a, b))
b = (a, b) -> Set (a, b)
forall a. a -> Set a
Set.singleton (a
Domain (Set (a, b))
a, b
Range (Set (a, b))
b)

  dom :: Ord (Domain (Set (a, b))) =>
Set (a, b) -> Set (Domain (Set (a, b)))
dom = ((a, b) -> a) -> Set (a, b) -> Set a
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (a, b) -> a
forall a b. (a, b) -> a
fst

  range :: Ord (Range (Set (a, b))) => Set (a, b) -> Set (Range (Set (a, b)))
range = ((a, b) -> b) -> Set (a, b) -> Set b
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (a, b) -> b
forall a b. (a, b) -> b
snd

  f (Domain (Set (a, b)))
s ◁ :: forall (f :: * -> *).
(Ord (Domain (Set (a, b))), Foldable f) =>
f (Domain (Set (a, b))) -> Set (a, b) -> Set (a, b)
 Set (a, b)
r = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
k, b
_) -> a
k a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` f a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
f (Domain (Set (a, b)))
s) Set (a, b)
r

  f (Domain (Set (a, b)))
s ⋪ :: forall (f :: * -> *).
(Ord (Domain (Set (a, b))), Foldable f) =>
f (Domain (Set (a, b))) -> Set (a, b) -> Set (a, b)
 Set (a, b)
r = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
k, b
_) -> a
k a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` f a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
f (Domain (Set (a, b)))
s) Set (a, b)
r

  Set (a, b)
r ▷ :: Ord (Range (Set (a, b))) =>
Set (a, b) -> Set (Range (Set (a, b))) -> Set (a, b)
 Set (Range (Set (a, b)))
s = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
_, b
v) -> b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member b
v Set b
Set (Range (Set (a, b)))
s) Set (a, b)
r

  Set (a, b)
r ⋫ :: Ord (Range (Set (a, b))) =>
Set (a, b) -> Set (Range (Set (a, b))) -> Set (a, b)
 Set (Range (Set (a, b)))
s = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
_, b
v) -> b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember b
v Set b
Set (Range (Set (a, b)))
s) Set (a, b)
r

  ∪ :: (Ord (Domain (Set (a, b))), Ord (Range (Set (a, b)))) =>
Set (a, b) -> Set (a, b) -> Set (a, b)
(∪) = Set (a, b) -> Set (a, b) -> Set (a, b)
forall a. Ord a => Set a -> Set a -> Set a
Set.union

  Set (a, b)
d0 ⨃ :: forall (f :: * -> *).
(Ord (Domain (Set (a, b))), Ord (Range (Set (a, b))),
 Foldable f) =>
Set (a, b)
-> f (Domain (Set (a, b)), Range (Set (a, b))) -> Set (a, b)
 f (Domain (Set (a, b)), Range (Set (a, b)))
d1 = Set (a, b)
d1' Set (a, b) -> Set (a, b) -> Set (a, b)
forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 ((Set (a, b) -> Set (Domain (Set (a, b)))
forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Set (a, b)
d1') Set (Domain (Set (a, b))) -> Set (a, b) -> Set (a, b)
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
forall (f :: * -> *).
(Ord (Domain (Set (a, b))), Foldable f) =>
f (Domain (Set (a, b))) -> Set (a, b) -> Set (a, b)
 Set (a, b)
d0)
    where
      d1' :: Set (a, b)
d1' = f (a, b) -> Set (a, b)
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f (a, b)
f (Domain (Set (a, b)), Range (Set (a, b)))
d1

  Domain (Set (a, b))
vmax <=◁ :: Ord (Domain (Set (a, b))) =>
Domain (Set (a, b)) -> Set (a, b) -> Set (a, b)
<=◁ Set (a, b)
r = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((Domain (Set (a, b)) -> Domain (Set (a, b)) -> Bool
forall a. Ord a => a -> a -> Bool
<= Domain (Set (a, b))
vmax) (a -> Bool) -> ((a, b) -> a) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> a
forall a b. (a, b) -> a
fst) (Set (a, b) -> Set (a, b)) -> Set (a, b) -> Set (a, b)
forall a b. (a -> b) -> a -> b
$ Set (a, b)
r

  Set (a, b)
r ▷<= :: Ord (Range (Set (a, b))) =>
Set (a, b) -> Range (Set (a, b)) -> Set (a, b)
▷<= Range (Set (a, b))
vmax = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((Range (Set (a, b)) -> Range (Set (a, b)) -> Bool
forall a. Ord a => a -> a -> Bool
<= Range (Set (a, b))
vmax) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) (Set (a, b) -> Set (a, b)) -> Set (a, b) -> Set (a, b)
forall a b. (a -> b) -> a -> b
$ Set (a, b)
r

  Set (a, b)
r ▷>= :: Ord (Range (Set (a, b))) =>
Set (a, b) -> Range (Set (a, b)) -> Set (a, b)
▷>= Range (Set (a, b))
vmax = ((a, b) -> Bool) -> Set (a, b) -> Set (a, b)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((Range (Set (a, b)) -> Range (Set (a, b)) -> Bool
forall a. Ord a => a -> a -> Bool
>= Range (Set (a, b))
vmax) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) (Set (a, b) -> Set (a, b)) -> Set (a, b) -> Set (a, b)
forall a b. (a -> b) -> a -> b
$ Set (a, b)
r

  size :: forall n. Integral n => Set (a, b) -> n
size = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> n) -> (Set (a, b) -> Int) -> Set (a, b) -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (a, b) -> Int
forall a. Set a -> Int
Set.size

instance Relation [(a, b)] where
  type Domain [(a, b)] = a
  type Range [(a, b)] = b

  singleton :: Domain [(a, b)] -> Range [(a, b)] -> [(a, b)]
singleton Domain [(a, b)]
a Range [(a, b)]
b = [(a
Domain [(a, b)]
a, b
Range [(a, b)]
b)]

  dom :: Ord (Domain [(a, b)]) => [(a, b)] -> Set (Domain [(a, b)])
dom = [a] -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet ([a] -> Set a) -> ([(a, b)] -> [a]) -> [(a, b)] -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> a) -> [(a, b)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> a
forall a b. (a, b) -> a
fst

  range :: Ord (Range [(a, b)]) => [(a, b)] -> Set (Range [(a, b)])
range = [b] -> Set b
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet ([b] -> Set b) -> ([(a, b)] -> [b]) -> [(a, b)] -> Set b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> b) -> [(a, b)] -> [b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> b
forall a b. (a, b) -> b
snd

  f (Domain [(a, b)])
s ◁ :: forall (f :: * -> *).
(Ord (Domain [(a, b)]), Foldable f) =>
f (Domain [(a, b)]) -> [(a, b)] -> [(a, b)]
 [(a, b)]
r = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` f a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
f (Domain [(a, b)])
s) (a -> Bool) -> ((a, b) -> a) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> a
forall a b. (a, b) -> a
fst) [(a, b)]
r

  f (Domain [(a, b)])
s ⋪ :: forall (f :: * -> *).
(Ord (Domain [(a, b)]), Foldable f) =>
f (Domain [(a, b)]) -> [(a, b)] -> [(a, b)]
 [(a, b)]
r = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` f a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
f (Domain [(a, b)])
s) (a -> Bool) -> ((a, b) -> a) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> a
forall a b. (a, b) -> a
fst) [(a, b)]
r

  [(a, b)]
r ▷ :: Ord (Range [(a, b)]) =>
[(a, b)] -> Set (Range [(a, b)]) -> [(a, b)]
 Set (Range [(a, b)])
s = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set b -> Set b
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet Set b
Set (Range [(a, b)])
s) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) [(a, b)]
r

  [(a, b)]
r ⋫ :: Ord (Range [(a, b)]) =>
[(a, b)] -> Set (Range [(a, b)]) -> [(a, b)]
 Set (Range [(a, b)])
s = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set b -> Set b
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet Set b
Set (Range [(a, b)])
s) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) [(a, b)]
r

  ∪ :: (Ord (Domain [(a, b)]), Ord (Range [(a, b)])) =>
[(a, b)] -> [(a, b)] -> [(a, b)]
(∪) = [(a, b)] -> [(a, b)] -> [(a, b)]
forall a. [a] -> [a] -> [a]
(++)

  -- In principle a list of pairs allows for duplicated keys.
  [(a, b)]
d0 ⨃ :: forall (f :: * -> *).
(Ord (Domain [(a, b)]), Ord (Range [(a, b)]), Foldable f) =>
[(a, b)] -> f (Domain [(a, b)], Range [(a, b)]) -> [(a, b)]
 f (Domain [(a, b)], Range [(a, b)])
d1 = [(a, b)]
d0 [(a, b)] -> [(a, b)] -> [(a, b)]
forall a. [a] -> [a] -> [a]
++ f (a, b) -> [(a, b)]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (a, b)
f (Domain [(a, b)], Range [(a, b)])
d1

  Domain [(a, b)]
vmax <=◁ :: Ord (Domain [(a, b)]) => Domain [(a, b)] -> [(a, b)] -> [(a, b)]
<=◁ [(a, b)]
r = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Domain [(a, b)] -> Domain [(a, b)] -> Bool
forall a. Ord a => a -> a -> Bool
<= Domain [(a, b)]
vmax) (a -> Bool) -> ((a, b) -> a) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> a
forall a b. (a, b) -> a
fst) [(a, b)]
r

  [(a, b)]
r ▷<= :: Ord (Range [(a, b)]) => [(a, b)] -> Range [(a, b)] -> [(a, b)]
▷<= Range [(a, b)]
vmax = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Range [(a, b)] -> Range [(a, b)] -> Bool
forall a. Ord a => a -> a -> Bool
<= Range [(a, b)]
vmax) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) [(a, b)]
r

  [(a, b)]
r ▷>= :: Ord (Range [(a, b)]) => [(a, b)] -> Range [(a, b)] -> [(a, b)]
▷>= Range [(a, b)]
vmin = ((a, b) -> Bool) -> [(a, b)] -> [(a, b)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((b
Range [(a, b)]
vmin b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<=) (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd) [(a, b)]
r

  size :: forall n. Integral n => [(a, b)] -> n
size = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> n) -> ([(a, b)] -> Int) -> [(a, b)] -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(a, b)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length

---------------------------------------------------------------------------------
-- Aliases
---------------------------------------------------------------------------------

-- | Inclusion among foldables.
--
-- Unicode: 2286
(⊆) :: (Foldable f, Foldable g, Ord a) => f a -> g a -> Bool
f a
x ⊆ :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
f a -> g a -> Bool
 g a
y = f a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
x Set a -> Set a -> Bool
forall a. Ord a => Set a -> Set a -> Bool
`isSubsetOf` g a -> Set a
forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet g a
y

toSet :: (Foldable f, Ord a) => f a -> Set a
toSet :: forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet = [a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList ([a] -> Set a) -> (f a -> [a]) -> f a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList

(∩) :: Ord a => Set a -> Set a -> Set a
∩ :: forall a. Ord a => Set a -> Set a -> Set a
(∩) = Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
intersection