{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE EmptyDataDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MonadComprehensions #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Byron.Spec.Ledger.Update (
module Byron.Spec.Ledger.Update,
PredicateFailure (),
)
where
import Byron.Spec.Ledger.Core (
BlockCount (..),
HasHash,
Owner (Owner),
Relation (..),
Slot,
SlotCount (..),
VKey (VKey),
VKeyGenesis (VKeyGenesis),
dom,
hash,
(*.),
(-.),
(∈),
(∉),
(⋪),
(▷),
(▷<=),
(▷>=),
(◁),
(⨃),
)
import qualified Byron.Spec.Ledger.Core as Core
import qualified Byron.Spec.Ledger.Core.Generators as CoreGen
import Byron.Spec.Ledger.Core.Omniscient (skey)
import qualified Byron.Spec.Ledger.GlobalParams as GP
import Control.Arrow (second, (&&&))
import Control.State.Transition
import Data.AbstractSize (HasTypeReps)
import Data.Bimap (Bimap, empty, lookupR)
import qualified Data.Bimap as Bimap
import Data.Char (isAscii)
import Data.Data (Data, Typeable)
import Data.Foldable as F (foldl', toList)
import Data.Hashable (Hashable)
import qualified Data.Hashable as H
import Data.Ix (inRange)
import Data.List (sortOn)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (catMaybes, fromMaybe)
import Data.Ord (Down (Down))
import Data.Set (Set, union, (\\))
import qualified Data.Set as Set
import Data.Tuple (swap)
import Data.Word (Word8)
import GHC.Generics (Generic)
import Hedgehog (Gen)
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Lens.Micro
import Lens.Micro.Extras (view)
import Lens.Micro.Internal (Field1 (..), Field2 (..), Field3 (..))
import Lens.Micro.TH (makeLenses)
import NoThunks.Class (NoThunks (..))
import Numeric.Natural
import Test.Control.State.Transition.Generator (
HasTrace,
envGen,
sigGen,
)
import Prelude
newtype FactorA = FactorA Int
deriving stock (forall x. Rep FactorA x -> FactorA
forall x. FactorA -> Rep FactorA x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FactorA x -> FactorA
$cfrom :: forall x. FactorA -> Rep FactorA x
Generic, Int -> FactorA -> ShowS
[FactorA] -> ShowS
FactorA -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FactorA] -> ShowS
$cshowList :: [FactorA] -> ShowS
show :: FactorA -> String
$cshow :: FactorA -> String
showsPrec :: Int -> FactorA -> ShowS
$cshowsPrec :: Int -> FactorA -> ShowS
Show, Typeable FactorA
FactorA -> DataType
FactorA -> Constr
(forall b. Data b => b -> b) -> FactorA -> FactorA
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) -> FactorA -> u
forall u. (forall d. Data d => d -> u) -> FactorA -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorA
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorA -> c FactorA
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorA)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorA)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorA -> m FactorA
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FactorA -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FactorA -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> FactorA -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FactorA -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorA -> r
gmapT :: (forall b. Data b => b -> b) -> FactorA -> FactorA
$cgmapT :: (forall b. Data b => b -> b) -> FactorA -> FactorA
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorA)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorA)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorA)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorA)
dataTypeOf :: FactorA -> DataType
$cdataTypeOf :: FactorA -> DataType
toConstr :: FactorA -> Constr
$ctoConstr :: FactorA -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorA
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorA
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorA -> c FactorA
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorA -> c FactorA
Data, Typeable)
deriving newtype (FactorA -> FactorA -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FactorA -> FactorA -> Bool
$c/= :: FactorA -> FactorA -> Bool
== :: FactorA -> FactorA -> Bool
$c== :: FactorA -> FactorA -> Bool
Eq, Eq FactorA
FactorA -> FactorA -> Bool
FactorA -> FactorA -> Ordering
FactorA -> FactorA -> FactorA
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 :: FactorA -> FactorA -> FactorA
$cmin :: FactorA -> FactorA -> FactorA
max :: FactorA -> FactorA -> FactorA
$cmax :: FactorA -> FactorA -> FactorA
>= :: FactorA -> FactorA -> Bool
$c>= :: FactorA -> FactorA -> Bool
> :: FactorA -> FactorA -> Bool
$c> :: FactorA -> FactorA -> Bool
<= :: FactorA -> FactorA -> Bool
$c<= :: FactorA -> FactorA -> Bool
< :: FactorA -> FactorA -> Bool
$c< :: FactorA -> FactorA -> Bool
compare :: FactorA -> FactorA -> Ordering
$ccompare :: FactorA -> FactorA -> Ordering
Ord, Eq FactorA
Int -> FactorA -> Int
FactorA -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FactorA -> Int
$chash :: FactorA -> Int
hashWithSalt :: Int -> FactorA -> Int
$chashWithSalt :: Int -> FactorA -> Int
Hashable, Context -> FactorA -> IO (Maybe ThunkInfo)
Proxy FactorA -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy FactorA -> String
$cshowTypeOf :: Proxy FactorA -> String
wNoThunks :: Context -> FactorA -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> FactorA -> IO (Maybe ThunkInfo)
noThunks :: Context -> FactorA -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> FactorA -> IO (Maybe ThunkInfo)
NoThunks)
deriving anyclass (FactorA -> Seq TypeRep
forall a. (a -> Seq TypeRep) -> HasTypeReps a
typeReps :: FactorA -> Seq TypeRep
$ctypeReps :: FactorA -> Seq TypeRep
HasTypeReps)
newtype FactorB = FactorB Int
deriving stock (forall x. Rep FactorB x -> FactorB
forall x. FactorB -> Rep FactorB x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FactorB x -> FactorB
$cfrom :: forall x. FactorB -> Rep FactorB x
Generic, Int -> FactorB -> ShowS
[FactorB] -> ShowS
FactorB -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FactorB] -> ShowS
$cshowList :: [FactorB] -> ShowS
show :: FactorB -> String
$cshow :: FactorB -> String
showsPrec :: Int -> FactorB -> ShowS
$cshowsPrec :: Int -> FactorB -> ShowS
Show, Typeable FactorB
FactorB -> DataType
FactorB -> Constr
(forall b. Data b => b -> b) -> FactorB -> FactorB
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) -> FactorB -> u
forall u. (forall d. Data d => d -> u) -> FactorB -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorB
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorB -> c FactorB
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorB)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorB)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FactorB -> m FactorB
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FactorB -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FactorB -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> FactorB -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FactorB -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FactorB -> r
gmapT :: (forall b. Data b => b -> b) -> FactorB -> FactorB
$cgmapT :: (forall b. Data b => b -> b) -> FactorB -> FactorB
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorB)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FactorB)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorB)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FactorB)
dataTypeOf :: FactorB -> DataType
$cdataTypeOf :: FactorB -> DataType
toConstr :: FactorB -> Constr
$ctoConstr :: FactorB -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorB
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FactorB
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorB -> c FactorB
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FactorB -> c FactorB
Data, Typeable)
deriving newtype (FactorB -> FactorB -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FactorB -> FactorB -> Bool
$c/= :: FactorB -> FactorB -> Bool
== :: FactorB -> FactorB -> Bool
$c== :: FactorB -> FactorB -> Bool
Eq, Eq FactorB
FactorB -> FactorB -> Bool
FactorB -> FactorB -> Ordering
FactorB -> FactorB -> FactorB
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 :: FactorB -> FactorB -> FactorB
$cmin :: FactorB -> FactorB -> FactorB
max :: FactorB -> FactorB -> FactorB
$cmax :: FactorB -> FactorB -> FactorB
>= :: FactorB -> FactorB -> Bool
$c>= :: FactorB -> FactorB -> Bool
> :: FactorB -> FactorB -> Bool
$c> :: FactorB -> FactorB -> Bool
<= :: FactorB -> FactorB -> Bool
$c<= :: FactorB -> FactorB -> Bool
< :: FactorB -> FactorB -> Bool
$c< :: FactorB -> FactorB -> Bool
compare :: FactorB -> FactorB -> Ordering
$ccompare :: FactorB -> FactorB -> Ordering
Ord, Eq FactorB
Int -> FactorB -> Int
FactorB -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FactorB -> Int
$chash :: FactorB -> Int
hashWithSalt :: Int -> FactorB -> Int
$chashWithSalt :: Int -> FactorB -> Int
Hashable, Context -> FactorB -> IO (Maybe ThunkInfo)
Proxy FactorB -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy FactorB -> String
$cshowTypeOf :: Proxy FactorB -> String
wNoThunks :: Context -> FactorB -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> FactorB -> IO (Maybe ThunkInfo)
noThunks :: Context -> FactorB -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> FactorB -> IO (Maybe ThunkInfo)
NoThunks)
deriving anyclass (FactorB -> Seq TypeRep
forall a. (a -> Seq TypeRep) -> HasTypeReps a
typeReps :: FactorB -> Seq TypeRep
$ctypeReps :: FactorB -> Seq TypeRep
HasTypeReps)
newtype UpAdptThd = UpAdptThd Double
deriving stock (forall x. Rep UpAdptThd x -> UpAdptThd
forall x. UpAdptThd -> Rep UpAdptThd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpAdptThd x -> UpAdptThd
$cfrom :: forall x. UpAdptThd -> Rep UpAdptThd x
Generic, Int -> UpAdptThd -> ShowS
[UpAdptThd] -> ShowS
UpAdptThd -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpAdptThd] -> ShowS
$cshowList :: [UpAdptThd] -> ShowS
show :: UpAdptThd -> String
$cshow :: UpAdptThd -> String
showsPrec :: Int -> UpAdptThd -> ShowS
$cshowsPrec :: Int -> UpAdptThd -> ShowS
Show, Typeable UpAdptThd
UpAdptThd -> DataType
UpAdptThd -> Constr
(forall b. Data b => b -> b) -> UpAdptThd -> UpAdptThd
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) -> UpAdptThd -> u
forall u. (forall d. Data d => d -> u) -> UpAdptThd -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpAdptThd
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpAdptThd -> c UpAdptThd
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpAdptThd)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpAdptThd)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpAdptThd -> m UpAdptThd
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpAdptThd -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpAdptThd -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UpAdptThd -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UpAdptThd -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpAdptThd -> r
gmapT :: (forall b. Data b => b -> b) -> UpAdptThd -> UpAdptThd
$cgmapT :: (forall b. Data b => b -> b) -> UpAdptThd -> UpAdptThd
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpAdptThd)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpAdptThd)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpAdptThd)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpAdptThd)
dataTypeOf :: UpAdptThd -> DataType
$cdataTypeOf :: UpAdptThd -> DataType
toConstr :: UpAdptThd -> Constr
$ctoConstr :: UpAdptThd -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpAdptThd
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpAdptThd
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpAdptThd -> c UpAdptThd
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpAdptThd -> c UpAdptThd
Data, Typeable)
deriving newtype (UpAdptThd -> UpAdptThd -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpAdptThd -> UpAdptThd -> Bool
$c/= :: UpAdptThd -> UpAdptThd -> Bool
== :: UpAdptThd -> UpAdptThd -> Bool
$c== :: UpAdptThd -> UpAdptThd -> Bool
Eq, Eq UpAdptThd
UpAdptThd -> UpAdptThd -> Bool
UpAdptThd -> UpAdptThd -> Ordering
UpAdptThd -> UpAdptThd -> UpAdptThd
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 :: UpAdptThd -> UpAdptThd -> UpAdptThd
$cmin :: UpAdptThd -> UpAdptThd -> UpAdptThd
max :: UpAdptThd -> UpAdptThd -> UpAdptThd
$cmax :: UpAdptThd -> UpAdptThd -> UpAdptThd
>= :: UpAdptThd -> UpAdptThd -> Bool
$c>= :: UpAdptThd -> UpAdptThd -> Bool
> :: UpAdptThd -> UpAdptThd -> Bool
$c> :: UpAdptThd -> UpAdptThd -> Bool
<= :: UpAdptThd -> UpAdptThd -> Bool
$c<= :: UpAdptThd -> UpAdptThd -> Bool
< :: UpAdptThd -> UpAdptThd -> Bool
$c< :: UpAdptThd -> UpAdptThd -> Bool
compare :: UpAdptThd -> UpAdptThd -> Ordering
$ccompare :: UpAdptThd -> UpAdptThd -> Ordering
Ord, Eq UpAdptThd
Int -> UpAdptThd -> Int
UpAdptThd -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UpAdptThd -> Int
$chash :: UpAdptThd -> Int
hashWithSalt :: Int -> UpAdptThd -> Int
$chashWithSalt :: Int -> UpAdptThd -> Int
Hashable, Integer -> UpAdptThd
UpAdptThd -> UpAdptThd
UpAdptThd -> UpAdptThd -> UpAdptThd
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> UpAdptThd
$cfromInteger :: Integer -> UpAdptThd
signum :: UpAdptThd -> UpAdptThd
$csignum :: UpAdptThd -> UpAdptThd
abs :: UpAdptThd -> UpAdptThd
$cabs :: UpAdptThd -> UpAdptThd
negate :: UpAdptThd -> UpAdptThd
$cnegate :: UpAdptThd -> UpAdptThd
* :: UpAdptThd -> UpAdptThd -> UpAdptThd
$c* :: UpAdptThd -> UpAdptThd -> UpAdptThd
- :: UpAdptThd -> UpAdptThd -> UpAdptThd
$c- :: UpAdptThd -> UpAdptThd -> UpAdptThd
+ :: UpAdptThd -> UpAdptThd -> UpAdptThd
$c+ :: UpAdptThd -> UpAdptThd -> UpAdptThd
Num, Num UpAdptThd
Ord UpAdptThd
UpAdptThd -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: UpAdptThd -> Rational
$ctoRational :: UpAdptThd -> Rational
Real, Num UpAdptThd
Rational -> UpAdptThd
UpAdptThd -> UpAdptThd
UpAdptThd -> UpAdptThd -> UpAdptThd
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> UpAdptThd
$cfromRational :: Rational -> UpAdptThd
recip :: UpAdptThd -> UpAdptThd
$crecip :: UpAdptThd -> UpAdptThd
/ :: UpAdptThd -> UpAdptThd -> UpAdptThd
$c/ :: UpAdptThd -> UpAdptThd -> UpAdptThd
Fractional, Fractional UpAdptThd
Real UpAdptThd
forall b. Integral b => UpAdptThd -> b
forall b. Integral b => UpAdptThd -> (b, UpAdptThd)
forall a.
Real a
-> Fractional a
-> (forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
floor :: forall b. Integral b => UpAdptThd -> b
$cfloor :: forall b. Integral b => UpAdptThd -> b
ceiling :: forall b. Integral b => UpAdptThd -> b
$cceiling :: forall b. Integral b => UpAdptThd -> b
round :: forall b. Integral b => UpAdptThd -> b
$cround :: forall b. Integral b => UpAdptThd -> b
truncate :: forall b. Integral b => UpAdptThd -> b
$ctruncate :: forall b. Integral b => UpAdptThd -> b
properFraction :: forall b. Integral b => UpAdptThd -> (b, UpAdptThd)
$cproperFraction :: forall b. Integral b => UpAdptThd -> (b, UpAdptThd)
RealFrac, Context -> UpAdptThd -> IO (Maybe ThunkInfo)
Proxy UpAdptThd -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpAdptThd -> String
$cshowTypeOf :: Proxy UpAdptThd -> String
wNoThunks :: Context -> UpAdptThd -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpAdptThd -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpAdptThd -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpAdptThd -> IO (Maybe ThunkInfo)
NoThunks)
deriving anyclass (UpAdptThd -> Seq TypeRep
forall a. (a -> Seq TypeRep) -> HasTypeReps a
typeReps :: UpAdptThd -> Seq TypeRep
$ctypeReps :: UpAdptThd -> Seq TypeRep
HasTypeReps)
newtype BkSgnCntT = BkSgnCntT Double
deriving stock (forall x. Rep BkSgnCntT x -> BkSgnCntT
forall x. BkSgnCntT -> Rep BkSgnCntT x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BkSgnCntT x -> BkSgnCntT
$cfrom :: forall x. BkSgnCntT -> Rep BkSgnCntT x
Generic, Int -> BkSgnCntT -> ShowS
[BkSgnCntT] -> ShowS
BkSgnCntT -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BkSgnCntT] -> ShowS
$cshowList :: [BkSgnCntT] -> ShowS
show :: BkSgnCntT -> String
$cshow :: BkSgnCntT -> String
showsPrec :: Int -> BkSgnCntT -> ShowS
$cshowsPrec :: Int -> BkSgnCntT -> ShowS
Show, Typeable BkSgnCntT
BkSgnCntT -> DataType
BkSgnCntT -> Constr
(forall b. Data b => b -> b) -> BkSgnCntT -> BkSgnCntT
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) -> BkSgnCntT -> u
forall u. (forall d. Data d => d -> u) -> BkSgnCntT -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BkSgnCntT
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BkSgnCntT -> c BkSgnCntT
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BkSgnCntT)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BkSgnCntT)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BkSgnCntT -> m BkSgnCntT
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BkSgnCntT -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BkSgnCntT -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> BkSgnCntT -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BkSgnCntT -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BkSgnCntT -> r
gmapT :: (forall b. Data b => b -> b) -> BkSgnCntT -> BkSgnCntT
$cgmapT :: (forall b. Data b => b -> b) -> BkSgnCntT -> BkSgnCntT
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BkSgnCntT)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BkSgnCntT)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BkSgnCntT)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BkSgnCntT)
dataTypeOf :: BkSgnCntT -> DataType
$cdataTypeOf :: BkSgnCntT -> DataType
toConstr :: BkSgnCntT -> Constr
$ctoConstr :: BkSgnCntT -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BkSgnCntT
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BkSgnCntT
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BkSgnCntT -> c BkSgnCntT
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BkSgnCntT -> c BkSgnCntT
Data, Typeable)
deriving newtype (BkSgnCntT -> BkSgnCntT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BkSgnCntT -> BkSgnCntT -> Bool
$c/= :: BkSgnCntT -> BkSgnCntT -> Bool
== :: BkSgnCntT -> BkSgnCntT -> Bool
$c== :: BkSgnCntT -> BkSgnCntT -> Bool
Eq, Eq BkSgnCntT
BkSgnCntT -> BkSgnCntT -> Bool
BkSgnCntT -> BkSgnCntT -> Ordering
BkSgnCntT -> BkSgnCntT -> BkSgnCntT
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 :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$cmin :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
max :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$cmax :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
>= :: BkSgnCntT -> BkSgnCntT -> Bool
$c>= :: BkSgnCntT -> BkSgnCntT -> Bool
> :: BkSgnCntT -> BkSgnCntT -> Bool
$c> :: BkSgnCntT -> BkSgnCntT -> Bool
<= :: BkSgnCntT -> BkSgnCntT -> Bool
$c<= :: BkSgnCntT -> BkSgnCntT -> Bool
< :: BkSgnCntT -> BkSgnCntT -> Bool
$c< :: BkSgnCntT -> BkSgnCntT -> Bool
compare :: BkSgnCntT -> BkSgnCntT -> Ordering
$ccompare :: BkSgnCntT -> BkSgnCntT -> Ordering
Ord, Eq BkSgnCntT
Int -> BkSgnCntT -> Int
BkSgnCntT -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: BkSgnCntT -> Int
$chash :: BkSgnCntT -> Int
hashWithSalt :: Int -> BkSgnCntT -> Int
$chashWithSalt :: Int -> BkSgnCntT -> Int
Hashable, Integer -> BkSgnCntT
BkSgnCntT -> BkSgnCntT
BkSgnCntT -> BkSgnCntT -> BkSgnCntT
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> BkSgnCntT
$cfromInteger :: Integer -> BkSgnCntT
signum :: BkSgnCntT -> BkSgnCntT
$csignum :: BkSgnCntT -> BkSgnCntT
abs :: BkSgnCntT -> BkSgnCntT
$cabs :: BkSgnCntT -> BkSgnCntT
negate :: BkSgnCntT -> BkSgnCntT
$cnegate :: BkSgnCntT -> BkSgnCntT
* :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$c* :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
- :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$c- :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
+ :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$c+ :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
Num, Num BkSgnCntT
Rational -> BkSgnCntT
BkSgnCntT -> BkSgnCntT
BkSgnCntT -> BkSgnCntT -> BkSgnCntT
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> BkSgnCntT
$cfromRational :: Rational -> BkSgnCntT
recip :: BkSgnCntT -> BkSgnCntT
$crecip :: BkSgnCntT -> BkSgnCntT
/ :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
$c/ :: BkSgnCntT -> BkSgnCntT -> BkSgnCntT
Fractional, Context -> BkSgnCntT -> IO (Maybe ThunkInfo)
Proxy BkSgnCntT -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy BkSgnCntT -> String
$cshowTypeOf :: Proxy BkSgnCntT -> String
wNoThunks :: Context -> BkSgnCntT -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> BkSgnCntT -> IO (Maybe ThunkInfo)
noThunks :: Context -> BkSgnCntT -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> BkSgnCntT -> IO (Maybe ThunkInfo)
NoThunks)
deriving anyclass (BkSgnCntT -> Seq TypeRep
forall a. (a -> Seq TypeRep) -> HasTypeReps a
typeReps :: BkSgnCntT -> Seq TypeRep
$ctypeReps :: BkSgnCntT -> Seq TypeRep
HasTypeReps)
data PParams = PParams
{ PParams -> Natural
_maxBkSz :: !Natural
, PParams -> Natural
_maxHdrSz :: !Natural
, PParams -> Natural
_maxTxSz :: !Natural
, PParams -> Natural
_maxPropSz :: !Natural
, PParams -> BkSgnCntT
_bkSgnCntT :: !BkSgnCntT
, PParams -> SlotCount
_bkSlotsPerEpoch :: !Core.SlotCount
, PParams -> SlotCount
_upTtl :: !Core.SlotCount
, PParams -> Natural
_scriptVersion :: !Natural
, PParams -> UpAdptThd
_upAdptThd :: !UpAdptThd
, PParams -> FactorA
_factorA :: !FactorA
, PParams -> FactorB
_factorB :: !FactorB
}
deriving (PParams -> PParams -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PParams -> PParams -> Bool
$c/= :: PParams -> PParams -> Bool
== :: PParams -> PParams -> Bool
$c== :: PParams -> PParams -> Bool
Eq, forall x. Rep PParams x -> PParams
forall x. PParams -> Rep PParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PParams x -> PParams
$cfrom :: forall x. PParams -> Rep PParams x
Generic, Eq PParams
PParams -> PParams -> Bool
PParams -> PParams -> Ordering
PParams -> PParams -> PParams
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 :: PParams -> PParams -> PParams
$cmin :: PParams -> PParams -> PParams
max :: PParams -> PParams -> PParams
$cmax :: PParams -> PParams -> PParams
>= :: PParams -> PParams -> Bool
$c>= :: PParams -> PParams -> Bool
> :: PParams -> PParams -> Bool
$c> :: PParams -> PParams -> Bool
<= :: PParams -> PParams -> Bool
$c<= :: PParams -> PParams -> Bool
< :: PParams -> PParams -> Bool
$c< :: PParams -> PParams -> Bool
compare :: PParams -> PParams -> Ordering
$ccompare :: PParams -> PParams -> Ordering
Ord, Int -> PParams -> ShowS
[PParams] -> ShowS
PParams -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PParams] -> ShowS
$cshowList :: [PParams] -> ShowS
show :: PParams -> String
$cshow :: PParams -> String
showsPrec :: Int -> PParams -> ShowS
$cshowsPrec :: Int -> PParams -> ShowS
Show, Eq PParams
Int -> PParams -> Int
PParams -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PParams -> Int
$chash :: PParams -> Int
hashWithSalt :: Int -> PParams -> Int
$chashWithSalt :: Int -> PParams -> Int
Hashable, Typeable PParams
PParams -> DataType
PParams -> Constr
(forall b. Data b => b -> b) -> PParams -> PParams
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) -> PParams -> u
forall u. (forall d. Data d => d -> u) -> PParams -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PParams
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PParams -> c PParams
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PParams)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PParams)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PParams -> m PParams
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PParams -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PParams -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PParams -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PParams -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PParams -> r
gmapT :: (forall b. Data b => b -> b) -> PParams -> PParams
$cgmapT :: (forall b. Data b => b -> b) -> PParams -> PParams
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PParams)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PParams)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PParams)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PParams)
dataTypeOf :: PParams -> DataType
$cdataTypeOf :: PParams -> DataType
toConstr :: PParams -> Constr
$ctoConstr :: PParams -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PParams
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PParams
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PParams -> c PParams
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PParams -> c PParams
Data, Typeable, Context -> PParams -> IO (Maybe ThunkInfo)
Proxy PParams -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy PParams -> String
$cshowTypeOf :: Proxy PParams -> String
wNoThunks :: Context -> PParams -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PParams -> IO (Maybe ThunkInfo)
noThunks :: Context -> PParams -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PParams -> IO (Maybe ThunkInfo)
NoThunks)
makeLenses ''PParams
instance HasTypeReps PParams
newtype UpId = UpId Int
deriving stock (forall x. Rep UpId x -> UpId
forall x. UpId -> Rep UpId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpId x -> UpId
$cfrom :: forall x. UpId -> Rep UpId x
Generic, Int -> UpId -> ShowS
[UpId] -> ShowS
UpId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpId] -> ShowS
$cshowList :: [UpId] -> ShowS
show :: UpId -> String
$cshow :: UpId -> String
showsPrec :: Int -> UpId -> ShowS
$cshowsPrec :: Int -> UpId -> ShowS
Show, Typeable UpId
UpId -> DataType
UpId -> Constr
(forall b. Data b => b -> b) -> UpId -> UpId
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) -> UpId -> u
forall u. (forall d. Data d => d -> u) -> UpId -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpId
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpId -> c UpId
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpId)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpId)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UpId -> m UpId
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpId -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpId -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UpId -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UpId -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpId -> r
gmapT :: (forall b. Data b => b -> b) -> UpId -> UpId
$cgmapT :: (forall b. Data b => b -> b) -> UpId -> UpId
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpId)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpId)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpId)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpId)
dataTypeOf :: UpId -> DataType
$cdataTypeOf :: UpId -> DataType
toConstr :: UpId -> Constr
$ctoConstr :: UpId -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpId
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpId
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpId -> c UpId
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UpId -> c UpId
Data, Typeable)
deriving newtype (UpId -> UpId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpId -> UpId -> Bool
$c/= :: UpId -> UpId -> Bool
== :: UpId -> UpId -> Bool
$c== :: UpId -> UpId -> Bool
Eq, Eq UpId
UpId -> UpId -> Bool
UpId -> UpId -> Ordering
UpId -> UpId -> UpId
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 :: UpId -> UpId -> UpId
$cmin :: UpId -> UpId -> UpId
max :: UpId -> UpId -> UpId
$cmax :: UpId -> UpId -> UpId
>= :: UpId -> UpId -> Bool
$c>= :: UpId -> UpId -> Bool
> :: UpId -> UpId -> Bool
$c> :: UpId -> UpId -> Bool
<= :: UpId -> UpId -> Bool
$c<= :: UpId -> UpId -> Bool
< :: UpId -> UpId -> Bool
$c< :: UpId -> UpId -> Bool
compare :: UpId -> UpId -> Ordering
$ccompare :: UpId -> UpId -> Ordering
Ord, Eq UpId
Int -> UpId -> Int
UpId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UpId -> Int
$chash :: UpId -> Int
hashWithSalt :: Int -> UpId -> Int
$chashWithSalt :: Int -> UpId -> Int
Hashable, Context -> UpId -> IO (Maybe ThunkInfo)
Proxy UpId -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpId -> String
$cshowTypeOf :: Proxy UpId -> String
wNoThunks :: Context -> UpId -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpId -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpId -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpId -> IO (Maybe ThunkInfo)
NoThunks)
deriving anyclass (UpId -> Seq TypeRep
forall a. (a -> Seq TypeRep) -> HasTypeReps a
typeReps :: UpId -> Seq TypeRep
$ctypeReps :: UpId -> Seq TypeRep
HasTypeReps)
data ProtVer = ProtVer
{ ProtVer -> Natural
_pvMaj :: Natural
, ProtVer -> Natural
_pvMin :: Natural
, ProtVer -> Natural
_pvAlt :: Natural
}
deriving (ProtVer -> ProtVer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProtVer -> ProtVer -> Bool
$c/= :: ProtVer -> ProtVer -> Bool
== :: ProtVer -> ProtVer -> Bool
$c== :: ProtVer -> ProtVer -> Bool
Eq, forall x. Rep ProtVer x -> ProtVer
forall x. ProtVer -> Rep ProtVer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProtVer x -> ProtVer
$cfrom :: forall x. ProtVer -> Rep ProtVer x
Generic, Eq ProtVer
ProtVer -> ProtVer -> Bool
ProtVer -> ProtVer -> Ordering
ProtVer -> ProtVer -> ProtVer
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 :: ProtVer -> ProtVer -> ProtVer
$cmin :: ProtVer -> ProtVer -> ProtVer
max :: ProtVer -> ProtVer -> ProtVer
$cmax :: ProtVer -> ProtVer -> ProtVer
>= :: ProtVer -> ProtVer -> Bool
$c>= :: ProtVer -> ProtVer -> Bool
> :: ProtVer -> ProtVer -> Bool
$c> :: ProtVer -> ProtVer -> Bool
<= :: ProtVer -> ProtVer -> Bool
$c<= :: ProtVer -> ProtVer -> Bool
< :: ProtVer -> ProtVer -> Bool
$c< :: ProtVer -> ProtVer -> Bool
compare :: ProtVer -> ProtVer -> Ordering
$ccompare :: ProtVer -> ProtVer -> Ordering
Ord, Int -> ProtVer -> ShowS
[ProtVer] -> ShowS
ProtVer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProtVer] -> ShowS
$cshowList :: [ProtVer] -> ShowS
show :: ProtVer -> String
$cshow :: ProtVer -> String
showsPrec :: Int -> ProtVer -> ShowS
$cshowsPrec :: Int -> ProtVer -> ShowS
Show, Eq ProtVer
Int -> ProtVer -> Int
ProtVer -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ProtVer -> Int
$chash :: ProtVer -> Int
hashWithSalt :: Int -> ProtVer -> Int
$chashWithSalt :: Int -> ProtVer -> Int
Hashable, Typeable ProtVer
ProtVer -> DataType
ProtVer -> Constr
(forall b. Data b => b -> b) -> ProtVer -> ProtVer
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) -> ProtVer -> u
forall u. (forall d. Data d => d -> u) -> ProtVer -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProtVer
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProtVer -> c ProtVer
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProtVer)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtVer)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProtVer -> m ProtVer
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ProtVer -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ProtVer -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ProtVer -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ProtVer -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProtVer -> r
gmapT :: (forall b. Data b => b -> b) -> ProtVer -> ProtVer
$cgmapT :: (forall b. Data b => b -> b) -> ProtVer -> ProtVer
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtVer)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtVer)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProtVer)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProtVer)
dataTypeOf :: ProtVer -> DataType
$cdataTypeOf :: ProtVer -> DataType
toConstr :: ProtVer -> Constr
$ctoConstr :: ProtVer -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProtVer
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProtVer
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProtVer -> c ProtVer
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProtVer -> c ProtVer
Data, Typeable, Context -> ProtVer -> IO (Maybe ThunkInfo)
Proxy ProtVer -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy ProtVer -> String
$cshowTypeOf :: Proxy ProtVer -> String
wNoThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)
noThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)
NoThunks)
makeLenses ''ProtVer
instance HasTypeReps ProtVer
newtype ApName = ApName String
deriving stock (forall x. Rep ApName x -> ApName
forall x. ApName -> Rep ApName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ApName x -> ApName
$cfrom :: forall x. ApName -> Rep ApName x
Generic, Int -> ApName -> ShowS
[ApName] -> ShowS
ApName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApName] -> ShowS
$cshowList :: [ApName] -> ShowS
show :: ApName -> String
$cshow :: ApName -> String
showsPrec :: Int -> ApName -> ShowS
$cshowsPrec :: Int -> ApName -> ShowS
Show, Typeable ApName
ApName -> DataType
ApName -> Constr
(forall b. Data b => b -> b) -> ApName -> ApName
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) -> ApName -> u
forall u. (forall d. Data d => d -> u) -> ApName -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApName -> c ApName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApName)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApName -> m ApName
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApName -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApName -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApName -> r
gmapT :: (forall b. Data b => b -> b) -> ApName -> ApName
$cgmapT :: (forall b. Data b => b -> b) -> ApName -> ApName
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApName)
dataTypeOf :: ApName -> DataType
$cdataTypeOf :: ApName -> DataType
toConstr :: ApName -> Constr
$ctoConstr :: ApName -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApName -> c ApName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApName -> c ApName
Data, Typeable)
deriving newtype (ApName -> ApName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApName -> ApName -> Bool
$c/= :: ApName -> ApName -> Bool
== :: ApName -> ApName -> Bool
$c== :: ApName -> ApName -> Bool
Eq, Eq ApName
ApName -> ApName -> Bool
ApName -> ApName -> Ordering
ApName -> ApName -> ApName
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 :: ApName -> ApName -> ApName
$cmin :: ApName -> ApName -> ApName
max :: ApName -> ApName -> ApName
$cmax :: ApName -> ApName -> ApName
>= :: ApName -> ApName -> Bool
$c>= :: ApName -> ApName -> Bool
> :: ApName -> ApName -> Bool
$c> :: ApName -> ApName -> Bool
<= :: ApName -> ApName -> Bool
$c<= :: ApName -> ApName -> Bool
< :: ApName -> ApName -> Bool
$c< :: ApName -> ApName -> Bool
compare :: ApName -> ApName -> Ordering
$ccompare :: ApName -> ApName -> Ordering
Ord, Eq ApName
Int -> ApName -> Int
ApName -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ApName -> Int
$chash :: ApName -> Int
hashWithSalt :: Int -> ApName -> Int
$chashWithSalt :: Int -> ApName -> Int
Hashable, Context -> ApName -> IO (Maybe ThunkInfo)
Proxy ApName -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy ApName -> String
$cshowTypeOf :: Proxy ApName -> String
wNoThunks :: Context -> ApName -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ApName -> IO (Maybe ThunkInfo)
noThunks :: Context -> ApName -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> ApName -> IO (Maybe ThunkInfo)
NoThunks)
instance HasTypeReps ApName
newtype ApVer = ApVer Natural
deriving stock (forall x. Rep ApVer x -> ApVer
forall x. ApVer -> Rep ApVer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ApVer x -> ApVer
$cfrom :: forall x. ApVer -> Rep ApVer x
Generic, Int -> ApVer -> ShowS
[ApVer] -> ShowS
ApVer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApVer] -> ShowS
$cshowList :: [ApVer] -> ShowS
show :: ApVer -> String
$cshow :: ApVer -> String
showsPrec :: Int -> ApVer -> ShowS
$cshowsPrec :: Int -> ApVer -> ShowS
Show, Typeable ApVer
ApVer -> DataType
ApVer -> Constr
(forall b. Data b => b -> b) -> ApVer -> ApVer
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) -> ApVer -> u
forall u. (forall d. Data d => d -> u) -> ApVer -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApVer
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApVer -> c ApVer
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApVer)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApVer)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApVer -> m ApVer
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApVer -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApVer -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApVer -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApVer -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApVer -> r
gmapT :: (forall b. Data b => b -> b) -> ApVer -> ApVer
$cgmapT :: (forall b. Data b => b -> b) -> ApVer -> ApVer
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApVer)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApVer)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApVer)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApVer)
dataTypeOf :: ApVer -> DataType
$cdataTypeOf :: ApVer -> DataType
toConstr :: ApVer -> Constr
$ctoConstr :: ApVer -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApVer
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApVer
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApVer -> c ApVer
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApVer -> c ApVer
Data, Typeable)
deriving newtype (ApVer -> ApVer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApVer -> ApVer -> Bool
$c/= :: ApVer -> ApVer -> Bool
== :: ApVer -> ApVer -> Bool
$c== :: ApVer -> ApVer -> Bool
Eq, Eq ApVer
ApVer -> ApVer -> Bool
ApVer -> ApVer -> Ordering
ApVer -> ApVer -> ApVer
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 :: ApVer -> ApVer -> ApVer
$cmin :: ApVer -> ApVer -> ApVer
max :: ApVer -> ApVer -> ApVer
$cmax :: ApVer -> ApVer -> ApVer
>= :: ApVer -> ApVer -> Bool
$c>= :: ApVer -> ApVer -> Bool
> :: ApVer -> ApVer -> Bool
$c> :: ApVer -> ApVer -> Bool
<= :: ApVer -> ApVer -> Bool
$c<= :: ApVer -> ApVer -> Bool
< :: ApVer -> ApVer -> Bool
$c< :: ApVer -> ApVer -> Bool
compare :: ApVer -> ApVer -> Ordering
$ccompare :: ApVer -> ApVer -> Ordering
Ord, Integer -> ApVer
ApVer -> ApVer
ApVer -> ApVer -> ApVer
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ApVer
$cfromInteger :: Integer -> ApVer
signum :: ApVer -> ApVer
$csignum :: ApVer -> ApVer
abs :: ApVer -> ApVer
$cabs :: ApVer -> ApVer
negate :: ApVer -> ApVer
$cnegate :: ApVer -> ApVer
* :: ApVer -> ApVer -> ApVer
$c* :: ApVer -> ApVer -> ApVer
- :: ApVer -> ApVer -> ApVer
$c- :: ApVer -> ApVer -> ApVer
+ :: ApVer -> ApVer -> ApVer
$c+ :: ApVer -> ApVer -> ApVer
Num, Eq ApVer
Int -> ApVer -> Int
ApVer -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ApVer -> Int
$chash :: ApVer -> Int
hashWithSalt :: Int -> ApVer -> Int
$chashWithSalt :: Int -> ApVer -> Int
Hashable, Context -> ApVer -> IO (Maybe ThunkInfo)
Proxy ApVer -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy ApVer -> String
$cshowTypeOf :: Proxy ApVer -> String
wNoThunks :: Context -> ApVer -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ApVer -> IO (Maybe ThunkInfo)
noThunks :: Context -> ApVer -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> ApVer -> IO (Maybe ThunkInfo)
NoThunks)
instance HasTypeReps ApVer
data SwVer = SwVer
{ SwVer -> ApName
_svName :: ApName
, SwVer -> ApVer
_svVer :: ApVer
}
deriving (SwVer -> SwVer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwVer -> SwVer -> Bool
$c/= :: SwVer -> SwVer -> Bool
== :: SwVer -> SwVer -> Bool
$c== :: SwVer -> SwVer -> Bool
Eq, forall x. Rep SwVer x -> SwVer
forall x. SwVer -> Rep SwVer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SwVer x -> SwVer
$cfrom :: forall x. SwVer -> Rep SwVer x
Generic, Int -> SwVer -> ShowS
[SwVer] -> ShowS
SwVer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwVer] -> ShowS
$cshowList :: [SwVer] -> ShowS
show :: SwVer -> String
$cshow :: SwVer -> String
showsPrec :: Int -> SwVer -> ShowS
$cshowsPrec :: Int -> SwVer -> ShowS
Show, Eq SwVer
Int -> SwVer -> Int
SwVer -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: SwVer -> Int
$chash :: SwVer -> Int
hashWithSalt :: Int -> SwVer -> Int
$chashWithSalt :: Int -> SwVer -> Int
Hashable, Typeable SwVer
SwVer -> DataType
SwVer -> Constr
(forall b. Data b => b -> b) -> SwVer -> SwVer
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) -> SwVer -> u
forall u. (forall d. Data d => d -> u) -> SwVer -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwVer
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwVer -> c SwVer
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwVer)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwVer)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SwVer -> m SwVer
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SwVer -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SwVer -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SwVer -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SwVer -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwVer -> r
gmapT :: (forall b. Data b => b -> b) -> SwVer -> SwVer
$cgmapT :: (forall b. Data b => b -> b) -> SwVer -> SwVer
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwVer)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwVer)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwVer)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwVer)
dataTypeOf :: SwVer -> DataType
$cdataTypeOf :: SwVer -> DataType
toConstr :: SwVer -> Constr
$ctoConstr :: SwVer -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwVer
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwVer
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwVer -> c SwVer
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwVer -> c SwVer
Data, Typeable, Context -> SwVer -> IO (Maybe ThunkInfo)
Proxy SwVer -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy SwVer -> String
$cshowTypeOf :: Proxy SwVer -> String
wNoThunks :: Context -> SwVer -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SwVer -> IO (Maybe ThunkInfo)
noThunks :: Context -> SwVer -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SwVer -> IO (Maybe ThunkInfo)
NoThunks)
makeLenses ''SwVer
instance HasTypeReps SwVer
type UpSD =
( ProtVer
, PParams
, SwVer
, Set STag
, Metadata
)
type STag = String
data Metadata = Metadata
deriving (Metadata -> Metadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Metadata -> Metadata -> Bool
$c/= :: Metadata -> Metadata -> Bool
== :: Metadata -> Metadata -> Bool
$c== :: Metadata -> Metadata -> Bool
Eq, Eq Metadata
Metadata -> Metadata -> Bool
Metadata -> Metadata -> Ordering
Metadata -> Metadata -> Metadata
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 :: Metadata -> Metadata -> Metadata
$cmin :: Metadata -> Metadata -> Metadata
max :: Metadata -> Metadata -> Metadata
$cmax :: Metadata -> Metadata -> Metadata
>= :: Metadata -> Metadata -> Bool
$c>= :: Metadata -> Metadata -> Bool
> :: Metadata -> Metadata -> Bool
$c> :: Metadata -> Metadata -> Bool
<= :: Metadata -> Metadata -> Bool
$c<= :: Metadata -> Metadata -> Bool
< :: Metadata -> Metadata -> Bool
$c< :: Metadata -> Metadata -> Bool
compare :: Metadata -> Metadata -> Ordering
$ccompare :: Metadata -> Metadata -> Ordering
Ord, Int -> Metadata -> ShowS
[Metadata] -> ShowS
Metadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Metadata] -> ShowS
$cshowList :: [Metadata] -> ShowS
show :: Metadata -> String
$cshow :: Metadata -> String
showsPrec :: Int -> Metadata -> ShowS
$cshowsPrec :: Int -> Metadata -> ShowS
Show, forall x. Rep Metadata x -> Metadata
forall x. Metadata -> Rep Metadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Metadata x -> Metadata
$cfrom :: forall x. Metadata -> Rep Metadata x
Generic, Eq Metadata
Int -> Metadata -> Int
Metadata -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Metadata -> Int
$chash :: Metadata -> Int
hashWithSalt :: Int -> Metadata -> Int
$chashWithSalt :: Int -> Metadata -> Int
Hashable, Typeable Metadata
Metadata -> DataType
Metadata -> Constr
(forall b. Data b => b -> b) -> Metadata -> Metadata
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) -> Metadata -> u
forall u. (forall d. Data d => d -> u) -> Metadata -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Metadata
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Metadata -> c Metadata
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Metadata)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metadata)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Metadata -> m Metadata
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Metadata -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Metadata -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Metadata -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Metadata -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Metadata -> r
gmapT :: (forall b. Data b => b -> b) -> Metadata -> Metadata
$cgmapT :: (forall b. Data b => b -> b) -> Metadata -> Metadata
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metadata)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metadata)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Metadata)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Metadata)
dataTypeOf :: Metadata -> DataType
$cdataTypeOf :: Metadata -> DataType
toConstr :: Metadata -> Constr
$ctoConstr :: Metadata -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Metadata
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Metadata
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Metadata -> c Metadata
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Metadata -> c Metadata
Data, Typeable, Context -> Metadata -> IO (Maybe ThunkInfo)
Proxy Metadata -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Metadata -> String
$cshowTypeOf :: Proxy Metadata -> String
wNoThunks :: Context -> Metadata -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Metadata -> IO (Maybe ThunkInfo)
noThunks :: Context -> Metadata -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Metadata -> IO (Maybe ThunkInfo)
NoThunks)
data UProp = UProp
{ UProp -> UpId
_upId :: UpId
, UProp -> VKey
_upIssuer :: Core.VKey
, UProp -> PParams
_upParams :: PParams
, UProp -> ProtVer
_upPV :: ProtVer
, UProp -> SwVer
_upSwVer :: SwVer
, UProp -> Sig UpSD
_upSig :: Core.Sig UpSD
, UProp -> Set String
_upSTags :: Set STag
, UProp -> Metadata
_upMdt :: Metadata
}
deriving (UProp -> UProp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UProp -> UProp -> Bool
$c/= :: UProp -> UProp -> Bool
== :: UProp -> UProp -> Bool
$c== :: UProp -> UProp -> Bool
Eq, forall x. Rep UProp x -> UProp
forall x. UProp -> Rep UProp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UProp x -> UProp
$cfrom :: forall x. UProp -> Rep UProp x
Generic, Int -> UProp -> ShowS
[UProp] -> ShowS
UProp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UProp] -> ShowS
$cshowList :: [UProp] -> ShowS
show :: UProp -> String
$cshow :: UProp -> String
showsPrec :: Int -> UProp -> ShowS
$cshowsPrec :: Int -> UProp -> ShowS
Show, Eq UProp
Int -> UProp -> Int
UProp -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UProp -> Int
$chash :: UProp -> Int
hashWithSalt :: Int -> UProp -> Int
$chashWithSalt :: Int -> UProp -> Int
Hashable, Typeable UProp
UProp -> DataType
UProp -> Constr
(forall b. Data b => b -> b) -> UProp -> UProp
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) -> UProp -> u
forall u. (forall d. Data d => d -> u) -> UProp -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UProp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UProp -> c UProp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UProp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UProp)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UProp -> m UProp
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UProp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UProp -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UProp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UProp -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UProp -> r
gmapT :: (forall b. Data b => b -> b) -> UProp -> UProp
$cgmapT :: (forall b. Data b => b -> b) -> UProp -> UProp
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UProp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UProp)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UProp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UProp)
dataTypeOf :: UProp -> DataType
$cdataTypeOf :: UProp -> DataType
toConstr :: UProp -> Constr
$ctoConstr :: UProp -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UProp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UProp
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UProp -> c UProp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UProp -> c UProp
Data, Typeable, Context -> UProp -> IO (Maybe ThunkInfo)
Proxy UProp -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UProp -> String
$cshowTypeOf :: Proxy UProp -> String
wNoThunks :: Context -> UProp -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UProp -> IO (Maybe ThunkInfo)
noThunks :: Context -> UProp -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UProp -> IO (Maybe ThunkInfo)
NoThunks)
#if MIN_VERSION_hashable(1,3,4)
#else
instance Hashable a => Hashable (Set a) where
hashWithSalt = H.hashUsing Set.toList
#endif
makeLenses ''UProp
upSigData :: Lens' UProp UpSD
upSigData :: Lens' UProp UpSD
upSigData =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\UProp
up -> (UProp
up forall s a. s -> Getting a s a -> a
^. Lens' UProp ProtVer
upPV, UProp
up forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams, UProp
up forall s a. s -> Getting a s a -> a
^. Lens' UProp SwVer
upSwVer, UProp
up forall s a. s -> Getting a s a -> a
^. Lens' UProp (Set String)
upSTags, UProp
up forall s a. s -> Getting a s a -> a
^. Lens' UProp Metadata
upMdt))
( \UProp
up (ProtVer
pv, PParams
pps, SwVer
sv, Set String
stags, Metadata
mdt) ->
UProp
up
forall a b. a -> (a -> b) -> b
& Lens' UProp PParams
upParams forall s t a b. ASetter s t a b -> b -> s -> t
.~ PParams
pps
forall a b. a -> (a -> b) -> b
& Lens' UProp ProtVer
upPV forall s t a b. ASetter s t a b -> b -> s -> t
.~ ProtVer
pv
forall a b. a -> (a -> b) -> b
& Lens' UProp SwVer
upSwVer forall s t a b. ASetter s t a b -> b -> s -> t
.~ SwVer
sv
forall a b. a -> (a -> b) -> b
& Lens' UProp (Set String)
upSTags forall s t a b. ASetter s t a b -> b -> s -> t
.~ Set String
stags
forall a b. a -> (a -> b) -> b
& Lens' UProp Metadata
upMdt forall s t a b. ASetter s t a b -> b -> s -> t
.~ Metadata
mdt
)
getUpSigData :: UProp -> UpSD
getUpSigData :: UProp -> UpSD
getUpSigData = forall a s. Getting a s a -> s -> a
view Lens' UProp UpSD
upSigData
mkUProp ::
UpId ->
Core.VKey ->
ProtVer ->
PParams ->
SwVer ->
Set STag ->
Metadata ->
UProp
mkUProp :: UpId
-> VKey
-> ProtVer
-> PParams
-> SwVer
-> Set String
-> Metadata
-> UProp
mkUProp UpId
aUpId VKey
issuer ProtVer
pv PParams
pps SwVer
sv Set String
stags Metadata
mdt = UProp
uprop
where
uprop :: UProp
uprop =
UProp
{ _upId :: UpId
_upId = UpId
aUpId
, _upIssuer :: VKey
_upIssuer = VKey
issuer
, _upParams :: PParams
_upParams = PParams
pps
, _upPV :: ProtVer
_upPV = ProtVer
pv
, _upSwVer :: SwVer
_upSwVer = SwVer
sv
, _upSig :: Sig UpSD
_upSig = forall a. SKey -> a -> Sig a
Core.sign (VKey -> SKey
skey VKey
issuer) (UProp
uprop forall s a. s -> Getting a s a -> a
^. Lens' UProp UpSD
upSigData)
, _upSTags :: Set String
_upSTags = Set String
stags
, _upMdt :: Metadata
_upMdt = Metadata
mdt
}
instance HasTypeReps (ProtVer, PParams, SwVer, Set STag, Metadata)
instance HasTypeReps Metadata
instance HasTypeReps UProp
inMap :: (Ord key, Eq v) => key -> v -> Map key v -> Bool
inMap :: forall key v. (Ord key, Eq v) => key -> v -> Map key v -> Bool
inMap key
key v
v Map key v
m = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup key
key Map key v
m of
Just v
x | v
x forall a. Eq a => a -> a -> Bool
== v
v -> Bool
True
Maybe v
_ -> Bool
False
invertMap ::
(Ord k, Ord v) =>
Map k v ->
Map v (Set k)
invertMap :: forall k v. (Ord k, Ord v) => Map k v -> Map v (Set k)
invertMap =
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith (forall a. Ord a => Set a -> Set a -> Set a
Set.union)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Set a
Set.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> (b, a)
swap)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Map.toList
invertBijection ::
Ord v =>
Map k v ->
Map v k
invertBijection :: forall v k. Ord v => Map k v -> Map v k
invertBijection =
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a b. a -> b -> a
const
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, a)
swap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Map.toList
(==>) :: Bool -> Bool -> Bool
Bool
a ==> :: Bool -> Bool -> Bool
==> Bool
b = Bool -> Bool
not Bool
a Bool -> Bool -> Bool
|| Bool
b
infix 1 ==>
pvCanFollow ::
ProtVer ->
ProtVer ->
Bool
pvCanFollow :: ProtVer -> ProtVer -> Bool
pvCanFollow (ProtVer Natural
mjn Natural
mn Natural
an) (ProtVer Natural
mjp Natural
mip Natural
ap) =
(Natural
mjp, Natural
mip, Natural
ap) forall a. Ord a => a -> a -> Bool
< (Natural
mjn, Natural
mn, Natural
an)
Bool -> Bool -> Bool
&& (forall a. Ix a => (a, a) -> a -> Bool
inRange (Natural
0, Natural
1) (Natural
mjn forall a. Num a => a -> a -> a
- Natural
mjp))
Bool -> Bool -> Bool
&& ((Natural
mjp forall a. Eq a => a -> a -> Bool
== Natural
mjn) Bool -> Bool -> Bool
==> (Natural
mip forall a. Num a => a -> a -> a
+ Natural
1 forall a. Eq a => a -> a -> Bool
== Natural
mn))
Bool -> Bool -> Bool
&& ((Natural
mjp forall a. Num a => a -> a -> a
+ Natural
1 forall a. Eq a => a -> a -> Bool
== Natural
mjn) Bool -> Bool -> Bool
==> (Natural
mn forall a. Eq a => a -> a -> Bool
== Natural
0))
checkUpdateConstraints ::
PParams ->
UProp ->
[UpdateConstraintViolation]
checkUpdateConstraints :: PParams -> UProp -> [UpdateConstraintViolation]
checkUpdateConstraints PParams
pps UProp
prop =
forall a. [Maybe a] -> [a]
catMaybes
[ (UProp
prop forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PParams Natural
maxBkSz forall a. Ord a => a -> a -> Maybe (a, Threshold a)
<=? Natural
2 forall a. Num a => a -> a -> a
* PParams
pps forall s a. s -> Getting a s a -> a
^. Lens' PParams Natural
maxBkSz)
forall a b e. Maybe (a, b) -> (a -> b -> e) -> Maybe e
`orError` Natural -> Threshold Natural -> UpdateConstraintViolation
BlockSizeTooLarge
, (UProp
prop forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PParams Natural
maxTxSz forall a. Num a => a -> a -> a
+ Natural
1 forall a. Ord a => a -> a -> Maybe (a, Threshold a)
<=? UProp
prop forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PParams Natural
maxBkSz)
forall a b e. Maybe (a, b) -> (a -> b -> e) -> Maybe e
`orError` Natural -> Threshold Natural -> UpdateConstraintViolation
TransactionSizeTooLarge
, (PParams
pps forall s a. s -> Getting a s a -> a
^. Lens' PParams Natural
scriptVersion forall a. Ord a => a -> a -> Maybe (a, Threshold a)
<=? UProp
prop forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PParams Natural
scriptVersion)
forall a b e. Maybe (a, b) -> (a -> b -> e) -> Maybe e
`orError` Natural -> Threshold Natural -> UpdateConstraintViolation
ScriptVersionTooSmall
, (UProp
prop forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PParams Natural
scriptVersion forall a. Ord a => a -> a -> Maybe (a, Threshold a)
<=? PParams
pps forall s a. s -> Getting a s a -> a
^. Lens' PParams Natural
scriptVersion forall a. Num a => a -> a -> a
+ Natural
1)
forall a b e. Maybe (a, b) -> (a -> b -> e) -> Maybe e
`orError` Natural -> Threshold Natural -> UpdateConstraintViolation
ScriptVersionTooLarge
]
(<=?) :: Ord a => a -> a -> Maybe (a, Threshold a)
a
x <=? :: forall a. Ord a => a -> a -> Maybe (a, Threshold a)
<=? a
y = if a
x forall a. Ord a => a -> a -> Bool
<= a
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (a
x, forall a. a -> Threshold a
Threshold a
y)
infix 4 <=?
orError :: Maybe (a, b) -> (a -> b -> e) -> Maybe e
orError :: forall a b e. Maybe (a, b) -> (a -> b -> e) -> Maybe e
orError Maybe (a, b)
mab a -> b -> e
ferr = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> b -> e
ferr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (a, b)
mab
canUpdate :: PParams -> UProp -> Rule UPPVV ctx ()
canUpdate :: forall (ctx :: RuleType). PParams -> UProp -> Rule UPPVV ctx ()
canUpdate PParams
pps UProp
prop = [UpdateConstraintViolation]
violations forall a. Eq a => a -> a -> Bool
== [] forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! [UpdateConstraintViolation] -> UppvvPredicateFailure
CannotUpdatePv [UpdateConstraintViolation]
violations
where
violations :: [UpdateConstraintViolation]
violations = PParams -> UProp -> [UpdateConstraintViolation]
checkUpdateConstraints PParams
pps UProp
prop
data UpdateConstraintViolation
= BlockSizeTooLarge Natural (Threshold Natural)
| TransactionSizeTooLarge Natural (Threshold Natural)
| ScriptVersionTooLarge Natural (Threshold Natural)
| ScriptVersionTooSmall Natural (Threshold Natural)
deriving (UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c/= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
== :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c== :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
Eq, Eq UpdateConstraintViolation
UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
UpdateConstraintViolation -> UpdateConstraintViolation -> Ordering
UpdateConstraintViolation
-> UpdateConstraintViolation -> UpdateConstraintViolation
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 :: UpdateConstraintViolation
-> UpdateConstraintViolation -> UpdateConstraintViolation
$cmin :: UpdateConstraintViolation
-> UpdateConstraintViolation -> UpdateConstraintViolation
max :: UpdateConstraintViolation
-> UpdateConstraintViolation -> UpdateConstraintViolation
$cmax :: UpdateConstraintViolation
-> UpdateConstraintViolation -> UpdateConstraintViolation
>= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c>= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
> :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c> :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
<= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c<= :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
< :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
$c< :: UpdateConstraintViolation -> UpdateConstraintViolation -> Bool
compare :: UpdateConstraintViolation -> UpdateConstraintViolation -> Ordering
$ccompare :: UpdateConstraintViolation -> UpdateConstraintViolation -> Ordering
Ord, Int -> UpdateConstraintViolation -> ShowS
[UpdateConstraintViolation] -> ShowS
UpdateConstraintViolation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConstraintViolation] -> ShowS
$cshowList :: [UpdateConstraintViolation] -> ShowS
show :: UpdateConstraintViolation -> String
$cshow :: UpdateConstraintViolation -> String
showsPrec :: Int -> UpdateConstraintViolation -> ShowS
$cshowsPrec :: Int -> UpdateConstraintViolation -> ShowS
Show, Typeable UpdateConstraintViolation
UpdateConstraintViolation -> DataType
UpdateConstraintViolation -> Constr
(forall b. Data b => b -> b)
-> UpdateConstraintViolation -> UpdateConstraintViolation
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) -> UpdateConstraintViolation -> u
forall u.
(forall d. Data d => d -> u) -> UpdateConstraintViolation -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpdateConstraintViolation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpdateConstraintViolation
-> c UpdateConstraintViolation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c UpdateConstraintViolation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpdateConstraintViolation)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpdateConstraintViolation -> m UpdateConstraintViolation
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> UpdateConstraintViolation -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> UpdateConstraintViolation -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpdateConstraintViolation -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpdateConstraintViolation -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpdateConstraintViolation
-> r
gmapT :: (forall b. Data b => b -> b)
-> UpdateConstraintViolation -> UpdateConstraintViolation
$cgmapT :: (forall b. Data b => b -> b)
-> UpdateConstraintViolation -> UpdateConstraintViolation
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpdateConstraintViolation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpdateConstraintViolation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c UpdateConstraintViolation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c UpdateConstraintViolation)
dataTypeOf :: UpdateConstraintViolation -> DataType
$cdataTypeOf :: UpdateConstraintViolation -> DataType
toConstr :: UpdateConstraintViolation -> Constr
$ctoConstr :: UpdateConstraintViolation -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpdateConstraintViolation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpdateConstraintViolation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpdateConstraintViolation
-> c UpdateConstraintViolation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpdateConstraintViolation
-> c UpdateConstraintViolation
Data, Typeable, forall x.
Rep UpdateConstraintViolation x -> UpdateConstraintViolation
forall x.
UpdateConstraintViolation -> Rep UpdateConstraintViolation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConstraintViolation x -> UpdateConstraintViolation
$cfrom :: forall x.
UpdateConstraintViolation -> Rep UpdateConstraintViolation x
Generic, Context -> UpdateConstraintViolation -> IO (Maybe ThunkInfo)
Proxy UpdateConstraintViolation -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpdateConstraintViolation -> String
$cshowTypeOf :: Proxy UpdateConstraintViolation -> String
wNoThunks :: Context -> UpdateConstraintViolation -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpdateConstraintViolation -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpdateConstraintViolation -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpdateConstraintViolation -> IO (Maybe ThunkInfo)
NoThunks)
svCanFollow ::
Map ApName (ApVer, Core.Slot, Metadata) ->
(ApName, ApVer) ->
Bool
svCanFollow :: Map ApName (ApVer, Slot, Metadata) -> (ApName, ApVer) -> Bool
svCanFollow Map ApName (ApVer, Slot, Metadata)
avs (ApName
an, ApVer
av) =
( case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ApName
an Map ApName (ApVer, Slot, Metadata)
avs of
Maybe (ApVer, Slot, Metadata)
Nothing -> Bool
True
Just (ApVer
x, Slot
_, Metadata
_) -> ApVer
av forall a. Eq a => a -> a -> Bool
== ApVer
x forall a. Num a => a -> a -> a
+ ApVer
1
)
Bool -> Bool -> Bool
&& (ApName
an forall a. Ord a => a -> Set a -> Bool
`Set.notMember` forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map ApName (ApVer, Slot, Metadata)
avs Bool -> Bool -> Bool
==> (ApVer
av forall a. Eq a => a -> a -> Bool
== Natural -> ApVer
ApVer Natural
0 Bool -> Bool -> Bool
|| ApVer
av forall a. Eq a => a -> a -> Bool
== Natural -> ApVer
ApVer Natural
1))
where
data UPSVV deriving (forall x. Rep UPSVV x -> UPSVV
forall x. UPSVV -> Rep UPSVV x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPSVV x -> UPSVV
$cfrom :: forall x. UPSVV -> Rep UPSVV x
Generic, Typeable UPSVV
UPSVV -> DataType
UPSVV -> Constr
(forall b. Data b => b -> b) -> UPSVV -> UPSVV
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) -> UPSVV -> u
forall u. (forall d. Data d => d -> u) -> UPSVV -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPSVV
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPSVV -> c UPSVV
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPSVV)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPSVV)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPSVV -> m UPSVV
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPSVV -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPSVV -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPSVV -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPSVV -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPSVV -> r
gmapT :: (forall b. Data b => b -> b) -> UPSVV -> UPSVV
$cgmapT :: (forall b. Data b => b -> b) -> UPSVV -> UPSVV
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPSVV)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPSVV)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPSVV)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPSVV)
dataTypeOf :: UPSVV -> DataType
$cdataTypeOf :: UPSVV -> DataType
toConstr :: UPSVV -> Constr
$ctoConstr :: UPSVV -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPSVV
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPSVV
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPSVV -> c UPSVV
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPSVV -> c UPSVV
Data, Typeable)
data UpsvvPredicateFailure
= AlreadyProposedSv
| CannotFollowSv
| InvalidApplicationName
| InvalidSystemTags
deriving (UpsvvPredicateFailure -> UpsvvPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpsvvPredicateFailure -> UpsvvPredicateFailure -> Bool
$c/= :: UpsvvPredicateFailure -> UpsvvPredicateFailure -> Bool
== :: UpsvvPredicateFailure -> UpsvvPredicateFailure -> Bool
$c== :: UpsvvPredicateFailure -> UpsvvPredicateFailure -> Bool
Eq, Int -> UpsvvPredicateFailure -> ShowS
[UpsvvPredicateFailure] -> ShowS
UpsvvPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpsvvPredicateFailure] -> ShowS
$cshowList :: [UpsvvPredicateFailure] -> ShowS
show :: UpsvvPredicateFailure -> String
$cshow :: UpsvvPredicateFailure -> String
showsPrec :: Int -> UpsvvPredicateFailure -> ShowS
$cshowsPrec :: Int -> UpsvvPredicateFailure -> ShowS
Show, Typeable UpsvvPredicateFailure
UpsvvPredicateFailure -> DataType
UpsvvPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpsvvPredicateFailure -> UpsvvPredicateFailure
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) -> UpsvvPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpsvvPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpsvvPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpsvvPredicateFailure
-> c UpsvvPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpsvvPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpsvvPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpsvvPredicateFailure -> m UpsvvPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpsvvPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpsvvPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpsvvPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpsvvPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpsvvPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> UpsvvPredicateFailure -> UpsvvPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpsvvPredicateFailure -> UpsvvPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpsvvPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpsvvPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpsvvPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpsvvPredicateFailure)
dataTypeOf :: UpsvvPredicateFailure -> DataType
$cdataTypeOf :: UpsvvPredicateFailure -> DataType
toConstr :: UpsvvPredicateFailure -> Constr
$ctoConstr :: UpsvvPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpsvvPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpsvvPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpsvvPredicateFailure
-> c UpsvvPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpsvvPredicateFailure
-> c UpsvvPredicateFailure
Data, Typeable, forall x. Rep UpsvvPredicateFailure x -> UpsvvPredicateFailure
forall x. UpsvvPredicateFailure -> Rep UpsvvPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpsvvPredicateFailure x -> UpsvvPredicateFailure
$cfrom :: forall x. UpsvvPredicateFailure -> Rep UpsvvPredicateFailure x
Generic, Context -> UpsvvPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpsvvPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpsvvPredicateFailure -> String
$cshowTypeOf :: Proxy UpsvvPredicateFailure -> String
wNoThunks :: Context -> UpsvvPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpsvvPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpsvvPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpsvvPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPSVV where
type Environment UPSVV = Map ApName (ApVer, Core.Slot, Metadata)
type State UPSVV = Map UpId (ApName, ApVer, Metadata)
type Signal UPSVV = UProp
type PredicateFailure UPSVV = UpsvvPredicateFailure
initialRules :: [InitialRule UPSVV]
initialRules = []
transitionRules :: [TransitionRule UPSVV]
transitionRules =
[ do
TRC (Environment UPSVV
avs, State UPSVV
raus, Signal UPSVV
up) <- forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
let SwVer ApName
an ApVer
av = Signal UPSVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp SwVer
upSwVer
ApName -> Bool
apNameValid ApName
an forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpsvvPredicateFailure
InvalidApplicationName
Map ApName (ApVer, Slot, Metadata) -> (ApName, ApVer) -> Bool
svCanFollow Environment UPSVV
avs (ApName
an, ApVer
av) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpsvvPredicateFailure
CannotFollowSv
ApName
an forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a} {b} {c}. (a, b, c) -> a
fst' (forall k a. Map k a -> [a]
Map.elems State UPSVV
raus) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpsvvPredicateFailure
AlreadyProposedSv
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all forall {t :: * -> *}. Foldable t => t Char -> Bool
sTagValid (Signal UPSVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp (Set String)
upSTags) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpsvvPredicateFailure
InvalidSystemTags
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! State UPSVV
raus forall m (f :: * -> *).
(Relation m, Ord (Domain m), Ord (Range m), Foldable f) =>
m -> f (Domain m, Range m) -> m
⨃ [(Signal UPSVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp UpId
upId, (ApName
an, ApVer
av, Signal UPSVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp Metadata
upMdt))]
]
where
fst' :: (a, b, c) -> a
fst' (a
x, b
_, c
_) = a
x
apNameValid :: ApName -> Bool
apNameValid (ApName String
n) = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii String
n Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Int
length String
n forall a. Ord a => a -> a -> Bool
<= Int
12
sTagValid :: t Char -> Bool
sTagValid t Char
tag = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii t Char
tag Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Int
length t Char
tag forall a. Ord a => a -> a -> Bool
<= Int
10
data UPPVV deriving (forall x. Rep UPPVV x -> UPPVV
forall x. UPPVV -> Rep UPPVV x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPPVV x -> UPPVV
$cfrom :: forall x. UPPVV -> Rep UPPVV x
Generic, Typeable UPPVV
UPPVV -> DataType
UPPVV -> Constr
(forall b. Data b => b -> b) -> UPPVV -> UPPVV
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) -> UPPVV -> u
forall u. (forall d. Data d => d -> u) -> UPPVV -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPPVV
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPPVV -> c UPPVV
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPPVV)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPPVV)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPPVV -> m UPPVV
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPPVV -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPPVV -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPPVV -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPPVV -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPPVV -> r
gmapT :: (forall b. Data b => b -> b) -> UPPVV -> UPPVV
$cgmapT :: (forall b. Data b => b -> b) -> UPPVV -> UPPVV
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPPVV)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPPVV)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPPVV)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPPVV)
dataTypeOf :: UPPVV -> DataType
$cdataTypeOf :: UPPVV -> DataType
toConstr :: UPPVV -> Constr
$ctoConstr :: UPPVV -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPPVV
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPPVV
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPPVV -> c UPPVV
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPPVV -> c UPPVV
Data, Typeable)
data UppvvPredicateFailure
= CannotFollowPv
| CannotUpdatePv [UpdateConstraintViolation]
| AlreadyProposedPv
deriving (UppvvPredicateFailure -> UppvvPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UppvvPredicateFailure -> UppvvPredicateFailure -> Bool
$c/= :: UppvvPredicateFailure -> UppvvPredicateFailure -> Bool
== :: UppvvPredicateFailure -> UppvvPredicateFailure -> Bool
$c== :: UppvvPredicateFailure -> UppvvPredicateFailure -> Bool
Eq, Int -> UppvvPredicateFailure -> ShowS
[UppvvPredicateFailure] -> ShowS
UppvvPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UppvvPredicateFailure] -> ShowS
$cshowList :: [UppvvPredicateFailure] -> ShowS
show :: UppvvPredicateFailure -> String
$cshow :: UppvvPredicateFailure -> String
showsPrec :: Int -> UppvvPredicateFailure -> ShowS
$cshowsPrec :: Int -> UppvvPredicateFailure -> ShowS
Show, Typeable UppvvPredicateFailure
UppvvPredicateFailure -> DataType
UppvvPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UppvvPredicateFailure -> UppvvPredicateFailure
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) -> UppvvPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UppvvPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UppvvPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UppvvPredicateFailure
-> c UppvvPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UppvvPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UppvvPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UppvvPredicateFailure -> m UppvvPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UppvvPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UppvvPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UppvvPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UppvvPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UppvvPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> UppvvPredicateFailure -> UppvvPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UppvvPredicateFailure -> UppvvPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UppvvPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UppvvPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UppvvPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UppvvPredicateFailure)
dataTypeOf :: UppvvPredicateFailure -> DataType
$cdataTypeOf :: UppvvPredicateFailure -> DataType
toConstr :: UppvvPredicateFailure -> Constr
$ctoConstr :: UppvvPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UppvvPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UppvvPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UppvvPredicateFailure
-> c UppvvPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UppvvPredicateFailure
-> c UppvvPredicateFailure
Data, Typeable, forall x. Rep UppvvPredicateFailure x -> UppvvPredicateFailure
forall x. UppvvPredicateFailure -> Rep UppvvPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UppvvPredicateFailure x -> UppvvPredicateFailure
$cfrom :: forall x. UppvvPredicateFailure -> Rep UppvvPredicateFailure x
Generic, Context -> UppvvPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UppvvPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UppvvPredicateFailure -> String
$cshowTypeOf :: Proxy UppvvPredicateFailure -> String
wNoThunks :: Context -> UppvvPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UppvvPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UppvvPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UppvvPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPPVV where
type
Environment UPPVV =
( ProtVer
, PParams
)
type State UPPVV = Map UpId (ProtVer, PParams)
type Signal UPPVV = UProp
type PredicateFailure UPPVV = UppvvPredicateFailure
initialRules :: [InitialRule UPPVV]
initialRules = []
transitionRules :: [TransitionRule UPPVV]
transitionRules =
[ do
TRC ((ProtVer
pv, PParams
pps), State UPPVV
rpus, Signal UPPVV
up) <- forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
let pid :: UpId
pid = Signal UPPVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp UpId
upId
nv :: ProtVer
nv = Signal UPPVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp ProtVer
upPV
ppsn :: PParams
ppsn = Signal UPPVV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams
ProtVer -> ProtVer -> Bool
pvCanFollow ProtVer
nv ProtVer
pv forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UppvvPredicateFailure
CannotFollowPv
forall (ctx :: RuleType). PParams -> UProp -> Rule UPPVV ctx ()
canUpdate PParams
pps Signal UPPVV
up
ProtVer
nv forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Map k a -> [a]
Map.elems State UPPVV
rpus) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UppvvPredicateFailure
AlreadyProposedPv
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! State UPPVV
rpus forall m (f :: * -> *).
(Relation m, Ord (Domain m), Ord (Range m), Foldable f) =>
m -> f (Domain m, Range m) -> m
⨃ [(UpId
pid, (ProtVer
nv, PParams
ppsn))]
]
data UPV deriving (forall x. Rep UPV x -> UPV
forall x. UPV -> Rep UPV x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPV x -> UPV
$cfrom :: forall x. UPV -> Rep UPV x
Generic, Typeable UPV
UPV -> DataType
UPV -> Constr
(forall b. Data b => b -> b) -> UPV -> UPV
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) -> UPV -> u
forall u. (forall d. Data d => d -> u) -> UPV -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPV
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPV -> c UPV
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPV)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPV)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPV -> m UPV
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPV -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPV -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPV -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPV -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPV -> r
gmapT :: (forall b. Data b => b -> b) -> UPV -> UPV
$cgmapT :: (forall b. Data b => b -> b) -> UPV -> UPV
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPV)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPV)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPV)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPV)
dataTypeOf :: UPV -> DataType
$cdataTypeOf :: UPV -> DataType
toConstr :: UPV -> Constr
$ctoConstr :: UPV -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPV
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPV
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPV -> c UPV
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPV -> c UPV
Data, Typeable)
data UpvPredicateFailure
= UPPVVFailure (PredicateFailure UPPVV)
| UPSVVFailure (PredicateFailure UPSVV)
| AVChangedInPVUpdate ApName ApVer (Maybe (ApVer, Slot, Metadata))
| ParamsChangedInSVUpdate
| PVChangedInSVUpdate
deriving (UpvPredicateFailure -> UpvPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpvPredicateFailure -> UpvPredicateFailure -> Bool
$c/= :: UpvPredicateFailure -> UpvPredicateFailure -> Bool
== :: UpvPredicateFailure -> UpvPredicateFailure -> Bool
$c== :: UpvPredicateFailure -> UpvPredicateFailure -> Bool
Eq, Int -> UpvPredicateFailure -> ShowS
[UpvPredicateFailure] -> ShowS
UpvPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpvPredicateFailure] -> ShowS
$cshowList :: [UpvPredicateFailure] -> ShowS
show :: UpvPredicateFailure -> String
$cshow :: UpvPredicateFailure -> String
showsPrec :: Int -> UpvPredicateFailure -> ShowS
$cshowsPrec :: Int -> UpvPredicateFailure -> ShowS
Show, Typeable UpvPredicateFailure
UpvPredicateFailure -> DataType
UpvPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpvPredicateFailure -> UpvPredicateFailure
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) -> UpvPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpvPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvPredicateFailure
-> c UpvPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvPredicateFailure -> m UpvPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpvPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpvPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpvPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpvPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpvPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> UpvPredicateFailure -> UpvPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpvPredicateFailure -> UpvPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvPredicateFailure)
dataTypeOf :: UpvPredicateFailure -> DataType
$cdataTypeOf :: UpvPredicateFailure -> DataType
toConstr :: UpvPredicateFailure -> Constr
$ctoConstr :: UpvPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvPredicateFailure
-> c UpvPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvPredicateFailure
-> c UpvPredicateFailure
Data, Typeable, forall x. Rep UpvPredicateFailure x -> UpvPredicateFailure
forall x. UpvPredicateFailure -> Rep UpvPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpvPredicateFailure x -> UpvPredicateFailure
$cfrom :: forall x. UpvPredicateFailure -> Rep UpvPredicateFailure x
Generic, Context -> UpvPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpvPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpvPredicateFailure -> String
$cshowTypeOf :: Proxy UpvPredicateFailure -> String
wNoThunks :: Context -> UpvPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpvPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpvPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpvPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPV where
type
Environment UPV =
( ProtVer
, PParams
, Map ApName (ApVer, Core.Slot, Metadata)
)
type
State UPV =
( Map UpId (ProtVer, PParams)
, Map UpId (ApName, ApVer, Metadata)
)
type Signal UPV = UProp
type PredicateFailure UPV = UpvPredicateFailure
initialRules :: [InitialRule UPV]
initialRules = []
transitionRules :: [TransitionRule UPV]
transitionRules =
[ do
TRC
( (ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs)
, (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus)
, Signal UPV
up
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
Map UpId (ProtVer, PParams)
rpus' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPPVV forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((ProtVer
pv, PParams
pps), Map UpId (ProtVer, PParams)
rpus, Signal UPV
up)
let SwVer ApName
an ApVer
av = Signal UPV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp SwVer
upSwVer
forall key v. (Ord key, Eq v) => key -> v -> Map key v -> Bool
inMap ApName
an ApVer
av (forall {a} {b} {c}. (a, b, c) -> a
swVer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map ApName (ApVer, Slot, Metadata)
avs) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! ApName
-> ApVer -> Maybe (ApVer, Slot, Metadata) -> UpvPredicateFailure
AVChangedInPVUpdate ApName
an ApVer
av (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ApName
an Map ApName (ApVer, Slot, Metadata)
avs)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (Map UpId (ProtVer, PParams)
rpus', Map UpId (ApName, ApVer, Metadata)
raus)
, do
TRC
( (ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs)
, (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus)
, Signal UPV
up
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
ProtVer
pv forall a. Eq a => a -> a -> Bool
== Signal UPV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp ProtVer
upPV forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpvPredicateFailure
PVChangedInSVUpdate
Signal UPV
up forall s a. s -> Getting a s a -> a
^. Lens' UProp PParams
upParams forall a. Eq a => a -> a -> Bool
== PParams
pps forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpvPredicateFailure
ParamsChangedInSVUpdate
Map UpId (ApName, ApVer, Metadata)
raus' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPSVV forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (Map ApName (ApVer, Slot, Metadata)
avs, Map UpId (ApName, ApVer, Metadata)
raus, Signal UPV
up)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus')
, do
TRC
( (ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs)
, (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus)
, Signal UPV
up
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
Map UpId (ProtVer, PParams)
rpus' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPPVV forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((ProtVer
pv, PParams
pps), Map UpId (ProtVer, PParams)
rpus, Signal UPV
up)
Map UpId (ApName, ApVer, Metadata)
raus' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPSVV forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (Map ApName (ApVer, Slot, Metadata)
avs, Map UpId (ApName, ApVer, Metadata)
raus, Signal UPV
up)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (Map UpId (ProtVer, PParams)
rpus', Map UpId (ApName, ApVer, Metadata)
raus')
]
where
swVer :: (a, b, c) -> a
swVer (a
x, b
_, c
_) = a
x
instance Embed UPPVV UPV where
wrapFailed :: PredicateFailure UPPVV -> PredicateFailure UPV
wrapFailed = PredicateFailure UPPVV -> UpvPredicateFailure
UPPVVFailure
instance Embed UPSVV UPV where
wrapFailed :: PredicateFailure UPSVV -> PredicateFailure UPV
wrapFailed = PredicateFailure UPSVV -> UpvPredicateFailure
UPSVVFailure
data UPREG deriving (forall x. Rep UPREG x -> UPREG
forall x. UPREG -> Rep UPREG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPREG x -> UPREG
$cfrom :: forall x. UPREG -> Rep UPREG x
Generic, Typeable UPREG
UPREG -> DataType
UPREG -> Constr
(forall b. Data b => b -> b) -> UPREG -> UPREG
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) -> UPREG -> u
forall u. (forall d. Data d => d -> u) -> UPREG -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPREG
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPREG -> c UPREG
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPREG)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPREG)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPREG -> m UPREG
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPREG -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPREG -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPREG -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPREG -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPREG -> r
gmapT :: (forall b. Data b => b -> b) -> UPREG -> UPREG
$cgmapT :: (forall b. Data b => b -> b) -> UPREG -> UPREG
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPREG)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPREG)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPREG)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPREG)
dataTypeOf :: UPREG -> DataType
$cdataTypeOf :: UPREG -> DataType
toConstr :: UPREG -> Constr
$ctoConstr :: UPREG -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPREG
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPREG
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPREG -> c UPREG
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPREG -> c UPREG
Data, Typeable)
data UpregPredicateFailure
= UPVFailure (PredicateFailure UPV)
| NotGenesisDelegate
| DoesNotVerify
deriving (UpregPredicateFailure -> UpregPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpregPredicateFailure -> UpregPredicateFailure -> Bool
$c/= :: UpregPredicateFailure -> UpregPredicateFailure -> Bool
== :: UpregPredicateFailure -> UpregPredicateFailure -> Bool
$c== :: UpregPredicateFailure -> UpregPredicateFailure -> Bool
Eq, Int -> UpregPredicateFailure -> ShowS
[UpregPredicateFailure] -> ShowS
UpregPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpregPredicateFailure] -> ShowS
$cshowList :: [UpregPredicateFailure] -> ShowS
show :: UpregPredicateFailure -> String
$cshow :: UpregPredicateFailure -> String
showsPrec :: Int -> UpregPredicateFailure -> ShowS
$cshowsPrec :: Int -> UpregPredicateFailure -> ShowS
Show, Typeable UpregPredicateFailure
UpregPredicateFailure -> DataType
UpregPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpregPredicateFailure -> UpregPredicateFailure
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) -> UpregPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpregPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpregPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpregPredicateFailure
-> c UpregPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpregPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpregPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpregPredicateFailure -> m UpregPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpregPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpregPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpregPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpregPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpregPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> UpregPredicateFailure -> UpregPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpregPredicateFailure -> UpregPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpregPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpregPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpregPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpregPredicateFailure)
dataTypeOf :: UpregPredicateFailure -> DataType
$cdataTypeOf :: UpregPredicateFailure -> DataType
toConstr :: UpregPredicateFailure -> Constr
$ctoConstr :: UpregPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpregPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpregPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpregPredicateFailure
-> c UpregPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpregPredicateFailure
-> c UpregPredicateFailure
Data, Typeable, forall x. Rep UpregPredicateFailure x -> UpregPredicateFailure
forall x. UpregPredicateFailure -> Rep UpregPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpregPredicateFailure x -> UpregPredicateFailure
$cfrom :: forall x. UpregPredicateFailure -> Rep UpregPredicateFailure x
Generic, Context -> UpregPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpregPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpregPredicateFailure -> String
$cshowTypeOf :: Proxy UpregPredicateFailure -> String
wNoThunks :: Context -> UpregPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpregPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpregPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpregPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPREG where
type
Environment UPREG =
( ProtVer
, PParams
, Map ApName (ApVer, Core.Slot, Metadata)
, Bimap Core.VKeyGenesis Core.VKey
)
type
State UPREG =
( Map UpId (ProtVer, PParams)
, Map UpId (ApName, ApVer, Metadata)
)
type Signal UPREG = UProp
type PredicateFailure UPREG = UpregPredicateFailure
initialRules :: [InitialRule UPREG]
initialRules = []
transitionRules :: [TransitionRule UPREG]
transitionRules =
[ do
TRC
( (ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs, Bimap VKeyGenesis VKey
dms)
, (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus)
, Signal UPREG
up
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
(Map UpId (ProtVer, PParams)
rpus', Map UpId (ApName, ApVer, Metadata)
raus') <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPV forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs), (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus), Signal UPREG
up)
let vk :: VKey
vk = Signal UPREG
up forall s a. s -> Getting a s a -> a
^. Lens' UProp VKey
upIssuer
Bimap VKeyGenesis VKey
dms forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
▷ forall a. a -> Set a
Set.singleton VKey
vk forall a. Eq a => a -> a -> Bool
/= forall a b. Bimap a b
empty forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpregPredicateFailure
NotGenesisDelegate
forall a. Eq a => VKey -> a -> Sig a -> Bool
Core.verify VKey
vk (Signal UPREG
up forall s a. s -> Getting a s a -> a
^. Lens' UProp UpSD
upSigData) (Signal UPREG
up forall s a. s -> Getting a s a -> a
^. Lens' UProp (Sig UpSD)
upSig) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpregPredicateFailure
DoesNotVerify
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! (Map UpId (ProtVer, PParams)
rpus', Map UpId (ApName, ApVer, Metadata)
raus')
]
instance Embed UPV UPREG where
wrapFailed :: PredicateFailure UPV -> PredicateFailure UPREG
wrapFailed = PredicateFailure UPV -> UpregPredicateFailure
UPVFailure
data Vote = Vote
{ Vote -> VKey
_vCaster :: Core.VKey
, Vote -> UpId
_vPropId :: UpId
, Vote -> Sig UpId
_vSig :: Core.Sig UpId
}
deriving (Vote -> Vote -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vote -> Vote -> Bool
$c/= :: Vote -> Vote -> Bool
== :: Vote -> Vote -> Bool
$c== :: Vote -> Vote -> Bool
Eq, forall x. Rep Vote x -> Vote
forall x. Vote -> Rep Vote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Vote x -> Vote
$cfrom :: forall x. Vote -> Rep Vote x
Generic, Int -> Vote -> ShowS
[Vote] -> ShowS
Vote -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vote] -> ShowS
$cshowList :: [Vote] -> ShowS
show :: Vote -> String
$cshow :: Vote -> String
showsPrec :: Int -> Vote -> ShowS
$cshowsPrec :: Int -> Vote -> ShowS
Show, Eq Vote
Int -> Vote -> Int
Vote -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Vote -> Int
$chash :: Vote -> Int
hashWithSalt :: Int -> Vote -> Int
$chashWithSalt :: Int -> Vote -> Int
Hashable, Typeable Vote
Vote -> DataType
Vote -> Constr
(forall b. Data b => b -> b) -> Vote -> Vote
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) -> Vote -> u
forall u. (forall d. Data d => d -> u) -> Vote -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Vote
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Vote -> c Vote
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Vote)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Vote)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Vote -> m Vote
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Vote -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Vote -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Vote -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Vote -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vote -> r
gmapT :: (forall b. Data b => b -> b) -> Vote -> Vote
$cgmapT :: (forall b. Data b => b -> b) -> Vote -> Vote
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Vote)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Vote)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Vote)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Vote)
dataTypeOf :: Vote -> DataType
$cdataTypeOf :: Vote -> DataType
toConstr :: Vote -> Constr
$ctoConstr :: Vote -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Vote
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Vote
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Vote -> c Vote
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Vote -> c Vote
Data, Typeable, Context -> Vote -> IO (Maybe ThunkInfo)
Proxy Vote -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Vote -> String
$cshowTypeOf :: Proxy Vote -> String
wNoThunks :: Context -> Vote -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Vote -> IO (Maybe ThunkInfo)
noThunks :: Context -> Vote -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Vote -> IO (Maybe ThunkInfo)
NoThunks)
makeLenses ''Vote
instance HasTypeReps Vote
mkVote :: Core.VKey -> UpId -> Vote
mkVote :: VKey -> UpId -> Vote
mkVote VKey
caster UpId
proposalId =
Vote
{ _vCaster :: VKey
_vCaster = VKey
caster
, _vPropId :: UpId
_vPropId = UpId
proposalId
, _vSig :: Sig UpId
_vSig = forall a. SKey -> a -> Sig a
Core.sign (VKey -> SKey
skey VKey
caster) UpId
proposalId
}
instance HasHash (Maybe Byron.Spec.Ledger.Update.UProp, [Byron.Spec.Ledger.Update.Vote]) where
hash :: (Maybe UProp, [Vote]) -> Hash
hash = Maybe Int -> Hash
Core.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
data ADDVOTE deriving (forall x. Rep ADDVOTE x -> ADDVOTE
forall x. ADDVOTE -> Rep ADDVOTE x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ADDVOTE x -> ADDVOTE
$cfrom :: forall x. ADDVOTE -> Rep ADDVOTE x
Generic, Typeable ADDVOTE
ADDVOTE -> DataType
ADDVOTE -> Constr
(forall b. Data b => b -> b) -> ADDVOTE -> ADDVOTE
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) -> ADDVOTE -> u
forall u. (forall d. Data d => d -> u) -> ADDVOTE -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ADDVOTE
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ADDVOTE -> c ADDVOTE
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ADDVOTE)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADDVOTE)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ADDVOTE -> m ADDVOTE
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ADDVOTE -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ADDVOTE -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ADDVOTE -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ADDVOTE -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ADDVOTE -> r
gmapT :: (forall b. Data b => b -> b) -> ADDVOTE -> ADDVOTE
$cgmapT :: (forall b. Data b => b -> b) -> ADDVOTE -> ADDVOTE
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADDVOTE)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADDVOTE)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ADDVOTE)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ADDVOTE)
dataTypeOf :: ADDVOTE -> DataType
$cdataTypeOf :: ADDVOTE -> DataType
toConstr :: ADDVOTE -> Constr
$ctoConstr :: ADDVOTE -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ADDVOTE
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ADDVOTE
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ADDVOTE -> c ADDVOTE
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ADDVOTE -> c ADDVOTE
Data, Typeable)
data AddvotePredicateFailure
= AVSigDoesNotVerify
| NoUpdateProposal UpId
| VoteByNonGenesisDelegate VKey
| RepeatVoteByGenesisDelegate VKey
deriving (AddvotePredicateFailure -> AddvotePredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddvotePredicateFailure -> AddvotePredicateFailure -> Bool
$c/= :: AddvotePredicateFailure -> AddvotePredicateFailure -> Bool
== :: AddvotePredicateFailure -> AddvotePredicateFailure -> Bool
$c== :: AddvotePredicateFailure -> AddvotePredicateFailure -> Bool
Eq, Int -> AddvotePredicateFailure -> ShowS
[AddvotePredicateFailure] -> ShowS
AddvotePredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddvotePredicateFailure] -> ShowS
$cshowList :: [AddvotePredicateFailure] -> ShowS
show :: AddvotePredicateFailure -> String
$cshow :: AddvotePredicateFailure -> String
showsPrec :: Int -> AddvotePredicateFailure -> ShowS
$cshowsPrec :: Int -> AddvotePredicateFailure -> ShowS
Show, Typeable AddvotePredicateFailure
AddvotePredicateFailure -> DataType
AddvotePredicateFailure -> Constr
(forall b. Data b => b -> b)
-> AddvotePredicateFailure -> AddvotePredicateFailure
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) -> AddvotePredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> AddvotePredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AddvotePredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AddvotePredicateFailure
-> c AddvotePredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AddvotePredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AddvotePredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AddvotePredicateFailure -> m AddvotePredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AddvotePredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AddvotePredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> AddvotePredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> AddvotePredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> AddvotePredicateFailure
-> r
gmapT :: (forall b. Data b => b -> b)
-> AddvotePredicateFailure -> AddvotePredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> AddvotePredicateFailure -> AddvotePredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AddvotePredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AddvotePredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AddvotePredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AddvotePredicateFailure)
dataTypeOf :: AddvotePredicateFailure -> DataType
$cdataTypeOf :: AddvotePredicateFailure -> DataType
toConstr :: AddvotePredicateFailure -> Constr
$ctoConstr :: AddvotePredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AddvotePredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AddvotePredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AddvotePredicateFailure
-> c AddvotePredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AddvotePredicateFailure
-> c AddvotePredicateFailure
Data, Typeable, forall x. Rep AddvotePredicateFailure x -> AddvotePredicateFailure
forall x. AddvotePredicateFailure -> Rep AddvotePredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddvotePredicateFailure x -> AddvotePredicateFailure
$cfrom :: forall x. AddvotePredicateFailure -> Rep AddvotePredicateFailure x
Generic, Context -> AddvotePredicateFailure -> IO (Maybe ThunkInfo)
Proxy AddvotePredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy AddvotePredicateFailure -> String
$cshowTypeOf :: Proxy AddvotePredicateFailure -> String
wNoThunks :: Context -> AddvotePredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> AddvotePredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> AddvotePredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> AddvotePredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS ADDVOTE where
type
Environment ADDVOTE =
( Set UpId
, Bimap Core.VKeyGenesis Core.VKey
)
type State ADDVOTE = Set (UpId, Core.VKeyGenesis)
type Signal ADDVOTE = Vote
type PredicateFailure ADDVOTE = AddvotePredicateFailure
initialRules :: [InitialRule ADDVOTE]
initialRules = []
transitionRules :: [TransitionRule ADDVOTE]
transitionRules =
[ do
TRC
( (Set UpId
rups, Bimap VKeyGenesis VKey
dms)
, State ADDVOTE
vts
, Signal ADDVOTE
vote
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
let pid :: UpId
pid = Signal ADDVOTE
vote forall s a. s -> Getting a s a -> a
^. Lens' Vote UpId
vPropId
vk :: VKey
vk = Signal ADDVOTE
vote forall s a. s -> Getting a s a -> a
^. Lens' Vote VKey
vCaster
vtsPid :: Set (UpId, VKeyGenesis)
vtsPid =
case forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR VKey
vk Bimap VKeyGenesis VKey
dms of
Just VKeyGenesis
vks -> forall a. a -> Set a
Set.singleton (UpId
pid, VKeyGenesis
vks)
Maybe VKeyGenesis
Nothing -> forall a. Set a
Set.empty
Set (UpId, VKeyGenesis)
vtsPid forall a. Eq a => a -> a -> Bool
/= forall a. Set a
Set.empty forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! VKey -> AddvotePredicateFailure
VoteByNonGenesisDelegate VKey
vk
Bool -> Bool
not (Set (UpId, VKeyGenesis)
vtsPid forall a. Ord a => Set a -> Set a -> Bool
`Set.isSubsetOf` State ADDVOTE
vts) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! VKey -> AddvotePredicateFailure
RepeatVoteByGenesisDelegate VKey
vk
forall a. Ord a => a -> Set a -> Bool
Set.member UpId
pid Set UpId
rups forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpId -> AddvotePredicateFailure
NoUpdateProposal UpId
pid
forall a. Eq a => VKey -> a -> Sig a -> Bool
Core.verify VKey
vk UpId
pid (Signal ADDVOTE
vote forall s a. s -> Getting a s a -> a
^. Lens' Vote (Sig UpId)
vSig) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! AddvotePredicateFailure
AVSigDoesNotVerify
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! State ADDVOTE
vts forall a. Semigroup a => a -> a -> a
<> Set (UpId, VKeyGenesis)
vtsPid
]
data UPVOTE deriving (forall x. Rep UPVOTE x -> UPVOTE
forall x. UPVOTE -> Rep UPVOTE x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPVOTE x -> UPVOTE
$cfrom :: forall x. UPVOTE -> Rep UPVOTE x
Generic, Typeable UPVOTE
UPVOTE -> DataType
UPVOTE -> Constr
(forall b. Data b => b -> b) -> UPVOTE -> UPVOTE
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) -> UPVOTE -> u
forall u. (forall d. Data d => d -> u) -> UPVOTE -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPVOTE
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPVOTE -> c UPVOTE
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPVOTE)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPVOTE)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPVOTE -> m UPVOTE
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPVOTE -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPVOTE -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPVOTE -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPVOTE -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPVOTE -> r
gmapT :: (forall b. Data b => b -> b) -> UPVOTE -> UPVOTE
$cgmapT :: (forall b. Data b => b -> b) -> UPVOTE -> UPVOTE
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPVOTE)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPVOTE)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPVOTE)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPVOTE)
dataTypeOf :: UPVOTE -> DataType
$cdataTypeOf :: UPVOTE -> DataType
toConstr :: UPVOTE -> Constr
$ctoConstr :: UPVOTE -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPVOTE
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPVOTE
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPVOTE -> c UPVOTE
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPVOTE -> c UPVOTE
Data, Typeable)
data UpvotePredicateFailure
= ADDVOTEFailure (PredicateFailure ADDVOTE)
| S_HigherThanThdAndNotAlreadyConfirmed
| S_CfmThdNotReached
| S_AlreadyConfirmed
deriving (UpvotePredicateFailure -> UpvotePredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpvotePredicateFailure -> UpvotePredicateFailure -> Bool
$c/= :: UpvotePredicateFailure -> UpvotePredicateFailure -> Bool
== :: UpvotePredicateFailure -> UpvotePredicateFailure -> Bool
$c== :: UpvotePredicateFailure -> UpvotePredicateFailure -> Bool
Eq, Int -> UpvotePredicateFailure -> ShowS
[UpvotePredicateFailure] -> ShowS
UpvotePredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpvotePredicateFailure] -> ShowS
$cshowList :: [UpvotePredicateFailure] -> ShowS
show :: UpvotePredicateFailure -> String
$cshow :: UpvotePredicateFailure -> String
showsPrec :: Int -> UpvotePredicateFailure -> ShowS
$cshowsPrec :: Int -> UpvotePredicateFailure -> ShowS
Show, Typeable UpvotePredicateFailure
UpvotePredicateFailure -> DataType
UpvotePredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpvotePredicateFailure -> UpvotePredicateFailure
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) -> UpvotePredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpvotePredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvotePredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvotePredicateFailure
-> c UpvotePredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvotePredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvotePredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpvotePredicateFailure -> m UpvotePredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpvotePredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpvotePredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpvotePredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpvotePredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpvotePredicateFailure
-> r
gmapT :: (forall b. Data b => b -> b)
-> UpvotePredicateFailure -> UpvotePredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpvotePredicateFailure -> UpvotePredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvotePredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpvotePredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvotePredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpvotePredicateFailure)
dataTypeOf :: UpvotePredicateFailure -> DataType
$cdataTypeOf :: UpvotePredicateFailure -> DataType
toConstr :: UpvotePredicateFailure -> Constr
$ctoConstr :: UpvotePredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvotePredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpvotePredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvotePredicateFailure
-> c UpvotePredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpvotePredicateFailure
-> c UpvotePredicateFailure
Data, forall x. Rep UpvotePredicateFailure x -> UpvotePredicateFailure
forall x. UpvotePredicateFailure -> Rep UpvotePredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpvotePredicateFailure x -> UpvotePredicateFailure
$cfrom :: forall x. UpvotePredicateFailure -> Rep UpvotePredicateFailure x
Generic, Typeable, Context -> UpvotePredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpvotePredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpvotePredicateFailure -> String
$cshowTypeOf :: Proxy UpvotePredicateFailure -> String
wNoThunks :: Context -> UpvotePredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpvotePredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpvotePredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpvotePredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPVOTE where
type
Environment UPVOTE =
( Core.Slot
, Word8
, Set UpId
, Bimap Core.VKeyGenesis Core.VKey
)
type
State UPVOTE =
( Map UpId Core.Slot
, Set (UpId, Core.VKeyGenesis)
)
type Signal UPVOTE = Vote
type PredicateFailure UPVOTE = UpvotePredicateFailure
initialRules :: [InitialRule UPVOTE]
initialRules = []
transitionRules :: [TransitionRule UPVOTE]
transitionRules =
[ do
TRC
( (Slot
_, Word8
t, Set UpId
rups, Bimap VKeyGenesis VKey
dms)
, (Map UpId Slot
cps, Set (UpId, VKeyGenesis)
vts)
, Signal UPVOTE
vote
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
Set (UpId, VKeyGenesis)
vts' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @ADDVOTE forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((Set UpId
rups, Bimap VKeyGenesis VKey
dms), Set (UpId, VKeyGenesis)
vts, Signal UPVOTE
vote)
let pid :: UpId
pid = Signal UPVOTE
vote forall s a. s -> Getting a s a -> a
^. Lens' Vote UpId
vPropId
forall m n. (Relation m, Integral n) => m -> n
size ([UpId
pid] forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ Set (UpId, VKeyGenesis)
vts') forall a. Ord a => a -> a -> Bool
< Word8
t Bool -> Bool -> Bool
|| UpId
pid forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
∈ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map UpId Slot
cps forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpvotePredicateFailure
S_HigherThanThdAndNotAlreadyConfirmed
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$!
( Map UpId Slot
cps
, Set (UpId, VKeyGenesis)
vts'
)
, do
TRC
( (Slot
sn, Word8
t, Set UpId
rups, Bimap VKeyGenesis VKey
dms)
, (Map UpId Slot
cps, Set (UpId, VKeyGenesis)
vts)
, Signal UPVOTE
vote
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
Set (UpId, VKeyGenesis)
vts' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @ADDVOTE forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((Set UpId
rups, Bimap VKeyGenesis VKey
dms), Set (UpId, VKeyGenesis)
vts, Signal UPVOTE
vote)
let pid :: UpId
pid = Signal UPVOTE
vote forall s a. s -> Getting a s a -> a
^. Lens' Vote UpId
vPropId
Word8
t forall a. Ord a => a -> a -> Bool
<= forall m n. (Relation m, Integral n) => m -> n
size ([UpId
pid] forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ Set (UpId, VKeyGenesis)
vts') forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpvotePredicateFailure
S_CfmThdNotReached
UpId
pid forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
∉ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map UpId Slot
cps forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpvotePredicateFailure
S_AlreadyConfirmed
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$!
( Map UpId Slot
cps forall m (f :: * -> *).
(Relation m, Ord (Domain m), Ord (Range m), Foldable f) =>
m -> f (Domain m, Range m) -> m
⨃ [(UpId
pid, Slot
sn)]
, Set (UpId, VKeyGenesis)
vts'
)
]
instance Embed ADDVOTE UPVOTE where
wrapFailed :: PredicateFailure ADDVOTE -> PredicateFailure UPVOTE
wrapFailed = PredicateFailure ADDVOTE -> UpvotePredicateFailure
ADDVOTEFailure
data FADS deriving (forall x. Rep FADS x -> FADS
forall x. FADS -> Rep FADS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FADS x -> FADS
$cfrom :: forall x. FADS -> Rep FADS x
Generic, Typeable FADS
FADS -> DataType
FADS -> Constr
(forall b. Data b => b -> b) -> FADS -> FADS
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) -> FADS -> u
forall u. (forall d. Data d => d -> u) -> FADS -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FADS
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FADS -> c FADS
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FADS)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FADS)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FADS -> m FADS
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FADS -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FADS -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> FADS -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FADS -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FADS -> r
gmapT :: (forall b. Data b => b -> b) -> FADS -> FADS
$cgmapT :: (forall b. Data b => b -> b) -> FADS -> FADS
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FADS)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FADS)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FADS)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FADS)
dataTypeOf :: FADS -> DataType
$cdataTypeOf :: FADS -> DataType
toConstr :: FADS -> Constr
$ctoConstr :: FADS -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FADS
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FADS
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FADS -> c FADS
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FADS -> c FADS
Data, Typeable)
data FadsPredicateFailure
deriving (FadsPredicateFailure -> FadsPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FadsPredicateFailure -> FadsPredicateFailure -> Bool
$c/= :: FadsPredicateFailure -> FadsPredicateFailure -> Bool
== :: FadsPredicateFailure -> FadsPredicateFailure -> Bool
$c== :: FadsPredicateFailure -> FadsPredicateFailure -> Bool
Eq, Int -> FadsPredicateFailure -> ShowS
[FadsPredicateFailure] -> ShowS
FadsPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FadsPredicateFailure] -> ShowS
$cshowList :: [FadsPredicateFailure] -> ShowS
show :: FadsPredicateFailure -> String
$cshow :: FadsPredicateFailure -> String
showsPrec :: Int -> FadsPredicateFailure -> ShowS
$cshowsPrec :: Int -> FadsPredicateFailure -> ShowS
Show, Typeable FadsPredicateFailure
FadsPredicateFailure -> DataType
FadsPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> FadsPredicateFailure -> FadsPredicateFailure
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) -> FadsPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> FadsPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FadsPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FadsPredicateFailure
-> c FadsPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FadsPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FadsPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FadsPredicateFailure -> m FadsPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FadsPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FadsPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> FadsPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FadsPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FadsPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> FadsPredicateFailure -> FadsPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> FadsPredicateFailure -> FadsPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FadsPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FadsPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FadsPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FadsPredicateFailure)
dataTypeOf :: FadsPredicateFailure -> DataType
$cdataTypeOf :: FadsPredicateFailure -> DataType
toConstr :: FadsPredicateFailure -> Constr
$ctoConstr :: FadsPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FadsPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FadsPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FadsPredicateFailure
-> c FadsPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FadsPredicateFailure
-> c FadsPredicateFailure
Data, Typeable, forall x. Rep FadsPredicateFailure x -> FadsPredicateFailure
forall x. FadsPredicateFailure -> Rep FadsPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FadsPredicateFailure x -> FadsPredicateFailure
$cfrom :: forall x. FadsPredicateFailure -> Rep FadsPredicateFailure x
Generic)
instance STS FADS where
type Environment FADS = ()
type State FADS = [(Core.Slot, (ProtVer, PParams))]
type Signal FADS = (Core.Slot, (ProtVer, PParams))
type PredicateFailure FADS = FadsPredicateFailure
initialRules :: [InitialRule FADS]
initialRules = []
transitionRules :: [TransitionRule FADS]
transitionRules =
[ do
TRC
( ()
, State FADS
fads
, (Slot
sn, (ProtVer
bv, PParams
ppsc))
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case State FADS
fads of
((Slot
_, (ProtVer
pvc, PParams
_)) : [(Slot, (ProtVer, PParams))]
_) ->
if ProtVer
pvc forall a. Ord a => a -> a -> Bool
< ProtVer
bv
then (Slot
sn, (ProtVer
bv, PParams
ppsc)) forall a. a -> [a] -> [a]
: State FADS
fads
else State FADS
fads
State FADS
_ -> (Slot
sn, (ProtVer
bv, PParams
ppsc)) forall a. a -> [a] -> [a]
: State FADS
fads
]
data UPEND deriving (forall x. Rep UPEND x -> UPEND
forall x. UPEND -> Rep UPEND x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPEND x -> UPEND
$cfrom :: forall x. UPEND -> Rep UPEND x
Generic, Typeable UPEND
UPEND -> DataType
UPEND -> Constr
(forall b. Data b => b -> b) -> UPEND -> UPEND
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) -> UPEND -> u
forall u. (forall d. Data d => d -> u) -> UPEND -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPEND
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPEND -> c UPEND
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPEND)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPEND)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPEND -> m UPEND
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPEND -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPEND -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPEND -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPEND -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPEND -> r
gmapT :: (forall b. Data b => b -> b) -> UPEND -> UPEND
$cgmapT :: (forall b. Data b => b -> b) -> UPEND -> UPEND
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPEND)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPEND)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPEND)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPEND)
dataTypeOf :: UPEND -> DataType
$cdataTypeOf :: UPEND -> DataType
toConstr :: UPEND -> Constr
$ctoConstr :: UPEND -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPEND
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPEND
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPEND -> c UPEND
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPEND -> c UPEND
Data, Typeable)
findKey :: (v -> Bool) -> Map k v -> Maybe (k, v)
findKey :: forall v k. (v -> Bool) -> Map k v -> Maybe (k, v)
findKey v -> Bool
p Map k v
m =
case forall k a. Map k a -> [(k, a)]
Map.toList (forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter v -> Bool
p Map k v
m) of
[(k
k, v
v)] -> forall a. a -> Maybe a
Just (k
k, v
v)
[(k, v)]
_ -> forall a. Maybe a
Nothing
data UpendPredicateFailure
= ProtVerUnknown ProtVer
| S_TryNextRule
| CanAdopt ProtVer
| CannotAdopt ProtVer
| NotADelegate VKey
| UnconfirmedProposal UpId
deriving (UpendPredicateFailure -> UpendPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpendPredicateFailure -> UpendPredicateFailure -> Bool
$c/= :: UpendPredicateFailure -> UpendPredicateFailure -> Bool
== :: UpendPredicateFailure -> UpendPredicateFailure -> Bool
$c== :: UpendPredicateFailure -> UpendPredicateFailure -> Bool
Eq, Int -> UpendPredicateFailure -> ShowS
[UpendPredicateFailure] -> ShowS
UpendPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpendPredicateFailure] -> ShowS
$cshowList :: [UpendPredicateFailure] -> ShowS
show :: UpendPredicateFailure -> String
$cshow :: UpendPredicateFailure -> String
showsPrec :: Int -> UpendPredicateFailure -> ShowS
$cshowsPrec :: Int -> UpendPredicateFailure -> ShowS
Show, Typeable UpendPredicateFailure
UpendPredicateFailure -> DataType
UpendPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpendPredicateFailure -> UpendPredicateFailure
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) -> UpendPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpendPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpendPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpendPredicateFailure
-> c UpendPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpendPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpendPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpendPredicateFailure -> m UpendPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpendPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpendPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpendPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpendPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UpendPredicateFailure -> r
gmapT :: (forall b. Data b => b -> b)
-> UpendPredicateFailure -> UpendPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpendPredicateFailure -> UpendPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpendPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpendPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpendPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpendPredicateFailure)
dataTypeOf :: UpendPredicateFailure -> DataType
$cdataTypeOf :: UpendPredicateFailure -> DataType
toConstr :: UpendPredicateFailure -> Constr
$ctoConstr :: UpendPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpendPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpendPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpendPredicateFailure
-> c UpendPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpendPredicateFailure
-> c UpendPredicateFailure
Data, Typeable, forall x. Rep UpendPredicateFailure x -> UpendPredicateFailure
forall x. UpendPredicateFailure -> Rep UpendPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpendPredicateFailure x -> UpendPredicateFailure
$cfrom :: forall x. UpendPredicateFailure -> Rep UpendPredicateFailure x
Generic, Context -> UpendPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpendPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpendPredicateFailure -> String
$cshowTypeOf :: Proxy UpendPredicateFailure -> String
wNoThunks :: Context -> UpendPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpendPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpendPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpendPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPEND where
type
Environment UPEND =
( Core.Slot
, Natural
, Bimap VKeyGenesis VKey
, Map UpId Core.Slot
, Map UpId (ProtVer, PParams)
, BlockCount
)
type
State UPEND =
( [(Core.Slot, (ProtVer, PParams))]
, Set (ProtVer, Core.VKeyGenesis)
)
type Signal UPEND = (ProtVer, Core.VKey)
type PredicateFailure UPEND = UpendPredicateFailure
initialRules :: [InitialRule UPEND]
initialRules = []
transitionRules :: [TransitionRule UPEND]
transitionRules =
[ do
TRC
( (Slot
sn, Natural
_t, Bimap VKeyGenesis VKey
_dms, Map UpId Slot
cps, Map UpId (ProtVer, PParams)
rpus, BlockCount
k)
, ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
, (ProtVer
bv, VKey
_vk)
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
case forall v k. (v -> Bool) -> Map k v -> Maybe (k, v)
findKey ((forall a. Eq a => a -> a -> Bool
== ProtVer
bv) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) Map UpId (ProtVer, PParams)
rpus of
Just (UpId
pid, (ProtVer, PParams)
_) -> do
UpId
pid forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
∉ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom (Map UpId Slot
cps forall m. (Relation m, Ord (Range m)) => m -> Range m -> m
▷<= Slot
sn Slot -> SlotCount -> Slot
-. Word64
2 Word64 -> BlockCount -> SlotCount
*. BlockCount
k) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpendPredicateFailure
S_TryNextRule
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
Maybe (UpId, (ProtVer, PParams))
Nothing ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
, do
TRC
( (Slot
sn, Natural
t, Bimap VKeyGenesis VKey
dms, Map UpId Slot
cps, Map UpId (ProtVer, PParams)
rpus, BlockCount
k)
, ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
, (ProtVer
bv, VKey
vk)
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
case forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR VKey
vk Bimap VKeyGenesis VKey
dms of
Maybe VKeyGenesis
Nothing -> do
Bool
False forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpendPredicateFailure
S_TryNextRule
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
Just VKeyGenesis
vks -> do
let bvs' :: Set (ProtVer, VKeyGenesis)
bvs' = Set (ProtVer, VKeyGenesis)
bvs forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
∪ forall m. Relation m => Domain m -> Range m -> m
singleton ProtVer
bv VKeyGenesis
vks
forall m n. (Relation m, Integral n) => m -> n
size ([ProtVer
bv] forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ Set (ProtVer, VKeyGenesis)
bvs') forall a. Ord a => a -> a -> Bool
< Natural
t forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! ProtVer -> UpendPredicateFailure
CanAdopt ProtVer
bv
case forall v k. (v -> Bool) -> Map k v -> Maybe (k, v)
findKey ((forall a. Eq a => a -> a -> Bool
== ProtVer
bv) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) Map UpId (ProtVer, PParams)
rpus of
Just (UpId
pid, (ProtVer, PParams)
_) -> do
UpId
pid forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
∈ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom (Map UpId Slot
cps forall m. (Relation m, Ord (Range m)) => m -> Range m -> m
▷<= Slot
sn Slot -> SlotCount -> Slot
-. Word64
2 Word64 -> BlockCount -> SlotCount
*. BlockCount
k) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpendPredicateFailure
S_TryNextRule
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs')
Maybe (UpId, (ProtVer, PParams))
Nothing -> do
Bool
False forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpendPredicateFailure
S_TryNextRule
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs')
, do
TRC
( (Slot
sn, Natural
t, Bimap VKeyGenesis VKey
dms, Map UpId Slot
cps, Map UpId (ProtVer, PParams)
rpus, BlockCount
k)
, ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
, (ProtVer
bv, VKey
vk)
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
case forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR VKey
vk Bimap VKeyGenesis VKey
dms of
Maybe VKeyGenesis
Nothing -> do
Bool
False forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! VKey -> UpendPredicateFailure
NotADelegate VKey
vk
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs)
Just VKeyGenesis
vks -> do
let bvs' :: Set (ProtVer, VKeyGenesis)
bvs' = Set (ProtVer, VKeyGenesis)
bvs forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
∪ forall m. Relation m => Domain m -> Range m -> m
singleton ProtVer
bv VKeyGenesis
vks
Natural
t forall a. Ord a => a -> a -> Bool
<= forall m n. (Relation m, Integral n) => m -> n
size ([ProtVer
bv] forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ Set (ProtVer, VKeyGenesis)
bvs') forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! ProtVer -> UpendPredicateFailure
CannotAdopt ProtVer
bv
case forall v k. (v -> Bool) -> Map k v -> Maybe (k, v)
findKey ((forall a. Eq a => a -> a -> Bool
== ProtVer
bv) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) Map UpId (ProtVer, PParams)
rpus of
Just (UpId
pid, (ProtVer
_, PParams
ppsc)) -> do
UpId
pid forall a (f :: * -> *). (Eq a, Foldable f) => a -> f a -> Bool
∈ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom (Map UpId Slot
cps forall m. (Relation m, Ord (Range m)) => m -> Range m -> m
▷<= Slot
sn Slot -> SlotCount -> Slot
-. Word64
2 Word64 -> BlockCount -> SlotCount
*. BlockCount
k) forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! UpId -> UpendPredicateFailure
UnconfirmedProposal UpId
pid
[(Slot, (ProtVer, PParams))]
fads' <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @FADS forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((), [(Slot, (ProtVer, PParams))]
fads, (Slot
sn, (ProtVer
bv, PParams
ppsc)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads', Set (ProtVer, VKeyGenesis)
bvs')
Maybe (UpId, (ProtVer, PParams))
Nothing -> do
Bool
False forall sts (ctx :: RuleType).
Bool -> PredicateFailure sts -> Rule sts ctx ()
?! ProtVer -> UpendPredicateFailure
ProtVerUnknown ProtVer
bv
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! ([(Slot, (ProtVer, PParams))]
fads, Set (ProtVer, VKeyGenesis)
bvs')
]
instance Embed FADS UPEND where
wrapFailed :: PredicateFailure FADS -> PredicateFailure UPEND
wrapFailed = forall a. HasCallStack => String -> a
error String
"No possible failures in FADS"
type UPIEnv =
( Core.Slot
, Bimap Core.VKeyGenesis Core.VKey
, BlockCount
, Word8
)
delegationMap :: UPIEnv -> Bimap Core.VKeyGenesis Core.VKey
delegationMap :: UPIEnv -> Bimap VKeyGenesis VKey
delegationMap (Slot
_, Bimap VKeyGenesis VKey
dms, BlockCount
_, Word8
_) = Bimap VKeyGenesis VKey
dms
type UPIState =
( (ProtVer, PParams)
, [(Core.Slot, (ProtVer, PParams))]
, Map ApName (ApVer, Core.Slot, Metadata)
, Map UpId (ProtVer, PParams)
, Map UpId (ApName, ApVer, Metadata)
, Map UpId Core.Slot
, Set (UpId, Core.VKeyGenesis)
, Set (ProtVer, Core.VKeyGenesis)
, Map UpId Core.Slot
)
fstUPIState :: UPIState -> (ProtVer, PParams)
fstUPIState :: UPIState -> (ProtVer, PParams)
fstUPIState ((ProtVer, PParams)
f, [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = (ProtVer, PParams)
f
sndUPIState :: UPIState -> [(Core.Slot, (ProtVer, PParams))]
sndUPIState :: UPIState -> [(Slot, (ProtVer, PParams))]
sndUPIState ((ProtVer, PParams)
_, [(Slot, (ProtVer, PParams))]
s, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = [(Slot, (ProtVer, PParams))]
s
trdUPIState :: UPIState -> Map ApName (ApVer, Core.Slot, Metadata)
trdUPIState :: UPIState -> Map ApName (ApVer, Slot, Metadata)
trdUPIState ((ProtVer, PParams)
_, [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
t, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = Map ApName (ApVer, Slot, Metadata)
t
emptyUPIState :: UPIState
emptyUPIState :: UPIState
emptyUPIState =
(
( Natural -> Natural -> Natural -> ProtVer
ProtVer Natural
0 Natural
0 Natural
0
, PParams
initialPParams
)
, []
, forall k a. Map k a
Map.empty
, forall k a. Map k a
Map.empty
, forall k a. Map k a
Map.empty
, forall k a. Map k a
Map.empty
, forall a. Set a
Set.empty
, forall a. Set a
Set.empty
, forall k a. Map k a
Map.empty
)
initialPParams :: PParams
initialPParams :: PParams
initialPParams =
PParams
{ _maxBkSz :: Natural
_maxBkSz = Natural
10000
, _maxHdrSz :: Natural
_maxHdrSz = Natural
1000
, _maxTxSz :: Natural
_maxTxSz = Natural
500
, _maxPropSz :: Natural
_maxPropSz = Natural
10
, _bkSgnCntT :: BkSgnCntT
_bkSgnCntT = BkSgnCntT
0.22
, _bkSlotsPerEpoch :: SlotCount
_bkSlotsPerEpoch = SlotCount
10
, _upTtl :: SlotCount
_upTtl = SlotCount
10
, _scriptVersion :: Natural
_scriptVersion = Natural
0
, _upAdptThd :: UpAdptThd
_upAdptThd = UpAdptThd
0.6
,
_factorA :: FactorA
_factorA = Int -> FactorA
FactorA Int
1
, _factorB :: FactorB
_factorB = Int -> FactorB
FactorB (Int
10 forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
GP.c)
}
protocolVersion :: UPIState -> ProtVer
protocolVersion :: UPIState -> ProtVer
protocolVersion ((ProtVer
pv, PParams
_), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = ProtVer
pv
protocolParameters :: UPIState -> PParams
protocolParameters :: UPIState -> PParams
protocolParameters ((ProtVer
_, PParams
pps), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = PParams
pps
applicationVersions :: UPIState -> Map ApName (ApVer, Core.Slot, Metadata)
applicationVersions :: UPIState -> Map ApName (ApVer, Slot, Metadata)
applicationVersions ((ProtVer
_, PParams
_), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
avs, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = Map ApName (ApVer, Slot, Metadata)
avs
confirmedProposals :: UPIState -> Map UpId Core.Slot
confirmedProposals :: UPIState -> Map UpId Slot
confirmedProposals ((ProtVer
_, PParams
_), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
cps, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = Map UpId Slot
cps
futureAdoptions :: UPIState -> [(Core.Slot, (ProtVer, PParams))]
futureAdoptions :: UPIState -> [(Slot, (ProtVer, PParams))]
futureAdoptions ((ProtVer
_, PParams
_), [(Slot, (ProtVer, PParams))]
fads, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = [(Slot, (ProtVer, PParams))]
fads
endorsements :: UPIState -> Set (ProtVer, Core.VKeyGenesis)
endorsements :: UPIState -> Set (ProtVer, VKeyGenesis)
endorsements ((ProtVer
_, PParams
_), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
_, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
bvs, Map UpId Slot
_) = Set (ProtVer, VKeyGenesis)
bvs
registeredProtocolUpdateProposals :: UPIState -> Map UpId (ProtVer, PParams)
registeredProtocolUpdateProposals :: UPIState -> Map UpId (ProtVer, PParams)
registeredProtocolUpdateProposals ((ProtVer
_, PParams
_), [(Slot, (ProtVer, PParams))]
_, Map ApName (ApVer, Slot, Metadata)
_, Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
_, Map UpId Slot
_, Set (UpId, VKeyGenesis)
_, Set (ProtVer, VKeyGenesis)
_, Map UpId Slot
_) = Map UpId (ProtVer, PParams)
rpus
data UPIREG deriving (forall x. Rep UPIREG x -> UPIREG
forall x. UPIREG -> Rep UPIREG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UPIREG x -> UPIREG
$cfrom :: forall x. UPIREG -> Rep UPIREG x
Generic, Typeable UPIREG
UPIREG -> DataType
UPIREG -> Constr
(forall b. Data b => b -> b) -> UPIREG -> UPIREG
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) -> UPIREG -> u
forall u. (forall d. Data d => d -> u) -> UPIREG -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPIREG
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPIREG -> c UPIREG
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPIREG)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPIREG)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UPIREG -> m UPIREG
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPIREG -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UPIREG -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UPIREG -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UPIREG -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UPIREG -> r
gmapT :: (forall b. Data b => b -> b) -> UPIREG -> UPIREG
$cgmapT :: (forall b. Data b => b -> b) -> UPIREG -> UPIREG
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPIREG)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UPIREG)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPIREG)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UPIREG)
dataTypeOf :: UPIREG -> DataType
$cdataTypeOf :: UPIREG -> DataType
toConstr :: UPIREG -> Constr
$ctoConstr :: UPIREG -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPIREG
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UPIREG
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPIREG -> c UPIREG
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UPIREG -> c UPIREG
Data, Typeable)
data UpiregPredicateFailure
= UPREGFailure (PredicateFailure UPREG)
deriving (UpiregPredicateFailure -> UpiregPredicateFailure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpiregPredicateFailure -> UpiregPredicateFailure -> Bool
$c/= :: UpiregPredicateFailure -> UpiregPredicateFailure -> Bool
== :: UpiregPredicateFailure -> UpiregPredicateFailure -> Bool
$c== :: UpiregPredicateFailure -> UpiregPredicateFailure -> Bool
Eq, Int -> UpiregPredicateFailure -> ShowS
[UpiregPredicateFailure] -> ShowS
UpiregPredicateFailure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpiregPredicateFailure] -> ShowS
$cshowList :: [UpiregPredicateFailure] -> ShowS
show :: UpiregPredicateFailure -> String
$cshow :: UpiregPredicateFailure -> String
showsPrec :: Int -> UpiregPredicateFailure -> ShowS
$cshowsPrec :: Int -> UpiregPredicateFailure -> ShowS
Show, Typeable UpiregPredicateFailure
UpiregPredicateFailure -> DataType
UpiregPredicateFailure -> Constr
(forall b. Data b => b -> b)
-> UpiregPredicateFailure -> UpiregPredicateFailure
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) -> UpiregPredicateFailure -> u
forall u.
(forall d. Data d => d -> u) -> UpiregPredicateFailure -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpiregPredicateFailure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpiregPredicateFailure
-> c UpiregPredicateFailure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpiregPredicateFailure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpiregPredicateFailure)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UpiregPredicateFailure -> m UpiregPredicateFailure
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpiregPredicateFailure -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UpiregPredicateFailure -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> UpiregPredicateFailure -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> UpiregPredicateFailure -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> UpiregPredicateFailure
-> r
gmapT :: (forall b. Data b => b -> b)
-> UpiregPredicateFailure -> UpiregPredicateFailure
$cgmapT :: (forall b. Data b => b -> b)
-> UpiregPredicateFailure -> UpiregPredicateFailure
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpiregPredicateFailure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UpiregPredicateFailure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpiregPredicateFailure)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UpiregPredicateFailure)
dataTypeOf :: UpiregPredicateFailure -> DataType
$cdataTypeOf :: UpiregPredicateFailure -> DataType
toConstr :: UpiregPredicateFailure -> Constr
$ctoConstr :: UpiregPredicateFailure -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpiregPredicateFailure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UpiregPredicateFailure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpiregPredicateFailure
-> c UpiregPredicateFailure
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> UpiregPredicateFailure
-> c UpiregPredicateFailure
Data, Typeable, forall x. Rep UpiregPredicateFailure x -> UpiregPredicateFailure
forall x. UpiregPredicateFailure -> Rep UpiregPredicateFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpiregPredicateFailure x -> UpiregPredicateFailure
$cfrom :: forall x. UpiregPredicateFailure -> Rep UpiregPredicateFailure x
Generic, Context -> UpiregPredicateFailure -> IO (Maybe ThunkInfo)
Proxy UpiregPredicateFailure -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UpiregPredicateFailure -> String
$cshowTypeOf :: Proxy UpiregPredicateFailure -> String
wNoThunks :: Context -> UpiregPredicateFailure -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UpiregPredicateFailure -> IO (Maybe ThunkInfo)
noThunks :: Context -> UpiregPredicateFailure -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UpiregPredicateFailure -> IO (Maybe ThunkInfo)
NoThunks)
instance STS UPIREG where
type Environment UPIREG = UPIEnv
type State UPIREG = UPIState
type Signal UPIREG = UProp
type PredicateFailure UPIREG = UpiregPredicateFailure
initialRules :: [InitialRule UPIREG]
initialRules = [forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! UPIState
emptyUPIState]
transitionRules :: [TransitionRule UPIREG]
transitionRules =
[ do
TRC
( (Slot
sn, Bimap VKeyGenesis VKey
dms, BlockCount
_k, Word8
_ngk)
, ( (ProtVer
pv, PParams
pps)
, [(Slot, (ProtVer, PParams))]
fads
, Map ApName (ApVer, Slot, Metadata)
avs
, Map UpId (ProtVer, PParams)
rpus
, Map UpId (ApName, ApVer, Metadata)
raus
, Map UpId Slot
cps
, Set (UpId, VKeyGenesis)
vts
, Set (ProtVer, VKeyGenesis)
bvs
, Map UpId Slot
pws
)
, Signal UPIREG
up
) <-
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
(Map UpId (ProtVer, PParams)
rpus', Map UpId (ApName, ApVer, Metadata)
raus') <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
trans @UPREG forall a b. (a -> b) -> a -> b
$ forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC ((ProtVer
pv, PParams
pps, Map ApName (ApVer, Slot, Metadata)
avs, Bimap VKeyGenesis VKey
dms), (Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus), Signal UPIREG
up)
let pws' :: Map UpId Slot
pws' = Map UpId Slot
pws forall m (f :: * -> *).
(Relation m, Ord (Domain m), Ord (Range m), Foldable f) =>
m -> f (Domain m, Range m) -> m
⨃ [(Signal UPIREG
up forall s a. s -> Getting a s a -> a
^. Lens' UProp UpId
upId, Slot
sn)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$!
( (ProtVer
pv, PParams
pps)
, [(Slot, (ProtVer, PParams))]
fads
, Map ApName (ApVer, Slot, Metadata)
avs
, Map UpId (ProtVer, PParams)
rpus'
, Map UpId (ApName, ApVer, Metadata)
raus'
, Map UpId Slot
cps
, Set (UpId, VKeyGenesis)
vts
, Set (ProtVer, VKeyGenesis)
bvs
, Map UpId Slot
pws'
)
]
instance Embed UPREG UPIREG where
wrapFailed :: PredicateFailure UPREG -> PredicateFailure UPIREG
wrapFailed = PredicateFailure UPREG -> UpiregPredicateFailure
UPREGFailure
instance HasTrace UPIREG where
envGen :: Word64 -> Gen (Environment UPIREG)
envGen Word64
_ = Gen UPIEnv
upiEnvGen
sigGen :: SignalGenerator UPIREG
sigGen (Slot
_slot, Bimap VKeyGenesis VKey
dms, BlockCount
_k, Word8
_ngk) ((ProtVer
pv, PParams
pps), [(Slot, (ProtVer, PParams))]
_fads, Map ApName (ApVer, Slot, Metadata)
avs, Map UpId (ProtVer, PParams)
rpus, Map UpId (ApName, ApVer, Metadata)
raus, Map UpId Slot
_cps, Set (UpId, VKeyGenesis)
_vts, Set (ProtVer, VKeyGenesis)
_bvs, Map UpId Slot
pws) =
do
(VKey
vk, ProtVer
pv', PParams
pps', SwVer
sv') <-
(,,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen VKey
issuerGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ProtVer
pvGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen PParams
pparamsGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen SwVer
swVerGen
forall (m :: * -> *) a. MonadGen m => [(Int, m a)] -> m a
Gen.frequency
[
(Int
10, VKey -> PParams -> ProtVer -> SwVer -> GenT Identity UProp
generateUpdateProposalWith VKey
vk PParams
pps ProtVer
pv SwVer
sv')
,
( Int
45
, do
let makeSoftwareVersion :: (ApName, (ApVer, b, c)) -> SwVer
makeSoftwareVersion (ApName
apName, (ApVer
apVersion, b
_, c
_)) = ApName -> ApVer -> SwVer
SwVer ApName
apName ApVer
apVersion
avsList :: [(ApName, (ApVer, Slot, Metadata))]
avsList = forall k a. Map k a -> [(k, a)]
Map.toList Map ApName (ApVer, Slot, Metadata)
avs
SwVer
currentSoftwareVersion <-
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ApName, (ApVer, Slot, Metadata))]
avsList
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! SwVer
sv'
else forall {b} {c}. (ApName, (ApVer, b, c)) -> SwVer
makeSoftwareVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element [(ApName, (ApVer, Slot, Metadata))]
avsList
VKey -> PParams -> ProtVer -> SwVer -> GenT Identity UProp
generateUpdateProposalWith VKey
vk PParams
pps' ProtVer
pv' SwVer
currentSoftwareVersion
)
,
(Int
45, VKey -> PParams -> ProtVer -> SwVer -> GenT Identity UProp
generateUpdateProposalWith VKey
vk PParams
pps' ProtVer
pv' SwVer
sv')
]
where
idGen :: Gen UpId
idGen :: Gen UpId
idGen = do
Int
inc <- forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. a -> a -> Range a
Range.constant Int
1 Int
10)
case forall a. Set a -> [a]
Set.toDescList forall a b. (a -> b) -> a -> b
$ forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map UpId Slot
pws of
[] -> Int -> UpId
UpId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element [Int
0 .. Int
inc]
(UpId Int
maxId : [UpId]
_) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Int -> UpId
UpId (Int
maxId forall a. Num a => a -> a -> a
+ Int
inc)
issuerGen :: Gen Core.VKey
issuerGen :: Gen VKey
issuerGen =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [VKey]
delegates
then forall a. HasCallStack => String -> a
error String
"There are no delegates to issue an update proposal."
else forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element [VKey]
delegates
where
delegates :: [VKey]
delegates = forall a. Set a -> [a]
Set.toList (forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range Bimap VKeyGenesis VKey
dms)
pparamsGen :: Gen PParams
pparamsGen :: Gen PParams
pparamsGen = PParams -> Gen PParams
ppsUpdateFrom PParams
pps
pvGen :: Gen ProtVer
pvGen :: Gen ProtVer
pvGen =
(Natural, Natural) -> ProtVer
nextAltVersion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element
[ (ProtVer -> Natural
_pvMaj ProtVer
pv forall a. Num a => a -> a -> a
+ Natural
1, Natural
0)
, (ProtVer -> Natural
_pvMaj ProtVer
pv, ProtVer -> Natural
_pvMin ProtVer
pv forall a. Num a => a -> a -> a
+ Natural
1)
]
where
nextAltVersion :: (Natural, Natural) -> ProtVer
nextAltVersion :: (Natural, Natural) -> ProtVer
nextAltVersion (Natural
maj, Natural
mn) =
forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom (forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range Map UpId (ProtVer, PParams)
rpus)
forall a b. a -> (a -> b) -> b
& forall a. (a -> Bool) -> Set a -> Set a
Set.filter ProtVer -> Bool
protocolVersionEqualsMajMin
forall a b. a -> (a -> b) -> b
& forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map ProtVer -> Natural
_pvAlt
forall a b. a -> (a -> b) -> b
& forall a. Set a -> [a]
Set.toDescList
forall a b. a -> (a -> b) -> b
& [Natural] -> ProtVer
nextVersion
where
protocolVersionEqualsMajMin :: ProtVer -> Bool
protocolVersionEqualsMajMin :: ProtVer -> Bool
protocolVersionEqualsMajMin ProtVer
pv' =
ProtVer -> Natural
_pvMaj ProtVer
pv' forall a. Eq a => a -> a -> Bool
== Natural
maj Bool -> Bool -> Bool
&& ProtVer -> Natural
_pvMin ProtVer
pv' forall a. Eq a => a -> a -> Bool
== Natural
mn
nextVersion :: [Natural] -> ProtVer
nextVersion :: [Natural] -> ProtVer
nextVersion [] = Natural -> Natural -> Natural -> ProtVer
ProtVer Natural
maj Natural
mn Natural
0
nextVersion (Natural
x : [Natural]
_) = Natural -> Natural -> Natural -> ProtVer
ProtVer Natural
maj Natural
mn (Natural
1 forall a. Num a => a -> a -> a
+ Natural
x)
swVerGen :: Gen SwVer
swVerGen :: Gen SwVer
swVerGen =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ApName, ApVer)]
possibleNextVersions
then Gen SwVer
genNewApp
else forall (m :: * -> *) a. MonadGen m => [m a] -> m a
Gen.choice [Gen SwVer
genANextVersion, Gen SwVer
genNewApp]
where
possibleNextVersions :: [(ApName, ApVer)]
possibleNextVersions :: [(ApName, ApVer)]
possibleNextVersions = forall a. Set a -> [a]
Set.toList forall a b. (a -> b) -> a -> b
$ Set (ApName, ApVer)
nextVersions forall a. Ord a => Set a -> Set a -> Set a
\\ Set (ApName, ApVer)
registeredNextVersions
where
nextVersions :: Set (ApName, ApVer)
nextVersions :: Set (ApName, ApVer)
nextVersions = forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [ApName]
currentAppNames [ApVer]
nextAppVersions
where
([ApName]
currentAppNames, [(ApVer, Slot, Metadata)]
currentAppVersions) = forall a b. [(a, b)] -> ([a], [b])
unzip forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList Map ApName (ApVer, Slot, Metadata)
avs
nextAppVersions :: [ApVer]
nextAppVersions :: [ApVer]
nextAppVersions = (forall a. Num a => a -> a -> a
+ ApVer
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a} {b} {c}. (a, b, c) -> a
fst3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(ApVer, Slot, Metadata)]
currentAppVersions
registeredNextVersions :: Set (ApName, ApVer)
registeredNextVersions :: Set (ApName, ApVer)
registeredNextVersions = forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (forall {a} {b} {c}. (a, b, c) -> a
fst3 forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall {a} {b} {c}. (a, b, c) -> b
snd3) (forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range Map UpId (ApName, ApVer, Metadata)
raus)
genANextVersion :: Gen SwVer
genANextVersion :: Gen SwVer
genANextVersion = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ApName -> ApVer -> SwVer
SwVer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element [(ApName, ApVer)]
possibleNextVersions
fst3 :: (a, b, c) -> a
fst3 (a
x, b
_, c
_) = a
x
snd3 :: (a, b, c) -> b
snd3 (a
_, b
y, c
_) = b
y
genNewApp :: Gen SwVer
genNewApp :: Gen SwVer
genNewApp =
(ApName -> ApVer -> SwVer
`SwVer` ApVer
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ApName
ApName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
(MonadGen m, GenBase m ~ Identity) =>
(a -> Bool) -> m a -> m a
Gen.filter
((forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Set ApName
usedNames) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ApName
ApName)
(forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list (forall a. a -> a -> Range a
Range.constant Int
0 Int
12) forall (m :: * -> *). MonadGen m => m Char
Gen.ascii)
where
usedNames :: Set ApName
usedNames =
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall {a} {b} {c}. (a, b, c) -> a
fst3 (forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range Map UpId (ApName, ApVer, Metadata)
raus)
forall a. Ord a => Set a -> Set a -> Set a
`union` forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom Map ApName (ApVer, Slot, Metadata)
avs
generateUpdateProposalWith ::
VKey ->
PParams ->
ProtVer ->
SwVer ->
Gen UProp
generateUpdateProposalWith :: VKey -> PParams -> ProtVer -> SwVer -> GenT Identity UProp
generateUpdateProposalWith VKey
vk PParams
pps' ProtVer
pv' SwVer
sv' =
UpId
-> VKey
-> ProtVer
-> PParams
-> SwVer
-> Set String
-> Metadata
-> UProp
mkUProp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen UpId
idGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure VKey
vk
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure ProtVer
pv'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure PParams
pps'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure SwVer
sv'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Set String)
stTagsGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Metadata
mdtGen
stTagsGen :: Gen (Set STag)
stTagsGen :: Gen (Set String)
stTagsGen =
forall a. Ord a => [a] -> Set a
Set.fromList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list (forall a. Integral a => a -> a -> Range a
Range.linear Int
0 Int
5) (forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list (forall a. a -> a -> Range a
Range.constant Int
0 Int
10) forall (m :: * -> *). MonadGen m => m Char
Gen.ascii)
mdtGen :: Gen Metadata
mdtGen :: Gen Metadata
mdtGen = forall (f :: * -> *) a. Applicative f => a -> f a
pure Metadata
Metadata
upiEnvGen :: Gen UPIEnv
upiEnvGen :: Gen UPIEnv
upiEnvGen = do
Word8
ngk <- forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. Integral a => a -> a -> Range a
Range.linear Word8
1 Word8
14)
(,,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word64 -> Word64 -> Gen Slot
CoreGen.slotGen Word64
0 Word64
10
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word8 -> Gen (Bimap VKeyGenesis VKey)
dmapGen Word8
ngk
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word64 -> BlockCount
BlockCount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadGen m => Range Word64 -> m Word64
Gen.word64 (forall a. a -> a -> Range a
Range.constant Word64
0 Word64
100))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Word8
ngk
dmapGen :: Word8 -> Gen (Bimap Core.VKeyGenesis Core.VKey)
dmapGen :: Word8 -> Gen (Bimap VKeyGenesis VKey)
dmapGen Word8
ngk = forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
Bimap.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. [a] -> [b] -> [(a, b)]
zip forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ([VKeyGenesis], [VKey])
vkgVkPairsGen
where
vkgVkPairsGen :: Gen ([Core.VKeyGenesis], [Core.VKey])
vkgVkPairsGen :: Gen ([VKeyGenesis], [VKey])
vkgVkPairsGen = ([VKeyGenesis]
vkgs,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
(MonadGen m, GenBase m ~ Identity) =>
(a -> Bool) -> m a -> m a
Gen.filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) (forall (m :: * -> *) a. MonadGen m => [a] -> m [a]
Gen.subsequence [VKey]
vks)
where
vkgs :: [VKeyGenesis]
vkgs = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word8
0 .. Word8
ngk forall a. Num a => a -> a -> a
- Word8
1]
vks :: [VKey]
vks = Owner -> VKey
VKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Owner
Owner forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word8
0 .. Word8
2 forall a. Num a => a -> a -> a
* (Word8
ngk forall a. Num a => a -> a -> a
- Word8
1)]
ppsUpdateFrom :: PParams -> Gen PParams
ppsUpdateFrom :: PParams -> Gen PParams
ppsUpdateFrom PParams
pps = do
Natural
newMaxBkSize <-
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral
( forall a. Integral a => a -> a -> a -> Range a
Range.linearFrom
Natural
_maxBkSz
(Natural
_maxBkSz Natural -> Natural -> Natural
-? Natural
100)
(Natural
2 forall a. Num a => a -> a -> a
* Natural
_maxBkSz)
)
forall a. Gen a -> (a, a) -> Gen a
`increasingProbabilityAt` (Natural
_maxBkSz Natural -> Natural -> Natural
-? Natural
100, Natural
2 forall a. Num a => a -> a -> a
* Natural
_maxBkSz)
let minTxSzBound :: Natural
minTxSzBound = Natural
_maxTxSz forall a. Ord a => a -> a -> a
`min` Natural
newMaxBkSize Natural -> Natural -> Natural
-? Natural
1
Natural
newMaxTxSize <-
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral
( forall a. Integral a => a -> a -> Range a
Range.exponential
(Natural
minTxSzBound Natural -> Natural -> Natural
-? Natural
10)
(Natural
newMaxBkSize Natural -> Natural -> Natural
-? Natural
1)
)
Natural
-> Natural
-> Natural
-> Natural
-> BkSgnCntT
-> SlotCount
-> SlotCount
-> Natural
-> UpAdptThd
-> FactorA
-> FactorB
-> PParams
PParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure Natural
newMaxBkSize
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Natural
nextMaxHdrSzGen
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Natural
newMaxTxSize
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Natural
nextMaxPropSz
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen BkSgnCntT
nextBkSgnCntT
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure SlotCount
_bkSlotsPerEpoch
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen SlotCount
nextUpTtl
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Natural
nextScriptVersion
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen UpAdptThd
nextUpAdptThd
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen FactorA
nextFactorA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen FactorB
nextFactorB
where
PParams
{ Natural
_maxBkSz :: Natural
_maxBkSz :: PParams -> Natural
_maxBkSz
, Natural
_maxHdrSz :: Natural
_maxHdrSz :: PParams -> Natural
_maxHdrSz
, Natural
_maxTxSz :: Natural
_maxTxSz :: PParams -> Natural
_maxTxSz
, Natural
_maxPropSz :: Natural
_maxPropSz :: PParams -> Natural
_maxPropSz
, BkSgnCntT
_bkSgnCntT :: BkSgnCntT
_bkSgnCntT :: PParams -> BkSgnCntT
_bkSgnCntT
, SlotCount
_bkSlotsPerEpoch :: SlotCount
_bkSlotsPerEpoch :: PParams -> SlotCount
_bkSlotsPerEpoch
, SlotCount
_upTtl :: SlotCount
_upTtl :: PParams -> SlotCount
_upTtl
, Natural
_scriptVersion :: Natural
_scriptVersion :: PParams -> Natural
_scriptVersion
, UpAdptThd
_upAdptThd :: UpAdptThd
_upAdptThd :: PParams -> UpAdptThd
_upAdptThd
, FactorA
_factorA :: FactorA
_factorA :: PParams -> FactorA
_factorA
, FactorB
_factorB :: FactorB
_factorB :: PParams -> FactorB
_factorB
} = PParams
pps
FactorA Int
fA = FactorA
_factorA
FactorB Int
fB = FactorB
_factorB
BkSgnCntT Double
bsct = BkSgnCntT
_bkSgnCntT
UpAdptThd Double
uat = UpAdptThd
_upAdptThd
nextMaxHdrSzGen :: Gen Natural
nextMaxHdrSzGen :: Gen Natural
nextMaxHdrSzGen =
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral
( forall a. Integral a => a -> a -> a -> Range a
Range.exponentialFrom
Natural
_maxHdrSz
(Natural
_maxHdrSz Natural -> Natural -> Natural
-? Natural
10)
(Natural
2 forall a. Num a => a -> a -> a
* Natural
_maxHdrSz)
)
nextMaxPropSz :: Gen Natural
nextMaxPropSz :: Gen Natural
nextMaxPropSz =
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral
( forall a. Integral a => a -> a -> a -> Range a
Range.exponentialFrom
Natural
_maxPropSz
(Natural
_maxPropSz Natural -> Natural -> Natural
-? Natural
1)
(Natural
2 forall a. Num a => a -> a -> a
* Natural
_maxPropSz)
)
nextBkSgnCntT :: Gen BkSgnCntT
nextBkSgnCntT :: Gen BkSgnCntT
nextBkSgnCntT =
Double -> BkSgnCntT
BkSgnCntT
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadGen m => Range Double -> m Double
Gen.double
( forall a. (Floating a, Ord a) => a -> a -> a -> Range a
Range.exponentialFloatFrom
Double
bsct
(Double
bsct forall a. Num a => a -> a -> a
- Double
0.01)
(Double
bsct forall a. Num a => a -> a -> a
+ Double
0.01)
)
nextUpTtl :: Gen SlotCount
nextUpTtl :: Gen SlotCount
nextUpTtl =
Word64 -> SlotCount
SlotCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. Integral a => a -> a -> a -> Range a
Range.exponentialFrom Word64
currUpTtl Word64
minTtl (Word64
2 forall a. Num a => a -> a -> a
* Word64
currUpTtl))
forall a. Gen a -> (a, a) -> Gen a
`increasingProbabilityAt` (Word64
minTtl, Word64
2 forall a. Num a => a -> a -> a
* Word64
currUpTtl)
where
SlotCount Word64
currUpTtl = SlotCount
_upTtl
minTtl :: Word64
minTtl = Word64
2
nextScriptVersion :: Gen Natural
nextScriptVersion :: Gen Natural
nextScriptVersion = forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, MonadGen m) =>
f a -> m a
Gen.element [Natural
_scriptVersion, Natural
_scriptVersion forall a. Num a => a -> a -> a
+ Natural
1]
nextUpAdptThd :: Gen UpAdptThd
nextUpAdptThd :: Gen UpAdptThd
nextUpAdptThd =
Double -> UpAdptThd
UpAdptThd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadGen m => Range Double -> m Double
Gen.double (forall a. (Floating a, Ord a) => a -> a -> a -> Range a
Range.exponentialFloatFrom Double
uat Double
0 Double
1)
forall a. Gen a -> (a, a) -> Gen a
`increasingProbabilityAt` (Double
0, Double
1)
nextFactorA :: Gen FactorA
nextFactorA :: Gen FactorA
nextFactorA =
Int -> FactorA
FactorA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. Integral a => a -> a -> a -> Range a
Range.exponentialFrom Int
fA Int
0 Int
10)
forall a. Gen a -> (a, a) -> Gen a
`increasingProbabilityAt` (Int
0, Int
10)
nextFactorB :: Gen FactorB
nextFactorB :: Gen FactorB
nextFactorB =
Int -> FactorB
FactorB
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. Integral a => a -> a -> a -> Range a
Range.exponentialFrom Int
fB Int
minFactorB Int
maxFactorB)