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

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

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

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

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

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

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

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

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

-- | Constant amount of Lovelace in the system.
lovelaceCap :: Lovelace
lovelaceCap :: Lovelace
lovelaceCap = Integer -> Lovelace
Lovelace forall a b. (a -> b) -> a -> b
$ Integer
45 forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int64
10 :: 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 forall m (f :: * -> *).
(Relation m, 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 forall m (f :: * -> *).
(Relation m, 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 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 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 = 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 forall a b. (a -> b) -> a -> b
$ 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 = 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 = forall a. Ord a => [a] -> Set a
Set.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> [a]
Bimap.keys
  range :: Ord (Range (Bimap k v)) => Bimap k v -> Set (Range (Bimap k v))
range = forall a. Ord a => [a] -> Set a
Set.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
k v
_ -> k
k forall a. Ord a => a -> Set a -> Bool
`Set.member` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
k v
_ -> k
k forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> forall a. Ord a => a -> Set a -> Bool
Set.member v
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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> forall a. Ord a => a -> Set a -> Bool
Set.notMember v
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 = forall a b c. (a -> b -> c -> c) -> c -> Bimap a b -> c
Bimap.fold 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 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
Bimap.insert) Bimap k v
d0 (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
v v
_ -> k
v forall a. Ord a => a -> a -> Bool
<= 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v
v forall a. Ord a => a -> a -> Bool
<= 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 = forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
Bimap.filter (\k
_ v
v -> v
v forall a. Ord a => a -> a -> Bool
>= Range (Bimap k v)
vmin) Bimap k v
r

  size :: forall n. Integral n => Bimap k v -> n
size = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = 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 = 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 = forall a. Ord a => [a] -> Set a
Set.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k forall a. Ord a => a -> Set a -> Bool
`Set.member` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> Set a -> Bool
Set.member 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 = forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> Set a -> Bool
Set.notMember 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 = 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 = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList 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 = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\k
k v
_ -> k
k forall a. Ord a => a -> a -> Bool
<= 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 = forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (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 = forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (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 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = ((forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map a b
a) forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
 Map a b
b) forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 ((forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map a b
b) forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
 Map a b
a) forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 (forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith 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 = forall a. a -> Set a
Set.singleton (Domain (Set (a, b))
a, Range (Set (a, b))
b)

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

  range :: Ord (Range (Set (a, b))) => Set (a, b) -> Set (Range (Set (a, b)))
range = forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
k, b
_) -> a
k forall a. Ord a => a -> Set a -> Bool
`Set.member` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
k, b
_) -> a
k forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
_, b
v) -> forall a. Ord a => a -> Set a -> Bool
Set.member b
v 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (\(a
_, b
v) -> forall a. Ord a => a -> Set a -> Bool
Set.notMember b
v 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)
(∪) = 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' forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
 ((forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Set (a, b)
d1') forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
 Set (a, b)
d0)
    where
      d1' :: Set (a, b)
d1' = forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((forall a. Ord a => a -> a -> Bool
<= Domain (Set (a, b))
vmax) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((forall a. Ord a => a -> a -> Bool
<= Range (Set (a, b))
vmax) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) 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 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((forall a. Ord a => a -> a -> Bool
>= Range (Set (a, b))
vmax) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) forall a b. (a -> b) -> a -> b
$ Set (a, b)
r

  size :: forall n. Integral n => Set (a, b) -> n
size = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = [(Domain [(a, b)]
a, Range [(a, b)]
b)]

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

  range :: Ord (Range [(a, b)]) => [(a, b)] -> Set (Range [(a, b)])
range = forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> Set a -> Bool
`Set.member` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f (Domain [(a, b)])
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f (Domain [(a, b)])
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> Set a -> Bool
`Set.member` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet Set (Range [(a, b)])
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet Set (Range [(a, b)])
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(a, b)]
r

  ∪ :: (Ord (Domain [(a, b)]), Ord (Range [(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 forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> a -> Bool
<= Domain [(a, b)]
vmax) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> a -> Bool
<= Range [(a, b)]
vmax) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. (a -> Bool) -> [a] -> [a]
filter ((Range [(a, b)]
vmin forall a. Ord a => a -> a -> Bool
<=) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(a, b)]
r

  size :: forall n. Integral n => [(a, b)] -> n
size = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall (f :: * -> *) a. (Foldable f, Ord a) => f a -> Set a
toSet f a
x forall a. Ord a => Set a -> Set a -> Bool
`isSubsetOf` 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 = forall a. Ord a => [a] -> Set a
Set.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
(∩) = forall a. Ord a => Set a -> Set a -> Set a
intersection