{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Cardano.Ledger.BaseTypes (
module Slotting,
ProtVer (..),
module Cardano.Ledger.Binary.Version,
FixedPoint,
(==>),
(⭒),
Network (..),
networkToWord8,
word8ToNetwork,
Nonce (..),
Seed (..),
UnitInterval,
PositiveUnitInterval,
PositiveInterval,
NonNegativeInterval,
BoundedRational (..),
fpPrecision,
integralToBounded,
promoteRatio,
invalidKey,
mkNonceFromOutputVRF,
mkNonceFromNumber,
Url,
urlToText,
textToUrl,
DnsName,
dnsToText,
textToDns,
Port (..),
ActiveSlotCoeff,
mkActiveSlotCoeff,
activeSlotVal,
activeSlotLog,
module Data.Maybe.Strict,
BlocksMade (..),
kindObject,
TxIx (..),
txIxToInt,
txIxFromIntegral,
mkTxIx,
mkTxIxPartial,
CertIx (..),
certIxToInt,
certIxFromIntegral,
mkCertIx,
mkCertIxPartial,
Anchor (..),
AnchorData (..),
hashAnchorData,
Globals (..),
epochInfoPure,
ShelleyBase,
Relation (..),
Mismatch (..),
swapMismatch,
unswapMismatch,
Inject (..),
)
where
import Cardano.Crypto.Hash
import Cardano.Crypto.Util (SignableRepresentation (..))
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.Binary (
CBORGroup (..),
DecCBOR (decCBOR),
DecCBORGroup (..),
Decoder,
DecoderError (..),
EncCBOR (encCBOR),
EncCBORGroup (..),
FromCBOR,
ToCBOR,
cborError,
decodeRationalWithTag,
encodeRatioWithTag,
encodedSizeExpr,
ifDecoderVersionAtLeast,
)
import Cardano.Ledger.Binary.Coders (
Decode (..),
Encode (..),
decode,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Binary.Plain (
FromCBOR (..),
ToCBOR (..),
decodeRecordSum,
encodeListLen,
invalidKey,
)
import Cardano.Ledger.Binary.Version
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import Cardano.Ledger.NonIntegral (ln')
import Cardano.Ledger.SafeHash (HashWithCrypto (..), SafeHash, SafeToHash)
import Cardano.Slotting.Block as Slotting (BlockNo (..))
import Cardano.Slotting.EpochInfo (EpochInfo, hoistEpochInfo)
import Cardano.Slotting.Slot as Slotting (
EpochInterval (..),
EpochNo (..),
EpochSize (..),
SlotNo (..),
WithOrigin (..),
addEpochInterval,
binOpEpochNo,
)
import Cardano.Slotting.Time (SystemStart)
import Control.DeepSeq (NFData (rnf), rwhnf)
import Control.Exception (throw)
import Control.Monad (when, (<=<))
import Control.Monad.Trans.Reader (ReaderT)
import Data.Aeson (
FromJSON (..),
KeyValue,
ToJSON (..),
Value (..),
object,
pairs,
withObject,
(.:),
(.=),
)
import Data.Aeson.Types (Pair)
import qualified Data.Binary.Put as B
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Data.Default (Default (def))
import qualified Data.Fixed as FP (Fixed, HasResolution, resolution)
import Data.Functor.Identity (Identity)
import Data.Map.Strict (Map)
import Data.Maybe (fromMaybe)
import Data.Maybe.Strict
import Data.Proxy
import Data.Ratio (Ratio, denominator, numerator, (%))
import Data.Scientific (
Scientific,
base10Exponent,
coefficient,
fromRationalRepetendLimited,
normalize,
)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Text.Encoding (encodeUtf8)
import Data.Typeable (Typeable)
import Data.Word (Word16, Word64, Word8)
import GHC.Exception.Type (Exception)
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
import NoThunks.Class (NoThunks (..))
import Numeric.Natural (Natural)
import Quiet (Quiet (Quiet))
maxDecimalsWord64 :: Int
maxDecimalsWord64 :: Int
maxDecimalsWord64 = Int
19
data ProtVer = ProtVer {ProtVer -> Version
pvMajor :: !Version, ProtVer -> Natural
pvMinor :: !Natural}
deriving (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, 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, ProtVer -> ()
forall a. (a -> ()) -> NFData a
rnf :: ProtVer -> ()
$crnf :: ProtVer -> ()
NFData)
deriving (Typeable ProtVer
ProtVer -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
encCBOR :: ProtVer -> Encoding
$cencCBOR :: ProtVer -> Encoding
EncCBOR) via (CBORGroup ProtVer)
deriving (Typeable ProtVer
Proxy ProtVer -> Text
forall s. Decoder s ProtVer
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy ProtVer -> Decoder s ()
label :: Proxy ProtVer -> Text
$clabel :: Proxy ProtVer -> Text
dropCBOR :: forall s. Proxy ProtVer -> Decoder s ()
$cdropCBOR :: forall s. Proxy ProtVer -> Decoder s ()
decCBOR :: forall s. Decoder s ProtVer
$cdecCBOR :: forall s. Decoder s ProtVer
DecCBOR) via (CBORGroup ProtVer)
instance ToCBOR ProtVer where
toCBOR :: ProtVer -> Encoding
toCBOR ProtVer {Natural
Version
pvMinor :: Natural
pvMajor :: Version
pvMinor :: ProtVer -> Natural
pvMajor :: ProtVer -> Version
..} = forall a. ToCBOR a => a -> Encoding
toCBOR (Version
pvMajor, Natural
pvMinor)
instance FromCBOR ProtVer where
fromCBOR :: forall s. Decoder s ProtVer
fromCBOR = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Version -> Natural -> ProtVer
ProtVer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. FromCBOR a => Decoder s a
fromCBOR
instance NoThunks ProtVer
instance ToJSON ProtVer where
toJSON :: ProtVer -> Value
toJSON (ProtVer Version
major Natural
minor) =
[Pair] -> Value
object
[ Key
"major" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Version -> Word64
getVersion64 Version
major
, Key
"minor" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Natural
minor
]
instance FromJSON ProtVer where
parseJSON :: Value -> Parser ProtVer
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ProtVer" forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
Version
pvMajor <- forall (m :: * -> *). MonadFail m => Word64 -> m Version
mkVersion64 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"major"
Natural
pvMinor <- Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"minor"
forall (f :: * -> *) a. Applicative f => a -> f a
pure ProtVer {Natural
Version
pvMinor :: Natural
pvMajor :: Version
pvMinor :: Natural
pvMajor :: Version
..}
instance EncCBORGroup ProtVer where
encCBORGroup :: ProtVer -> Encoding
encCBORGroup (ProtVer Version
x Natural
y) = forall a. EncCBOR a => a -> Encoding
encCBOR Version
x forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Natural
y
encodedGroupSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
encodedGroupSizeExpr forall t. EncCBOR t => Proxy t -> Size
l Proxy ProtVer
proxy =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
l (ProtVer -> Version
pvMajor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy ProtVer
proxy)
forall a. Num a => a -> a -> a
+ forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
l (Natural -> Word
toWord forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtVer -> Natural
pvMinor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy ProtVer
proxy)
where
toWord :: Natural -> Word
toWord :: Natural -> Word
toWord = forall a b. (Integral a, Num b) => a -> b
fromIntegral
listLen :: ProtVer -> Word
listLen ProtVer
_ = Word
2
listLenBound :: Proxy ProtVer -> Word
listLenBound Proxy ProtVer
_ = Word
2
instance DecCBORGroup ProtVer where
decCBORGroup :: forall s. Decoder s ProtVer
decCBORGroup = Version -> Natural -> ProtVer
ProtVer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
data E34
instance FP.HasResolution E34 where
resolution :: forall (p :: * -> *). p E34 -> Integer
resolution p E34
_ = (Integer
10 :: Integer) forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
34 :: Integer)
type Digits34 = FP.Fixed E34
type FixedPoint = Digits34
fpPrecision :: FixedPoint
fpPrecision :: FixedPoint
fpPrecision = (FixedPoint
10 :: FixedPoint) forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
34 :: Integer)
integralToBounded ::
forall i b m. (Integral i, Integral b, Bounded b, MonadFail m) => i -> m b
integralToBounded :: forall i b (m :: * -> *).
(Integral i, Integral b, Bounded b, MonadFail m) =>
i -> m b
integralToBounded i
i
| Integer
int forall a. Ord a => a -> a -> Bool
< Integer
minInt =
forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Value " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
int forall a. [a] -> [a] -> [a]
++ String
" less than expected minimum value: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
minInt
| Integer
int forall a. Ord a => a -> a -> Bool
> Integer
maxInt =
forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Value " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
int forall a. [a] -> [a] -> [a]
++ String
" greater than expected maximum value: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
maxInt
| Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
int
where
int :: Integer
int = forall a. Integral a => a -> Integer
toInteger i
i
minInt :: Integer
minInt = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound @b)
maxInt :: Integer
maxInt = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound @b)
{-# INLINE integralToBounded #-}
newtype BoundedRatio b a = BoundedRatio (Ratio a)
deriving (BoundedRatio b a -> BoundedRatio b a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall b a. Eq a => BoundedRatio b a -> BoundedRatio b a -> Bool
/= :: BoundedRatio b a -> BoundedRatio b a -> Bool
$c/= :: forall b a. Eq a => BoundedRatio b a -> BoundedRatio b a -> Bool
== :: BoundedRatio b a -> BoundedRatio b a -> Bool
$c== :: forall b a. Eq a => BoundedRatio b a -> BoundedRatio b a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b a x. Rep (BoundedRatio b a) x -> BoundedRatio b a
forall b a x. BoundedRatio b a -> Rep (BoundedRatio b a) x
$cto :: forall b a x. Rep (BoundedRatio b a) x -> BoundedRatio b a
$cfrom :: forall b a x. BoundedRatio b a -> Rep (BoundedRatio b a) x
Generic)
deriving newtype (Int -> BoundedRatio b a -> ShowS
[BoundedRatio b a] -> ShowS
BoundedRatio b a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall b a. Show a => Int -> BoundedRatio b a -> ShowS
forall b a. Show a => [BoundedRatio b a] -> ShowS
forall b a. Show a => BoundedRatio b a -> String
showList :: [BoundedRatio b a] -> ShowS
$cshowList :: forall b a. Show a => [BoundedRatio b a] -> ShowS
show :: BoundedRatio b a -> String
$cshow :: forall b a. Show a => BoundedRatio b a -> String
showsPrec :: Int -> BoundedRatio b a -> ShowS
$cshowsPrec :: forall b a. Show a => Int -> BoundedRatio b a -> ShowS
Show, Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
Proxy (BoundedRatio b a) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
forall b a. NoThunks a => Proxy (BoundedRatio b a) -> String
showTypeOf :: Proxy (BoundedRatio b a) -> String
$cshowTypeOf :: forall b a. NoThunks a => Proxy (BoundedRatio b a) -> String
wNoThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
noThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cnoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
NoThunks, BoundedRatio b a -> ()
forall a. (a -> ()) -> NFData a
forall b a. NFData a => BoundedRatio b a -> ()
rnf :: BoundedRatio b a -> ()
$crnf :: forall b a. NFData a => BoundedRatio b a -> ()
NFData)
instance Integral a => Ord (BoundedRatio b a) where
compare :: BoundedRatio b a -> BoundedRatio b a -> Ordering
compare (BoundedRatio Ratio a
a) (BoundedRatio Ratio a
b) = forall a. Ord a => a -> a -> Ordering
compare (forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
a) (forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
b)
promoteRatio :: Integral a => Ratio a -> Rational
promoteRatio :: forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
r = forall a. Integral a => a -> Integer
toInteger (forall a. Ratio a -> a
numerator Ratio a
r) forall a. Integral a => a -> a -> Ratio a
% forall a. Integral a => a -> Integer
toInteger (forall a. Ratio a -> a
denominator Ratio a
r)
class Bounded r => BoundedRational r where
boundRational :: Rational -> Maybe r
unboundRational :: r -> Rational
instance
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
BoundedRational (BoundedRatio b a)
where
boundRational :: Rational -> Maybe (BoundedRatio b a)
boundRational = forall b a.
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
Rational -> Maybe (BoundedRatio b a)
fromRationalBoundedRatio
unboundRational :: BoundedRatio b a -> Rational
unboundRational = forall a b. Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio
toRationalBoundedRatio :: Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio :: forall a b. Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio (BoundedRatio Ratio a
r) = forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
r
fromRationalBoundedRatio ::
forall b a.
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
Rational ->
Maybe (BoundedRatio b a)
fromRationalBoundedRatio :: forall b a.
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
Rational -> Maybe (BoundedRatio b a)
fromRationalBoundedRatio Rational
r
| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
minVal Bool -> Bool -> Bool
|| Integer
d forall a. Ord a => a -> a -> Bool
< Integer
minVal Bool -> Bool -> Bool
|| Integer
n forall a. Ord a => a -> a -> Bool
> Integer
maxVal Bool -> Bool -> Bool
|| Integer
d forall a. Ord a => a -> a -> Bool
> Integer
maxVal = forall a. Maybe a
Nothing
| Bool
otherwise = forall b a.
(Bounded a, Bounded (BoundedRatio b a), Integral a) =>
Ratio a -> Maybe (BoundedRatio b a)
fromRatioBoundedRatio forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
n forall a. Integral a => a -> a -> Ratio a
% forall a. Num a => Integer -> a
fromInteger Integer
d
where
minVal :: Integer
minVal = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a)
maxVal :: Integer
maxVal = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a)
n :: Integer
n = forall a. Ratio a -> a
numerator Rational
r
d :: Integer
d = forall a. Ratio a -> a
denominator Rational
r
fromRatioBoundedRatio ::
forall b a.
(Bounded a, Bounded (BoundedRatio b a), Integral a) =>
Ratio a ->
Maybe (BoundedRatio b a)
fromRatioBoundedRatio :: forall b a.
(Bounded a, Bounded (BoundedRatio b a), Integral a) =>
Ratio a -> Maybe (BoundedRatio b a)
fromRatioBoundedRatio Ratio a
ratio
| Rational
r forall a. Ord a => a -> a -> Bool
< forall r. BoundedRational r => r -> Rational
unboundRational BoundedRatio b a
lowerBound
Bool -> Bool -> Bool
|| Rational
r forall a. Ord a => a -> a -> Bool
> forall r. BoundedRational r => r -> Rational
unboundRational BoundedRatio b a
upperBound =
forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall b a. Ratio a -> BoundedRatio b a
BoundedRatio Ratio a
ratio
where
r :: Rational
r = forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
ratio
lowerBound :: BoundedRatio b a
lowerBound = forall a. Bounded a => a
minBound :: BoundedRatio b a
upperBound :: BoundedRatio b a
upperBound = forall a. Bounded a => a
maxBound :: BoundedRatio b a
instance (EncCBOR a, Integral a, Bounded a, Typeable b) => EncCBOR (BoundedRatio b a) where
encCBOR :: BoundedRatio b a -> Encoding
encCBOR (BoundedRatio Ratio a
u) = forall t. (t -> Encoding) -> Ratio t -> Encoding
encodeRatioWithTag forall a. EncCBOR a => a -> Encoding
encCBOR Ratio a
u
instance
(DecCBOR a, Bounded (BoundedRatio b a), Bounded a, Integral a, Typeable b, Show a) =>
DecCBOR (BoundedRatio b a)
where
decCBOR :: forall s. Decoder s (BoundedRatio b a)
decCBOR = do
Rational
r <- forall s. Decoder s Rational
decodeRationalWithTag
case forall r. BoundedRational r => Rational -> Maybe r
boundRational Rational
r of
Maybe (BoundedRatio b a)
Nothing ->
forall (m :: * -> *) e a. (MonadFail m, Buildable e) => e -> m a
cborError forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"BoundedRatio" (String -> Text
Text.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Rational
r)
Just BoundedRatio b a
u -> forall (f :: * -> *) a. Applicative f => a -> f a
pure BoundedRatio b a
u
instance Bounded (BoundedRatio b Word64) => ToJSON (BoundedRatio b Word64) where
toJSON :: BoundedRatio b Word64 -> Value
toJSON :: BoundedRatio b Word64 -> Value
toJSON BoundedRatio b Word64
br = case Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited Int
maxDecimalsWord64 Rational
r of
Right (Scientific
s, Maybe Int
Nothing) -> forall a. ToJSON a => a -> Value
toJSON Scientific
s
Either (Scientific, Rational) (Scientific, Maybe Int)
_ -> forall a. ToJSON a => a -> Value
toJSON Rational
r
where
r :: Rational
r = forall r. BoundedRational r => r -> Rational
unboundRational BoundedRatio b Word64
br
instance Bounded (BoundedRatio b Word64) => FromJSON (BoundedRatio b Word64) where
parseJSON :: Value -> Parser (BoundedRatio b Word64)
parseJSON = \case
rational :: Value
rational@(Object Object
_) -> forall {b} {c}.
FromJSON b =>
(b -> Either String c) -> Value -> Parser c
parseWith forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither Value
rational
Value
sci -> forall {b} {c}.
FromJSON b =>
(b -> Either String c) -> Value -> Parser c
parseWith forall b.
Bounded (BoundedRatio b Word64) =>
Scientific -> Either String (BoundedRatio b Word64)
fromScientificBoundedRatioWord64 Value
sci
where
parseWith :: (b -> Either String c) -> Value -> Parser c
parseWith b -> Either String c
f = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either String c
f forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall a. FromJSON a => Value -> Parser a
parseJSON
fromScientificBoundedRatioWord64 ::
Bounded (BoundedRatio b Word64) =>
Scientific ->
Either String (BoundedRatio b Word64)
fromScientificBoundedRatioWord64 :: forall b.
Bounded (BoundedRatio b Word64) =>
Scientific -> Either String (BoundedRatio b Word64)
fromScientificBoundedRatioWord64 (Scientific -> Scientific
normalize -> Scientific
sci)
| Integer
coeff forall a. Ord a => a -> a -> Bool
< Integer
0 = forall a b. Show a => String -> a -> Either String b
failWith String
"negative" Scientific
sci
| Int
exp10 forall a. Ord a => a -> a -> Bool
<= Int
0 = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
exp10 forall a. Ord a => a -> a -> Bool
< -Int
maxDecimalsWord64) forall a b. (a -> b) -> a -> b
$ forall a b. Show a => String -> a -> Either String b
failWith String
"too precise" Scientific
sci
forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither (Integer
coeff forall a. Integral a => a -> a -> Ratio a
% (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall a. Num a => a -> a
negate Int
exp10))
| Bool
otherwise = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
maxDecimalsWord64 forall a. Ord a => a -> a -> Bool
< Int
exp10) forall a b. (a -> b) -> a -> b
$ forall a b. Show a => String -> a -> Either String b
failWith String
"too big" Scientific
sci
forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither (Integer
coeff forall a. Num a => a -> a -> a
* Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ Int
exp10 forall a. Integral a => a -> a -> Ratio a
% Integer
1)
where
coeff :: Integer
coeff = Scientific -> Integer
coefficient Scientific
sci
exp10 :: Int
exp10 = Scientific -> Int
base10Exponent Scientific
sci
fromRationalEither ::
Bounded (BoundedRatio b Word64) => Rational -> Either String (BoundedRatio b Word64)
fromRationalEither :: forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither Rational
r = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. Show a => String -> a -> Either String b
failWith String
"outside of bounds" Rational
r) forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall r. BoundedRational r => Rational -> Maybe r
boundRational Rational
r
failWith :: Show a => String -> a -> Either String b
failWith :: forall a b. Show a => String -> a -> Either String b
failWith String
msg a
val = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String
"Value is " forall a. Semigroup a => a -> a -> a
<> String
msg forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show a
val
newtype NonNegativeInterval
= NonNegativeInterval (BoundedRatio NonNegativeInterval Word64)
deriving (Eq NonNegativeInterval
NonNegativeInterval -> NonNegativeInterval -> Bool
NonNegativeInterval -> NonNegativeInterval -> Ordering
NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
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 :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
$cmin :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
max :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
$cmax :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
>= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c>= :: NonNegativeInterval -> NonNegativeInterval -> Bool
> :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c> :: NonNegativeInterval -> NonNegativeInterval -> Bool
<= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c<= :: NonNegativeInterval -> NonNegativeInterval -> Bool
< :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c< :: NonNegativeInterval -> NonNegativeInterval -> Bool
compare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
$ccompare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
Ord, NonNegativeInterval -> NonNegativeInterval -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
== :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c== :: NonNegativeInterval -> NonNegativeInterval -> Bool
Eq, forall x. Rep NonNegativeInterval x -> NonNegativeInterval
forall x. NonNegativeInterval -> Rep NonNegativeInterval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NonNegativeInterval x -> NonNegativeInterval
$cfrom :: forall x. NonNegativeInterval -> Rep NonNegativeInterval x
Generic)
deriving newtype
( Int -> NonNegativeInterval -> ShowS
[NonNegativeInterval] -> ShowS
NonNegativeInterval -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonNegativeInterval] -> ShowS
$cshowList :: [NonNegativeInterval] -> ShowS
show :: NonNegativeInterval -> String
$cshow :: NonNegativeInterval -> String
showsPrec :: Int -> NonNegativeInterval -> ShowS
$cshowsPrec :: Int -> NonNegativeInterval -> ShowS
Show
, NonNegativeInterval
forall a. a -> a -> Bounded a
maxBound :: NonNegativeInterval
$cmaxBound :: NonNegativeInterval
minBound :: NonNegativeInterval
$cminBound :: NonNegativeInterval
Bounded
, Bounded NonNegativeInterval
Rational -> Maybe NonNegativeInterval
NonNegativeInterval -> Rational
forall r.
Bounded r
-> (Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
unboundRational :: NonNegativeInterval -> Rational
$cunboundRational :: NonNegativeInterval -> Rational
boundRational :: Rational -> Maybe NonNegativeInterval
$cboundRational :: Rational -> Maybe NonNegativeInterval
BoundedRational
, Typeable NonNegativeInterval
NonNegativeInterval -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
encCBOR :: NonNegativeInterval -> Encoding
$cencCBOR :: NonNegativeInterval -> Encoding
EncCBOR
, Typeable NonNegativeInterval
Proxy NonNegativeInterval -> Text
forall s. Decoder s NonNegativeInterval
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy NonNegativeInterval -> Decoder s ()
label :: Proxy NonNegativeInterval -> Text
$clabel :: Proxy NonNegativeInterval -> Text
dropCBOR :: forall s. Proxy NonNegativeInterval -> Decoder s ()
$cdropCBOR :: forall s. Proxy NonNegativeInterval -> Decoder s ()
decCBOR :: forall s. Decoder s NonNegativeInterval
$cdecCBOR :: forall s. Decoder s NonNegativeInterval
DecCBOR
, [NonNegativeInterval] -> Encoding
[NonNegativeInterval] -> Value
NonNegativeInterval -> Bool
NonNegativeInterval -> Encoding
NonNegativeInterval -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: NonNegativeInterval -> Bool
$comitField :: NonNegativeInterval -> Bool
toEncodingList :: [NonNegativeInterval] -> Encoding
$ctoEncodingList :: [NonNegativeInterval] -> Encoding
toJSONList :: [NonNegativeInterval] -> Value
$ctoJSONList :: [NonNegativeInterval] -> Value
toEncoding :: NonNegativeInterval -> Encoding
$ctoEncoding :: NonNegativeInterval -> Encoding
toJSON :: NonNegativeInterval -> Value
$ctoJSON :: NonNegativeInterval -> Value
ToJSON
, Maybe NonNegativeInterval
Value -> Parser [NonNegativeInterval]
Value -> Parser NonNegativeInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe NonNegativeInterval
$comittedField :: Maybe NonNegativeInterval
parseJSONList :: Value -> Parser [NonNegativeInterval]
$cparseJSONList :: Value -> Parser [NonNegativeInterval]
parseJSON :: Value -> Parser NonNegativeInterval
$cparseJSON :: Value -> Parser NonNegativeInterval
FromJSON
, Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
Proxy NonNegativeInterval -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy NonNegativeInterval -> String
$cshowTypeOf :: Proxy NonNegativeInterval -> String
wNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
NoThunks
, NonNegativeInterval -> ()
forall a. (a -> ()) -> NFData a
rnf :: NonNegativeInterval -> ()
$crnf :: NonNegativeInterval -> ()
NFData
)
instance Bounded (BoundedRatio NonNegativeInterval Word64) where
minBound :: BoundedRatio NonNegativeInterval Word64
minBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
0 forall a. Integral a => a -> a -> Ratio a
% Word64
1)
maxBound :: BoundedRatio NonNegativeInterval Word64
maxBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (forall a. Bounded a => a
maxBound forall a. Integral a => a -> a -> Ratio a
% Word64
1)
newtype PositiveInterval
= PositiveInterval (BoundedRatio PositiveInterval Word64)
deriving (Eq PositiveInterval
PositiveInterval -> PositiveInterval -> Bool
PositiveInterval -> PositiveInterval -> Ordering
PositiveInterval -> PositiveInterval -> PositiveInterval
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 :: PositiveInterval -> PositiveInterval -> PositiveInterval
$cmin :: PositiveInterval -> PositiveInterval -> PositiveInterval
max :: PositiveInterval -> PositiveInterval -> PositiveInterval
$cmax :: PositiveInterval -> PositiveInterval -> PositiveInterval
>= :: PositiveInterval -> PositiveInterval -> Bool
$c>= :: PositiveInterval -> PositiveInterval -> Bool
> :: PositiveInterval -> PositiveInterval -> Bool
$c> :: PositiveInterval -> PositiveInterval -> Bool
<= :: PositiveInterval -> PositiveInterval -> Bool
$c<= :: PositiveInterval -> PositiveInterval -> Bool
< :: PositiveInterval -> PositiveInterval -> Bool
$c< :: PositiveInterval -> PositiveInterval -> Bool
compare :: PositiveInterval -> PositiveInterval -> Ordering
$ccompare :: PositiveInterval -> PositiveInterval -> Ordering
Ord, PositiveInterval -> PositiveInterval -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveInterval -> PositiveInterval -> Bool
$c/= :: PositiveInterval -> PositiveInterval -> Bool
== :: PositiveInterval -> PositiveInterval -> Bool
$c== :: PositiveInterval -> PositiveInterval -> Bool
Eq, forall x. Rep PositiveInterval x -> PositiveInterval
forall x. PositiveInterval -> Rep PositiveInterval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PositiveInterval x -> PositiveInterval
$cfrom :: forall x. PositiveInterval -> Rep PositiveInterval x
Generic)
deriving newtype
( Int -> PositiveInterval -> ShowS
[PositiveInterval] -> ShowS
PositiveInterval -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositiveInterval] -> ShowS
$cshowList :: [PositiveInterval] -> ShowS
show :: PositiveInterval -> String
$cshow :: PositiveInterval -> String
showsPrec :: Int -> PositiveInterval -> ShowS
$cshowsPrec :: Int -> PositiveInterval -> ShowS
Show
, PositiveInterval
forall a. a -> a -> Bounded a
maxBound :: PositiveInterval
$cmaxBound :: PositiveInterval
minBound :: PositiveInterval
$cminBound :: PositiveInterval
Bounded
, Bounded PositiveInterval
Rational -> Maybe PositiveInterval
PositiveInterval -> Rational
forall r.
Bounded r
-> (Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
unboundRational :: PositiveInterval -> Rational
$cunboundRational :: PositiveInterval -> Rational
boundRational :: Rational -> Maybe PositiveInterval
$cboundRational :: Rational -> Maybe PositiveInterval
BoundedRational
, Typeable PositiveInterval
PositiveInterval -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
encCBOR :: PositiveInterval -> Encoding
$cencCBOR :: PositiveInterval -> Encoding
EncCBOR
, Typeable PositiveInterval
Proxy PositiveInterval -> Text
forall s. Decoder s PositiveInterval
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy PositiveInterval -> Decoder s ()
label :: Proxy PositiveInterval -> Text
$clabel :: Proxy PositiveInterval -> Text
dropCBOR :: forall s. Proxy PositiveInterval -> Decoder s ()
$cdropCBOR :: forall s. Proxy PositiveInterval -> Decoder s ()
decCBOR :: forall s. Decoder s PositiveInterval
$cdecCBOR :: forall s. Decoder s PositiveInterval
DecCBOR
, [PositiveInterval] -> Encoding
[PositiveInterval] -> Value
PositiveInterval -> Bool
PositiveInterval -> Encoding
PositiveInterval -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: PositiveInterval -> Bool
$comitField :: PositiveInterval -> Bool
toEncodingList :: [PositiveInterval] -> Encoding
$ctoEncodingList :: [PositiveInterval] -> Encoding
toJSONList :: [PositiveInterval] -> Value
$ctoJSONList :: [PositiveInterval] -> Value
toEncoding :: PositiveInterval -> Encoding
$ctoEncoding :: PositiveInterval -> Encoding
toJSON :: PositiveInterval -> Value
$ctoJSON :: PositiveInterval -> Value
ToJSON
, Maybe PositiveInterval
Value -> Parser [PositiveInterval]
Value -> Parser PositiveInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe PositiveInterval
$comittedField :: Maybe PositiveInterval
parseJSONList :: Value -> Parser [PositiveInterval]
$cparseJSONList :: Value -> Parser [PositiveInterval]
parseJSON :: Value -> Parser PositiveInterval
$cparseJSON :: Value -> Parser PositiveInterval
FromJSON
, Context -> PositiveInterval -> IO (Maybe ThunkInfo)
Proxy PositiveInterval -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy PositiveInterval -> String
$cshowTypeOf :: Proxy PositiveInterval -> String
wNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
NoThunks
, PositiveInterval -> ()
forall a. (a -> ()) -> NFData a
rnf :: PositiveInterval -> ()
$crnf :: PositiveInterval -> ()
NFData
)
instance Bounded (BoundedRatio PositiveInterval Word64) where
minBound :: BoundedRatio PositiveInterval Word64
minBound = forall b. BoundedRatio b Word64
positiveIntervalEpsilon
maxBound :: BoundedRatio PositiveInterval Word64
maxBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (forall a. Bounded a => a
maxBound forall a. Integral a => a -> a -> Ratio a
% Word64
1)
positiveIntervalEpsilon :: BoundedRatio b Word64
positiveIntervalEpsilon :: forall b. BoundedRatio b Word64
positiveIntervalEpsilon = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
1 forall a. Integral a => a -> a -> Ratio a
% Word64
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
maxDecimalsWord64 :: Int))
newtype PositiveUnitInterval
= PositiveUnitInterval (BoundedRatio PositiveUnitInterval Word64)
deriving (Eq PositiveUnitInterval
PositiveUnitInterval -> PositiveUnitInterval -> Bool
PositiveUnitInterval -> PositiveUnitInterval -> Ordering
PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
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 :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
$cmin :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
max :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
$cmax :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
>= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c>= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
> :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c> :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
<= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c<= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
< :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c< :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
compare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
$ccompare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
Ord, PositiveUnitInterval -> PositiveUnitInterval -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
Eq, forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval
forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval
$cfrom :: forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x
Generic)
deriving newtype
( Int -> PositiveUnitInterval -> ShowS
[PositiveUnitInterval] -> ShowS
PositiveUnitInterval -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositiveUnitInterval] -> ShowS
$cshowList :: [PositiveUnitInterval] -> ShowS
show :: PositiveUnitInterval -> String
$cshow :: PositiveUnitInterval -> String
showsPrec :: Int -> PositiveUnitInterval -> ShowS
$cshowsPrec :: Int -> PositiveUnitInterval -> ShowS
Show
, PositiveUnitInterval
forall a. a -> a -> Bounded a
maxBound :: PositiveUnitInterval
$cmaxBound :: PositiveUnitInterval
minBound :: PositiveUnitInterval
$cminBound :: PositiveUnitInterval
Bounded
, Bounded PositiveUnitInterval
Rational -> Maybe PositiveUnitInterval
PositiveUnitInterval -> Rational
forall r.
Bounded r
-> (Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
unboundRational :: PositiveUnitInterval -> Rational
$cunboundRational :: PositiveUnitInterval -> Rational
boundRational :: Rational -> Maybe PositiveUnitInterval
$cboundRational :: Rational -> Maybe PositiveUnitInterval
BoundedRational
, Typeable PositiveUnitInterval
PositiveUnitInterval -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
encCBOR :: PositiveUnitInterval -> Encoding
$cencCBOR :: PositiveUnitInterval -> Encoding
EncCBOR
, Typeable PositiveUnitInterval
Proxy PositiveUnitInterval -> Text
forall s. Decoder s PositiveUnitInterval
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy PositiveUnitInterval -> Decoder s ()
label :: Proxy PositiveUnitInterval -> Text
$clabel :: Proxy PositiveUnitInterval -> Text
dropCBOR :: forall s. Proxy PositiveUnitInterval -> Decoder s ()
$cdropCBOR :: forall s. Proxy PositiveUnitInterval -> Decoder s ()
decCBOR :: forall s. Decoder s PositiveUnitInterval
$cdecCBOR :: forall s. Decoder s PositiveUnitInterval
DecCBOR
, [PositiveUnitInterval] -> Encoding
[PositiveUnitInterval] -> Value
PositiveUnitInterval -> Bool
PositiveUnitInterval -> Encoding
PositiveUnitInterval -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: PositiveUnitInterval -> Bool
$comitField :: PositiveUnitInterval -> Bool
toEncodingList :: [PositiveUnitInterval] -> Encoding
$ctoEncodingList :: [PositiveUnitInterval] -> Encoding
toJSONList :: [PositiveUnitInterval] -> Value
$ctoJSONList :: [PositiveUnitInterval] -> Value
toEncoding :: PositiveUnitInterval -> Encoding
$ctoEncoding :: PositiveUnitInterval -> Encoding
toJSON :: PositiveUnitInterval -> Value
$ctoJSON :: PositiveUnitInterval -> Value
ToJSON
, Maybe PositiveUnitInterval
Value -> Parser [PositiveUnitInterval]
Value -> Parser PositiveUnitInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe PositiveUnitInterval
$comittedField :: Maybe PositiveUnitInterval
parseJSONList :: Value -> Parser [PositiveUnitInterval]
$cparseJSONList :: Value -> Parser [PositiveUnitInterval]
parseJSON :: Value -> Parser PositiveUnitInterval
$cparseJSON :: Value -> Parser PositiveUnitInterval
FromJSON
, Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
Proxy PositiveUnitInterval -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy PositiveUnitInterval -> String
$cshowTypeOf :: Proxy PositiveUnitInterval -> String
wNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
NoThunks
, PositiveUnitInterval -> ()
forall a. (a -> ()) -> NFData a
rnf :: PositiveUnitInterval -> ()
$crnf :: PositiveUnitInterval -> ()
NFData
)
instance Bounded (BoundedRatio PositiveUnitInterval Word64) where
minBound :: BoundedRatio PositiveUnitInterval Word64
minBound = forall b. BoundedRatio b Word64
positiveIntervalEpsilon
maxBound :: BoundedRatio PositiveUnitInterval Word64
maxBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
1 forall a. Integral a => a -> a -> Ratio a
% Word64
1)
newtype UnitInterval
= UnitInterval (BoundedRatio UnitInterval Word64)
deriving (Eq UnitInterval
UnitInterval -> UnitInterval -> Bool
UnitInterval -> UnitInterval -> Ordering
UnitInterval -> UnitInterval -> UnitInterval
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 :: UnitInterval -> UnitInterval -> UnitInterval
$cmin :: UnitInterval -> UnitInterval -> UnitInterval
max :: UnitInterval -> UnitInterval -> UnitInterval
$cmax :: UnitInterval -> UnitInterval -> UnitInterval
>= :: UnitInterval -> UnitInterval -> Bool
$c>= :: UnitInterval -> UnitInterval -> Bool
> :: UnitInterval -> UnitInterval -> Bool
$c> :: UnitInterval -> UnitInterval -> Bool
<= :: UnitInterval -> UnitInterval -> Bool
$c<= :: UnitInterval -> UnitInterval -> Bool
< :: UnitInterval -> UnitInterval -> Bool
$c< :: UnitInterval -> UnitInterval -> Bool
compare :: UnitInterval -> UnitInterval -> Ordering
$ccompare :: UnitInterval -> UnitInterval -> Ordering
Ord, UnitInterval -> UnitInterval -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnitInterval -> UnitInterval -> Bool
$c/= :: UnitInterval -> UnitInterval -> Bool
== :: UnitInterval -> UnitInterval -> Bool
$c== :: UnitInterval -> UnitInterval -> Bool
Eq, forall x. Rep UnitInterval x -> UnitInterval
forall x. UnitInterval -> Rep UnitInterval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnitInterval x -> UnitInterval
$cfrom :: forall x. UnitInterval -> Rep UnitInterval x
Generic)
deriving newtype
( Int -> UnitInterval -> ShowS
[UnitInterval] -> ShowS
UnitInterval -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnitInterval] -> ShowS
$cshowList :: [UnitInterval] -> ShowS
show :: UnitInterval -> String
$cshow :: UnitInterval -> String
showsPrec :: Int -> UnitInterval -> ShowS
$cshowsPrec :: Int -> UnitInterval -> ShowS
Show
, UnitInterval
forall a. a -> a -> Bounded a
maxBound :: UnitInterval
$cmaxBound :: UnitInterval
minBound :: UnitInterval
$cminBound :: UnitInterval
Bounded
, Bounded UnitInterval
Rational -> Maybe UnitInterval
UnitInterval -> Rational
forall r.
Bounded r
-> (Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
unboundRational :: UnitInterval -> Rational
$cunboundRational :: UnitInterval -> Rational
boundRational :: Rational -> Maybe UnitInterval
$cboundRational :: Rational -> Maybe UnitInterval
BoundedRational
, Typeable UnitInterval
UnitInterval -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
encCBOR :: UnitInterval -> Encoding
$cencCBOR :: UnitInterval -> Encoding
EncCBOR
, Typeable UnitInterval
Proxy UnitInterval -> Text
forall s. Decoder s UnitInterval
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy UnitInterval -> Decoder s ()
label :: Proxy UnitInterval -> Text
$clabel :: Proxy UnitInterval -> Text
dropCBOR :: forall s. Proxy UnitInterval -> Decoder s ()
$cdropCBOR :: forall s. Proxy UnitInterval -> Decoder s ()
decCBOR :: forall s. Decoder s UnitInterval
$cdecCBOR :: forall s. Decoder s UnitInterval
DecCBOR
, [UnitInterval] -> Encoding
[UnitInterval] -> Value
UnitInterval -> Bool
UnitInterval -> Encoding
UnitInterval -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: UnitInterval -> Bool
$comitField :: UnitInterval -> Bool
toEncodingList :: [UnitInterval] -> Encoding
$ctoEncodingList :: [UnitInterval] -> Encoding
toJSONList :: [UnitInterval] -> Value
$ctoJSONList :: [UnitInterval] -> Value
toEncoding :: UnitInterval -> Encoding
$ctoEncoding :: UnitInterval -> Encoding
toJSON :: UnitInterval -> Value
$ctoJSON :: UnitInterval -> Value
ToJSON
, Maybe UnitInterval
Value -> Parser [UnitInterval]
Value -> Parser UnitInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe UnitInterval
$comittedField :: Maybe UnitInterval
parseJSONList :: Value -> Parser [UnitInterval]
$cparseJSONList :: Value -> Parser [UnitInterval]
parseJSON :: Value -> Parser UnitInterval
$cparseJSON :: Value -> Parser UnitInterval
FromJSON
, Context -> UnitInterval -> IO (Maybe ThunkInfo)
Proxy UnitInterval -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy UnitInterval -> String
$cshowTypeOf :: Proxy UnitInterval -> String
wNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
NoThunks
, UnitInterval -> ()
forall a. (a -> ()) -> NFData a
rnf :: UnitInterval -> ()
$crnf :: UnitInterval -> ()
NFData
)
instance Integral a => Bounded (BoundedRatio UnitInterval a) where
minBound :: BoundedRatio UnitInterval a
minBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (a
0 forall a. Integral a => a -> a -> Ratio a
% a
1)
maxBound :: BoundedRatio UnitInterval a
maxBound = forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (a
1 forall a. Integral a => a -> a -> Ratio a
% a
1)
instance Default UnitInterval where
def :: UnitInterval
def = forall a. Bounded a => a
minBound
data Nonce
= Nonce !(Hash Blake2b_256 Nonce)
|
NeutralNonce
deriving (Nonce -> Nonce -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Nonce -> Nonce -> Bool
$c/= :: Nonce -> Nonce -> Bool
== :: Nonce -> Nonce -> Bool
$c== :: Nonce -> Nonce -> Bool
Eq, forall x. Rep Nonce x -> Nonce
forall x. Nonce -> Rep Nonce x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Nonce x -> Nonce
$cfrom :: forall x. Nonce -> Rep Nonce x
Generic, Eq Nonce
Nonce -> Nonce -> Bool
Nonce -> Nonce -> Ordering
Nonce -> Nonce -> Nonce
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 :: Nonce -> Nonce -> Nonce
$cmin :: Nonce -> Nonce -> Nonce
max :: Nonce -> Nonce -> Nonce
$cmax :: Nonce -> Nonce -> Nonce
>= :: Nonce -> Nonce -> Bool
$c>= :: Nonce -> Nonce -> Bool
> :: Nonce -> Nonce -> Bool
$c> :: Nonce -> Nonce -> Bool
<= :: Nonce -> Nonce -> Bool
$c<= :: Nonce -> Nonce -> Bool
< :: Nonce -> Nonce -> Bool
$c< :: Nonce -> Nonce -> Bool
compare :: Nonce -> Nonce -> Ordering
$ccompare :: Nonce -> Nonce -> Ordering
Ord, Int -> Nonce -> ShowS
[Nonce] -> ShowS
Nonce -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Nonce] -> ShowS
$cshowList :: [Nonce] -> ShowS
show :: Nonce -> String
$cshow :: Nonce -> String
showsPrec :: Int -> Nonce -> ShowS
$cshowsPrec :: Int -> Nonce -> ShowS
Show, Nonce -> ()
forall a. (a -> ()) -> NFData a
rnf :: Nonce -> ()
$crnf :: Nonce -> ()
NFData)
instance NoThunks Nonce
instance EncCBOR Nonce
instance DecCBOR Nonce
instance ToCBOR Nonce where
toCBOR :: Nonce -> Encoding
toCBOR Nonce
NeutralNonce = Word -> Encoding
encodeListLen Word
1 forall a. Semigroup a => a -> a -> a
<> forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
0 :: Word8)
toCBOR (Nonce Hash Blake2b_256 Nonce
n) = Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
1 :: Word8) forall a. Semigroup a => a -> a -> a
<> forall a. ToCBOR a => a -> Encoding
toCBOR Hash Blake2b_256 Nonce
n
instance FromCBOR Nonce where
fromCBOR :: forall s. Decoder s Nonce
fromCBOR = forall s a. Text -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum Text
"Nonce" forall a b. (a -> b) -> a -> b
$
\case
Word
0 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
1, Nonce
NeutralNonce)
Word
1 -> do
Hash Blake2b_256 Nonce
x <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
2, Hash Blake2b_256 Nonce -> Nonce
Nonce Hash Blake2b_256 Nonce
x)
Word
k -> forall (m :: * -> *) a. MonadFail m => Word -> m a
invalidKey Word
k
instance ToJSON Nonce where
toJSON :: Nonce -> Value
toJSON Nonce
NeutralNonce = Value
Null
toJSON (Nonce Hash Blake2b_256 Nonce
n) = forall a. ToJSON a => a -> Value
toJSON Hash Blake2b_256 Nonce
n
instance FromJSON Nonce where
parseJSON :: Value -> Parser Nonce
parseJSON Value
Null = forall (m :: * -> *) a. Monad m => a -> m a
return Nonce
NeutralNonce
parseJSON Value
x = Hash Blake2b_256 Nonce -> Nonce
Nonce forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
x
(⭒) :: Nonce -> Nonce -> Nonce
Nonce Hash Blake2b_256 Nonce
a ⭒ :: Nonce -> Nonce -> Nonce
⭒ Nonce Hash Blake2b_256 Nonce
b =
Hash Blake2b_256 Nonce -> Nonce
Nonce forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a b. Hash h a -> Hash h b
castHash forall a b. (a -> b) -> a -> b
$
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith forall a. a -> a
id (forall h a. Hash h a -> ByteString
hashToBytes Hash Blake2b_256 Nonce
a forall a. Semigroup a => a -> a -> a
<> forall h a. Hash h a -> ByteString
hashToBytes Hash Blake2b_256 Nonce
b)
Nonce
x ⭒ Nonce
NeutralNonce = Nonce
x
Nonce
NeutralNonce ⭒ Nonce
x = Nonce
x
mkNonceFromOutputVRF :: VRF.OutputVRF v -> Nonce
mkNonceFromOutputVRF :: forall v. OutputVRF v -> Nonce
mkNonceFromOutputVRF =
Hash Blake2b_256 Nonce -> Nonce
Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall h a b. Hash h a -> Hash h b
castHash :: Hash Blake2b_256 (VRF.OutputVRF v) -> Hash Blake2b_256 Nonce)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith forall v. OutputVRF v -> ByteString
VRF.getOutputVRFBytes
mkNonceFromNumber :: Word64 -> Nonce
mkNonceFromNumber :: Word64 -> Nonce
mkNonceFromNumber =
Hash Blake2b_256 Nonce -> Nonce
Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall h a b. Hash h a -> Hash h b
castHash :: Hash Blake2b_256 Word64 -> Hash Blake2b_256 Nonce)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith (ByteString -> ByteString
BSL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Put
B.putWord64be)
newtype Seed = Seed (Hash Blake2b_256 Seed)
deriving (Seed -> Seed -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seed -> Seed -> Bool
$c/= :: Seed -> Seed -> Bool
== :: Seed -> Seed -> Bool
$c== :: Seed -> Seed -> Bool
Eq, Eq Seed
Seed -> Seed -> Bool
Seed -> Seed -> Ordering
Seed -> Seed -> Seed
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 :: Seed -> Seed -> Seed
$cmin :: Seed -> Seed -> Seed
max :: Seed -> Seed -> Seed
$cmax :: Seed -> Seed -> Seed
>= :: Seed -> Seed -> Bool
$c>= :: Seed -> Seed -> Bool
> :: Seed -> Seed -> Bool
$c> :: Seed -> Seed -> Bool
<= :: Seed -> Seed -> Bool
$c<= :: Seed -> Seed -> Bool
< :: Seed -> Seed -> Bool
$c< :: Seed -> Seed -> Bool
compare :: Seed -> Seed -> Ordering
$ccompare :: Seed -> Seed -> Ordering
Ord, Int -> Seed -> ShowS
[Seed] -> ShowS
Seed -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seed] -> ShowS
$cshowList :: [Seed] -> ShowS
show :: Seed -> String
$cshow :: Seed -> String
showsPrec :: Int -> Seed -> ShowS
$cshowsPrec :: Int -> Seed -> ShowS
Show, forall x. Rep Seed x -> Seed
forall x. Seed -> Rep Seed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Seed x -> Seed
$cfrom :: forall x. Seed -> Rep Seed x
Generic)
deriving newtype (Context -> Seed -> IO (Maybe ThunkInfo)
Proxy Seed -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Seed -> String
$cshowTypeOf :: Proxy Seed -> String
wNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
noThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
NoThunks, Typeable Seed
Seed -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
encCBOR :: Seed -> Encoding
$cencCBOR :: Seed -> Encoding
EncCBOR)
instance SignableRepresentation Seed where
getSignableRepresentation :: Seed -> ByteString
getSignableRepresentation (Seed Hash Blake2b_256 Seed
x) = forall h a. Hash h a -> ByteString
hashToBytes Hash Blake2b_256 Seed
x
(==>) :: Bool -> Bool -> Bool
Bool
a ==> :: Bool -> Bool -> Bool
==> Bool
b = Bool -> Bool
not Bool
a Bool -> Bool -> Bool
|| Bool
b
infix 1 ==>
textSizeN :: MonadFail m => Int -> Text -> m Text
textSizeN :: forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n Text
t =
let len :: Int
len = ByteString -> Int
BS.length (Text -> ByteString
encodeUtf8 Text
t)
in if Int
len forall a. Ord a => a -> a -> Bool
<= Int
n
then forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
else
forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$
String
"Text exceeds "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" bytes:"
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
t
forall a. [a] -> [a] -> [a]
++ String
"\n Got "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
len
forall a. [a] -> [a] -> [a]
++ String
" bytes instead.\n"
textDecCBOR :: Int -> Decoder s Text
textDecCBOR :: forall s. Int -> Decoder s Text
textDecCBOR Int
n = forall a s. DecCBOR a => Decoder s a
decCBOR forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n
textToUrl :: MonadFail m => Int -> Text -> m Url
textToUrl :: forall (m :: * -> *). MonadFail m => Int -> Text -> m Url
textToUrl Int
n Text
t = Text -> Url
Url forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n Text
t
textToDns :: MonadFail m => Int -> Text -> m DnsName
textToDns :: forall (m :: * -> *). MonadFail m => Int -> Text -> m DnsName
textToDns Int
n Text
t = Text -> DnsName
DnsName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n Text
t
newtype Url = Url {Url -> Text
urlToText :: Text}
deriving (Url -> Url -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Url -> Url -> Bool
$c/= :: Url -> Url -> Bool
== :: Url -> Url -> Bool
$c== :: Url -> Url -> Bool
Eq, Eq Url
Url -> Url -> Bool
Url -> Url -> Ordering
Url -> Url -> Url
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 :: Url -> Url -> Url
$cmin :: Url -> Url -> Url
max :: Url -> Url -> Url
$cmax :: Url -> Url -> Url
>= :: Url -> Url -> Bool
$c>= :: Url -> Url -> Bool
> :: Url -> Url -> Bool
$c> :: Url -> Url -> Bool
<= :: Url -> Url -> Bool
$c<= :: Url -> Url -> Bool
< :: Url -> Url -> Bool
$c< :: Url -> Url -> Bool
compare :: Url -> Url -> Ordering
$ccompare :: Url -> Url -> Ordering
Ord, forall x. Rep Url x -> Url
forall x. Url -> Rep Url x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Url x -> Url
$cfrom :: forall x. Url -> Rep Url x
Generic, Int -> Url -> ShowS
[Url] -> ShowS
Url -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Url] -> ShowS
$cshowList :: [Url] -> ShowS
show :: Url -> String
$cshow :: Url -> String
showsPrec :: Int -> Url -> ShowS
$cshowsPrec :: Int -> Url -> ShowS
Show)
deriving newtype (Typeable Url
Url -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size
encCBOR :: Url -> Encoding
$cencCBOR :: Url -> Encoding
EncCBOR, Url -> ()
forall a. (a -> ()) -> NFData a
rnf :: Url -> ()
$crnf :: Url -> ()
NFData, Context -> Url -> IO (Maybe ThunkInfo)
Proxy Url -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Url -> String
$cshowTypeOf :: Proxy Url -> String
wNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
noThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
NoThunks, Maybe Url
Value -> Parser [Url]
Value -> Parser Url
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe Url
$comittedField :: Maybe Url
parseJSONList :: Value -> Parser [Url]
$cparseJSONList :: Value -> Parser [Url]
parseJSON :: Value -> Parser Url
$cparseJSON :: Value -> Parser Url
FromJSON, [Url] -> Encoding
[Url] -> Value
Url -> Bool
Url -> Encoding
Url -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: Url -> Bool
$comitField :: Url -> Bool
toEncodingList :: [Url] -> Encoding
$ctoEncodingList :: [Url] -> Encoding
toJSONList :: [Url] -> Value
$ctoJSONList :: [Url] -> Value
toEncoding :: Url -> Encoding
$ctoEncoding :: Url -> Encoding
toJSON :: Url -> Value
$ctoJSON :: Url -> Value
ToJSON)
instance DecCBOR Url where
decCBOR :: Decoder s Url
decCBOR :: forall s. Decoder s Url
decCBOR =
Text -> Url
Url
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. Version -> Decoder s a -> Decoder s a -> Decoder s a
ifDecoderVersionAtLeast
(forall (v :: Natural).
(KnownNat v, MinVersion <= v, v <= MaxVersion) =>
Version
natVersion @9)
(forall s. Int -> Decoder s Text
textDecCBOR Int
128)
(forall s. Int -> Decoder s Text
textDecCBOR Int
64)
newtype DnsName = DnsName {DnsName -> Text
dnsToText :: Text}
deriving (DnsName -> DnsName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DnsName -> DnsName -> Bool
$c/= :: DnsName -> DnsName -> Bool
== :: DnsName -> DnsName -> Bool
$c== :: DnsName -> DnsName -> Bool
Eq, Eq DnsName
DnsName -> DnsName -> Bool
DnsName -> DnsName -> Ordering
DnsName -> DnsName -> DnsName
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 :: DnsName -> DnsName -> DnsName
$cmin :: DnsName -> DnsName -> DnsName
max :: DnsName -> DnsName -> DnsName
$cmax :: DnsName -> DnsName -> DnsName
>= :: DnsName -> DnsName -> Bool
$c>= :: DnsName -> DnsName -> Bool
> :: DnsName -> DnsName -> Bool
$c> :: DnsName -> DnsName -> Bool
<= :: DnsName -> DnsName -> Bool
$c<= :: DnsName -> DnsName -> Bool
< :: DnsName -> DnsName -> Bool
$c< :: DnsName -> DnsName -> Bool
compare :: DnsName -> DnsName -> Ordering
$ccompare :: DnsName -> DnsName -> Ordering
Ord, forall x. Rep DnsName x -> DnsName
forall x. DnsName -> Rep DnsName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DnsName x -> DnsName
$cfrom :: forall x. DnsName -> Rep DnsName x
Generic, Int -> DnsName -> ShowS
[DnsName] -> ShowS
DnsName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DnsName] -> ShowS
$cshowList :: [DnsName] -> ShowS
show :: DnsName -> String
$cshow :: DnsName -> String
showsPrec :: Int -> DnsName -> ShowS
$cshowsPrec :: Int -> DnsName -> ShowS
Show)
deriving newtype (Typeable DnsName
DnsName -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
encCBOR :: DnsName -> Encoding
$cencCBOR :: DnsName -> Encoding
EncCBOR, Context -> DnsName -> IO (Maybe ThunkInfo)
Proxy DnsName -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy DnsName -> String
$cshowTypeOf :: Proxy DnsName -> String
wNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
noThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
NoThunks, DnsName -> ()
forall a. (a -> ()) -> NFData a
rnf :: DnsName -> ()
$crnf :: DnsName -> ()
NFData, Maybe DnsName
Value -> Parser [DnsName]
Value -> Parser DnsName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe DnsName
$comittedField :: Maybe DnsName
parseJSONList :: Value -> Parser [DnsName]
$cparseJSONList :: Value -> Parser [DnsName]
parseJSON :: Value -> Parser DnsName
$cparseJSON :: Value -> Parser DnsName
FromJSON, [DnsName] -> Encoding
[DnsName] -> Value
DnsName -> Bool
DnsName -> Encoding
DnsName -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: DnsName -> Bool
$comitField :: DnsName -> Bool
toEncodingList :: [DnsName] -> Encoding
$ctoEncodingList :: [DnsName] -> Encoding
toJSONList :: [DnsName] -> Value
$ctoJSONList :: [DnsName] -> Value
toEncoding :: DnsName -> Encoding
$ctoEncoding :: DnsName -> Encoding
toJSON :: DnsName -> Value
$ctoJSON :: DnsName -> Value
ToJSON)
instance DecCBOR DnsName where
decCBOR :: forall s. Decoder s DnsName
decCBOR =
Text -> DnsName
DnsName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. Version -> Decoder s a -> Decoder s a -> Decoder s a
ifDecoderVersionAtLeast
(forall (v :: Natural).
(KnownNat v, MinVersion <= v, v <= MaxVersion) =>
Version
natVersion @9)
(forall s. Int -> Decoder s Text
textDecCBOR Int
128)
(forall s. Int -> Decoder s Text
textDecCBOR Int
64)
newtype Port = Port {Port -> Word16
portToWord16 :: Word16}
deriving (Port -> Port -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Port -> Port -> Bool
$c/= :: Port -> Port -> Bool
== :: Port -> Port -> Bool
$c== :: Port -> Port -> Bool
Eq, Eq Port
Port -> Port -> Bool
Port -> Port -> Ordering
Port -> Port -> Port
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 :: Port -> Port -> Port
$cmin :: Port -> Port -> Port
max :: Port -> Port -> Port
$cmax :: Port -> Port -> Port
>= :: Port -> Port -> Bool
$c>= :: Port -> Port -> Bool
> :: Port -> Port -> Bool
$c> :: Port -> Port -> Bool
<= :: Port -> Port -> Bool
$c<= :: Port -> Port -> Bool
< :: Port -> Port -> Bool
$c< :: Port -> Port -> Bool
compare :: Port -> Port -> Ordering
$ccompare :: Port -> Port -> Ordering
Ord, forall x. Rep Port x -> Port
forall x. Port -> Rep Port x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Port x -> Port
$cfrom :: forall x. Port -> Rep Port x
Generic, Int -> Port -> ShowS
[Port] -> ShowS
Port -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Port] -> ShowS
$cshowList :: [Port] -> ShowS
show :: Port -> String
$cshow :: Port -> String
showsPrec :: Int -> Port -> ShowS
$cshowsPrec :: Int -> Port -> ShowS
Show)
deriving newtype (Integer -> Port
Port -> Port
Port -> Port -> Port
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Port
$cfromInteger :: Integer -> Port
signum :: Port -> Port
$csignum :: Port -> Port
abs :: Port -> Port
$cabs :: Port -> Port
negate :: Port -> Port
$cnegate :: Port -> Port
* :: Port -> Port -> Port
$c* :: Port -> Port -> Port
- :: Port -> Port -> Port
$c- :: Port -> Port -> Port
+ :: Port -> Port -> Port
$c+ :: Port -> Port -> Port
Num, Typeable Port
Proxy Port -> Text
forall s. Decoder s Port
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy Port -> Decoder s ()
label :: Proxy Port -> Text
$clabel :: Proxy Port -> Text
dropCBOR :: forall s. Proxy Port -> Decoder s ()
$cdropCBOR :: forall s. Proxy Port -> Decoder s ()
decCBOR :: forall s. Decoder s Port
$cdecCBOR :: forall s. Decoder s Port
DecCBOR, Typeable Port
Port -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size
encCBOR :: Port -> Encoding
$cencCBOR :: Port -> Encoding
EncCBOR, Port -> ()
forall a. (a -> ()) -> NFData a
rnf :: Port -> ()
$crnf :: Port -> ()
NFData, Context -> Port -> IO (Maybe ThunkInfo)
Proxy Port -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Port -> String
$cshowTypeOf :: Proxy Port -> String
wNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
noThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
NoThunks, [Port] -> Encoding
[Port] -> Value
Port -> Bool
Port -> Encoding
Port -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: Port -> Bool
$comitField :: Port -> Bool
toEncodingList :: [Port] -> Encoding
$ctoEncodingList :: [Port] -> Encoding
toJSONList :: [Port] -> Value
$ctoJSONList :: [Port] -> Value
toEncoding :: Port -> Encoding
$ctoEncoding :: Port -> Encoding
toJSON :: Port -> Value
$ctoJSON :: Port -> Value
ToJSON, Maybe Port
Value -> Parser [Port]
Value -> Parser Port
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe Port
$comittedField :: Maybe Port
parseJSONList :: Value -> Parser [Port]
$cparseJSONList :: Value -> Parser [Port]
parseJSON :: Value -> Parser Port
$cparseJSON :: Value -> Parser Port
FromJSON)
data ActiveSlotCoeff = ActiveSlotCoeff
{ ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal :: !PositiveUnitInterval
, ActiveSlotCoeff -> Integer
unActiveSlotLog :: !Integer
}
deriving (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
Eq, Eq ActiveSlotCoeff
ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
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 :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
$cmin :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
max :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
$cmax :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
>= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c>= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
> :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c> :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
<= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c<= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
< :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c< :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
compare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
$ccompare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
Ord, Int -> ActiveSlotCoeff -> ShowS
[ActiveSlotCoeff] -> ShowS
ActiveSlotCoeff -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActiveSlotCoeff] -> ShowS
$cshowList :: [ActiveSlotCoeff] -> ShowS
show :: ActiveSlotCoeff -> String
$cshow :: ActiveSlotCoeff -> String
showsPrec :: Int -> ActiveSlotCoeff -> ShowS
$cshowsPrec :: Int -> ActiveSlotCoeff -> ShowS
Show, forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff
forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff
$cfrom :: forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x
Generic)
instance NoThunks ActiveSlotCoeff
instance NFData ActiveSlotCoeff
instance DecCBOR ActiveSlotCoeff where
decCBOR :: forall s. Decoder s ActiveSlotCoeff
decCBOR = PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
instance EncCBOR ActiveSlotCoeff where
encCBOR :: ActiveSlotCoeff -> Encoding
encCBOR
ActiveSlotCoeff
{ unActiveSlotVal :: ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal = PositiveUnitInterval
slotVal
, unActiveSlotLog :: ActiveSlotCoeff -> Integer
unActiveSlotLog = Integer
_logVal
} =
forall a. EncCBOR a => a -> Encoding
encCBOR PositiveUnitInterval
slotVal
mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff PositiveUnitInterval
v =
ActiveSlotCoeff
{ unActiveSlotVal :: PositiveUnitInterval
unActiveSlotVal = PositiveUnitInterval
v
, unActiveSlotLog :: Integer
unActiveSlotLog =
if PositiveUnitInterval
v forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
maxBound
then
Integer
0
else
forall a b. (RealFrac a, Integral b) => a -> b
floor
(FixedPoint
fpPrecision forall a. Num a => a -> a -> a
* forall a. (RealFrac a, Enum a, Show a) => a -> a
ln' ((FixedPoint
1 :: FixedPoint) forall a. Num a => a -> a -> a
- forall a. Fractional a => Rational -> a
fromRational (forall r. BoundedRational r => r -> Rational
unboundRational PositiveUnitInterval
v)))
}
activeSlotVal :: ActiveSlotCoeff -> PositiveUnitInterval
activeSlotVal :: ActiveSlotCoeff -> PositiveUnitInterval
activeSlotVal = ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal
activeSlotLog :: ActiveSlotCoeff -> FixedPoint
activeSlotLog :: ActiveSlotCoeff -> FixedPoint
activeSlotLog ActiveSlotCoeff
f = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ActiveSlotCoeff -> Integer
unActiveSlotLog ActiveSlotCoeff
f) forall a. Fractional a => a -> a -> a
/ FixedPoint
fpPrecision
data Globals = Globals
{ Globals -> EpochInfo (Either Text)
epochInfo :: !(EpochInfo (Either Text))
, Globals -> Word64
slotsPerKESPeriod :: !Word64
, Globals -> Word64
stabilityWindow :: !Word64
, Globals -> Word64
randomnessStabilisationWindow :: !Word64
, Globals -> Word64
securityParameter :: !Word64
, Globals -> Word64
maxKESEvo :: !Word64
, Globals -> Word64
quorum :: !Word64
, Globals -> Word64
maxLovelaceSupply :: !Word64
, Globals -> ActiveSlotCoeff
activeSlotCoeff :: !ActiveSlotCoeff
, Globals -> Network
networkId :: !Network
, Globals -> SystemStart
systemStart :: !SystemStart
}
deriving (Int -> Globals -> ShowS
[Globals] -> ShowS
Globals -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Globals] -> ShowS
$cshowList :: [Globals] -> ShowS
show :: Globals -> String
$cshow :: Globals -> String
showsPrec :: Int -> Globals -> ShowS
$cshowsPrec :: Int -> Globals -> ShowS
Show, forall x. Rep Globals x -> Globals
forall x. Globals -> Rep Globals x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Globals x -> Globals
$cfrom :: forall x. Globals -> Rep Globals x
Generic)
instance NoThunks Globals
instance NFData Globals where
rnf :: Globals -> ()
rnf (Globals {}) = ()
type ShelleyBase = ReaderT Globals Identity
epochInfoPure :: Globals -> EpochInfo Identity
epochInfoPure :: Globals -> EpochInfo Identity
epochInfoPure = forall (m :: * -> *) (n :: * -> *).
(forall a. m a -> n a) -> EpochInfo m -> EpochInfo n
hoistEpochInfo (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a e. Exception e => e -> a
throw forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> EpochErr
EpochErr) forall (f :: * -> *) a. Applicative f => a -> f a
pure) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Globals -> EpochInfo (Either Text)
epochInfo
newtype EpochErr = EpochErr Text
deriving instance Show EpochErr
instance Exception EpochErr
data Relation
=
RelEQ
|
RelLT
|
RelGT
|
RelLTEQ
|
RelGTEQ
|
RelSubset
deriving (Relation -> Relation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Relation -> Relation -> Bool
$c/= :: Relation -> Relation -> Bool
== :: Relation -> Relation -> Bool
$c== :: Relation -> Relation -> Bool
Eq, Eq Relation
Relation -> Relation -> Bool
Relation -> Relation -> Ordering
Relation -> Relation -> Relation
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 :: Relation -> Relation -> Relation
$cmin :: Relation -> Relation -> Relation
max :: Relation -> Relation -> Relation
$cmax :: Relation -> Relation -> Relation
>= :: Relation -> Relation -> Bool
$c>= :: Relation -> Relation -> Bool
> :: Relation -> Relation -> Bool
$c> :: Relation -> Relation -> Bool
<= :: Relation -> Relation -> Bool
$c<= :: Relation -> Relation -> Bool
< :: Relation -> Relation -> Bool
$c< :: Relation -> Relation -> Bool
compare :: Relation -> Relation -> Ordering
$ccompare :: Relation -> Relation -> Ordering
Ord, Int -> Relation
Relation -> Int
Relation -> [Relation]
Relation -> Relation
Relation -> Relation -> [Relation]
Relation -> Relation -> Relation -> [Relation]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Relation -> Relation -> Relation -> [Relation]
$cenumFromThenTo :: Relation -> Relation -> Relation -> [Relation]
enumFromTo :: Relation -> Relation -> [Relation]
$cenumFromTo :: Relation -> Relation -> [Relation]
enumFromThen :: Relation -> Relation -> [Relation]
$cenumFromThen :: Relation -> Relation -> [Relation]
enumFrom :: Relation -> [Relation]
$cenumFrom :: Relation -> [Relation]
fromEnum :: Relation -> Int
$cfromEnum :: Relation -> Int
toEnum :: Int -> Relation
$ctoEnum :: Int -> Relation
pred :: Relation -> Relation
$cpred :: Relation -> Relation
succ :: Relation -> Relation
$csucc :: Relation -> Relation
Enum, Relation
forall a. a -> a -> Bounded a
maxBound :: Relation
$cmaxBound :: Relation
minBound :: Relation
$cminBound :: Relation
Bounded, Int -> Relation -> ShowS
[Relation] -> ShowS
Relation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Relation] -> ShowS
$cshowList :: [Relation] -> ShowS
show :: Relation -> String
$cshow :: Relation -> String
showsPrec :: Int -> Relation -> ShowS
$cshowsPrec :: Int -> Relation -> ShowS
Show, forall x. Rep Relation x -> Relation
forall x. Relation -> Rep Relation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Relation x -> Relation
$cfrom :: forall x. Relation -> Rep Relation x
Generic, Relation -> ()
forall a. (a -> ()) -> NFData a
rnf :: Relation -> ()
$crnf :: Relation -> ()
NFData, [Relation] -> Encoding
[Relation] -> Value
Relation -> Bool
Relation -> Encoding
Relation -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: Relation -> Bool
$comitField :: Relation -> Bool
toEncodingList :: [Relation] -> Encoding
$ctoEncodingList :: [Relation] -> Encoding
toJSONList :: [Relation] -> Value
$ctoJSONList :: [Relation] -> Value
toEncoding :: Relation -> Encoding
$ctoEncoding :: Relation -> Encoding
toJSON :: Relation -> Value
$ctoJSON :: Relation -> Value
ToJSON, Maybe Relation
Value -> Parser [Relation]
Value -> Parser Relation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe Relation
$comittedField :: Maybe Relation
parseJSONList :: Value -> Parser [Relation]
$cparseJSONList :: Value -> Parser [Relation]
parseJSON :: Value -> Parser Relation
$cparseJSON :: Value -> Parser Relation
FromJSON, Context -> Relation -> IO (Maybe ThunkInfo)
Proxy Relation -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Relation -> String
$cshowTypeOf :: Proxy Relation -> String
wNoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
noThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
NoThunks, Typeable)
data Mismatch (r :: Relation) a = Mismatch
{ forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied :: !a
, forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected :: !a
}
deriving (Mismatch r a -> Mismatch r a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (r :: Relation) a.
Eq a =>
Mismatch r a -> Mismatch r a -> Bool
/= :: Mismatch r a -> Mismatch r a -> Bool
$c/= :: forall (r :: Relation) a.
Eq a =>
Mismatch r a -> Mismatch r a -> Bool
== :: Mismatch r a -> Mismatch r a -> Bool
$c== :: forall (r :: Relation) a.
Eq a =>
Mismatch r a -> Mismatch r a -> Bool
Eq, Mismatch r a -> Mismatch r a -> Bool
Mismatch r a -> Mismatch r a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {r :: Relation} {a}. Ord a => Eq (Mismatch r a)
forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Bool
forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Ordering
forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Mismatch r a
min :: Mismatch r a -> Mismatch r a -> Mismatch r a
$cmin :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Mismatch r a
max :: Mismatch r a -> Mismatch r a -> Mismatch r a
$cmax :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Mismatch r a
>= :: Mismatch r a -> Mismatch r a -> Bool
$c>= :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Bool
> :: Mismatch r a -> Mismatch r a -> Bool
$c> :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Bool
<= :: Mismatch r a -> Mismatch r a -> Bool
$c<= :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Bool
< :: Mismatch r a -> Mismatch r a -> Bool
$c< :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Bool
compare :: Mismatch r a -> Mismatch r a -> Ordering
$ccompare :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Ordering
Ord, Int -> Mismatch r a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (r :: Relation) a. Show a => Int -> Mismatch r a -> ShowS
forall (r :: Relation) a. Show a => [Mismatch r a] -> ShowS
forall (r :: Relation) a. Show a => Mismatch r a -> String
showList :: [Mismatch r a] -> ShowS
$cshowList :: forall (r :: Relation) a. Show a => [Mismatch r a] -> ShowS
show :: Mismatch r a -> String
$cshow :: forall (r :: Relation) a. Show a => Mismatch r a -> String
showsPrec :: Int -> Mismatch r a -> ShowS
$cshowsPrec :: forall (r :: Relation) a. Show a => Int -> Mismatch r a -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (r :: Relation) a x. Rep (Mismatch r a) x -> Mismatch r a
forall (r :: Relation) a x. Mismatch r a -> Rep (Mismatch r a) x
$cto :: forall (r :: Relation) a x. Rep (Mismatch r a) x -> Mismatch r a
$cfrom :: forall (r :: Relation) a x. Mismatch r a -> Rep (Mismatch r a) x
Generic, forall a. (a -> ()) -> NFData a
forall (r :: Relation) a. NFData a => Mismatch r a -> ()
rnf :: Mismatch r a -> ()
$crnf :: forall (r :: Relation) a. NFData a => Mismatch r a -> ()
NFData, forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Encoding
forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Value
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Bool
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Encoding
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Value
omitField :: Mismatch r a -> Bool
$comitField :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Bool
toEncodingList :: [Mismatch r a] -> Encoding
$ctoEncodingList :: forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Encoding
toJSONList :: [Mismatch r a] -> Value
$ctoJSONList :: forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Value
toEncoding :: Mismatch r a -> Encoding
$ctoEncoding :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Encoding
toJSON :: Mismatch r a -> Value
$ctoJSON :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Value
ToJSON, forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
forall (r :: Relation) a. FromJSON a => Maybe (Mismatch r a)
forall (r :: Relation) a.
FromJSON a =>
Value -> Parser [Mismatch r a]
forall (r :: Relation) a.
FromJSON a =>
Value -> Parser (Mismatch r a)
omittedField :: Maybe (Mismatch r a)
$comittedField :: forall (r :: Relation) a. FromJSON a => Maybe (Mismatch r a)
parseJSONList :: Value -> Parser [Mismatch r a]
$cparseJSONList :: forall (r :: Relation) a.
FromJSON a =>
Value -> Parser [Mismatch r a]
parseJSON :: Value -> Parser (Mismatch r a)
$cparseJSON :: forall (r :: Relation) a.
FromJSON a =>
Value -> Parser (Mismatch r a)
FromJSON, forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (r :: Relation) a.
NoThunks a =>
Context -> Mismatch r a -> IO (Maybe ThunkInfo)
forall (r :: Relation) a.
NoThunks a =>
Proxy (Mismatch r a) -> String
showTypeOf :: Proxy (Mismatch r a) -> String
$cshowTypeOf :: forall (r :: Relation) a.
NoThunks a =>
Proxy (Mismatch r a) -> String
wNoThunks :: Context -> Mismatch r a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (r :: Relation) a.
NoThunks a =>
Context -> Mismatch r a -> IO (Maybe ThunkInfo)
noThunks :: Context -> Mismatch r a -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (r :: Relation) a.
NoThunks a =>
Context -> Mismatch r a -> IO (Maybe ThunkInfo)
NoThunks)
swapMismatch :: Mismatch r a -> (a, a)
swapMismatch :: forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch {a
mismatchSupplied :: a
mismatchSupplied :: forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied, a
mismatchExpected :: a
mismatchExpected :: forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected} = (a
mismatchExpected, a
mismatchSupplied)
unswapMismatch :: (a, a) -> Mismatch r a
unswapMismatch :: forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch (a
mismatchExpected, a
mismatchSupplied) = Mismatch {a
mismatchSupplied :: a
mismatchSupplied :: a
mismatchSupplied, a
mismatchExpected :: a
mismatchExpected :: a
mismatchExpected}
instance (EncCBOR a, Typeable r) => EncCBOR (Mismatch r a) where
encCBOR :: Mismatch r a -> Encoding
encCBOR (Mismatch a
supplied a
expected) =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec forall (r :: Relation) a. a -> a -> Mismatch r a
Mismatch
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To a
supplied
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To a
expected
instance (DecCBOR a, Typeable r) => DecCBOR (Mismatch r a) where
decCBOR :: forall s. Decoder s (Mismatch r a)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall (r :: Relation) a. a -> a -> Mismatch r a
Mismatch
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance (Typeable r, EncCBOR a) => EncCBORGroup (Mismatch r a) where
encCBORGroup :: Mismatch r a -> Encoding
encCBORGroup Mismatch {a
mismatchExpected :: a
mismatchSupplied :: a
mismatchExpected :: forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied :: forall (r :: Relation) a. Mismatch r a -> a
..} = forall a. EncCBOR a => a -> Encoding
encCBOR a
mismatchSupplied forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
mismatchExpected
encodedGroupSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Mismatch r a) -> Size
encodedGroupSizeExpr forall t. EncCBOR t => Proxy t -> Size
size_ Proxy (Mismatch r a)
proxy =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size_ (forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Mismatch r a)
proxy)
forall a. Num a => a -> a -> a
+ forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size_ (forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Mismatch r a)
proxy)
listLen :: Mismatch r a -> Word
listLen Mismatch r a
_ = Word
2
listLenBound :: Proxy (Mismatch r a) -> Word
listLenBound Proxy (Mismatch r a)
_ = Word
2
instance (Typeable r, DecCBOR a) => DecCBORGroup (Mismatch r a) where
decCBORGroup :: forall s. Decoder s (Mismatch r a)
decCBORGroup = do
a
mismatchSupplied <- forall a s. DecCBOR a => Decoder s a
decCBOR
a
mismatchExpected <- forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mismatch {a
mismatchExpected :: a
mismatchSupplied :: a
mismatchExpected :: a
mismatchSupplied :: a
..}
data Network
= Testnet
| Mainnet
deriving (Network -> Network -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Network -> Network -> Bool
$c/= :: Network -> Network -> Bool
== :: Network -> Network -> Bool
$c== :: Network -> Network -> Bool
Eq, Eq Network
Network -> Network -> Bool
Network -> Network -> Ordering
Network -> Network -> Network
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 :: Network -> Network -> Network
$cmin :: Network -> Network -> Network
max :: Network -> Network -> Network
$cmax :: Network -> Network -> Network
>= :: Network -> Network -> Bool
$c>= :: Network -> Network -> Bool
> :: Network -> Network -> Bool
$c> :: Network -> Network -> Bool
<= :: Network -> Network -> Bool
$c<= :: Network -> Network -> Bool
< :: Network -> Network -> Bool
$c< :: Network -> Network -> Bool
compare :: Network -> Network -> Ordering
$ccompare :: Network -> Network -> Ordering
Ord, Int -> Network
Network -> Int
Network -> [Network]
Network -> Network
Network -> Network -> [Network]
Network -> Network -> Network -> [Network]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Network -> Network -> Network -> [Network]
$cenumFromThenTo :: Network -> Network -> Network -> [Network]
enumFromTo :: Network -> Network -> [Network]
$cenumFromTo :: Network -> Network -> [Network]
enumFromThen :: Network -> Network -> [Network]
$cenumFromThen :: Network -> Network -> [Network]
enumFrom :: Network -> [Network]
$cenumFrom :: Network -> [Network]
fromEnum :: Network -> Int
$cfromEnum :: Network -> Int
toEnum :: Int -> Network
$ctoEnum :: Int -> Network
pred :: Network -> Network
$cpred :: Network -> Network
succ :: Network -> Network
$csucc :: Network -> Network
Enum, Network
forall a. a -> a -> Bounded a
maxBound :: Network
$cmaxBound :: Network
minBound :: Network
$cminBound :: Network
Bounded, Int -> Network -> ShowS
[Network] -> ShowS
Network -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Network] -> ShowS
$cshowList :: [Network] -> ShowS
show :: Network -> String
$cshow :: Network -> String
showsPrec :: Int -> Network -> ShowS
$cshowsPrec :: Int -> Network -> ShowS
Show, forall x. Rep Network x -> Network
forall x. Network -> Rep Network x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Network x -> Network
$cfrom :: forall x. Network -> Rep Network x
Generic, Network -> ()
forall a. (a -> ()) -> NFData a
rnf :: Network -> ()
$crnf :: Network -> ()
NFData, [Network] -> Encoding
[Network] -> Value
Network -> Bool
Network -> Encoding
Network -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: Network -> Bool
$comitField :: Network -> Bool
toEncodingList :: [Network] -> Encoding
$ctoEncodingList :: [Network] -> Encoding
toJSONList :: [Network] -> Value
$ctoJSONList :: [Network] -> Value
toEncoding :: Network -> Encoding
$ctoEncoding :: Network -> Encoding
toJSON :: Network -> Value
$ctoJSON :: Network -> Value
ToJSON, Maybe Network
Value -> Parser [Network]
Value -> Parser Network
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe Network
$comittedField :: Maybe Network
parseJSONList :: Value -> Parser [Network]
$cparseJSONList :: Value -> Parser [Network]
parseJSON :: Value -> Parser Network
$cparseJSON :: Value -> Parser Network
FromJSON, Context -> Network -> IO (Maybe ThunkInfo)
Proxy Network -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy Network -> String
$cshowTypeOf :: Proxy Network -> String
wNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
noThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
NoThunks)
networkToWord8 :: Network -> Word8
networkToWord8 :: Network -> Word8
networkToWord8 = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum
word8ToNetwork :: Word8 -> Maybe Network
word8ToNetwork :: Word8 -> Maybe Network
word8ToNetwork Word8
e
| forall a. Enum a => a -> Int
fromEnum Word8
e forall a. Ord a => a -> a -> Bool
> forall a. Enum a => a -> Int
fromEnum (forall a. Bounded a => a
maxBound :: Network) = forall a. Maybe a
Nothing
| forall a. Enum a => a -> Int
fromEnum Word8
e forall a. Ord a => a -> a -> Bool
< forall a. Enum a => a -> Int
fromEnum (forall a. Bounded a => a
minBound :: Network) = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum (forall a. Enum a => a -> Int
fromEnum Word8
e)
instance EncCBOR Network where
encCBOR :: Network -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Word8
networkToWord8
instance DecCBOR Network where
decCBOR :: forall s. Decoder s Network
decCBOR =
Word8 -> Maybe Network
word8ToNetwork forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Network
Nothing -> forall (m :: * -> *) e a. (MonadFail m, Buildable e) => e -> m a
cborError forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"Network" Text
"Unknown network id"
Just Network
n -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Network
n
{-# INLINE decCBOR #-}
newtype BlocksMade c = BlocksMade
{ forall c. BlocksMade c -> Map (KeyHash 'StakePool c) Natural
unBlocksMade :: Map (KeyHash 'StakePool c) Natural
}
deriving (BlocksMade c -> BlocksMade c -> Bool
forall c. BlocksMade c -> BlocksMade c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlocksMade c -> BlocksMade c -> Bool
$c/= :: forall c. BlocksMade c -> BlocksMade c -> Bool
== :: BlocksMade c -> BlocksMade c -> Bool
$c== :: forall c. BlocksMade c -> BlocksMade c -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall c x. Rep (BlocksMade c) x -> BlocksMade c
forall c x. BlocksMade c -> Rep (BlocksMade c) x
$cto :: forall c x. Rep (BlocksMade c) x -> BlocksMade c
$cfrom :: forall c x. BlocksMade c -> Rep (BlocksMade c) x
Generic)
deriving (Int -> BlocksMade c -> ShowS
[BlocksMade c] -> ShowS
BlocksMade c -> String
forall c. Int -> BlocksMade c -> ShowS
forall c. [BlocksMade c] -> ShowS
forall c. BlocksMade c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlocksMade c] -> ShowS
$cshowList :: forall c. [BlocksMade c] -> ShowS
show :: BlocksMade c -> String
$cshow :: forall c. BlocksMade c -> String
showsPrec :: Int -> BlocksMade c -> ShowS
$cshowsPrec :: forall c. Int -> BlocksMade c -> ShowS
Show) via Quiet (BlocksMade c)
deriving newtype (Context -> BlocksMade c -> IO (Maybe ThunkInfo)
Proxy (BlocksMade c) -> String
forall c. Context -> BlocksMade c -> IO (Maybe ThunkInfo)
forall c. Proxy (BlocksMade c) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (BlocksMade c) -> String
$cshowTypeOf :: forall c. Proxy (BlocksMade c) -> String
wNoThunks :: Context -> BlocksMade c -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall c. Context -> BlocksMade c -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlocksMade c -> IO (Maybe ThunkInfo)
$cnoThunks :: forall c. Context -> BlocksMade c -> IO (Maybe ThunkInfo)
NoThunks, BlocksMade c -> ()
forall c. BlocksMade c -> ()
forall a. (a -> ()) -> NFData a
rnf :: BlocksMade c -> ()
$crnf :: forall c. BlocksMade c -> ()
NFData, [BlocksMade c] -> Encoding
[BlocksMade c] -> Value
BlocksMade c -> Bool
BlocksMade c -> Encoding
BlocksMade c -> Value
forall c. Crypto c => [BlocksMade c] -> Encoding
forall c. Crypto c => [BlocksMade c] -> Value
forall c. Crypto c => BlocksMade c -> Bool
forall c. Crypto c => BlocksMade c -> Encoding
forall c. Crypto c => BlocksMade c -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: BlocksMade c -> Bool
$comitField :: forall c. Crypto c => BlocksMade c -> Bool
toEncodingList :: [BlocksMade c] -> Encoding
$ctoEncodingList :: forall c. Crypto c => [BlocksMade c] -> Encoding
toJSONList :: [BlocksMade c] -> Value
$ctoJSONList :: forall c. Crypto c => [BlocksMade c] -> Value
toEncoding :: BlocksMade c -> Encoding
$ctoEncoding :: forall c. Crypto c => BlocksMade c -> Encoding
toJSON :: BlocksMade c -> Value
$ctoJSON :: forall c. Crypto c => BlocksMade c -> Value
ToJSON, Maybe (BlocksMade c)
Value -> Parser [BlocksMade c]
Value -> Parser (BlocksMade c)
forall c. Crypto c => Maybe (BlocksMade c)
forall c. Crypto c => Value -> Parser [BlocksMade c]
forall c. Crypto c => Value -> Parser (BlocksMade c)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe (BlocksMade c)
$comittedField :: forall c. Crypto c => Maybe (BlocksMade c)
parseJSONList :: Value -> Parser [BlocksMade c]
$cparseJSONList :: forall c. Crypto c => Value -> Parser [BlocksMade c]
parseJSON :: Value -> Parser (BlocksMade c)
$cparseJSON :: forall c. Crypto c => Value -> Parser (BlocksMade c)
FromJSON, BlocksMade c -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade c] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade c) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
forall {c}. Crypto c => Typeable (BlocksMade c)
forall c. Crypto c => BlocksMade c -> Encoding
forall c.
Crypto c =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade c] -> Size
forall c.
Crypto c =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade c) -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade c] -> Size
$cencodedListSizeExpr :: forall c.
Crypto c =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade c] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade c) -> Size
$cencodedSizeExpr :: forall c.
Crypto c =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade c) -> Size
encCBOR :: BlocksMade c -> Encoding
$cencCBOR :: forall c. Crypto c => BlocksMade c -> Encoding
EncCBOR, Proxy (BlocksMade c) -> Text
forall s. Decoder s (BlocksMade c)
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy (BlocksMade c) -> Decoder s ()
forall {c}. Crypto c => Typeable (BlocksMade c)
forall c. Crypto c => Proxy (BlocksMade c) -> Text
forall c s. Crypto c => Decoder s (BlocksMade c)
forall c s. Crypto c => Proxy (BlocksMade c) -> Decoder s ()
label :: Proxy (BlocksMade c) -> Text
$clabel :: forall c. Crypto c => Proxy (BlocksMade c) -> Text
dropCBOR :: forall s. Proxy (BlocksMade c) -> Decoder s ()
$cdropCBOR :: forall c s. Crypto c => Proxy (BlocksMade c) -> Decoder s ()
decCBOR :: forall s. Decoder s (BlocksMade c)
$cdecCBOR :: forall c s. Crypto c => Decoder s (BlocksMade c)
DecCBOR)
newtype TxIx = TxIx {TxIx -> Word64
unTxIx :: Word64}
deriving stock (TxIx -> TxIx -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxIx -> TxIx -> Bool
$c/= :: TxIx -> TxIx -> Bool
== :: TxIx -> TxIx -> Bool
$c== :: TxIx -> TxIx -> Bool
Eq, Eq TxIx
TxIx -> TxIx -> Bool
TxIx -> TxIx -> Ordering
TxIx -> TxIx -> TxIx
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 :: TxIx -> TxIx -> TxIx
$cmin :: TxIx -> TxIx -> TxIx
max :: TxIx -> TxIx -> TxIx
$cmax :: TxIx -> TxIx -> TxIx
>= :: TxIx -> TxIx -> Bool
$c>= :: TxIx -> TxIx -> Bool
> :: TxIx -> TxIx -> Bool
$c> :: TxIx -> TxIx -> Bool
<= :: TxIx -> TxIx -> Bool
$c<= :: TxIx -> TxIx -> Bool
< :: TxIx -> TxIx -> Bool
$c< :: TxIx -> TxIx -> Bool
compare :: TxIx -> TxIx -> Ordering
$ccompare :: TxIx -> TxIx -> Ordering
Ord, Int -> TxIx -> ShowS
[TxIx] -> ShowS
TxIx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxIx] -> ShowS
$cshowList :: [TxIx] -> ShowS
show :: TxIx -> String
$cshow :: TxIx -> String
showsPrec :: Int -> TxIx -> ShowS
$cshowsPrec :: Int -> TxIx -> ShowS
Show, forall x. Rep TxIx x -> TxIx
forall x. TxIx -> Rep TxIx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxIx x -> TxIx
$cfrom :: forall x. TxIx -> Rep TxIx x
Generic)
deriving newtype (TxIx -> ()
forall a. (a -> ()) -> NFData a
rnf :: TxIx -> ()
$crnf :: TxIx -> ()
NFData, Int -> TxIx
TxIx -> Int
TxIx -> [TxIx]
TxIx -> TxIx
TxIx -> TxIx -> [TxIx]
TxIx -> TxIx -> TxIx -> [TxIx]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
$cenumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
enumFromTo :: TxIx -> TxIx -> [TxIx]
$cenumFromTo :: TxIx -> TxIx -> [TxIx]
enumFromThen :: TxIx -> TxIx -> [TxIx]
$cenumFromThen :: TxIx -> TxIx -> [TxIx]
enumFrom :: TxIx -> [TxIx]
$cenumFrom :: TxIx -> [TxIx]
fromEnum :: TxIx -> Int
$cfromEnum :: TxIx -> Int
toEnum :: Int -> TxIx
$ctoEnum :: Int -> TxIx
pred :: TxIx -> TxIx
$cpred :: TxIx -> TxIx
succ :: TxIx -> TxIx
$csucc :: TxIx -> TxIx
Enum, TxIx
forall a. a -> a -> Bounded a
maxBound :: TxIx
$cmaxBound :: TxIx
minBound :: TxIx
$cminBound :: TxIx
Bounded, Context -> TxIx -> IO (Maybe ThunkInfo)
Proxy TxIx -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy TxIx -> String
$cshowTypeOf :: Proxy TxIx -> String
wNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
NoThunks, Typeable TxIx
Proxy TxIx -> Text
forall s. Decoder s TxIx
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy TxIx -> Text
$clabel :: Proxy TxIx -> Text
fromCBOR :: forall s. Decoder s TxIx
$cfromCBOR :: forall s. Decoder s TxIx
FromCBOR, Typeable TxIx
TxIx -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
toCBOR :: TxIx -> Encoding
$ctoCBOR :: TxIx -> Encoding
ToCBOR, Typeable TxIx
TxIx -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
encCBOR :: TxIx -> Encoding
$cencCBOR :: TxIx -> Encoding
EncCBOR, [TxIx] -> Encoding
[TxIx] -> Value
TxIx -> Bool
TxIx -> Encoding
TxIx -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: TxIx -> Bool
$comitField :: TxIx -> Bool
toEncodingList :: [TxIx] -> Encoding
$ctoEncodingList :: [TxIx] -> Encoding
toJSONList :: [TxIx] -> Value
$ctoJSONList :: [TxIx] -> Value
toEncoding :: TxIx -> Encoding
$ctoEncoding :: TxIx -> Encoding
toJSON :: TxIx -> Value
$ctoJSON :: TxIx -> Value
ToJSON)
instance DecCBOR TxIx where
decCBOR :: forall s. Decoder s TxIx
decCBOR =
forall s a. Version -> Decoder s a -> Decoder s a -> Decoder s a
ifDecoderVersionAtLeast
(forall (v :: Natural).
(KnownNat v, MinVersion <= v, v <= MaxVersion) =>
Version
natVersion @9)
(Word64 -> TxIx
TxIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word16 @Word64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR)
(Word64 -> TxIx
TxIx forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR)
mkTxIx :: Word16 -> TxIx
mkTxIx :: Word16 -> TxIx
mkTxIx = Word64 -> TxIx
TxIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
txIxToInt :: TxIx -> Int
txIxToInt :: TxIx -> Int
txIxToInt (TxIx Word64
w16) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w16
txIxFromIntegral :: forall a m. (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral :: forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word64 -> TxIx
TxIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i b (m :: * -> *).
(Integral i, Integral b, Bounded b, MonadFail m) =>
i -> m b
integralToBounded @a @Word16 @m
{-# INLINE txIxFromIntegral #-}
mkTxIxPartial :: HasCallStack => Integer -> TxIx
mkTxIxPartial :: HasCallStack => Integer -> TxIx
mkTxIxPartial Integer
i =
forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Value for TxIx is out of a valid range: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
i) forall a b. (a -> b) -> a -> b
$
forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral Integer
i
newtype CertIx = CertIx {CertIx -> Word64
unCertIx :: Word64}
deriving stock (CertIx -> CertIx -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertIx -> CertIx -> Bool
$c/= :: CertIx -> CertIx -> Bool
== :: CertIx -> CertIx -> Bool
$c== :: CertIx -> CertIx -> Bool
Eq, Eq CertIx
CertIx -> CertIx -> Bool
CertIx -> CertIx -> Ordering
CertIx -> CertIx -> CertIx
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 :: CertIx -> CertIx -> CertIx
$cmin :: CertIx -> CertIx -> CertIx
max :: CertIx -> CertIx -> CertIx
$cmax :: CertIx -> CertIx -> CertIx
>= :: CertIx -> CertIx -> Bool
$c>= :: CertIx -> CertIx -> Bool
> :: CertIx -> CertIx -> Bool
$c> :: CertIx -> CertIx -> Bool
<= :: CertIx -> CertIx -> Bool
$c<= :: CertIx -> CertIx -> Bool
< :: CertIx -> CertIx -> Bool
$c< :: CertIx -> CertIx -> Bool
compare :: CertIx -> CertIx -> Ordering
$ccompare :: CertIx -> CertIx -> Ordering
Ord, Int -> CertIx -> ShowS
[CertIx] -> ShowS
CertIx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CertIx] -> ShowS
$cshowList :: [CertIx] -> ShowS
show :: CertIx -> String
$cshow :: CertIx -> String
showsPrec :: Int -> CertIx -> ShowS
$cshowsPrec :: Int -> CertIx -> ShowS
Show)
deriving newtype (CertIx -> ()
forall a. (a -> ()) -> NFData a
rnf :: CertIx -> ()
$crnf :: CertIx -> ()
NFData, Int -> CertIx
CertIx -> Int
CertIx -> [CertIx]
CertIx -> CertIx
CertIx -> CertIx -> [CertIx]
CertIx -> CertIx -> CertIx -> [CertIx]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
$cenumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
enumFromTo :: CertIx -> CertIx -> [CertIx]
$cenumFromTo :: CertIx -> CertIx -> [CertIx]
enumFromThen :: CertIx -> CertIx -> [CertIx]
$cenumFromThen :: CertIx -> CertIx -> [CertIx]
enumFrom :: CertIx -> [CertIx]
$cenumFrom :: CertIx -> [CertIx]
fromEnum :: CertIx -> Int
$cfromEnum :: CertIx -> Int
toEnum :: Int -> CertIx
$ctoEnum :: Int -> CertIx
pred :: CertIx -> CertIx
$cpred :: CertIx -> CertIx
succ :: CertIx -> CertIx
$csucc :: CertIx -> CertIx
Enum, CertIx
forall a. a -> a -> Bounded a
maxBound :: CertIx
$cmaxBound :: CertIx
minBound :: CertIx
$cminBound :: CertIx
Bounded, Context -> CertIx -> IO (Maybe ThunkInfo)
Proxy CertIx -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy CertIx -> String
$cshowTypeOf :: Proxy CertIx -> String
wNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
NoThunks, Typeable CertIx
CertIx -> Encoding
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
encCBOR :: CertIx -> Encoding
$cencCBOR :: CertIx -> Encoding
EncCBOR, Typeable CertIx
CertIx -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
toCBOR :: CertIx -> Encoding
$ctoCBOR :: CertIx -> Encoding
ToCBOR, Typeable CertIx
Proxy CertIx -> Text
forall s. Decoder s CertIx
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy CertIx -> Text
$clabel :: Proxy CertIx -> Text
fromCBOR :: forall s. Decoder s CertIx
$cfromCBOR :: forall s. Decoder s CertIx
FromCBOR, [CertIx] -> Encoding
[CertIx] -> Value
CertIx -> Bool
CertIx -> Encoding
CertIx -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: CertIx -> Bool
$comitField :: CertIx -> Bool
toEncodingList :: [CertIx] -> Encoding
$ctoEncodingList :: [CertIx] -> Encoding
toJSONList :: [CertIx] -> Value
$ctoJSONList :: [CertIx] -> Value
toEncoding :: CertIx -> Encoding
$ctoEncoding :: CertIx -> Encoding
toJSON :: CertIx -> Value
$ctoJSON :: CertIx -> Value
ToJSON)
instance DecCBOR CertIx where
decCBOR :: forall s. Decoder s CertIx
decCBOR =
forall s a. Version -> Decoder s a -> Decoder s a -> Decoder s a
ifDecoderVersionAtLeast
(forall (v :: Natural).
(KnownNat v, MinVersion <= v, v <= MaxVersion) =>
Version
natVersion @9)
(Word64 -> CertIx
CertIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word16 @Word64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR)
(Word64 -> CertIx
CertIx forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR)
mkCertIx :: Word16 -> CertIx
mkCertIx :: Word16 -> CertIx
mkCertIx = Word64 -> CertIx
CertIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
certIxToInt :: CertIx -> Int
certIxToInt :: CertIx -> Int
certIxToInt (CertIx Word64
w16) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w16
certIxFromIntegral :: forall a m. (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral :: forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word64 -> CertIx
CertIx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i b (m :: * -> *).
(Integral i, Integral b, Bounded b, MonadFail m) =>
i -> m b
integralToBounded @a @Word16 @m
{-# INLINE certIxFromIntegral #-}
mkCertIxPartial :: HasCallStack => Integer -> CertIx
mkCertIxPartial :: HasCallStack => Integer -> CertIx
mkCertIxPartial Integer
i =
forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Value for CertIx is out of a valid range: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
i) forall a b. (a -> b) -> a -> b
$
forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral Integer
i
newtype AnchorData = AnchorData ByteString
deriving (AnchorData -> AnchorData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnchorData -> AnchorData -> Bool
$c/= :: AnchorData -> AnchorData -> Bool
== :: AnchorData -> AnchorData -> Bool
$c== :: AnchorData -> AnchorData -> Bool
Eq)
deriving newtype (AnchorData -> Int
AnchorData -> ByteString
forall t.
(t -> ByteString)
-> (t -> Int)
-> (forall c index.
HashAlgorithm (HASH c) =>
Proxy c -> Proxy index -> t -> SafeHash c index)
-> SafeToHash t
forall c index.
HashAlgorithm (HASH c) =>
Proxy c -> Proxy index -> AnchorData -> SafeHash c index
makeHashWithExplicitProxys :: forall c index.
HashAlgorithm (HASH c) =>
Proxy c -> Proxy index -> AnchorData -> SafeHash c index
$cmakeHashWithExplicitProxys :: forall c index.
HashAlgorithm (HASH c) =>
Proxy c -> Proxy index -> AnchorData -> SafeHash c index
originalBytesSize :: AnchorData -> Int
$coriginalBytesSize :: AnchorData -> Int
originalBytes :: AnchorData -> ByteString
$coriginalBytes :: AnchorData -> ByteString
SafeToHash)
instance HashWithCrypto AnchorData AnchorData
hashAnchorData :: forall c. Crypto c => AnchorData -> SafeHash c AnchorData
hashAnchorData :: forall c. Crypto c => AnchorData -> SafeHash c AnchorData
hashAnchorData = forall x index c.
(HashWithCrypto x index, HashAlgorithm (HASH c)) =>
Proxy c -> x -> SafeHash c index
hashWithCrypto (forall {k} (t :: k). Proxy t
Proxy @c)
data Anchor c = Anchor
{ forall c. Anchor c -> Url
anchorUrl :: !Url
, forall c. Anchor c -> SafeHash c AnchorData
anchorDataHash :: !(SafeHash c AnchorData)
}
deriving (Anchor c -> Anchor c -> Bool
forall c. Anchor c -> Anchor c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Anchor c -> Anchor c -> Bool
$c/= :: forall c. Anchor c -> Anchor c -> Bool
== :: Anchor c -> Anchor c -> Bool
$c== :: forall c. Anchor c -> Anchor c -> Bool
Eq, Anchor c -> Anchor c -> Bool
Anchor c -> Anchor c -> Ordering
forall c. Eq (Anchor c)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Anchor c -> Anchor c -> Bool
forall c. Anchor c -> Anchor c -> Ordering
forall c. Anchor c -> Anchor c -> Anchor c
min :: Anchor c -> Anchor c -> Anchor c
$cmin :: forall c. Anchor c -> Anchor c -> Anchor c
max :: Anchor c -> Anchor c -> Anchor c
$cmax :: forall c. Anchor c -> Anchor c -> Anchor c
>= :: Anchor c -> Anchor c -> Bool
$c>= :: forall c. Anchor c -> Anchor c -> Bool
> :: Anchor c -> Anchor c -> Bool
$c> :: forall c. Anchor c -> Anchor c -> Bool
<= :: Anchor c -> Anchor c -> Bool
$c<= :: forall c. Anchor c -> Anchor c -> Bool
< :: Anchor c -> Anchor c -> Bool
$c< :: forall c. Anchor c -> Anchor c -> Bool
compare :: Anchor c -> Anchor c -> Ordering
$ccompare :: forall c. Anchor c -> Anchor c -> Ordering
Ord, Int -> Anchor c -> ShowS
forall c. Int -> Anchor c -> ShowS
forall c. [Anchor c] -> ShowS
forall c. Anchor c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Anchor c] -> ShowS
$cshowList :: forall c. [Anchor c] -> ShowS
show :: Anchor c -> String
$cshow :: forall c. Anchor c -> String
showsPrec :: Int -> Anchor c -> ShowS
$cshowsPrec :: forall c. Int -> Anchor c -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall c x. Rep (Anchor c) x -> Anchor c
forall c x. Anchor c -> Rep (Anchor c) x
$cto :: forall c x. Rep (Anchor c) x -> Anchor c
$cfrom :: forall c x. Anchor c -> Rep (Anchor c) x
Generic)
instance NoThunks (Anchor c)
instance Crypto c => NFData (Anchor c) where
rnf :: Anchor c -> ()
rnf = forall a. a -> ()
rwhnf
instance Crypto c => DecCBOR (Anchor c) where
decCBOR :: forall s. Decoder s (Anchor c)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall c. Url -> SafeHash c AnchorData -> Anchor c
Anchor
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance Crypto c => EncCBOR (Anchor c) where
encCBOR :: Anchor c -> Encoding
encCBOR Anchor {SafeHash c AnchorData
Url
anchorDataHash :: SafeHash c AnchorData
anchorUrl :: Url
anchorDataHash :: forall c. Anchor c -> SafeHash c AnchorData
anchorUrl :: forall c. Anchor c -> Url
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec forall c. Url -> SafeHash c AnchorData -> Anchor c
Anchor
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Url
anchorUrl
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To SafeHash c AnchorData
anchorDataHash
instance Crypto c => ToJSON (Anchor c) where
toJSON :: Anchor c -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a c. (KeyValue e a, Crypto c) => Anchor c -> [a]
toAnchorPairs
toEncoding :: Anchor c -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a c. (KeyValue e a, Crypto c) => Anchor c -> [a]
toAnchorPairs
instance Crypto c => FromJSON (Anchor c) where
parseJSON :: Value -> Parser (Anchor c)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Anchor" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Url
anchorUrl <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
SafeHash c AnchorData
anchorDataHash <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dataHash"
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Anchor {SafeHash c AnchorData
Url
anchorDataHash :: SafeHash c AnchorData
anchorUrl :: Url
anchorDataHash :: SafeHash c AnchorData
anchorUrl :: Url
..}
instance Crypto c => Default (Anchor c) where
def :: Anchor c
def = forall c. Url -> SafeHash c AnchorData -> Anchor c
Anchor (Text -> Url
Url Text
"") forall a. Default a => a
def
toAnchorPairs :: (KeyValue e a, Crypto c) => Anchor c -> [a]
toAnchorPairs :: forall e a c. (KeyValue e a, Crypto c) => Anchor c -> [a]
toAnchorPairs vote :: Anchor c
vote@(Anchor Url
_ SafeHash c AnchorData
_) =
let Anchor {SafeHash c AnchorData
Url
anchorDataHash :: SafeHash c AnchorData
anchorUrl :: Url
anchorDataHash :: forall c. Anchor c -> SafeHash c AnchorData
anchorUrl :: forall c. Anchor c -> Url
..} = Anchor c
vote
in [ Key
"url" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Url
anchorUrl
, Key
"dataHash" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= SafeHash c AnchorData
anchorDataHash
]
instance Default Network where
def :: Network
def = Network
Mainnet
class Inject t s where
inject :: t -> s
instance Inject a a where
inject :: a -> a
inject = forall a. a -> a
id
kindObject :: Text -> [Pair] -> Value
kindObject :: Text -> [Pair] -> Value
kindObject Text
name [Pair]
obj = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ (Key
"kind" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name) forall a. a -> [a] -> [a]
: [Pair]
obj