{-# 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,
  module NonZero,
  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,

  -- * Indices
  TxIx (..),
  txIxToInt,
  txIxFromIntegral,
  mkTxIx,
  mkTxIxPartial,
  CertIx (..),
  certIxToInt,
  certIxFromIntegral,
  mkCertIx,
  mkCertIxPartial,
  Anchor (..),
  AnchorData (..),
  hashAnchorData,

  -- * STS Base
  Globals (..),
  epochInfoPure,
  ShelleyBase,
  Relation (..),
  Mismatch (..),
  swapMismatch,
  unswapMismatch,

  -- * Injection
  Inject (..),
  positiveUnitIntervalNonZeroRational,
) where

import Cardano.Crypto.Hash
import Cardano.Crypto.Util (SignableRepresentation (..))
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.BaseTypes.NonZero as NonZero
import Cardano.Ledger.Binary (
  CBORGroup (..),
  DecCBOR (decCBOR),
  DecCBORGroup (..),
  Decoder,
  DecoderError (..),
  EncCBOR (encCBOR),
  EncCBORGroup (..),
  FromCBOR,
  ToCBOR,
  cborError,
  encodedSizeExpr,
  ifDecoderVersionAtLeast,
 )
import Cardano.Ledger.Binary.Coders (
  Decode (..),
  Encode (..),
  decode,
  encode,
  (!>),
  (<!),
 )
import Cardano.Ledger.Binary.Plain (
  FromCBOR (..),
  ToCBOR (..),
  decodeRecordSum,
  decodeWord8,
  encodeListLen,
  invalidKey,
 )
import qualified Cardano.Ledger.Binary.Plain as Plain (decodeRationalWithTag, encodeRatioWithTag)
import Cardano.Ledger.Binary.Version
import Cardano.Ledger.Hashes (HashAnnotated (hashAnnotated), SafeHash, SafeToHash)
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import Cardano.Ledger.NonIntegral (ln')
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.MemPack
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
(Int -> ProtVer -> ShowS)
-> (ProtVer -> String) -> ([ProtVer] -> ShowS) -> Show ProtVer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtVer -> ShowS
showsPrec :: Int -> ProtVer -> ShowS
$cshow :: ProtVer -> String
show :: ProtVer -> String
$cshowList :: [ProtVer] -> ShowS
showList :: [ProtVer] -> ShowS
Show, ProtVer -> ProtVer -> Bool
(ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> Bool) -> Eq ProtVer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtVer -> ProtVer -> Bool
== :: ProtVer -> ProtVer -> Bool
$c/= :: ProtVer -> ProtVer -> Bool
/= :: ProtVer -> ProtVer -> Bool
Eq, (forall x. ProtVer -> Rep ProtVer x)
-> (forall x. Rep ProtVer x -> ProtVer) -> Generic ProtVer
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
$cfrom :: forall x. ProtVer -> Rep ProtVer x
from :: forall x. ProtVer -> Rep ProtVer x
$cto :: forall x. Rep ProtVer x -> ProtVer
to :: forall x. Rep ProtVer x -> ProtVer
Generic, Eq ProtVer
Eq ProtVer =>
(ProtVer -> ProtVer -> Ordering)
-> (ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> ProtVer)
-> (ProtVer -> ProtVer -> ProtVer)
-> Ord 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
$ccompare :: ProtVer -> ProtVer -> Ordering
compare :: ProtVer -> ProtVer -> Ordering
$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
>= :: ProtVer -> ProtVer -> Bool
$cmax :: ProtVer -> ProtVer -> ProtVer
max :: ProtVer -> ProtVer -> ProtVer
$cmin :: ProtVer -> ProtVer -> ProtVer
min :: ProtVer -> ProtVer -> ProtVer
Ord, ProtVer -> ()
(ProtVer -> ()) -> NFData ProtVer
forall a. (a -> ()) -> NFData a
$crnf :: ProtVer -> ()
rnf :: ProtVer -> ()
NFData)
  deriving (Typeable ProtVer
Typeable ProtVer =>
(ProtVer -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy ProtVer -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [ProtVer] -> Size)
-> EncCBOR 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
$cencCBOR :: ProtVer -> Encoding
encCBOR :: ProtVer -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
EncCBOR) via (CBORGroup ProtVer)
  deriving (Typeable ProtVer
Typeable ProtVer =>
(forall s. Decoder s ProtVer)
-> (forall s. Proxy ProtVer -> Decoder s ())
-> (Proxy ProtVer -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s ProtVer
decCBOR :: forall s. Decoder s ProtVer
$cdropCBOR :: forall s. Proxy ProtVer -> Decoder s ()
dropCBOR :: forall s. Proxy ProtVer -> Decoder s ()
$clabel :: Proxy ProtVer -> Text
label :: Proxy ProtVer -> Text
DecCBOR) via (CBORGroup ProtVer)

instance ToCBOR ProtVer where
  toCBOR :: ProtVer -> Encoding
toCBOR ProtVer {Natural
Version
pvMajor :: ProtVer -> Version
pvMinor :: ProtVer -> Natural
pvMajor :: Version
pvMinor :: Natural
..} = (Version, Natural) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Version
pvMajor, Natural
pvMinor)

instance FromCBOR ProtVer where
  fromCBOR :: forall s. Decoder s ProtVer
fromCBOR = (Version -> Natural -> ProtVer) -> (Version, Natural) -> ProtVer
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Version -> Natural -> ProtVer
ProtVer ((Version, Natural) -> ProtVer)
-> Decoder s (Version, Natural) -> Decoder s ProtVer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Version, Natural)
forall s. Decoder s (Version, Natural)
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" Key -> Word64 -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Version -> Word64
getVersion64 Version
major
      , Key
"minor" Key -> Natural -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Natural
minor
      ]

instance FromJSON ProtVer where
  parseJSON :: Value -> Parser ProtVer
parseJSON =
    String -> (Object -> Parser ProtVer) -> Value -> Parser ProtVer
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ProtVer" ((Object -> Parser ProtVer) -> Value -> Parser ProtVer)
-> (Object -> Parser ProtVer) -> Value -> Parser ProtVer
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
      Version
pvMajor <- Word64 -> Parser Version
forall (m :: * -> *). MonadFail m => Word64 -> m Version
mkVersion64 (Word64 -> Parser Version) -> Parser Word64 -> Parser Version
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
obj Object -> Key -> Parser Word64
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"major"
      Natural
pvMinor <- Object
obj Object -> Key -> Parser Natural
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"minor"
      ProtVer -> Parser ProtVer
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ProtVer {Natural
Version
pvMajor :: Version
pvMinor :: Natural
pvMajor :: Version
pvMinor :: Natural
..}

instance EncCBORGroup ProtVer where
  encCBORGroup :: ProtVer -> Encoding
encCBORGroup (ProtVer Version
x Natural
y) = Version -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR Version
x Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Natural -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy Version -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
l (ProtVer -> Version
pvMajor (ProtVer -> Version) -> Proxy ProtVer -> Proxy Version
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy ProtVer
proxy)
      Size -> Size -> Size
forall a. Num a => a -> a -> a
+ (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
l (Natural -> Word
toWord (Natural -> Word) -> (ProtVer -> Natural) -> ProtVer -> Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtVer -> Natural
pvMinor (ProtVer -> Word) -> Proxy ProtVer -> Proxy Word
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy ProtVer
proxy)
    where
      toWord :: Natural -> Word
      toWord :: Natural -> Word
toWord = Natural -> Word
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 (Version -> Natural -> ProtVer)
-> Decoder s Version -> Decoder s (Natural -> ProtVer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Version
forall s. Decoder s Version
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s (Natural -> ProtVer)
-> Decoder s Natural -> Decoder s ProtVer
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Natural
forall s. Decoder s Natural
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) Integer -> Integer -> 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) FixedPoint -> Integer -> 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 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
minInt =
      String -> m b
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$ String
"Value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
int String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" less than expected minimum value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
minInt
  | Integer
int Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
maxInt =
      String -> m b
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$ String
"Value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
int String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" greater than expected maximum value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
maxInt
  | Bool
otherwise = b -> m b
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> m b) -> b -> m b
forall a b. (a -> b) -> a -> b
$ Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
int
  where
    int :: Integer
int = i -> Integer
forall a. Integral a => a -> Integer
toInteger i
i
    minInt :: Integer
minInt = b -> Integer
forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound @b)
    maxInt :: Integer
maxInt = b -> Integer
forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound @b)
{-# INLINE integralToBounded #-}

-- | This is an internal type for representing rational numbers that are bounded on some
-- interval that is controlled by phantom type variable @b@ as well as by
-- the bounds of underlying type @a@.
newtype BoundedRatio b a = BoundedRatio (Ratio a)
  deriving (BoundedRatio b a -> BoundedRatio b a -> Bool
(BoundedRatio b a -> BoundedRatio b a -> Bool)
-> (BoundedRatio b a -> BoundedRatio b a -> Bool)
-> Eq (BoundedRatio b a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall b a. Eq a => 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
/= :: BoundedRatio b a -> BoundedRatio b a -> Bool
Eq, (forall x. BoundedRatio b a -> Rep (BoundedRatio b a) x)
-> (forall x. Rep (BoundedRatio b a) x -> BoundedRatio b a)
-> Generic (BoundedRatio b a)
forall x. Rep (BoundedRatio b a) x -> BoundedRatio b a
forall x. BoundedRatio b a -> Rep (BoundedRatio b a) x
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
$cfrom :: forall b a x. BoundedRatio b a -> Rep (BoundedRatio b a) x
from :: forall x. BoundedRatio b a -> Rep (BoundedRatio b a) x
$cto :: forall b a x. Rep (BoundedRatio b a) x -> BoundedRatio b a
to :: forall x. Rep (BoundedRatio b a) x -> BoundedRatio b a
Generic)
  deriving newtype (Int -> BoundedRatio b a -> ShowS
[BoundedRatio b a] -> ShowS
BoundedRatio b a -> String
(Int -> BoundedRatio b a -> ShowS)
-> (BoundedRatio b a -> String)
-> ([BoundedRatio b a] -> ShowS)
-> Show (BoundedRatio b a)
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
$cshowsPrec :: forall b a. Show a => Int -> BoundedRatio b a -> ShowS
showsPrec :: Int -> BoundedRatio b a -> ShowS
$cshow :: forall b a. Show a => BoundedRatio b a -> String
show :: BoundedRatio b a -> String
$cshowList :: forall b a. Show a => [BoundedRatio b a] -> ShowS
showList :: [BoundedRatio b a] -> ShowS
Show, Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
Proxy (BoundedRatio b a) -> String
(Context -> BoundedRatio b a -> IO (Maybe ThunkInfo))
-> (Context -> BoundedRatio b a -> IO (Maybe ThunkInfo))
-> (Proxy (BoundedRatio b a) -> String)
-> NoThunks (BoundedRatio b a)
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
$cnoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
noThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall b a. NoThunks a => Proxy (BoundedRatio b a) -> String
showTypeOf :: Proxy (BoundedRatio b a) -> String
NoThunks, BoundedRatio b a -> ()
(BoundedRatio b a -> ()) -> NFData (BoundedRatio b a)
forall a. (a -> ()) -> NFData a
forall b a. NFData a => BoundedRatio b a -> ()
$crnf :: forall b a. NFData a => BoundedRatio b a -> ()
rnf :: BoundedRatio b a -> ()
NFData)

-- Deriving Ord instance can lead to integer overflow. We must go through Rational.
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) = Rational -> Rational -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Ratio a -> Rational
forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
a) (Ratio a -> Rational
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 = a -> Integer
forall a. Integral a => a -> Integer
toInteger (Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
r) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% a -> Integer
forall a. Integral a => a -> Integer
toInteger (Ratio a -> a
forall a. Ratio a -> a
denominator Ratio a
r)

-- | Type clases that allows conversion between `Rational` and some form of bounded
-- rational type. Bounds can be restricted by both the `Bounded` type class and underlyng
-- representation.
--
-- > maybe True (\br -> minBound <= br && br <= maxBound) . boundRational
--
-- Roundtrip properties must hold:
--
-- > \r -> maybe True ((r ==) . unboundRational) (boundRational r)
-- > \br -> Just br == boundRational (unboundRational br)
class Bounded r => BoundedRational r where
  -- | Returns `Nothing` when supplied value is not within bounds or when precision is
  -- too high to be represented by the underlying type
  --
  -- ===__Example__
  --
  -- >>> :set -XTypeApplications
  -- >>> import Data.Ratio
  -- >>> boundRational @UnitInterval $ 2 % 3
  -- Just (2 % 3)
  -- >>> boundRational @UnitInterval (-0.5)
  -- Nothing
  -- >>> boundRational @UnitInterval (1.5)
  -- Nothing
  -- >>> boundRational @UnitInterval 0
  -- Just (0 % 1)
  -- >>> boundRational @PositiveUnitInterval 0
  -- Nothing
  boundRational :: Rational -> Maybe r

  -- | Promote bounded rational type into the unbounded `Rational`.
  unboundRational :: r -> Rational

instance
  (Bounded (BoundedRatio b a), Bounded a, Integral a) =>
  BoundedRational (BoundedRatio b a)
  where
  boundRational :: Rational -> Maybe (BoundedRatio b a)
boundRational = Rational -> Maybe (BoundedRatio b a)
forall b a.
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
Rational -> Maybe (BoundedRatio b a)
fromRationalBoundedRatio
  unboundRational :: BoundedRatio b a -> Rational
unboundRational = BoundedRatio b a -> Rational
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) = Ratio a -> Rational
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 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
minVal Bool -> Bool -> Bool
|| Integer
d Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
minVal Bool -> Bool -> Bool
|| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
maxVal Bool -> Bool -> Bool
|| Integer
d Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
maxVal = Maybe (BoundedRatio b a)
forall a. Maybe a
Nothing -- protect against overflow
  | Bool
otherwise = Ratio a -> Maybe (BoundedRatio b a)
forall b a.
(Bounded a, Bounded (BoundedRatio b a), Integral a) =>
Ratio a -> Maybe (BoundedRatio b a)
fromRatioBoundedRatio (Ratio a -> Maybe (BoundedRatio b a))
-> Ratio a -> Maybe (BoundedRatio b a)
forall a b. (a -> b) -> a -> b
$ Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
n a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
d
  where
    minVal :: Integer
minVal = a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound :: a)
    maxVal :: Integer
maxVal = a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound :: a)
    n :: Integer
n = Rational -> Integer
forall a. Ratio a -> a
numerator Rational
r
    d :: Integer
d = Rational -> Integer
forall a. Ratio a -> a
denominator Rational
r

-- | Convert to `BoundedRatio`, while checking the bounds. This function doesn't guard
-- against overflow, therefore use `fromRationalBoundedRatio . promoteRatio` instead
-- when in doubt.
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 Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
< BoundedRatio b a -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational BoundedRatio b a
lowerBound
      Bool -> Bool -> Bool
|| Rational
r Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
> BoundedRatio b a -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational BoundedRatio b a
upperBound =
      Maybe (BoundedRatio b a)
forall a. Maybe a
Nothing -- ensure valid range
  | Bool
otherwise = BoundedRatio b a -> Maybe (BoundedRatio b a)
forall a. a -> Maybe a
Just (BoundedRatio b a -> Maybe (BoundedRatio b a))
-> BoundedRatio b a -> Maybe (BoundedRatio b a)
forall a b. (a -> b) -> a -> b
$ Ratio a -> BoundedRatio b a
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio Ratio a
ratio
  where
    r :: Rational
r = Ratio a -> Rational
forall a. Integral a => Ratio a -> Rational
promoteRatio Ratio a
ratio
    lowerBound :: BoundedRatio b a
lowerBound = BoundedRatio b a
forall a. Bounded a => a
minBound :: BoundedRatio b a
    upperBound :: BoundedRatio b a
upperBound = BoundedRatio b a
forall a. Bounded a => a
maxBound :: BoundedRatio b a

instance (ToCBOR a, Integral a, Bounded a, Typeable b) => ToCBOR (BoundedRatio b a) where
  toCBOR :: BoundedRatio b a -> Encoding
toCBOR (BoundedRatio Ratio a
u) = (a -> Encoding) -> Ratio a -> Encoding
forall t. (t -> Encoding) -> Ratio t -> Encoding
Plain.encodeRatioWithTag a -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Ratio a
u

instance
  (FromCBOR a, Bounded (BoundedRatio b a), Bounded a, Integral a, Typeable b, Show a) =>
  FromCBOR (BoundedRatio b a)
  where
  fromCBOR :: forall s. Decoder s (BoundedRatio b a)
fromCBOR = do
    Rational
r <- Decoder s Rational
forall s. Decoder s Rational
Plain.decodeRationalWithTag
    case Rational -> Maybe (BoundedRatio b a)
forall r. BoundedRational r => Rational -> Maybe r
boundRational Rational
r of
      Maybe (BoundedRatio b a)
Nothing ->
        DecoderError -> Decoder s (BoundedRatio b a)
forall (m :: * -> *) e a. (MonadFail m, Buildable e) => e -> m a
cborError (DecoderError -> Decoder s (BoundedRatio b a))
-> DecoderError -> Decoder s (BoundedRatio b a)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"BoundedRatio" (String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Rational -> String
forall a. Show a => a -> String
show Rational
r)
      Just BoundedRatio b a
u -> BoundedRatio b a -> Decoder s (BoundedRatio b a)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BoundedRatio b a
u

instance (ToCBOR (BoundedRatio b a), Typeable b, Typeable a) => EncCBOR (BoundedRatio b a)

instance (FromCBOR (BoundedRatio b a), Typeable b, Typeable a) => DecCBOR (BoundedRatio b a)

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) -> Scientific -> Value
forall a. ToJSON a => a -> Value
toJSON Scientific
s
    Either (Scientific, Rational) (Scientific, Maybe Int)
_ -> Rational -> Value
forall a. ToJSON a => a -> Value
toJSON Rational
r
    where
      r :: Rational
r = BoundedRatio b Word64 -> Rational
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
_) -> (Rational -> Either String (BoundedRatio b Word64))
-> Value -> Parser (BoundedRatio b Word64)
forall {b} {c}.
FromJSON b =>
(b -> Either String c) -> Value -> Parser c
parseWith Rational -> Either String (BoundedRatio b Word64)
forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither Value
rational
    Value
sci -> (Scientific -> Either String (BoundedRatio b Word64))
-> Value -> Parser (BoundedRatio b Word64)
forall {b} {c}.
FromJSON b =>
(b -> Either String c) -> Value -> Parser c
parseWith Scientific -> Either String (BoundedRatio b Word64)
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 = (String -> Parser c)
-> (c -> Parser c) -> Either String c -> Parser c
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser c
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail c -> Parser c
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String c -> Parser c)
-> (b -> Either String c) -> b -> Parser c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either String c
f (b -> Parser c) -> (Value -> Parser b) -> Value -> Parser c
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser b
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 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = String -> Scientific -> Either String (BoundedRatio b Word64)
forall a b. Show a => String -> a -> Either String b
failWith String
"negative" Scientific
sci
  | Int
exp10 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = do
      Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
exp10 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< -Int
maxDecimalsWord64) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$ String -> Scientific -> Either String ()
forall a b. Show a => String -> a -> Either String b
failWith String
"too precise" Scientific
sci
      Rational -> Either String (BoundedRatio b Word64)
forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither (Integer
coeff Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int -> Int
forall a. Num a => a -> a
negate Int
exp10))
  | Bool
otherwise = do
      Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
maxDecimalsWord64 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
exp10) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$ String -> Scientific -> Either String ()
forall a b. Show a => String -> a -> Either String b
failWith String
"too big" Scientific
sci
      Rational -> Either String (BoundedRatio b Word64)
forall b.
Bounded (BoundedRatio b Word64) =>
Rational -> Either String (BoundedRatio b Word64)
fromRationalEither (Integer
coeff Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
exp10 Integer -> Integer -> Rational
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 = Either String (BoundedRatio b Word64)
-> (BoundedRatio b Word64 -> Either String (BoundedRatio b Word64))
-> Maybe (BoundedRatio b Word64)
-> Either String (BoundedRatio b Word64)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Rational -> Either String (BoundedRatio b Word64)
forall a b. Show a => String -> a -> Either String b
failWith String
"outside of bounds" Rational
r) BoundedRatio b Word64 -> Either String (BoundedRatio b Word64)
forall a b. b -> Either a b
Right (Maybe (BoundedRatio b Word64)
 -> Either String (BoundedRatio b Word64))
-> Maybe (BoundedRatio b Word64)
-> Either String (BoundedRatio b Word64)
forall a b. (a -> b) -> a -> b
$ Rational -> Maybe (BoundedRatio b Word64)
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 = String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b) -> String -> Either String b
forall a b. (a -> b) -> a -> b
$ String
"Value is " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
msg String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
": " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
val

-- | Type to represent a value in the interval [0; +∞)
newtype NonNegativeInterval
  = NonNegativeInterval (BoundedRatio NonNegativeInterval Word64)
  deriving (Eq NonNegativeInterval
Eq NonNegativeInterval =>
(NonNegativeInterval -> NonNegativeInterval -> Ordering)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval
    -> NonNegativeInterval -> NonNegativeInterval)
-> (NonNegativeInterval
    -> NonNegativeInterval -> NonNegativeInterval)
-> Ord 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
$ccompare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
compare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
$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
>= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$cmax :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
max :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
$cmin :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
min :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
Ord, NonNegativeInterval -> NonNegativeInterval -> Bool
(NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> Eq NonNegativeInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonNegativeInterval -> NonNegativeInterval -> Bool
== :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
Eq, (forall x. NonNegativeInterval -> Rep NonNegativeInterval x)
-> (forall x. Rep NonNegativeInterval x -> NonNegativeInterval)
-> Generic NonNegativeInterval
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
$cfrom :: forall x. NonNegativeInterval -> Rep NonNegativeInterval x
from :: forall x. NonNegativeInterval -> Rep NonNegativeInterval x
$cto :: forall x. Rep NonNegativeInterval x -> NonNegativeInterval
to :: forall x. Rep NonNegativeInterval x -> NonNegativeInterval
Generic)
  deriving newtype
    ( Int -> NonNegativeInterval -> ShowS
[NonNegativeInterval] -> ShowS
NonNegativeInterval -> String
(Int -> NonNegativeInterval -> ShowS)
-> (NonNegativeInterval -> String)
-> ([NonNegativeInterval] -> ShowS)
-> Show NonNegativeInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NonNegativeInterval -> ShowS
showsPrec :: Int -> NonNegativeInterval -> ShowS
$cshow :: NonNegativeInterval -> String
show :: NonNegativeInterval -> String
$cshowList :: [NonNegativeInterval] -> ShowS
showList :: [NonNegativeInterval] -> ShowS
Show
    , NonNegativeInterval
NonNegativeInterval
-> NonNegativeInterval -> Bounded NonNegativeInterval
forall a. a -> a -> Bounded a
$cminBound :: NonNegativeInterval
minBound :: NonNegativeInterval
$cmaxBound :: NonNegativeInterval
maxBound :: NonNegativeInterval
Bounded
    , Bounded NonNegativeInterval
Bounded NonNegativeInterval =>
(Rational -> Maybe NonNegativeInterval)
-> (NonNegativeInterval -> Rational)
-> BoundedRational NonNegativeInterval
Rational -> Maybe NonNegativeInterval
NonNegativeInterval -> Rational
forall r.
Bounded r =>
(Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
$cboundRational :: Rational -> Maybe NonNegativeInterval
boundRational :: Rational -> Maybe NonNegativeInterval
$cunboundRational :: NonNegativeInterval -> Rational
unboundRational :: NonNegativeInterval -> Rational
BoundedRational
    , Typeable NonNegativeInterval
Typeable NonNegativeInterval =>
(NonNegativeInterval -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy NonNegativeInterval -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [NonNegativeInterval] -> Size)
-> EncCBOR 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
$cencCBOR :: NonNegativeInterval -> Encoding
encCBOR :: NonNegativeInterval -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
EncCBOR
    , Typeable NonNegativeInterval
Typeable NonNegativeInterval =>
(forall s. Decoder s NonNegativeInterval)
-> (forall s. Proxy NonNegativeInterval -> Decoder s ())
-> (Proxy NonNegativeInterval -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s NonNegativeInterval
decCBOR :: forall s. Decoder s NonNegativeInterval
$cdropCBOR :: forall s. Proxy NonNegativeInterval -> Decoder s ()
dropCBOR :: forall s. Proxy NonNegativeInterval -> Decoder s ()
$clabel :: Proxy NonNegativeInterval -> Text
label :: Proxy NonNegativeInterval -> Text
DecCBOR
    , [NonNegativeInterval] -> Value
[NonNegativeInterval] -> Encoding
NonNegativeInterval -> Bool
NonNegativeInterval -> Value
NonNegativeInterval -> Encoding
(NonNegativeInterval -> Value)
-> (NonNegativeInterval -> Encoding)
-> ([NonNegativeInterval] -> Value)
-> ([NonNegativeInterval] -> Encoding)
-> (NonNegativeInterval -> Bool)
-> ToJSON NonNegativeInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: NonNegativeInterval -> Value
toJSON :: NonNegativeInterval -> Value
$ctoEncoding :: NonNegativeInterval -> Encoding
toEncoding :: NonNegativeInterval -> Encoding
$ctoJSONList :: [NonNegativeInterval] -> Value
toJSONList :: [NonNegativeInterval] -> Value
$ctoEncodingList :: [NonNegativeInterval] -> Encoding
toEncodingList :: [NonNegativeInterval] -> Encoding
$comitField :: NonNegativeInterval -> Bool
omitField :: NonNegativeInterval -> Bool
ToJSON
    , Maybe NonNegativeInterval
Value -> Parser [NonNegativeInterval]
Value -> Parser NonNegativeInterval
(Value -> Parser NonNegativeInterval)
-> (Value -> Parser [NonNegativeInterval])
-> Maybe NonNegativeInterval
-> FromJSON NonNegativeInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser NonNegativeInterval
parseJSON :: Value -> Parser NonNegativeInterval
$cparseJSONList :: Value -> Parser [NonNegativeInterval]
parseJSONList :: Value -> Parser [NonNegativeInterval]
$comittedField :: Maybe NonNegativeInterval
omittedField :: Maybe NonNegativeInterval
FromJSON
    , Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
Proxy NonNegativeInterval -> String
(Context -> NonNegativeInterval -> IO (Maybe ThunkInfo))
-> (Context -> NonNegativeInterval -> IO (Maybe ThunkInfo))
-> (Proxy NonNegativeInterval -> String)
-> NoThunks NonNegativeInterval
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy NonNegativeInterval -> String
showTypeOf :: Proxy NonNegativeInterval -> String
NoThunks
    , NonNegativeInterval -> ()
(NonNegativeInterval -> ()) -> NFData NonNegativeInterval
forall a. (a -> ()) -> NFData a
$crnf :: NonNegativeInterval -> ()
rnf :: NonNegativeInterval -> ()
NFData
    )

instance Bounded (BoundedRatio NonNegativeInterval Word64) where
  minBound :: BoundedRatio NonNegativeInterval Word64
minBound = Ratio Word64 -> BoundedRatio NonNegativeInterval Word64
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
0 Word64 -> Word64 -> Ratio Word64
forall a. Integral a => a -> a -> Ratio a
% Word64
1)
  maxBound :: BoundedRatio NonNegativeInterval Word64
maxBound = Ratio Word64 -> BoundedRatio NonNegativeInterval Word64
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
forall a. Bounded a => a
maxBound Word64 -> Word64 -> Ratio Word64
forall a. Integral a => a -> a -> Ratio a
% Word64
1)

-- | Type to represent a value in the interval (0; +∞)
newtype PositiveInterval
  = PositiveInterval (BoundedRatio PositiveInterval Word64)
  deriving (Eq PositiveInterval
Eq PositiveInterval =>
(PositiveInterval -> PositiveInterval -> Ordering)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> PositiveInterval)
-> (PositiveInterval -> PositiveInterval -> PositiveInterval)
-> Ord 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
$ccompare :: PositiveInterval -> PositiveInterval -> Ordering
compare :: PositiveInterval -> PositiveInterval -> Ordering
$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
>= :: PositiveInterval -> PositiveInterval -> Bool
$cmax :: PositiveInterval -> PositiveInterval -> PositiveInterval
max :: PositiveInterval -> PositiveInterval -> PositiveInterval
$cmin :: PositiveInterval -> PositiveInterval -> PositiveInterval
min :: PositiveInterval -> PositiveInterval -> PositiveInterval
Ord, PositiveInterval -> PositiveInterval -> Bool
(PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> Eq PositiveInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PositiveInterval -> PositiveInterval -> Bool
== :: PositiveInterval -> PositiveInterval -> Bool
$c/= :: PositiveInterval -> PositiveInterval -> Bool
/= :: PositiveInterval -> PositiveInterval -> Bool
Eq, (forall x. PositiveInterval -> Rep PositiveInterval x)
-> (forall x. Rep PositiveInterval x -> PositiveInterval)
-> Generic PositiveInterval
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
$cfrom :: forall x. PositiveInterval -> Rep PositiveInterval x
from :: forall x. PositiveInterval -> Rep PositiveInterval x
$cto :: forall x. Rep PositiveInterval x -> PositiveInterval
to :: forall x. Rep PositiveInterval x -> PositiveInterval
Generic)
  deriving newtype
    ( Int -> PositiveInterval -> ShowS
[PositiveInterval] -> ShowS
PositiveInterval -> String
(Int -> PositiveInterval -> ShowS)
-> (PositiveInterval -> String)
-> ([PositiveInterval] -> ShowS)
-> Show PositiveInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PositiveInterval -> ShowS
showsPrec :: Int -> PositiveInterval -> ShowS
$cshow :: PositiveInterval -> String
show :: PositiveInterval -> String
$cshowList :: [PositiveInterval] -> ShowS
showList :: [PositiveInterval] -> ShowS
Show
    , PositiveInterval
PositiveInterval -> PositiveInterval -> Bounded PositiveInterval
forall a. a -> a -> Bounded a
$cminBound :: PositiveInterval
minBound :: PositiveInterval
$cmaxBound :: PositiveInterval
maxBound :: PositiveInterval
Bounded
    , Bounded PositiveInterval
Bounded PositiveInterval =>
(Rational -> Maybe PositiveInterval)
-> (PositiveInterval -> Rational)
-> BoundedRational PositiveInterval
Rational -> Maybe PositiveInterval
PositiveInterval -> Rational
forall r.
Bounded r =>
(Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
$cboundRational :: Rational -> Maybe PositiveInterval
boundRational :: Rational -> Maybe PositiveInterval
$cunboundRational :: PositiveInterval -> Rational
unboundRational :: PositiveInterval -> Rational
BoundedRational
    , Typeable PositiveInterval
Typeable PositiveInterval =>
(PositiveInterval -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy PositiveInterval -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [PositiveInterval] -> Size)
-> EncCBOR 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
$cencCBOR :: PositiveInterval -> Encoding
encCBOR :: PositiveInterval -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
EncCBOR
    , Typeable PositiveInterval
Typeable PositiveInterval =>
(forall s. Decoder s PositiveInterval)
-> (forall s. Proxy PositiveInterval -> Decoder s ())
-> (Proxy PositiveInterval -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s PositiveInterval
decCBOR :: forall s. Decoder s PositiveInterval
$cdropCBOR :: forall s. Proxy PositiveInterval -> Decoder s ()
dropCBOR :: forall s. Proxy PositiveInterval -> Decoder s ()
$clabel :: Proxy PositiveInterval -> Text
label :: Proxy PositiveInterval -> Text
DecCBOR
    , [PositiveInterval] -> Value
[PositiveInterval] -> Encoding
PositiveInterval -> Bool
PositiveInterval -> Value
PositiveInterval -> Encoding
(PositiveInterval -> Value)
-> (PositiveInterval -> Encoding)
-> ([PositiveInterval] -> Value)
-> ([PositiveInterval] -> Encoding)
-> (PositiveInterval -> Bool)
-> ToJSON PositiveInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PositiveInterval -> Value
toJSON :: PositiveInterval -> Value
$ctoEncoding :: PositiveInterval -> Encoding
toEncoding :: PositiveInterval -> Encoding
$ctoJSONList :: [PositiveInterval] -> Value
toJSONList :: [PositiveInterval] -> Value
$ctoEncodingList :: [PositiveInterval] -> Encoding
toEncodingList :: [PositiveInterval] -> Encoding
$comitField :: PositiveInterval -> Bool
omitField :: PositiveInterval -> Bool
ToJSON
    , Maybe PositiveInterval
Value -> Parser [PositiveInterval]
Value -> Parser PositiveInterval
(Value -> Parser PositiveInterval)
-> (Value -> Parser [PositiveInterval])
-> Maybe PositiveInterval
-> FromJSON PositiveInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PositiveInterval
parseJSON :: Value -> Parser PositiveInterval
$cparseJSONList :: Value -> Parser [PositiveInterval]
parseJSONList :: Value -> Parser [PositiveInterval]
$comittedField :: Maybe PositiveInterval
omittedField :: Maybe PositiveInterval
FromJSON
    , Context -> PositiveInterval -> IO (Maybe ThunkInfo)
Proxy PositiveInterval -> String
(Context -> PositiveInterval -> IO (Maybe ThunkInfo))
-> (Context -> PositiveInterval -> IO (Maybe ThunkInfo))
-> (Proxy PositiveInterval -> String)
-> NoThunks PositiveInterval
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy PositiveInterval -> String
showTypeOf :: Proxy PositiveInterval -> String
NoThunks
    , PositiveInterval -> ()
(PositiveInterval -> ()) -> NFData PositiveInterval
forall a. (a -> ()) -> NFData a
$crnf :: PositiveInterval -> ()
rnf :: PositiveInterval -> ()
NFData
    )

instance Bounded (BoundedRatio PositiveInterval Word64) where
  minBound :: BoundedRatio PositiveInterval Word64
minBound = BoundedRatio PositiveInterval Word64
forall b. BoundedRatio b Word64
positiveIntervalEpsilon
  maxBound :: BoundedRatio PositiveInterval Word64
maxBound = Ratio Word64 -> BoundedRatio PositiveInterval Word64
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
forall a. Bounded a => a
maxBound Word64 -> Word64 -> Ratio Word64
forall a. Integral a => a -> a -> Ratio a
% Word64
1)

-- | The smallest decimal value that can roundtrip JSON
positiveIntervalEpsilon :: BoundedRatio b Word64
positiveIntervalEpsilon :: forall b. BoundedRatio b Word64
positiveIntervalEpsilon = Ratio Word64 -> BoundedRatio b Word64
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
1 Word64 -> Word64 -> Ratio Word64
forall a. Integral a => a -> a -> Ratio a
% Word64
10 Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
maxDecimalsWord64 :: Int))

-- | Type to represent a value in the unit interval (0; 1]
newtype PositiveUnitInterval
  = PositiveUnitInterval (BoundedRatio PositiveUnitInterval Word64)
  deriving (Eq PositiveUnitInterval
Eq PositiveUnitInterval =>
(PositiveUnitInterval -> PositiveUnitInterval -> Ordering)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval
    -> PositiveUnitInterval -> PositiveUnitInterval)
-> (PositiveUnitInterval
    -> PositiveUnitInterval -> PositiveUnitInterval)
-> Ord 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
$ccompare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
compare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
$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
>= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$cmax :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
max :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
$cmin :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
min :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
Ord, PositiveUnitInterval -> PositiveUnitInterval -> Bool
(PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> Eq PositiveUnitInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
Eq, (forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x)
-> (forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval)
-> Generic PositiveUnitInterval
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
$cfrom :: forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x
from :: forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x
$cto :: forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval
to :: forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval
Generic)
  deriving newtype
    ( Int -> PositiveUnitInterval -> ShowS
[PositiveUnitInterval] -> ShowS
PositiveUnitInterval -> String
(Int -> PositiveUnitInterval -> ShowS)
-> (PositiveUnitInterval -> String)
-> ([PositiveUnitInterval] -> ShowS)
-> Show PositiveUnitInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PositiveUnitInterval -> ShowS
showsPrec :: Int -> PositiveUnitInterval -> ShowS
$cshow :: PositiveUnitInterval -> String
show :: PositiveUnitInterval -> String
$cshowList :: [PositiveUnitInterval] -> ShowS
showList :: [PositiveUnitInterval] -> ShowS
Show
    , PositiveUnitInterval
PositiveUnitInterval
-> PositiveUnitInterval -> Bounded PositiveUnitInterval
forall a. a -> a -> Bounded a
$cminBound :: PositiveUnitInterval
minBound :: PositiveUnitInterval
$cmaxBound :: PositiveUnitInterval
maxBound :: PositiveUnitInterval
Bounded
    , Bounded PositiveUnitInterval
Bounded PositiveUnitInterval =>
(Rational -> Maybe PositiveUnitInterval)
-> (PositiveUnitInterval -> Rational)
-> BoundedRational PositiveUnitInterval
Rational -> Maybe PositiveUnitInterval
PositiveUnitInterval -> Rational
forall r.
Bounded r =>
(Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
$cboundRational :: Rational -> Maybe PositiveUnitInterval
boundRational :: Rational -> Maybe PositiveUnitInterval
$cunboundRational :: PositiveUnitInterval -> Rational
unboundRational :: PositiveUnitInterval -> Rational
BoundedRational
    , Typeable PositiveUnitInterval
Typeable PositiveUnitInterval =>
(PositiveUnitInterval -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy PositiveUnitInterval -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [PositiveUnitInterval] -> Size)
-> EncCBOR 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
$cencCBOR :: PositiveUnitInterval -> Encoding
encCBOR :: PositiveUnitInterval -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
EncCBOR
    , Typeable PositiveUnitInterval
Typeable PositiveUnitInterval =>
(forall s. Decoder s PositiveUnitInterval)
-> (forall s. Proxy PositiveUnitInterval -> Decoder s ())
-> (Proxy PositiveUnitInterval -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s PositiveUnitInterval
decCBOR :: forall s. Decoder s PositiveUnitInterval
$cdropCBOR :: forall s. Proxy PositiveUnitInterval -> Decoder s ()
dropCBOR :: forall s. Proxy PositiveUnitInterval -> Decoder s ()
$clabel :: Proxy PositiveUnitInterval -> Text
label :: Proxy PositiveUnitInterval -> Text
DecCBOR
    , Typeable PositiveUnitInterval
Typeable PositiveUnitInterval =>
(PositiveUnitInterval -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy PositiveUnitInterval -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [PositiveUnitInterval] -> Size)
-> ToCBOR PositiveUnitInterval
PositiveUnitInterval -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: PositiveUnitInterval -> Encoding
toCBOR :: PositiveUnitInterval -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
ToCBOR
    , Typeable PositiveUnitInterval
Typeable PositiveUnitInterval =>
(forall s. Decoder s PositiveUnitInterval)
-> (Proxy PositiveUnitInterval -> Text)
-> FromCBOR PositiveUnitInterval
Proxy PositiveUnitInterval -> Text
forall s. Decoder s PositiveUnitInterval
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s PositiveUnitInterval
fromCBOR :: forall s. Decoder s PositiveUnitInterval
$clabel :: Proxy PositiveUnitInterval -> Text
label :: Proxy PositiveUnitInterval -> Text
FromCBOR
    , [PositiveUnitInterval] -> Value
[PositiveUnitInterval] -> Encoding
PositiveUnitInterval -> Bool
PositiveUnitInterval -> Value
PositiveUnitInterval -> Encoding
(PositiveUnitInterval -> Value)
-> (PositiveUnitInterval -> Encoding)
-> ([PositiveUnitInterval] -> Value)
-> ([PositiveUnitInterval] -> Encoding)
-> (PositiveUnitInterval -> Bool)
-> ToJSON PositiveUnitInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PositiveUnitInterval -> Value
toJSON :: PositiveUnitInterval -> Value
$ctoEncoding :: PositiveUnitInterval -> Encoding
toEncoding :: PositiveUnitInterval -> Encoding
$ctoJSONList :: [PositiveUnitInterval] -> Value
toJSONList :: [PositiveUnitInterval] -> Value
$ctoEncodingList :: [PositiveUnitInterval] -> Encoding
toEncodingList :: [PositiveUnitInterval] -> Encoding
$comitField :: PositiveUnitInterval -> Bool
omitField :: PositiveUnitInterval -> Bool
ToJSON
    , Maybe PositiveUnitInterval
Value -> Parser [PositiveUnitInterval]
Value -> Parser PositiveUnitInterval
(Value -> Parser PositiveUnitInterval)
-> (Value -> Parser [PositiveUnitInterval])
-> Maybe PositiveUnitInterval
-> FromJSON PositiveUnitInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PositiveUnitInterval
parseJSON :: Value -> Parser PositiveUnitInterval
$cparseJSONList :: Value -> Parser [PositiveUnitInterval]
parseJSONList :: Value -> Parser [PositiveUnitInterval]
$comittedField :: Maybe PositiveUnitInterval
omittedField :: Maybe PositiveUnitInterval
FromJSON
    , Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
Proxy PositiveUnitInterval -> String
(Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo))
-> (Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo))
-> (Proxy PositiveUnitInterval -> String)
-> NoThunks PositiveUnitInterval
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy PositiveUnitInterval -> String
showTypeOf :: Proxy PositiveUnitInterval -> String
NoThunks
    , PositiveUnitInterval -> ()
(PositiveUnitInterval -> ()) -> NFData PositiveUnitInterval
forall a. (a -> ()) -> NFData a
$crnf :: PositiveUnitInterval -> ()
rnf :: PositiveUnitInterval -> ()
NFData
    )

instance Bounded (BoundedRatio PositiveUnitInterval Word64) where
  minBound :: BoundedRatio PositiveUnitInterval Word64
minBound = BoundedRatio PositiveUnitInterval Word64
forall b. BoundedRatio b Word64
positiveIntervalEpsilon
  maxBound :: BoundedRatio PositiveUnitInterval Word64
maxBound = Ratio Word64 -> BoundedRatio PositiveUnitInterval Word64
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (Word64
1 Word64 -> Word64 -> Ratio Word64
forall a. Integral a => a -> a -> Ratio a
% Word64
1)

-- | Type to represent a value in the unit interval [0; 1]
newtype UnitInterval
  = UnitInterval (BoundedRatio UnitInterval Word64)
  deriving (Eq UnitInterval
Eq UnitInterval =>
(UnitInterval -> UnitInterval -> Ordering)
-> (UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> UnitInterval)
-> (UnitInterval -> UnitInterval -> UnitInterval)
-> Ord 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
$ccompare :: UnitInterval -> UnitInterval -> Ordering
compare :: UnitInterval -> UnitInterval -> Ordering
$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
>= :: UnitInterval -> UnitInterval -> Bool
$cmax :: UnitInterval -> UnitInterval -> UnitInterval
max :: UnitInterval -> UnitInterval -> UnitInterval
$cmin :: UnitInterval -> UnitInterval -> UnitInterval
min :: UnitInterval -> UnitInterval -> UnitInterval
Ord, UnitInterval -> UnitInterval -> Bool
(UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> Bool) -> Eq UnitInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnitInterval -> UnitInterval -> Bool
== :: UnitInterval -> UnitInterval -> Bool
$c/= :: UnitInterval -> UnitInterval -> Bool
/= :: UnitInterval -> UnitInterval -> Bool
Eq, (forall x. UnitInterval -> Rep UnitInterval x)
-> (forall x. Rep UnitInterval x -> UnitInterval)
-> Generic UnitInterval
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
$cfrom :: forall x. UnitInterval -> Rep UnitInterval x
from :: forall x. UnitInterval -> Rep UnitInterval x
$cto :: forall x. Rep UnitInterval x -> UnitInterval
to :: forall x. Rep UnitInterval x -> UnitInterval
Generic)
  deriving newtype
    ( Int -> UnitInterval -> ShowS
[UnitInterval] -> ShowS
UnitInterval -> String
(Int -> UnitInterval -> ShowS)
-> (UnitInterval -> String)
-> ([UnitInterval] -> ShowS)
-> Show UnitInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnitInterval -> ShowS
showsPrec :: Int -> UnitInterval -> ShowS
$cshow :: UnitInterval -> String
show :: UnitInterval -> String
$cshowList :: [UnitInterval] -> ShowS
showList :: [UnitInterval] -> ShowS
Show
    , UnitInterval
UnitInterval -> UnitInterval -> Bounded UnitInterval
forall a. a -> a -> Bounded a
$cminBound :: UnitInterval
minBound :: UnitInterval
$cmaxBound :: UnitInterval
maxBound :: UnitInterval
Bounded
    , Bounded UnitInterval
Bounded UnitInterval =>
(Rational -> Maybe UnitInterval)
-> (UnitInterval -> Rational) -> BoundedRational UnitInterval
Rational -> Maybe UnitInterval
UnitInterval -> Rational
forall r.
Bounded r =>
(Rational -> Maybe r) -> (r -> Rational) -> BoundedRational r
$cboundRational :: Rational -> Maybe UnitInterval
boundRational :: Rational -> Maybe UnitInterval
$cunboundRational :: UnitInterval -> Rational
unboundRational :: UnitInterval -> Rational
BoundedRational
    , Typeable UnitInterval
Typeable UnitInterval =>
(UnitInterval -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy UnitInterval -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [UnitInterval] -> Size)
-> EncCBOR 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
$cencCBOR :: UnitInterval -> Encoding
encCBOR :: UnitInterval -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
EncCBOR
    , Typeable UnitInterval
Typeable UnitInterval =>
(forall s. Decoder s UnitInterval)
-> (forall s. Proxy UnitInterval -> Decoder s ())
-> (Proxy UnitInterval -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s UnitInterval
decCBOR :: forall s. Decoder s UnitInterval
$cdropCBOR :: forall s. Proxy UnitInterval -> Decoder s ()
dropCBOR :: forall s. Proxy UnitInterval -> Decoder s ()
$clabel :: Proxy UnitInterval -> Text
label :: Proxy UnitInterval -> Text
DecCBOR
    , [UnitInterval] -> Value
[UnitInterval] -> Encoding
UnitInterval -> Bool
UnitInterval -> Value
UnitInterval -> Encoding
(UnitInterval -> Value)
-> (UnitInterval -> Encoding)
-> ([UnitInterval] -> Value)
-> ([UnitInterval] -> Encoding)
-> (UnitInterval -> Bool)
-> ToJSON UnitInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UnitInterval -> Value
toJSON :: UnitInterval -> Value
$ctoEncoding :: UnitInterval -> Encoding
toEncoding :: UnitInterval -> Encoding
$ctoJSONList :: [UnitInterval] -> Value
toJSONList :: [UnitInterval] -> Value
$ctoEncodingList :: [UnitInterval] -> Encoding
toEncodingList :: [UnitInterval] -> Encoding
$comitField :: UnitInterval -> Bool
omitField :: UnitInterval -> Bool
ToJSON
    , Maybe UnitInterval
Value -> Parser [UnitInterval]
Value -> Parser UnitInterval
(Value -> Parser UnitInterval)
-> (Value -> Parser [UnitInterval])
-> Maybe UnitInterval
-> FromJSON UnitInterval
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UnitInterval
parseJSON :: Value -> Parser UnitInterval
$cparseJSONList :: Value -> Parser [UnitInterval]
parseJSONList :: Value -> Parser [UnitInterval]
$comittedField :: Maybe UnitInterval
omittedField :: Maybe UnitInterval
FromJSON
    , Context -> UnitInterval -> IO (Maybe ThunkInfo)
Proxy UnitInterval -> String
(Context -> UnitInterval -> IO (Maybe ThunkInfo))
-> (Context -> UnitInterval -> IO (Maybe ThunkInfo))
-> (Proxy UnitInterval -> String)
-> NoThunks UnitInterval
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy UnitInterval -> String
showTypeOf :: Proxy UnitInterval -> String
NoThunks
    , UnitInterval -> ()
(UnitInterval -> ()) -> NFData UnitInterval
forall a. (a -> ()) -> NFData a
$crnf :: UnitInterval -> ()
rnf :: UnitInterval -> ()
NFData
    )

instance Integral a => Bounded (BoundedRatio UnitInterval a) where
  minBound :: BoundedRatio UnitInterval a
minBound = Ratio a -> BoundedRatio UnitInterval a
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (a
0 a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% a
1)
  maxBound :: BoundedRatio UnitInterval a
maxBound = Ratio a -> BoundedRatio UnitInterval a
forall b a. Ratio a -> BoundedRatio b a
BoundedRatio (a
1 a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% a
1)

instance Default UnitInterval where
  def :: UnitInterval
def = UnitInterval
forall a. Bounded a => a
minBound

-- | Evolving nonce type.
data Nonce
  = Nonce !(Hash Blake2b_256 Nonce)
  | -- | Identity element
    NeutralNonce
  deriving (Nonce -> Nonce -> Bool
(Nonce -> Nonce -> Bool) -> (Nonce -> Nonce -> Bool) -> Eq Nonce
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Nonce -> Nonce -> Bool
== :: Nonce -> Nonce -> Bool
$c/= :: Nonce -> Nonce -> Bool
/= :: Nonce -> Nonce -> Bool
Eq, (forall x. Nonce -> Rep Nonce x)
-> (forall x. Rep Nonce x -> Nonce) -> Generic Nonce
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
$cfrom :: forall x. Nonce -> Rep Nonce x
from :: forall x. Nonce -> Rep Nonce x
$cto :: forall x. Rep Nonce x -> Nonce
to :: forall x. Rep Nonce x -> Nonce
Generic, Eq Nonce
Eq Nonce =>
(Nonce -> Nonce -> Ordering)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Nonce)
-> (Nonce -> Nonce -> Nonce)
-> Ord 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
$ccompare :: Nonce -> Nonce -> Ordering
compare :: Nonce -> Nonce -> Ordering
$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
>= :: Nonce -> Nonce -> Bool
$cmax :: Nonce -> Nonce -> Nonce
max :: Nonce -> Nonce -> Nonce
$cmin :: Nonce -> Nonce -> Nonce
min :: Nonce -> Nonce -> Nonce
Ord, Int -> Nonce -> ShowS
[Nonce] -> ShowS
Nonce -> String
(Int -> Nonce -> ShowS)
-> (Nonce -> String) -> ([Nonce] -> ShowS) -> Show Nonce
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Nonce -> ShowS
showsPrec :: Int -> Nonce -> ShowS
$cshow :: Nonce -> String
show :: Nonce -> String
$cshowList :: [Nonce] -> ShowS
showList :: [Nonce] -> ShowS
Show, Nonce -> ()
(Nonce -> ()) -> NFData Nonce
forall a. (a -> ()) -> NFData a
$crnf :: Nonce -> ()
rnf :: 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 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
0 :: Word8)
  toCBOR (Nonce Hash Blake2b_256 Nonce
n) = Word -> Encoding
encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
1 :: Word8) Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Hash Blake2b_256 Nonce -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Hash Blake2b_256 Nonce
n

instance FromCBOR Nonce where
  fromCBOR :: forall s. Decoder s Nonce
fromCBOR = Text -> (Word -> Decoder s (Int, Nonce)) -> Decoder s Nonce
forall s a. Text -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum Text
"Nonce" ((Word -> Decoder s (Int, Nonce)) -> Decoder s Nonce)
-> (Word -> Decoder s (Int, Nonce)) -> Decoder s Nonce
forall a b. (a -> b) -> a -> b
$
    \case
      Word
0 -> (Int, Nonce) -> Decoder s (Int, Nonce)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
1, Nonce
NeutralNonce)
      Word
1 -> do
        Hash Blake2b_256 Nonce
x <- Decoder s (Hash Blake2b_256 Nonce)
forall s. Decoder s (Hash Blake2b_256 Nonce)
forall a s. FromCBOR a => Decoder s a
fromCBOR
        (Int, Nonce) -> Decoder s (Int, Nonce)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
2, Hash Blake2b_256 Nonce -> Nonce
Nonce Hash Blake2b_256 Nonce
x)
      Word
k -> Word -> Decoder s (Int, Nonce)
forall a (m :: * -> *). (Typeable 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) = Hash Blake2b_256 Nonce -> Value
forall a. ToJSON a => a -> Value
toJSON Hash Blake2b_256 Nonce
n

instance FromJSON Nonce where
  parseJSON :: Value -> Parser Nonce
parseJSON Value
Null = Nonce -> Parser Nonce
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Nonce
NeutralNonce
  parseJSON Value
x = Hash Blake2b_256 Nonce -> Nonce
Nonce (Hash Blake2b_256 Nonce -> Nonce)
-> Parser (Hash Blake2b_256 Nonce) -> Parser Nonce
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Hash Blake2b_256 Nonce)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x

-- | Evolve the nonce
(⭒) :: Nonce -> Nonce -> Nonce
Nonce Hash Blake2b_256 Nonce
a ⭒ :: Nonce -> Nonce -> Nonce
 Nonce Hash Blake2b_256 Nonce
b =
  Hash Blake2b_256 Nonce -> Nonce
Nonce (Hash Blake2b_256 Nonce -> Nonce)
-> (Hash Blake2b_256 ByteString -> Hash Blake2b_256 Nonce)
-> Hash Blake2b_256 ByteString
-> Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_256 ByteString -> Hash Blake2b_256 Nonce
forall h a b. Hash h a -> Hash h b
castHash (Hash Blake2b_256 ByteString -> Nonce)
-> Hash Blake2b_256 ByteString -> Nonce
forall a b. (a -> b) -> a -> b
$
    (ByteString -> ByteString)
-> ByteString -> Hash Blake2b_256 ByteString
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith ByteString -> ByteString
forall a. a -> a
id (Hash Blake2b_256 Nonce -> ByteString
forall h a. Hash h a -> ByteString
hashToBytes Hash Blake2b_256 Nonce
a ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Hash Blake2b_256 Nonce -> ByteString
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

-- | Make a nonce from the VRF output bytes
mkNonceFromOutputVRF :: VRF.OutputVRF v -> Nonce
mkNonceFromOutputVRF :: forall v. OutputVRF v -> Nonce
mkNonceFromOutputVRF =
  Hash Blake2b_256 Nonce -> Nonce
Nonce
    (Hash Blake2b_256 Nonce -> Nonce)
-> (OutputVRF v -> Hash Blake2b_256 Nonce) -> OutputVRF v -> Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Hash Blake2b_256 (OutputVRF v) -> Hash Blake2b_256 Nonce
forall {v}.
Hash Blake2b_256 (OutputVRF v) -> Hash Blake2b_256 Nonce
forall h a b. Hash h a -> Hash h b
castHash :: Hash Blake2b_256 (VRF.OutputVRF v) -> Hash Blake2b_256 Nonce)
    (Hash Blake2b_256 (OutputVRF v) -> Hash Blake2b_256 Nonce)
-> (OutputVRF v -> Hash Blake2b_256 (OutputVRF v))
-> OutputVRF v
-> Hash Blake2b_256 Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OutputVRF v -> ByteString)
-> OutputVRF v -> Hash Blake2b_256 (OutputVRF v)
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith OutputVRF v -> ByteString
forall v. OutputVRF v -> ByteString
VRF.getOutputVRFBytes

-- | Make a nonce from a number.
mkNonceFromNumber :: Word64 -> Nonce
mkNonceFromNumber :: Word64 -> Nonce
mkNonceFromNumber =
  Hash Blake2b_256 Nonce -> Nonce
Nonce
    (Hash Blake2b_256 Nonce -> Nonce)
-> (Word64 -> Hash Blake2b_256 Nonce) -> Word64 -> Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Hash Blake2b_256 Word64 -> Hash Blake2b_256 Nonce
forall h a b. Hash h a -> Hash h b
castHash :: Hash Blake2b_256 Word64 -> Hash Blake2b_256 Nonce)
    (Hash Blake2b_256 Word64 -> Hash Blake2b_256 Nonce)
-> (Word64 -> Hash Blake2b_256 Word64)
-> Word64
-> Hash Blake2b_256 Nonce
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word64 -> ByteString) -> Word64 -> Hash Blake2b_256 Word64
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
hashWith (ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> (Word64 -> ByteString) -> Word64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut (Put -> ByteString) -> (Word64 -> Put) -> Word64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Put
B.putWord64be)

-- | Seed to the verifiable random function.
newtype Seed = Seed (Hash Blake2b_256 Seed)
  deriving (Seed -> Seed -> Bool
(Seed -> Seed -> Bool) -> (Seed -> Seed -> Bool) -> Eq Seed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Seed -> Seed -> Bool
== :: Seed -> Seed -> Bool
$c/= :: Seed -> Seed -> Bool
/= :: Seed -> Seed -> Bool
Eq, Eq Seed
Eq Seed =>
(Seed -> Seed -> Ordering)
-> (Seed -> Seed -> Bool)
-> (Seed -> Seed -> Bool)
-> (Seed -> Seed -> Bool)
-> (Seed -> Seed -> Bool)
-> (Seed -> Seed -> Seed)
-> (Seed -> Seed -> Seed)
-> Ord 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
$ccompare :: Seed -> Seed -> Ordering
compare :: Seed -> Seed -> Ordering
$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
>= :: Seed -> Seed -> Bool
$cmax :: Seed -> Seed -> Seed
max :: Seed -> Seed -> Seed
$cmin :: Seed -> Seed -> Seed
min :: Seed -> Seed -> Seed
Ord, Int -> Seed -> ShowS
[Seed] -> ShowS
Seed -> String
(Int -> Seed -> ShowS)
-> (Seed -> String) -> ([Seed] -> ShowS) -> Show Seed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Seed -> ShowS
showsPrec :: Int -> Seed -> ShowS
$cshow :: Seed -> String
show :: Seed -> String
$cshowList :: [Seed] -> ShowS
showList :: [Seed] -> ShowS
Show, (forall x. Seed -> Rep Seed x)
-> (forall x. Rep Seed x -> Seed) -> Generic Seed
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
$cfrom :: forall x. Seed -> Rep Seed x
from :: forall x. Seed -> Rep Seed x
$cto :: forall x. Rep Seed x -> Seed
to :: forall x. Rep Seed x -> Seed
Generic)
  deriving newtype (Context -> Seed -> IO (Maybe ThunkInfo)
Proxy Seed -> String
(Context -> Seed -> IO (Maybe ThunkInfo))
-> (Context -> Seed -> IO (Maybe ThunkInfo))
-> (Proxy Seed -> String)
-> NoThunks Seed
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
noThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Seed -> String
showTypeOf :: Proxy Seed -> String
NoThunks, Typeable Seed
Typeable Seed =>
(Seed -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Seed] -> Size)
-> EncCBOR 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
$cencCBOR :: Seed -> Encoding
encCBOR :: Seed -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
EncCBOR)

instance SignableRepresentation Seed where
  getSignableRepresentation :: Seed -> ByteString
getSignableRepresentation (Seed Hash Blake2b_256 Seed
x) = Hash Blake2b_256 Seed -> ByteString
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 ==>

--
-- Helper functions for text with byte-length bounds
--

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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n
        then Text -> m Text
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
        else
          String -> m Text
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m Text) -> String -> m Text
forall a b. (a -> b) -> a -> b
$
            String
"Text exceeds "
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" bytes:"
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n  Got "
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
len
              String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" bytes instead.\n"

textDecCBOR :: Int -> Decoder s Text
textDecCBOR :: forall s. Int -> Decoder s Text
textDecCBOR Int
n = Decoder s Text
forall s. Decoder s Text
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s Text -> (Text -> Decoder s Text) -> Decoder s Text
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Text -> Decoder s Text
forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n

-- |  Turn a Text into a Url, fail if the Text has more than 'n' Bytes
textToUrl :: MonadFail m => Int -> Text -> m Url
textToUrl :: forall (m :: * -> *). MonadFail m => Int -> Text -> m Url
textToUrl Int
n Text
t = Text -> Url
Url (Text -> Url) -> m Text -> m Url
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Text -> m Text
forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n Text
t

-- |  Turn a Text into a DnsName, fail if the Text has more than 'n' Bytes
textToDns :: MonadFail m => Int -> Text -> m DnsName
textToDns :: forall (m :: * -> *). MonadFail m => Int -> Text -> m DnsName
textToDns Int
n Text
t = Text -> DnsName
DnsName (Text -> DnsName) -> m Text -> m DnsName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Text -> m Text
forall (m :: * -> *). MonadFail m => Int -> Text -> m Text
textSizeN Int
n Text
t

--
-- Types used in the Stake Pool Relays
--

newtype Url = Url {Url -> Text
urlToText :: Text}
  deriving (Url -> Url -> Bool
(Url -> Url -> Bool) -> (Url -> Url -> Bool) -> Eq Url
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Url -> Url -> Bool
== :: Url -> Url -> Bool
$c/= :: Url -> Url -> Bool
/= :: Url -> Url -> Bool
Eq, Eq Url
Eq Url =>
(Url -> Url -> Ordering)
-> (Url -> Url -> Bool)
-> (Url -> Url -> Bool)
-> (Url -> Url -> Bool)
-> (Url -> Url -> Bool)
-> (Url -> Url -> Url)
-> (Url -> Url -> Url)
-> Ord 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
$ccompare :: Url -> Url -> Ordering
compare :: Url -> Url -> Ordering
$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
>= :: Url -> Url -> Bool
$cmax :: Url -> Url -> Url
max :: Url -> Url -> Url
$cmin :: Url -> Url -> Url
min :: Url -> Url -> Url
Ord, (forall x. Url -> Rep Url x)
-> (forall x. Rep Url x -> Url) -> Generic Url
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
$cfrom :: forall x. Url -> Rep Url x
from :: forall x. Url -> Rep Url x
$cto :: forall x. Rep Url x -> Url
to :: forall x. Rep Url x -> Url
Generic, Int -> Url -> ShowS
[Url] -> ShowS
Url -> String
(Int -> Url -> ShowS)
-> (Url -> String) -> ([Url] -> ShowS) -> Show Url
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Url -> ShowS
showsPrec :: Int -> Url -> ShowS
$cshow :: Url -> String
show :: Url -> String
$cshowList :: [Url] -> ShowS
showList :: [Url] -> ShowS
Show)
  deriving newtype (Typeable Url
Typeable Url =>
(Url -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Url] -> Size)
-> EncCBOR 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
$cencCBOR :: Url -> Encoding
encCBOR :: Url -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
EncCBOR, Url -> ()
(Url -> ()) -> NFData Url
forall a. (a -> ()) -> NFData a
$crnf :: Url -> ()
rnf :: Url -> ()
NFData, Context -> Url -> IO (Maybe ThunkInfo)
Proxy Url -> String
(Context -> Url -> IO (Maybe ThunkInfo))
-> (Context -> Url -> IO (Maybe ThunkInfo))
-> (Proxy Url -> String)
-> NoThunks Url
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
noThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Url -> String
showTypeOf :: Proxy Url -> String
NoThunks, Maybe Url
Value -> Parser [Url]
Value -> Parser Url
(Value -> Parser Url)
-> (Value -> Parser [Url]) -> Maybe Url -> FromJSON Url
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Url
parseJSON :: Value -> Parser Url
$cparseJSONList :: Value -> Parser [Url]
parseJSONList :: Value -> Parser [Url]
$comittedField :: Maybe Url
omittedField :: Maybe Url
FromJSON, [Url] -> Value
[Url] -> Encoding
Url -> Bool
Url -> Value
Url -> Encoding
(Url -> Value)
-> (Url -> Encoding)
-> ([Url] -> Value)
-> ([Url] -> Encoding)
-> (Url -> Bool)
-> ToJSON Url
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Url -> Value
toJSON :: Url -> Value
$ctoEncoding :: Url -> Encoding
toEncoding :: Url -> Encoding
$ctoJSONList :: [Url] -> Value
toJSONList :: [Url] -> Value
$ctoEncodingList :: [Url] -> Encoding
toEncodingList :: [Url] -> Encoding
$comitField :: Url -> Bool
omitField :: Url -> Bool
ToJSON)

instance DecCBOR Url where
  decCBOR :: Decoder s Url
  decCBOR :: forall s. Decoder s Url
decCBOR =
    Text -> Url
Url
      (Text -> Url) -> Decoder s Text -> Decoder s Url
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Version -> Decoder s Text -> Decoder s Text -> Decoder s Text
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)
        (Int -> Decoder s Text
forall s. Int -> Decoder s Text
textDecCBOR Int
128)
        (Int -> Decoder s Text
forall s. Int -> Decoder s Text
textDecCBOR Int
64)

newtype DnsName = DnsName {DnsName -> Text
dnsToText :: Text}
  deriving (DnsName -> DnsName -> Bool
(DnsName -> DnsName -> Bool)
-> (DnsName -> DnsName -> Bool) -> Eq DnsName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DnsName -> DnsName -> Bool
== :: DnsName -> DnsName -> Bool
$c/= :: DnsName -> DnsName -> Bool
/= :: DnsName -> DnsName -> Bool
Eq, Eq DnsName
Eq DnsName =>
(DnsName -> DnsName -> Ordering)
-> (DnsName -> DnsName -> Bool)
-> (DnsName -> DnsName -> Bool)
-> (DnsName -> DnsName -> Bool)
-> (DnsName -> DnsName -> Bool)
-> (DnsName -> DnsName -> DnsName)
-> (DnsName -> DnsName -> DnsName)
-> Ord 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
$ccompare :: DnsName -> DnsName -> Ordering
compare :: DnsName -> DnsName -> Ordering
$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
>= :: DnsName -> DnsName -> Bool
$cmax :: DnsName -> DnsName -> DnsName
max :: DnsName -> DnsName -> DnsName
$cmin :: DnsName -> DnsName -> DnsName
min :: DnsName -> DnsName -> DnsName
Ord, (forall x. DnsName -> Rep DnsName x)
-> (forall x. Rep DnsName x -> DnsName) -> Generic DnsName
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
$cfrom :: forall x. DnsName -> Rep DnsName x
from :: forall x. DnsName -> Rep DnsName x
$cto :: forall x. Rep DnsName x -> DnsName
to :: forall x. Rep DnsName x -> DnsName
Generic, Int -> DnsName -> ShowS
[DnsName] -> ShowS
DnsName -> String
(Int -> DnsName -> ShowS)
-> (DnsName -> String) -> ([DnsName] -> ShowS) -> Show DnsName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DnsName -> ShowS
showsPrec :: Int -> DnsName -> ShowS
$cshow :: DnsName -> String
show :: DnsName -> String
$cshowList :: [DnsName] -> ShowS
showList :: [DnsName] -> ShowS
Show)
  deriving newtype (Typeable DnsName
Typeable DnsName =>
(DnsName -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy DnsName -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [DnsName] -> Size)
-> EncCBOR 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
$cencCBOR :: DnsName -> Encoding
encCBOR :: DnsName -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
EncCBOR, Context -> DnsName -> IO (Maybe ThunkInfo)
Proxy DnsName -> String
(Context -> DnsName -> IO (Maybe ThunkInfo))
-> (Context -> DnsName -> IO (Maybe ThunkInfo))
-> (Proxy DnsName -> String)
-> NoThunks DnsName
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
noThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy DnsName -> String
showTypeOf :: Proxy DnsName -> String
NoThunks, DnsName -> ()
(DnsName -> ()) -> NFData DnsName
forall a. (a -> ()) -> NFData a
$crnf :: DnsName -> ()
rnf :: DnsName -> ()
NFData, Maybe DnsName
Value -> Parser [DnsName]
Value -> Parser DnsName
(Value -> Parser DnsName)
-> (Value -> Parser [DnsName]) -> Maybe DnsName -> FromJSON DnsName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DnsName
parseJSON :: Value -> Parser DnsName
$cparseJSONList :: Value -> Parser [DnsName]
parseJSONList :: Value -> Parser [DnsName]
$comittedField :: Maybe DnsName
omittedField :: Maybe DnsName
FromJSON, [DnsName] -> Value
[DnsName] -> Encoding
DnsName -> Bool
DnsName -> Value
DnsName -> Encoding
(DnsName -> Value)
-> (DnsName -> Encoding)
-> ([DnsName] -> Value)
-> ([DnsName] -> Encoding)
-> (DnsName -> Bool)
-> ToJSON DnsName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: DnsName -> Value
toJSON :: DnsName -> Value
$ctoEncoding :: DnsName -> Encoding
toEncoding :: DnsName -> Encoding
$ctoJSONList :: [DnsName] -> Value
toJSONList :: [DnsName] -> Value
$ctoEncodingList :: [DnsName] -> Encoding
toEncodingList :: [DnsName] -> Encoding
$comitField :: DnsName -> Bool
omitField :: DnsName -> Bool
ToJSON)

instance DecCBOR DnsName where
  decCBOR :: forall s. Decoder s DnsName
decCBOR =
    Text -> DnsName
DnsName
      (Text -> DnsName) -> Decoder s Text -> Decoder s DnsName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Version -> Decoder s Text -> Decoder s Text -> Decoder s Text
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)
        (Int -> Decoder s Text
forall s. Int -> Decoder s Text
textDecCBOR Int
128)
        (Int -> Decoder s Text
forall s. Int -> Decoder s Text
textDecCBOR Int
64)

newtype Port = Port {Port -> Word16
portToWord16 :: Word16}
  deriving (Port -> Port -> Bool
(Port -> Port -> Bool) -> (Port -> Port -> Bool) -> Eq Port
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Port -> Port -> Bool
== :: Port -> Port -> Bool
$c/= :: Port -> Port -> Bool
/= :: Port -> Port -> Bool
Eq, Eq Port
Eq Port =>
(Port -> Port -> Ordering)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Port)
-> (Port -> Port -> Port)
-> Ord 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
$ccompare :: Port -> Port -> Ordering
compare :: Port -> Port -> Ordering
$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
>= :: Port -> Port -> Bool
$cmax :: Port -> Port -> Port
max :: Port -> Port -> Port
$cmin :: Port -> Port -> Port
min :: Port -> Port -> Port
Ord, (forall x. Port -> Rep Port x)
-> (forall x. Rep Port x -> Port) -> Generic Port
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
$cfrom :: forall x. Port -> Rep Port x
from :: forall x. Port -> Rep Port x
$cto :: forall x. Rep Port x -> Port
to :: forall x. Rep Port x -> Port
Generic, Int -> Port -> ShowS
[Port] -> ShowS
Port -> String
(Int -> Port -> ShowS)
-> (Port -> String) -> ([Port] -> ShowS) -> Show Port
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Port -> ShowS
showsPrec :: Int -> Port -> ShowS
$cshow :: Port -> String
show :: Port -> String
$cshowList :: [Port] -> ShowS
showList :: [Port] -> ShowS
Show)
  deriving newtype (Integer -> Port
Port -> Port
Port -> Port -> Port
(Port -> Port -> Port)
-> (Port -> Port -> Port)
-> (Port -> Port -> Port)
-> (Port -> Port)
-> (Port -> Port)
-> (Port -> Port)
-> (Integer -> Port)
-> Num Port
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Port -> Port -> Port
+ :: Port -> Port -> Port
$c- :: Port -> Port -> Port
- :: Port -> Port -> Port
$c* :: Port -> Port -> Port
* :: Port -> Port -> Port
$cnegate :: Port -> Port
negate :: Port -> Port
$cabs :: Port -> Port
abs :: Port -> Port
$csignum :: Port -> Port
signum :: Port -> Port
$cfromInteger :: Integer -> Port
fromInteger :: Integer -> Port
Num, Typeable Port
Typeable Port =>
(forall s. Decoder s Port)
-> (forall s. Proxy Port -> Decoder s ())
-> (Proxy Port -> Text)
-> DecCBOR 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 ()
$cdecCBOR :: forall s. Decoder s Port
decCBOR :: forall s. Decoder s Port
$cdropCBOR :: forall s. Proxy Port -> Decoder s ()
dropCBOR :: forall s. Proxy Port -> Decoder s ()
$clabel :: Proxy Port -> Text
label :: Proxy Port -> Text
DecCBOR, Typeable Port
Typeable Port =>
(Port -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [Port] -> Size)
-> EncCBOR 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
$cencCBOR :: Port -> Encoding
encCBOR :: Port -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Port -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
EncCBOR, Port -> ()
(Port -> ()) -> NFData Port
forall a. (a -> ()) -> NFData a
$crnf :: Port -> ()
rnf :: Port -> ()
NFData, Context -> Port -> IO (Maybe ThunkInfo)
Proxy Port -> String
(Context -> Port -> IO (Maybe ThunkInfo))
-> (Context -> Port -> IO (Maybe ThunkInfo))
-> (Proxy Port -> String)
-> NoThunks Port
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
noThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Port -> String
showTypeOf :: Proxy Port -> String
NoThunks, [Port] -> Value
[Port] -> Encoding
Port -> Bool
Port -> Value
Port -> Encoding
(Port -> Value)
-> (Port -> Encoding)
-> ([Port] -> Value)
-> ([Port] -> Encoding)
-> (Port -> Bool)
-> ToJSON Port
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Port -> Value
toJSON :: Port -> Value
$ctoEncoding :: Port -> Encoding
toEncoding :: Port -> Encoding
$ctoJSONList :: [Port] -> Value
toJSONList :: [Port] -> Value
$ctoEncodingList :: [Port] -> Encoding
toEncodingList :: [Port] -> Encoding
$comitField :: Port -> Bool
omitField :: Port -> Bool
ToJSON, Maybe Port
Value -> Parser [Port]
Value -> Parser Port
(Value -> Parser Port)
-> (Value -> Parser [Port]) -> Maybe Port -> FromJSON Port
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Port
parseJSON :: Value -> Parser Port
$cparseJSONList :: Value -> Parser [Port]
parseJSONList :: Value -> Parser [Port]
$comittedField :: Maybe Port
omittedField :: Maybe Port
FromJSON)

--------------------------------------------------------------------------------
-- Active Slot Coefficent, named f in
-- "Ouroboros Praos: An adaptively-secure, semi-synchronous proof-of-stake protocol"
--------------------------------------------------------------------------------

data ActiveSlotCoeff = ActiveSlotCoeff
  { ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal :: !PositiveUnitInterval
  , ActiveSlotCoeff -> Integer
unActiveSlotLog :: !Integer -- TODO mgudemann make this FixedPoint,
  -- currently a problem because of
  -- NoThunks instance for FixedPoint
  }
  deriving (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
(ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> Eq ActiveSlotCoeff
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
Eq, Eq ActiveSlotCoeff
Eq ActiveSlotCoeff =>
(ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff)
-> Ord 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
$ccompare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
compare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
$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
>= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$cmax :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
max :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
$cmin :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
min :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
Ord, Int -> ActiveSlotCoeff -> ShowS
[ActiveSlotCoeff] -> ShowS
ActiveSlotCoeff -> String
(Int -> ActiveSlotCoeff -> ShowS)
-> (ActiveSlotCoeff -> String)
-> ([ActiveSlotCoeff] -> ShowS)
-> Show ActiveSlotCoeff
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActiveSlotCoeff -> ShowS
showsPrec :: Int -> ActiveSlotCoeff -> ShowS
$cshow :: ActiveSlotCoeff -> String
show :: ActiveSlotCoeff -> String
$cshowList :: [ActiveSlotCoeff] -> ShowS
showList :: [ActiveSlotCoeff] -> ShowS
Show, (forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x)
-> (forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff)
-> Generic ActiveSlotCoeff
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
$cfrom :: forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x
from :: forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x
$cto :: forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff
to :: forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff
Generic)

instance NoThunks ActiveSlotCoeff

instance NFData ActiveSlotCoeff

instance FromCBOR ActiveSlotCoeff where
  fromCBOR :: forall s. Decoder s ActiveSlotCoeff
fromCBOR = PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff (PositiveUnitInterval -> ActiveSlotCoeff)
-> Decoder s PositiveUnitInterval -> Decoder s ActiveSlotCoeff
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s PositiveUnitInterval
forall s. Decoder s PositiveUnitInterval
forall a s. FromCBOR a => Decoder s a
fromCBOR

instance ToCBOR ActiveSlotCoeff where
  toCBOR :: ActiveSlotCoeff -> Encoding
toCBOR x :: ActiveSlotCoeff
x@(ActiveSlotCoeff PositiveUnitInterval
_ Integer
_) =
    let ActiveSlotCoeff {Integer
PositiveUnitInterval
unActiveSlotVal :: ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotLog :: ActiveSlotCoeff -> Integer
unActiveSlotVal :: PositiveUnitInterval
unActiveSlotLog :: Integer
..} = ActiveSlotCoeff
x
     in -- `unActiveSlotLog` is not encoded, since it can be derived from `unActiveSlotVal`
        PositiveUnitInterval -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR PositiveUnitInterval
unActiveSlotVal

instance DecCBOR ActiveSlotCoeff

instance EncCBOR ActiveSlotCoeff

mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff PositiveUnitInterval
v =
  ActiveSlotCoeff
    { unActiveSlotVal :: PositiveUnitInterval
unActiveSlotVal = PositiveUnitInterval
v
    , unActiveSlotLog :: Integer
unActiveSlotLog =
        if PositiveUnitInterval
v PositiveUnitInterval -> PositiveUnitInterval -> Bool
forall a. Eq a => a -> a -> Bool
== PositiveUnitInterval
forall a. Bounded a => a
maxBound
          then -- If the active slot coefficient is equal to one,
          -- then nearly every stake pool can produce a block every slot.
          -- In this degenerate case, where ln (1-f) is not defined,
          -- we set the unActiveSlotLog to zero.
            Integer
0
          else
            FixedPoint -> Integer
forall b. Integral b => FixedPoint -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor
              (FixedPoint
fpPrecision FixedPoint -> FixedPoint -> FixedPoint
forall a. Num a => a -> a -> a
* FixedPoint -> FixedPoint
forall a. (RealFrac a, Enum a, Show a) => a -> a
ln' ((FixedPoint
1 :: FixedPoint) FixedPoint -> FixedPoint -> FixedPoint
forall a. Num a => a -> a -> a
- Rational -> FixedPoint
forall a. Fractional a => Rational -> a
fromRational (PositiveUnitInterval -> Rational
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 = Integer -> FixedPoint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ActiveSlotCoeff -> Integer
unActiveSlotLog ActiveSlotCoeff
f) FixedPoint -> FixedPoint -> FixedPoint
forall a. Fractional a => a -> a -> a
/ FixedPoint
fpPrecision

--------------------------------------------------------------------------------
-- Base monad for all STS systems
--------------------------------------------------------------------------------

data Globals = Globals
  { Globals -> EpochInfo (Either Text)
epochInfo :: !(EpochInfo (Either Text))
  , Globals -> Word64
slotsPerKESPeriod :: !Word64
  , Globals -> Word64
stabilityWindow :: !Word64
  -- ^ The window size in which our chosen chain growth property
  --   guarantees at least k blocks. From the paper
  --   "Ouroboros praos: An adaptively-secure, semi-synchronous proof-of-stake protocol".
  --   The 'stabilityWindow' constant is used in a number of places; for example,
  --   protocol updates must be submitted at least twice this many slots before an epoch boundary.
  , Globals -> Word64
randomnessStabilisationWindow :: !Word64
  -- ^ Number of slots before the end of the epoch at which we stop updating
  --   the candidate nonce for the next epoch.
  , Globals -> NonZero Word64
securityParameter :: !(NonZero Word64)
  -- ^ Maximum number of blocks we are allowed to roll back
  , Globals -> Word64
maxKESEvo :: !Word64
  -- ^ Maximum number of KES iterations
  , Globals -> Word64
quorum :: !Word64
  -- ^ Quorum for update system votes and MIR certificates
  , Globals -> Word64
maxLovelaceSupply :: !Word64
  -- ^ Maximum number of lovelace in the system
  , Globals -> ActiveSlotCoeff
activeSlotCoeff :: !ActiveSlotCoeff
  -- ^ Active Slot Coefficient, named f in
  -- "Ouroboros Praos: An adaptively-secure, semi-synchronous proof-of-stake protocol"
  , Globals -> Network
networkId :: !Network
  -- ^ The network ID
  , Globals -> SystemStart
systemStart :: !SystemStart
  -- ^ System start time
  }
  deriving (Int -> Globals -> ShowS
[Globals] -> ShowS
Globals -> String
(Int -> Globals -> ShowS)
-> (Globals -> String) -> ([Globals] -> ShowS) -> Show Globals
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Globals -> ShowS
showsPrec :: Int -> Globals -> ShowS
$cshow :: Globals -> String
show :: Globals -> String
$cshowList :: [Globals] -> ShowS
showList :: [Globals] -> ShowS
Show, (forall x. Globals -> Rep Globals x)
-> (forall x. Rep Globals x -> Globals) -> Generic Globals
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
$cfrom :: forall x. Globals -> Rep Globals x
from :: forall x. Globals -> Rep Globals x
$cto :: forall x. Rep Globals x -> Globals
to :: forall x. Rep Globals x -> Globals
Generic)

instance NoThunks Globals

instance NFData Globals where
  rnf :: Globals -> ()
rnf (Globals {}) = ()

type ShelleyBase = ReaderT Globals Identity

-- | Pure epoch info via throw. Note that this should only be used when we can
-- guarantee the validity of the translation; in particular, the `EpochInfo`
-- used here should never be applied to user-supplied input.
epochInfoPure :: Globals -> EpochInfo Identity
epochInfoPure :: Globals -> EpochInfo Identity
epochInfoPure = (forall a. Either Text a -> Identity a)
-> EpochInfo (Either Text) -> EpochInfo Identity
forall (m :: * -> *) (n :: * -> *).
(forall a. m a -> n a) -> EpochInfo m -> EpochInfo n
hoistEpochInfo ((Text -> Identity a)
-> (a -> Identity a) -> Either Text a -> Identity a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (EpochErr -> Identity a
forall a e. Exception e => e -> a
throw (EpochErr -> Identity a)
-> (Text -> EpochErr) -> Text -> Identity a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> EpochErr
EpochErr) a -> Identity a
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure) (EpochInfo (Either Text) -> EpochInfo Identity)
-> (Globals -> EpochInfo (Either Text))
-> Globals
-> EpochInfo Identity
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

-- | Relationship descriptor for the expectation in the 'Mismatch' type.
data Relation
  = -- | Equal
    RelEQ
  | -- | Less then
    RelLT
  | -- | Greater then
    RelGT
  | -- | Less then or equal
    RelLTEQ
  | -- | Greater then or equal
    RelGTEQ
  | -- | Is subset of
    RelSubset
  deriving (Relation -> Relation -> Bool
(Relation -> Relation -> Bool)
-> (Relation -> Relation -> Bool) -> Eq Relation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Relation -> Relation -> Bool
== :: Relation -> Relation -> Bool
$c/= :: Relation -> Relation -> Bool
/= :: Relation -> Relation -> Bool
Eq, Eq Relation
Eq Relation =>
(Relation -> Relation -> Ordering)
-> (Relation -> Relation -> Bool)
-> (Relation -> Relation -> Bool)
-> (Relation -> Relation -> Bool)
-> (Relation -> Relation -> Bool)
-> (Relation -> Relation -> Relation)
-> (Relation -> Relation -> Relation)
-> Ord 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
$ccompare :: Relation -> Relation -> Ordering
compare :: Relation -> Relation -> Ordering
$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
>= :: Relation -> Relation -> Bool
$cmax :: Relation -> Relation -> Relation
max :: Relation -> Relation -> Relation
$cmin :: Relation -> Relation -> Relation
min :: Relation -> Relation -> Relation
Ord, Int -> Relation
Relation -> Int
Relation -> [Relation]
Relation -> Relation
Relation -> Relation -> [Relation]
Relation -> Relation -> Relation -> [Relation]
(Relation -> Relation)
-> (Relation -> Relation)
-> (Int -> Relation)
-> (Relation -> Int)
-> (Relation -> [Relation])
-> (Relation -> Relation -> [Relation])
-> (Relation -> Relation -> [Relation])
-> (Relation -> Relation -> Relation -> [Relation])
-> Enum 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
$csucc :: Relation -> Relation
succ :: Relation -> Relation
$cpred :: Relation -> Relation
pred :: Relation -> Relation
$ctoEnum :: Int -> Relation
toEnum :: Int -> Relation
$cfromEnum :: Relation -> Int
fromEnum :: Relation -> Int
$cenumFrom :: Relation -> [Relation]
enumFrom :: Relation -> [Relation]
$cenumFromThen :: Relation -> Relation -> [Relation]
enumFromThen :: Relation -> Relation -> [Relation]
$cenumFromTo :: Relation -> Relation -> [Relation]
enumFromTo :: Relation -> Relation -> [Relation]
$cenumFromThenTo :: Relation -> Relation -> Relation -> [Relation]
enumFromThenTo :: Relation -> Relation -> Relation -> [Relation]
Enum, Relation
Relation -> Relation -> Bounded Relation
forall a. a -> a -> Bounded a
$cminBound :: Relation
minBound :: Relation
$cmaxBound :: Relation
maxBound :: Relation
Bounded, Int -> Relation -> ShowS
[Relation] -> ShowS
Relation -> String
(Int -> Relation -> ShowS)
-> (Relation -> String) -> ([Relation] -> ShowS) -> Show Relation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Relation -> ShowS
showsPrec :: Int -> Relation -> ShowS
$cshow :: Relation -> String
show :: Relation -> String
$cshowList :: [Relation] -> ShowS
showList :: [Relation] -> ShowS
Show, (forall x. Relation -> Rep Relation x)
-> (forall x. Rep Relation x -> Relation) -> Generic Relation
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
$cfrom :: forall x. Relation -> Rep Relation x
from :: forall x. Relation -> Rep Relation x
$cto :: forall x. Rep Relation x -> Relation
to :: forall x. Rep Relation x -> Relation
Generic, Relation -> ()
(Relation -> ()) -> NFData Relation
forall a. (a -> ()) -> NFData a
$crnf :: Relation -> ()
rnf :: Relation -> ()
NFData, [Relation] -> Value
[Relation] -> Encoding
Relation -> Bool
Relation -> Value
Relation -> Encoding
(Relation -> Value)
-> (Relation -> Encoding)
-> ([Relation] -> Value)
-> ([Relation] -> Encoding)
-> (Relation -> Bool)
-> ToJSON Relation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Relation -> Value
toJSON :: Relation -> Value
$ctoEncoding :: Relation -> Encoding
toEncoding :: Relation -> Encoding
$ctoJSONList :: [Relation] -> Value
toJSONList :: [Relation] -> Value
$ctoEncodingList :: [Relation] -> Encoding
toEncodingList :: [Relation] -> Encoding
$comitField :: Relation -> Bool
omitField :: Relation -> Bool
ToJSON, Maybe Relation
Value -> Parser [Relation]
Value -> Parser Relation
(Value -> Parser Relation)
-> (Value -> Parser [Relation])
-> Maybe Relation
-> FromJSON Relation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Relation
parseJSON :: Value -> Parser Relation
$cparseJSONList :: Value -> Parser [Relation]
parseJSONList :: Value -> Parser [Relation]
$comittedField :: Maybe Relation
omittedField :: Maybe Relation
FromJSON, Context -> Relation -> IO (Maybe ThunkInfo)
Proxy Relation -> String
(Context -> Relation -> IO (Maybe ThunkInfo))
-> (Context -> Relation -> IO (Maybe ThunkInfo))
-> (Proxy Relation -> String)
-> NoThunks Relation
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
noThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Relation -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Relation -> String
showTypeOf :: Proxy Relation -> String
NoThunks)

-- | This is intended to help clarify supplied and expected values reported by
-- predicate-failures in all eras.
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
(Mismatch r a -> Mismatch r a -> Bool)
-> (Mismatch r a -> Mismatch r a -> Bool) -> Eq (Mismatch r a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (r :: Relation) a.
Eq a =>
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
/= :: Mismatch r a -> Mismatch r a -> Bool
Eq, Eq (Mismatch r a)
Eq (Mismatch r a) =>
(Mismatch r a -> Mismatch r a -> Ordering)
-> (Mismatch r a -> Mismatch r a -> Bool)
-> (Mismatch r a -> Mismatch r a -> Bool)
-> (Mismatch r a -> Mismatch r a -> Bool)
-> (Mismatch r a -> Mismatch r a -> Bool)
-> (Mismatch r a -> Mismatch r a -> Mismatch r a)
-> (Mismatch r a -> Mismatch r a -> Mismatch r a)
-> Ord (Mismatch r a)
Mismatch r a -> Mismatch r a -> Bool
Mismatch r a -> Mismatch r a -> Ordering
Mismatch r a -> Mismatch r a -> Mismatch r a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (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
$ccompare :: forall (r :: Relation) a.
Ord a =>
Mismatch r a -> Mismatch r a -> Ordering
compare :: Mismatch r a -> Mismatch r a -> Ordering
$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
>= :: Mismatch r a -> Mismatch r a -> Bool
$cmax :: 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
$cmin :: 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
Ord, Int -> Mismatch r a -> ShowS
[Mismatch r a] -> ShowS
Mismatch r a -> String
(Int -> Mismatch r a -> ShowS)
-> (Mismatch r a -> String)
-> ([Mismatch r a] -> ShowS)
-> Show (Mismatch r a)
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
$cshowsPrec :: forall (r :: Relation) a. Show a => Int -> Mismatch r a -> ShowS
showsPrec :: Int -> Mismatch r a -> ShowS
$cshow :: forall (r :: Relation) a. Show a => Mismatch r a -> String
show :: Mismatch r a -> String
$cshowList :: forall (r :: Relation) a. Show a => [Mismatch r a] -> ShowS
showList :: [Mismatch r a] -> ShowS
Show, (forall x. Mismatch r a -> Rep (Mismatch r a) x)
-> (forall x. Rep (Mismatch r a) x -> Mismatch r a)
-> Generic (Mismatch r a)
forall x. Rep (Mismatch r a) x -> Mismatch r a
forall x. Mismatch r a -> Rep (Mismatch r a) x
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
$cfrom :: forall (r :: Relation) a x. Mismatch r a -> Rep (Mismatch r a) x
from :: forall x. Mismatch r a -> Rep (Mismatch r a) x
$cto :: forall (r :: Relation) a x. Rep (Mismatch r a) x -> Mismatch r a
to :: forall x. Rep (Mismatch r a) x -> Mismatch r a
Generic, Mismatch r a -> ()
(Mismatch r a -> ()) -> NFData (Mismatch r a)
forall a. (a -> ()) -> NFData a
forall (r :: Relation) a. NFData a => Mismatch r a -> ()
$crnf :: forall (r :: Relation) a. NFData a => Mismatch r a -> ()
rnf :: Mismatch r a -> ()
NFData, [Mismatch r a] -> Value
[Mismatch r a] -> Encoding
Mismatch r a -> Bool
Mismatch r a -> Value
Mismatch r a -> Encoding
(Mismatch r a -> Value)
-> (Mismatch r a -> Encoding)
-> ([Mismatch r a] -> Value)
-> ([Mismatch r a] -> Encoding)
-> (Mismatch r a -> Bool)
-> ToJSON (Mismatch r a)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Value
forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Encoding
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Bool
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Value
forall (r :: Relation) a. ToJSON a => Mismatch r a -> Encoding
$ctoJSON :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Value
toJSON :: Mismatch r a -> Value
$ctoEncoding :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Encoding
toEncoding :: Mismatch r a -> Encoding
$ctoJSONList :: forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Value
toJSONList :: [Mismatch r a] -> Value
$ctoEncodingList :: forall (r :: Relation) a. ToJSON a => [Mismatch r a] -> Encoding
toEncodingList :: [Mismatch r a] -> Encoding
$comitField :: forall (r :: Relation) a. ToJSON a => Mismatch r a -> Bool
omitField :: Mismatch r a -> Bool
ToJSON, Maybe (Mismatch r a)
Value -> Parser [Mismatch r a]
Value -> Parser (Mismatch r a)
(Value -> Parser (Mismatch r a))
-> (Value -> Parser [Mismatch r a])
-> Maybe (Mismatch r a)
-> FromJSON (Mismatch r a)
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)
$cparseJSON :: forall (r :: Relation) a.
FromJSON a =>
Value -> Parser (Mismatch r a)
parseJSON :: Value -> Parser (Mismatch r a)
$cparseJSONList :: forall (r :: Relation) a.
FromJSON a =>
Value -> Parser [Mismatch r a]
parseJSONList :: Value -> Parser [Mismatch r a]
$comittedField :: forall (r :: Relation) a. FromJSON a => Maybe (Mismatch r a)
omittedField :: Maybe (Mismatch r a)
FromJSON, Context -> Mismatch r a -> IO (Maybe ThunkInfo)
Proxy (Mismatch r a) -> String
(Context -> Mismatch r a -> IO (Maybe ThunkInfo))
-> (Context -> Mismatch r a -> IO (Maybe ThunkInfo))
-> (Proxy (Mismatch r a) -> String)
-> NoThunks (Mismatch r a)
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
$cnoThunks :: forall (r :: Relation) a.
NoThunks a =>
Context -> Mismatch r a -> IO (Maybe ThunkInfo)
noThunks :: Context -> Mismatch r a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (r :: Relation) a.
NoThunks a =>
Context -> Mismatch r a -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Mismatch r a -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall (r :: Relation) a.
NoThunks a =>
Proxy (Mismatch r a) -> String
showTypeOf :: Proxy (Mismatch r a) -> String
NoThunks)

-- | Convert a `Mismatch` to a tuple that has "supplied" and "expected" swapped places
swapMismatch :: Mismatch r a -> (a, a)
swapMismatch :: forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch {a
mismatchSupplied :: forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied :: a
mismatchSupplied, a
mismatchExpected :: forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected :: a
mismatchExpected} = (a
mismatchExpected, a
mismatchSupplied)

-- | Convert a tuple that has "supplied" and "expected" swapped places to a `Mismatch` type.
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) =
    Encode ('Closed 'Dense) (Mismatch Any a) -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode ('Closed 'Dense) (Mismatch Any a) -> Encoding)
-> Encode ('Closed 'Dense) (Mismatch Any a) -> Encoding
forall a b. (a -> b) -> a -> b
$
      (a -> a -> Mismatch Any a)
-> Encode ('Closed 'Dense) (a -> a -> Mismatch Any a)
forall t. t -> Encode ('Closed 'Dense) t
Rec a -> a -> Mismatch Any a
forall (r :: Relation) a. a -> a -> Mismatch r a
Mismatch
        Encode ('Closed 'Dense) (a -> a -> Mismatch Any a)
-> Encode ('Closed 'Dense) a
-> Encode ('Closed 'Dense) (a -> Mismatch Any a)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> a -> Encode ('Closed 'Dense) a
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To a
supplied
        Encode ('Closed 'Dense) (a -> Mismatch Any a)
-> Encode ('Closed 'Dense) a
-> Encode ('Closed 'Dense) (Mismatch Any a)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> a -> Encode ('Closed 'Dense) a
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 =
    Decode ('Closed 'Dense) (Mismatch r a) -> Decoder s (Mismatch r a)
forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t
decode (Decode ('Closed 'Dense) (Mismatch r a)
 -> Decoder s (Mismatch r a))
-> Decode ('Closed 'Dense) (Mismatch r a)
-> Decoder s (Mismatch r a)
forall a b. (a -> b) -> a -> b
$
      (a -> a -> Mismatch r a)
-> Decode ('Closed 'Dense) (a -> a -> Mismatch r a)
forall t. t -> Decode ('Closed 'Dense) t
RecD a -> a -> Mismatch r a
forall (r :: Relation) a. a -> a -> Mismatch r a
Mismatch
        Decode ('Closed 'Dense) (a -> a -> Mismatch r a)
-> Decode ('Closed Any) a
-> Decode ('Closed 'Dense) (a -> Mismatch r a)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) a
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode ('Closed 'Dense) (a -> Mismatch r a)
-> Decode ('Closed Any) a -> Decode ('Closed 'Dense) (Mismatch r a)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) a
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
mismatchSupplied :: forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected :: forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied :: a
mismatchExpected :: a
..} = a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
mismatchSupplied Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size_ (Mismatch r a -> a
forall (r :: Relation) a. Mismatch r a -> a
mismatchSupplied (Mismatch r a -> a) -> Proxy (Mismatch r a) -> Proxy a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Mismatch r a)
proxy)
      Size -> Size -> Size
forall a. Num a => a -> a -> a
+ (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size_ (Mismatch r a -> a
forall (r :: Relation) a. Mismatch r a -> a
mismatchExpected (Mismatch r a -> a) -> Proxy (Mismatch r a) -> Proxy a
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 <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
    a
mismatchExpected <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
    Mismatch r a -> Decoder s (Mismatch r a)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mismatch {a
mismatchSupplied :: a
mismatchExpected :: a
mismatchSupplied :: a
mismatchExpected :: a
..}

data Network
  = Testnet
  | Mainnet
  deriving (Network -> Network -> Bool
(Network -> Network -> Bool)
-> (Network -> Network -> Bool) -> Eq Network
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Network -> Network -> Bool
== :: Network -> Network -> Bool
$c/= :: Network -> Network -> Bool
/= :: Network -> Network -> Bool
Eq, Eq Network
Eq Network =>
(Network -> Network -> Ordering)
-> (Network -> Network -> Bool)
-> (Network -> Network -> Bool)
-> (Network -> Network -> Bool)
-> (Network -> Network -> Bool)
-> (Network -> Network -> Network)
-> (Network -> Network -> Network)
-> Ord 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
$ccompare :: Network -> Network -> Ordering
compare :: Network -> Network -> Ordering
$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
>= :: Network -> Network -> Bool
$cmax :: Network -> Network -> Network
max :: Network -> Network -> Network
$cmin :: Network -> Network -> Network
min :: Network -> Network -> Network
Ord, Int -> Network
Network -> Int
Network -> [Network]
Network -> Network
Network -> Network -> [Network]
Network -> Network -> Network -> [Network]
(Network -> Network)
-> (Network -> Network)
-> (Int -> Network)
-> (Network -> Int)
-> (Network -> [Network])
-> (Network -> Network -> [Network])
-> (Network -> Network -> [Network])
-> (Network -> Network -> Network -> [Network])
-> Enum 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
$csucc :: Network -> Network
succ :: Network -> Network
$cpred :: Network -> Network
pred :: Network -> Network
$ctoEnum :: Int -> Network
toEnum :: Int -> Network
$cfromEnum :: Network -> Int
fromEnum :: Network -> Int
$cenumFrom :: Network -> [Network]
enumFrom :: Network -> [Network]
$cenumFromThen :: Network -> Network -> [Network]
enumFromThen :: Network -> Network -> [Network]
$cenumFromTo :: Network -> Network -> [Network]
enumFromTo :: Network -> Network -> [Network]
$cenumFromThenTo :: Network -> Network -> Network -> [Network]
enumFromThenTo :: Network -> Network -> Network -> [Network]
Enum, Network
Network -> Network -> Bounded Network
forall a. a -> a -> Bounded a
$cminBound :: Network
minBound :: Network
$cmaxBound :: Network
maxBound :: Network
Bounded, Int -> Network -> ShowS
[Network] -> ShowS
Network -> String
(Int -> Network -> ShowS)
-> (Network -> String) -> ([Network] -> ShowS) -> Show Network
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Network -> ShowS
showsPrec :: Int -> Network -> ShowS
$cshow :: Network -> String
show :: Network -> String
$cshowList :: [Network] -> ShowS
showList :: [Network] -> ShowS
Show, (forall x. Network -> Rep Network x)
-> (forall x. Rep Network x -> Network) -> Generic Network
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
$cfrom :: forall x. Network -> Rep Network x
from :: forall x. Network -> Rep Network x
$cto :: forall x. Rep Network x -> Network
to :: forall x. Rep Network x -> Network
Generic, Network -> ()
(Network -> ()) -> NFData Network
forall a. (a -> ()) -> NFData a
$crnf :: Network -> ()
rnf :: Network -> ()
NFData, [Network] -> Value
[Network] -> Encoding
Network -> Bool
Network -> Value
Network -> Encoding
(Network -> Value)
-> (Network -> Encoding)
-> ([Network] -> Value)
-> ([Network] -> Encoding)
-> (Network -> Bool)
-> ToJSON Network
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Network -> Value
toJSON :: Network -> Value
$ctoEncoding :: Network -> Encoding
toEncoding :: Network -> Encoding
$ctoJSONList :: [Network] -> Value
toJSONList :: [Network] -> Value
$ctoEncodingList :: [Network] -> Encoding
toEncodingList :: [Network] -> Encoding
$comitField :: Network -> Bool
omitField :: Network -> Bool
ToJSON, Maybe Network
Value -> Parser [Network]
Value -> Parser Network
(Value -> Parser Network)
-> (Value -> Parser [Network]) -> Maybe Network -> FromJSON Network
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Network
parseJSON :: Value -> Parser Network
$cparseJSONList :: Value -> Parser [Network]
parseJSONList :: Value -> Parser [Network]
$comittedField :: Maybe Network
omittedField :: Maybe Network
FromJSON, Context -> Network -> IO (Maybe ThunkInfo)
Proxy Network -> String
(Context -> Network -> IO (Maybe ThunkInfo))
-> (Context -> Network -> IO (Maybe ThunkInfo))
-> (Proxy Network -> String)
-> NoThunks Network
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
noThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy Network -> String
showTypeOf :: Proxy Network -> String
NoThunks)

networkToWord8 :: Network -> Word8
networkToWord8 :: Network -> Word8
networkToWord8 = Int -> Word8
forall a. Enum a => Int -> a
toEnum (Int -> Word8) -> (Network -> Int) -> Network -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Int
forall a. Enum a => a -> Int
fromEnum

word8ToNetwork :: Word8 -> Maybe Network
word8ToNetwork :: Word8 -> Maybe Network
word8ToNetwork Word8
e
  | Word8 -> Int
forall a. Enum a => a -> Int
fromEnum Word8
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Network -> Int
forall a. Enum a => a -> Int
fromEnum (Network
forall a. Bounded a => a
maxBound :: Network) = Maybe Network
forall a. Maybe a
Nothing
  | Word8 -> Int
forall a. Enum a => a -> Int
fromEnum Word8
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Network -> Int
forall a. Enum a => a -> Int
fromEnum (Network
forall a. Bounded a => a
minBound :: Network) = Maybe Network
forall a. Maybe a
Nothing
  | Bool
otherwise = Network -> Maybe Network
forall a. a -> Maybe a
Just (Network -> Maybe Network) -> Network -> Maybe Network
forall a b. (a -> b) -> a -> b
$ Int -> Network
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a. Enum a => a -> Int
fromEnum Word8
e)

instance FromCBOR Network where
  fromCBOR :: forall s. Decoder s Network
fromCBOR = do
    Word8
w8 <- Decoder s Word8
forall s. Decoder s Word8
decodeWord8
    case Word8 -> Maybe Network
word8ToNetwork Word8
w8 of
      Maybe Network
Nothing -> DecoderError -> Decoder s Network
forall (m :: * -> *) e a. (MonadFail m, Buildable e) => e -> m a
cborError (DecoderError -> Decoder s Network)
-> DecoderError -> Decoder s Network
forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"Network" Text
"Unknown network id"
      Just Network
n -> Network -> Decoder s Network
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Network
n
  {-# INLINE fromCBOR #-}

instance ToCBOR Network where
  toCBOR :: Network -> Encoding
toCBOR = Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8 -> Encoding) -> (Network -> Word8) -> Network -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Word8
networkToWord8

instance EncCBOR Network

instance DecCBOR Network

-- | Number of blocks which have been created by stake pools in the current epoch.
newtype BlocksMade = BlocksMade
  { BlocksMade -> Map (KeyHash 'StakePool) Natural
unBlocksMade :: Map (KeyHash 'StakePool) Natural
  }
  deriving (BlocksMade -> BlocksMade -> Bool
(BlocksMade -> BlocksMade -> Bool)
-> (BlocksMade -> BlocksMade -> Bool) -> Eq BlocksMade
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlocksMade -> BlocksMade -> Bool
== :: BlocksMade -> BlocksMade -> Bool
$c/= :: BlocksMade -> BlocksMade -> Bool
/= :: BlocksMade -> BlocksMade -> Bool
Eq, (forall x. BlocksMade -> Rep BlocksMade x)
-> (forall x. Rep BlocksMade x -> BlocksMade) -> Generic BlocksMade
forall x. Rep BlocksMade x -> BlocksMade
forall x. BlocksMade -> Rep BlocksMade x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BlocksMade -> Rep BlocksMade x
from :: forall x. BlocksMade -> Rep BlocksMade x
$cto :: forall x. Rep BlocksMade x -> BlocksMade
to :: forall x. Rep BlocksMade x -> BlocksMade
Generic)
  deriving (Int -> BlocksMade -> ShowS
[BlocksMade] -> ShowS
BlocksMade -> String
(Int -> BlocksMade -> ShowS)
-> (BlocksMade -> String)
-> ([BlocksMade] -> ShowS)
-> Show BlocksMade
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlocksMade -> ShowS
showsPrec :: Int -> BlocksMade -> ShowS
$cshow :: BlocksMade -> String
show :: BlocksMade -> String
$cshowList :: [BlocksMade] -> ShowS
showList :: [BlocksMade] -> ShowS
Show) via Quiet BlocksMade
  deriving newtype (Context -> BlocksMade -> IO (Maybe ThunkInfo)
Proxy BlocksMade -> String
(Context -> BlocksMade -> IO (Maybe ThunkInfo))
-> (Context -> BlocksMade -> IO (Maybe ThunkInfo))
-> (Proxy BlocksMade -> String)
-> NoThunks BlocksMade
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> BlocksMade -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlocksMade -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> BlocksMade -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> BlocksMade -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy BlocksMade -> String
showTypeOf :: Proxy BlocksMade -> String
NoThunks, BlocksMade -> ()
(BlocksMade -> ()) -> NFData BlocksMade
forall a. (a -> ()) -> NFData a
$crnf :: BlocksMade -> ()
rnf :: BlocksMade -> ()
NFData, [BlocksMade] -> Value
[BlocksMade] -> Encoding
BlocksMade -> Bool
BlocksMade -> Value
BlocksMade -> Encoding
(BlocksMade -> Value)
-> (BlocksMade -> Encoding)
-> ([BlocksMade] -> Value)
-> ([BlocksMade] -> Encoding)
-> (BlocksMade -> Bool)
-> ToJSON BlocksMade
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BlocksMade -> Value
toJSON :: BlocksMade -> Value
$ctoEncoding :: BlocksMade -> Encoding
toEncoding :: BlocksMade -> Encoding
$ctoJSONList :: [BlocksMade] -> Value
toJSONList :: [BlocksMade] -> Value
$ctoEncodingList :: [BlocksMade] -> Encoding
toEncodingList :: [BlocksMade] -> Encoding
$comitField :: BlocksMade -> Bool
omitField :: BlocksMade -> Bool
ToJSON, Maybe BlocksMade
Value -> Parser [BlocksMade]
Value -> Parser BlocksMade
(Value -> Parser BlocksMade)
-> (Value -> Parser [BlocksMade])
-> Maybe BlocksMade
-> FromJSON BlocksMade
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BlocksMade
parseJSON :: Value -> Parser BlocksMade
$cparseJSONList :: Value -> Parser [BlocksMade]
parseJSONList :: Value -> Parser [BlocksMade]
$comittedField :: Maybe BlocksMade
omittedField :: Maybe BlocksMade
FromJSON, Typeable BlocksMade
Typeable BlocksMade =>
(BlocksMade -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy BlocksMade -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [BlocksMade] -> Size)
-> EncCBOR BlocksMade
BlocksMade -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlocksMade -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
$cencCBOR :: BlocksMade -> Encoding
encCBOR :: BlocksMade -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlocksMade -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy BlocksMade -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade] -> Size
EncCBOR, Typeable BlocksMade
Typeable BlocksMade =>
(forall s. Decoder s BlocksMade)
-> (forall s. Proxy BlocksMade -> Decoder s ())
-> (Proxy BlocksMade -> Text)
-> DecCBOR BlocksMade
Proxy BlocksMade -> Text
forall s. Decoder s BlocksMade
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy BlocksMade -> Decoder s ()
$cdecCBOR :: forall s. Decoder s BlocksMade
decCBOR :: forall s. Decoder s BlocksMade
$cdropCBOR :: forall s. Proxy BlocksMade -> Decoder s ()
dropCBOR :: forall s. Proxy BlocksMade -> Decoder s ()
$clabel :: Proxy BlocksMade -> Text
label :: Proxy BlocksMade -> Text
DecCBOR)

-- | Transaction index.
newtype TxIx = TxIx {TxIx -> Word16
unTxIx :: Word16}
  deriving stock (TxIx -> TxIx -> Bool
(TxIx -> TxIx -> Bool) -> (TxIx -> TxIx -> Bool) -> Eq TxIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxIx -> TxIx -> Bool
== :: TxIx -> TxIx -> Bool
$c/= :: TxIx -> TxIx -> Bool
/= :: TxIx -> TxIx -> Bool
Eq, Eq TxIx
Eq TxIx =>
(TxIx -> TxIx -> Ordering)
-> (TxIx -> TxIx -> Bool)
-> (TxIx -> TxIx -> Bool)
-> (TxIx -> TxIx -> Bool)
-> (TxIx -> TxIx -> Bool)
-> (TxIx -> TxIx -> TxIx)
-> (TxIx -> TxIx -> TxIx)
-> Ord 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
$ccompare :: TxIx -> TxIx -> Ordering
compare :: TxIx -> TxIx -> Ordering
$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
>= :: TxIx -> TxIx -> Bool
$cmax :: TxIx -> TxIx -> TxIx
max :: TxIx -> TxIx -> TxIx
$cmin :: TxIx -> TxIx -> TxIx
min :: TxIx -> TxIx -> TxIx
Ord, Int -> TxIx -> ShowS
[TxIx] -> ShowS
TxIx -> String
(Int -> TxIx -> ShowS)
-> (TxIx -> String) -> ([TxIx] -> ShowS) -> Show TxIx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxIx -> ShowS
showsPrec :: Int -> TxIx -> ShowS
$cshow :: TxIx -> String
show :: TxIx -> String
$cshowList :: [TxIx] -> ShowS
showList :: [TxIx] -> ShowS
Show, (forall x. TxIx -> Rep TxIx x)
-> (forall x. Rep TxIx x -> TxIx) -> Generic TxIx
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
$cfrom :: forall x. TxIx -> Rep TxIx x
from :: forall x. TxIx -> Rep TxIx x
$cto :: forall x. Rep TxIx x -> TxIx
to :: forall x. Rep TxIx x -> TxIx
Generic)
  deriving newtype
    (TxIx -> ()
(TxIx -> ()) -> NFData TxIx
forall a. (a -> ()) -> NFData a
$crnf :: TxIx -> ()
rnf :: TxIx -> ()
NFData, Int -> TxIx
TxIx -> Int
TxIx -> [TxIx]
TxIx -> TxIx
TxIx -> TxIx -> [TxIx]
TxIx -> TxIx -> TxIx -> [TxIx]
(TxIx -> TxIx)
-> (TxIx -> TxIx)
-> (Int -> TxIx)
-> (TxIx -> Int)
-> (TxIx -> [TxIx])
-> (TxIx -> TxIx -> [TxIx])
-> (TxIx -> TxIx -> [TxIx])
-> (TxIx -> TxIx -> TxIx -> [TxIx])
-> Enum 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
$csucc :: TxIx -> TxIx
succ :: TxIx -> TxIx
$cpred :: TxIx -> TxIx
pred :: TxIx -> TxIx
$ctoEnum :: Int -> TxIx
toEnum :: Int -> TxIx
$cfromEnum :: TxIx -> Int
fromEnum :: TxIx -> Int
$cenumFrom :: TxIx -> [TxIx]
enumFrom :: TxIx -> [TxIx]
$cenumFromThen :: TxIx -> TxIx -> [TxIx]
enumFromThen :: TxIx -> TxIx -> [TxIx]
$cenumFromTo :: TxIx -> TxIx -> [TxIx]
enumFromTo :: TxIx -> TxIx -> [TxIx]
$cenumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
enumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
Enum, TxIx
TxIx -> TxIx -> Bounded TxIx
forall a. a -> a -> Bounded a
$cminBound :: TxIx
minBound :: TxIx
$cmaxBound :: TxIx
maxBound :: TxIx
Bounded, Context -> TxIx -> IO (Maybe ThunkInfo)
Proxy TxIx -> String
(Context -> TxIx -> IO (Maybe ThunkInfo))
-> (Context -> TxIx -> IO (Maybe ThunkInfo))
-> (Proxy TxIx -> String)
-> NoThunks TxIx
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy TxIx -> String
showTypeOf :: Proxy TxIx -> String
NoThunks, Typeable TxIx
Typeable TxIx =>
(forall s. Decoder s TxIx) -> (Proxy TxIx -> Text) -> FromCBOR TxIx
Proxy TxIx -> Text
forall s. Decoder s TxIx
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s TxIx
fromCBOR :: forall s. Decoder s TxIx
$clabel :: Proxy TxIx -> Text
label :: Proxy TxIx -> Text
FromCBOR, Typeable TxIx
Typeable TxIx =>
(TxIx -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [TxIx] -> Size)
-> ToCBOR 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
$ctoCBOR :: TxIx -> Encoding
toCBOR :: TxIx -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
ToCBOR, Typeable TxIx
Typeable TxIx =>
(TxIx -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [TxIx] -> Size)
-> EncCBOR 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
$cencCBOR :: TxIx -> Encoding
encCBOR :: TxIx -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
EncCBOR, Typeable TxIx
Typeable TxIx =>
(forall s. Decoder s TxIx)
-> (forall s. Proxy TxIx -> Decoder s ())
-> (Proxy TxIx -> Text)
-> DecCBOR TxIx
Proxy TxIx -> Text
forall s. Decoder s TxIx
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy TxIx -> Decoder s ()
$cdecCBOR :: forall s. Decoder s TxIx
decCBOR :: forall s. Decoder s TxIx
$cdropCBOR :: forall s. Proxy TxIx -> Decoder s ()
dropCBOR :: forall s. Proxy TxIx -> Decoder s ()
$clabel :: Proxy TxIx -> Text
label :: Proxy TxIx -> Text
DecCBOR, [TxIx] -> Value
[TxIx] -> Encoding
TxIx -> Bool
TxIx -> Value
TxIx -> Encoding
(TxIx -> Value)
-> (TxIx -> Encoding)
-> ([TxIx] -> Value)
-> ([TxIx] -> Encoding)
-> (TxIx -> Bool)
-> ToJSON TxIx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: TxIx -> Value
toJSON :: TxIx -> Value
$ctoEncoding :: TxIx -> Encoding
toEncoding :: TxIx -> Encoding
$ctoJSONList :: [TxIx] -> Value
toJSONList :: [TxIx] -> Value
$ctoEncodingList :: [TxIx] -> Encoding
toEncodingList :: [TxIx] -> Encoding
$comitField :: TxIx -> Bool
omitField :: TxIx -> Bool
ToJSON, String
String
-> (TxIx -> Int)
-> (forall s. TxIx -> Pack s ())
-> (forall b. Buffer b => Unpack b TxIx)
-> MemPack TxIx
TxIx -> Int
forall a.
String
-> (a -> Int)
-> (forall s. a -> Pack s ())
-> (forall b. Buffer b => Unpack b a)
-> MemPack a
forall b. Buffer b => Unpack b TxIx
forall s. TxIx -> Pack s ()
$ctypeName :: String
typeName :: String
$cpackedByteCount :: TxIx -> Int
packedByteCount :: TxIx -> Int
$cpackM :: forall s. TxIx -> Pack s ()
packM :: forall s. TxIx -> Pack s ()
$cunpackM :: forall b. Buffer b => Unpack b TxIx
unpackM :: forall b. Buffer b => Unpack b TxIx
MemPack)

-- | Construct a `TxIx` from a 16 bit unsigned integer
mkTxIx :: Word16 -> TxIx
mkTxIx :: Word16 -> TxIx
mkTxIx = Word16 -> TxIx
TxIx (Word16 -> TxIx) -> (Word16 -> Word16) -> Word16 -> TxIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# DEPRECATED mkTxIx "In favor of `TxIx`" #-}

txIxToInt :: TxIx -> Int
txIxToInt :: TxIx -> Int
txIxToInt (TxIx Word16
w16) = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w16

txIxFromIntegral :: forall a m. (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral :: forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral = (Word16 -> TxIx) -> m Word16 -> m TxIx
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word16 -> TxIx
TxIx (Word16 -> TxIx) -> (Word16 -> Word16) -> Word16 -> TxIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (m Word16 -> m TxIx) -> (a -> m Word16) -> a -> m TxIx
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 #-}

-- | Construct a `TxIx` from an arbitrary precision `Integer`. Throws an error for
-- values out of range. Make sure to use it only for testing.
mkTxIxPartial :: HasCallStack => Integer -> TxIx
mkTxIxPartial :: HasCallStack => Integer -> TxIx
mkTxIxPartial Integer
i =
  TxIx -> Maybe TxIx -> TxIx
forall a. a -> Maybe a -> a
fromMaybe (String -> TxIx
forall a. HasCallStack => String -> a
error (String -> TxIx) -> String -> TxIx
forall a b. (a -> b) -> a -> b
$ String
"Value for TxIx is out of a valid range: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i) (Maybe TxIx -> TxIx) -> Maybe TxIx -> TxIx
forall a b. (a -> b) -> a -> b
$
    Integer -> Maybe TxIx
forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m TxIx
txIxFromIntegral Integer
i

-- | Certificate index. There is `mkCertIxPartial` that can be used for testing when constructing
-- from other integral types that are larger than `Word16`
newtype CertIx = CertIx {CertIx -> Word16
unCertIx :: Word16}
  deriving stock (CertIx -> CertIx -> Bool
(CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> Bool) -> Eq CertIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CertIx -> CertIx -> Bool
== :: CertIx -> CertIx -> Bool
$c/= :: CertIx -> CertIx -> Bool
/= :: CertIx -> CertIx -> Bool
Eq, Eq CertIx
Eq CertIx =>
(CertIx -> CertIx -> Ordering)
-> (CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> CertIx)
-> (CertIx -> CertIx -> CertIx)
-> Ord 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
$ccompare :: CertIx -> CertIx -> Ordering
compare :: CertIx -> CertIx -> Ordering
$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
>= :: CertIx -> CertIx -> Bool
$cmax :: CertIx -> CertIx -> CertIx
max :: CertIx -> CertIx -> CertIx
$cmin :: CertIx -> CertIx -> CertIx
min :: CertIx -> CertIx -> CertIx
Ord, Int -> CertIx -> ShowS
[CertIx] -> ShowS
CertIx -> String
(Int -> CertIx -> ShowS)
-> (CertIx -> String) -> ([CertIx] -> ShowS) -> Show CertIx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CertIx -> ShowS
showsPrec :: Int -> CertIx -> ShowS
$cshow :: CertIx -> String
show :: CertIx -> String
$cshowList :: [CertIx] -> ShowS
showList :: [CertIx] -> ShowS
Show)
  deriving newtype (CertIx -> ()
(CertIx -> ()) -> NFData CertIx
forall a. (a -> ()) -> NFData a
$crnf :: CertIx -> ()
rnf :: CertIx -> ()
NFData, Int -> CertIx
CertIx -> Int
CertIx -> [CertIx]
CertIx -> CertIx
CertIx -> CertIx -> [CertIx]
CertIx -> CertIx -> CertIx -> [CertIx]
(CertIx -> CertIx)
-> (CertIx -> CertIx)
-> (Int -> CertIx)
-> (CertIx -> Int)
-> (CertIx -> [CertIx])
-> (CertIx -> CertIx -> [CertIx])
-> (CertIx -> CertIx -> [CertIx])
-> (CertIx -> CertIx -> CertIx -> [CertIx])
-> Enum 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
$csucc :: CertIx -> CertIx
succ :: CertIx -> CertIx
$cpred :: CertIx -> CertIx
pred :: CertIx -> CertIx
$ctoEnum :: Int -> CertIx
toEnum :: Int -> CertIx
$cfromEnum :: CertIx -> Int
fromEnum :: CertIx -> Int
$cenumFrom :: CertIx -> [CertIx]
enumFrom :: CertIx -> [CertIx]
$cenumFromThen :: CertIx -> CertIx -> [CertIx]
enumFromThen :: CertIx -> CertIx -> [CertIx]
$cenumFromTo :: CertIx -> CertIx -> [CertIx]
enumFromTo :: CertIx -> CertIx -> [CertIx]
$cenumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
enumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
Enum, CertIx
CertIx -> CertIx -> Bounded CertIx
forall a. a -> a -> Bounded a
$cminBound :: CertIx
minBound :: CertIx
$cmaxBound :: CertIx
maxBound :: CertIx
Bounded, Context -> CertIx -> IO (Maybe ThunkInfo)
Proxy CertIx -> String
(Context -> CertIx -> IO (Maybe ThunkInfo))
-> (Context -> CertIx -> IO (Maybe ThunkInfo))
-> (Proxy CertIx -> String)
-> NoThunks CertIx
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy CertIx -> String
showTypeOf :: Proxy CertIx -> String
NoThunks, Typeable CertIx
Typeable CertIx =>
(CertIx -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy CertIx -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size)
    -> Proxy [CertIx] -> Size)
-> EncCBOR 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
$cencCBOR :: CertIx -> Encoding
encCBOR :: CertIx -> Encoding
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
EncCBOR, Typeable CertIx
Typeable CertIx =>
(forall s. Decoder s CertIx)
-> (forall s. Proxy CertIx -> Decoder s ())
-> (Proxy CertIx -> Text)
-> DecCBOR CertIx
Proxy CertIx -> Text
forall s. Decoder s CertIx
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy CertIx -> Decoder s ()
$cdecCBOR :: forall s. Decoder s CertIx
decCBOR :: forall s. Decoder s CertIx
$cdropCBOR :: forall s. Proxy CertIx -> Decoder s ()
dropCBOR :: forall s. Proxy CertIx -> Decoder s ()
$clabel :: Proxy CertIx -> Text
label :: Proxy CertIx -> Text
DecCBOR, Typeable CertIx
Typeable CertIx =>
(CertIx -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy CertIx -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [CertIx] -> Size)
-> ToCBOR 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
$ctoCBOR :: CertIx -> Encoding
toCBOR :: CertIx -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
ToCBOR, Typeable CertIx
Typeable CertIx =>
(forall s. Decoder s CertIx)
-> (Proxy CertIx -> Text) -> FromCBOR CertIx
Proxy CertIx -> Text
forall s. Decoder s CertIx
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s CertIx
fromCBOR :: forall s. Decoder s CertIx
$clabel :: Proxy CertIx -> Text
label :: Proxy CertIx -> Text
FromCBOR, [CertIx] -> Value
[CertIx] -> Encoding
CertIx -> Bool
CertIx -> Value
CertIx -> Encoding
(CertIx -> Value)
-> (CertIx -> Encoding)
-> ([CertIx] -> Value)
-> ([CertIx] -> Encoding)
-> (CertIx -> Bool)
-> ToJSON CertIx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CertIx -> Value
toJSON :: CertIx -> Value
$ctoEncoding :: CertIx -> Encoding
toEncoding :: CertIx -> Encoding
$ctoJSONList :: [CertIx] -> Value
toJSONList :: [CertIx] -> Value
$ctoEncodingList :: [CertIx] -> Encoding
toEncodingList :: [CertIx] -> Encoding
$comitField :: CertIx -> Bool
omitField :: CertIx -> Bool
ToJSON)

-- | Construct a `CertIx` from a 16 bit unsigned integer
mkCertIx :: Word16 -> CertIx
mkCertIx :: Word16 -> CertIx
mkCertIx = Word16 -> CertIx
CertIx (Word16 -> CertIx) -> (Word16 -> Word16) -> Word16 -> CertIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# DEPRECATED mkCertIx "In favor of `CertIx`" #-}

certIxToInt :: CertIx -> Int
certIxToInt :: CertIx -> Int
certIxToInt (CertIx Word16
w16) = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w16

certIxFromIntegral :: forall a m. (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral :: forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral = (Word16 -> CertIx) -> m Word16 -> m CertIx
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word16 -> CertIx
CertIx (Word16 -> CertIx) -> (Word16 -> Word16) -> Word16 -> CertIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (m Word16 -> m CertIx) -> (a -> m Word16) -> a -> m CertIx
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 #-}

-- | Construct a `CertIx` from an arbitrary precision `Integer`. Throws an error for
-- values out of range. Make sure to use it only for testing.
mkCertIxPartial :: HasCallStack => Integer -> CertIx
mkCertIxPartial :: HasCallStack => Integer -> CertIx
mkCertIxPartial Integer
i =
  CertIx -> Maybe CertIx -> CertIx
forall a. a -> Maybe a -> a
fromMaybe (String -> CertIx
forall a. HasCallStack => String -> a
error (String -> CertIx) -> String -> CertIx
forall a b. (a -> b) -> a -> b
$ String
"Value for CertIx is out of a valid range: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i) (Maybe CertIx -> CertIx) -> Maybe CertIx -> CertIx
forall a b. (a -> b) -> a -> b
$
    Integer -> Maybe CertIx
forall a (m :: * -> *). (Integral a, MonadFail m) => a -> m CertIx
certIxFromIntegral Integer
i

-- =================================

newtype AnchorData = AnchorData ByteString
  deriving (AnchorData -> AnchorData -> Bool
(AnchorData -> AnchorData -> Bool)
-> (AnchorData -> AnchorData -> Bool) -> Eq AnchorData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnchorData -> AnchorData -> Bool
== :: AnchorData -> AnchorData -> Bool
$c/= :: AnchorData -> AnchorData -> Bool
/= :: AnchorData -> AnchorData -> Bool
Eq)
  deriving newtype (AnchorData -> Int
AnchorData -> ByteString
(AnchorData -> ByteString)
-> (AnchorData -> Int)
-> (forall i. Proxy i -> AnchorData -> SafeHash i)
-> SafeToHash AnchorData
forall i. Proxy i -> AnchorData -> SafeHash i
forall t.
(t -> ByteString)
-> (t -> Int)
-> (forall i. Proxy i -> t -> SafeHash i)
-> SafeToHash t
$coriginalBytes :: AnchorData -> ByteString
originalBytes :: AnchorData -> ByteString
$coriginalBytesSize :: AnchorData -> Int
originalBytesSize :: AnchorData -> Int
$cmakeHashWithExplicitProxys :: forall i. Proxy i -> AnchorData -> SafeHash i
makeHashWithExplicitProxys :: forall i. Proxy i -> AnchorData -> SafeHash i
SafeToHash)

instance HashAnnotated AnchorData AnchorData

-- | Hash `AnchorData`
hashAnchorData :: AnchorData -> SafeHash AnchorData
hashAnchorData :: AnchorData -> SafeHash AnchorData
hashAnchorData = AnchorData -> SafeHash AnchorData
forall x i. HashAnnotated x i => x -> SafeHash i
hashAnnotated
{-# DEPRECATED hashAnchorData "In favor of `hashAnnotated`" #-}

data Anchor = Anchor
  { Anchor -> Url
anchorUrl :: !Url
  , Anchor -> SafeHash AnchorData
anchorDataHash :: !(SafeHash AnchorData)
  }
  deriving (Anchor -> Anchor -> Bool
(Anchor -> Anchor -> Bool)
-> (Anchor -> Anchor -> Bool) -> Eq Anchor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Anchor -> Anchor -> Bool
== :: Anchor -> Anchor -> Bool
$c/= :: Anchor -> Anchor -> Bool
/= :: Anchor -> Anchor -> Bool
Eq, Eq Anchor
Eq Anchor =>
(Anchor -> Anchor -> Ordering)
-> (Anchor -> Anchor -> Bool)
-> (Anchor -> Anchor -> Bool)
-> (Anchor -> Anchor -> Bool)
-> (Anchor -> Anchor -> Bool)
-> (Anchor -> Anchor -> Anchor)
-> (Anchor -> Anchor -> Anchor)
-> Ord Anchor
Anchor -> Anchor -> Bool
Anchor -> Anchor -> Ordering
Anchor -> Anchor -> Anchor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Anchor -> Anchor -> Ordering
compare :: Anchor -> Anchor -> Ordering
$c< :: Anchor -> Anchor -> Bool
< :: Anchor -> Anchor -> Bool
$c<= :: Anchor -> Anchor -> Bool
<= :: Anchor -> Anchor -> Bool
$c> :: Anchor -> Anchor -> Bool
> :: Anchor -> Anchor -> Bool
$c>= :: Anchor -> Anchor -> Bool
>= :: Anchor -> Anchor -> Bool
$cmax :: Anchor -> Anchor -> Anchor
max :: Anchor -> Anchor -> Anchor
$cmin :: Anchor -> Anchor -> Anchor
min :: Anchor -> Anchor -> Anchor
Ord, Int -> Anchor -> ShowS
[Anchor] -> ShowS
Anchor -> String
(Int -> Anchor -> ShowS)
-> (Anchor -> String) -> ([Anchor] -> ShowS) -> Show Anchor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Anchor -> ShowS
showsPrec :: Int -> Anchor -> ShowS
$cshow :: Anchor -> String
show :: Anchor -> String
$cshowList :: [Anchor] -> ShowS
showList :: [Anchor] -> ShowS
Show, (forall x. Anchor -> Rep Anchor x)
-> (forall x. Rep Anchor x -> Anchor) -> Generic Anchor
forall x. Rep Anchor x -> Anchor
forall x. Anchor -> Rep Anchor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Anchor -> Rep Anchor x
from :: forall x. Anchor -> Rep Anchor x
$cto :: forall x. Rep Anchor x -> Anchor
to :: forall x. Rep Anchor x -> Anchor
Generic)

instance NoThunks Anchor

instance NFData Anchor where
  rnf :: Anchor -> ()
rnf = Anchor -> ()
forall a. a -> ()
rwhnf

instance DecCBOR Anchor where
  decCBOR :: forall s. Decoder s Anchor
decCBOR =
    Decode ('Closed 'Dense) Anchor -> Decoder s Anchor
forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t
decode (Decode ('Closed 'Dense) Anchor -> Decoder s Anchor)
-> Decode ('Closed 'Dense) Anchor -> Decoder s Anchor
forall a b. (a -> b) -> a -> b
$
      (Url -> SafeHash AnchorData -> Anchor)
-> Decode ('Closed 'Dense) (Url -> SafeHash AnchorData -> Anchor)
forall t. t -> Decode ('Closed 'Dense) t
RecD Url -> SafeHash AnchorData -> Anchor
Anchor
        Decode ('Closed 'Dense) (Url -> SafeHash AnchorData -> Anchor)
-> Decode ('Closed Any) Url
-> Decode ('Closed 'Dense) (SafeHash AnchorData -> Anchor)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Url
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode ('Closed 'Dense) (SafeHash AnchorData -> Anchor)
-> Decode ('Closed Any) (SafeHash AnchorData)
-> Decode ('Closed 'Dense) Anchor
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (SafeHash AnchorData)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From

instance EncCBOR Anchor where
  encCBOR :: Anchor -> Encoding
encCBOR Anchor {SafeHash AnchorData
Url
anchorUrl :: Anchor -> Url
anchorDataHash :: Anchor -> SafeHash AnchorData
anchorUrl :: Url
anchorDataHash :: SafeHash AnchorData
..} =
    Encode ('Closed 'Dense) Anchor -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode ('Closed 'Dense) Anchor -> Encoding)
-> Encode ('Closed 'Dense) Anchor -> Encoding
forall a b. (a -> b) -> a -> b
$
      (Url -> SafeHash AnchorData -> Anchor)
-> Encode ('Closed 'Dense) (Url -> SafeHash AnchorData -> Anchor)
forall t. t -> Encode ('Closed 'Dense) t
Rec Url -> SafeHash AnchorData -> Anchor
Anchor
        Encode ('Closed 'Dense) (Url -> SafeHash AnchorData -> Anchor)
-> Encode ('Closed 'Dense) Url
-> Encode ('Closed 'Dense) (SafeHash AnchorData -> Anchor)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Url -> Encode ('Closed 'Dense) Url
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Url
anchorUrl
        Encode ('Closed 'Dense) (SafeHash AnchorData -> Anchor)
-> Encode ('Closed 'Dense) (SafeHash AnchorData)
-> Encode ('Closed 'Dense) Anchor
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> SafeHash AnchorData
-> Encode ('Closed 'Dense) (SafeHash AnchorData)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To SafeHash AnchorData
anchorDataHash

instance ToJSON Anchor where
  toJSON :: Anchor -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value) -> (Anchor -> [Pair]) -> Anchor -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Anchor -> [Pair]
forall e a. KeyValue e a => Anchor -> [a]
toAnchorPairs
  toEncoding :: Anchor -> Encoding
toEncoding = Series -> Encoding
pairs (Series -> Encoding) -> (Anchor -> Series) -> Anchor -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series) -> (Anchor -> [Series]) -> Anchor -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Anchor -> [Series]
forall e a. KeyValue e a => Anchor -> [a]
toAnchorPairs

instance FromJSON Anchor where
  parseJSON :: Value -> Parser Anchor
parseJSON = String -> (Object -> Parser Anchor) -> Value -> Parser Anchor
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Anchor" ((Object -> Parser Anchor) -> Value -> Parser Anchor)
-> (Object -> Parser Anchor) -> Value -> Parser Anchor
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Url
anchorUrl <- Object
o Object -> Key -> Parser Url
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
    SafeHash AnchorData
anchorDataHash <- Object
o Object -> Key -> Parser (SafeHash AnchorData)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dataHash"
    Anchor -> Parser Anchor
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Anchor -> Parser Anchor) -> Anchor -> Parser Anchor
forall a b. (a -> b) -> a -> b
$ Anchor {SafeHash AnchorData
Url
anchorUrl :: Url
anchorDataHash :: SafeHash AnchorData
anchorUrl :: Url
anchorDataHash :: SafeHash AnchorData
..}

instance Default Anchor where
  def :: Anchor
def = Url -> SafeHash AnchorData -> Anchor
Anchor (Text -> Url
Url Text
"") SafeHash AnchorData
forall a. Default a => a
def

toAnchorPairs :: KeyValue e a => Anchor -> [a]
toAnchorPairs :: forall e a. KeyValue e a => Anchor -> [a]
toAnchorPairs vote :: Anchor
vote@(Anchor Url
_ SafeHash AnchorData
_) =
  let Anchor {SafeHash AnchorData
Url
anchorUrl :: Anchor -> Url
anchorDataHash :: Anchor -> SafeHash AnchorData
anchorUrl :: Url
anchorDataHash :: SafeHash AnchorData
..} = Anchor
vote
   in [ Key
"url" Key -> Url -> a
forall v. ToJSON v => Key -> v -> a
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Url
anchorUrl
      , Key
"dataHash" Key -> SafeHash AnchorData -> a
forall v. ToJSON v => Key -> v -> a
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= SafeHash 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 = a -> a
forall a. a -> a
id

-- | Helper function for a common pattern of creating objects
kindObject :: Text -> [Pair] -> Value
kindObject :: Text -> [Pair] -> Value
kindObject Text
name [Pair]
obj = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ (Key
"kind" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name) Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
obj

positiveUnitIntervalNonZeroRational :: PositiveUnitInterval -> NonZero Rational
positiveUnitIntervalNonZeroRational :: PositiveUnitInterval -> NonZero Rational
positiveUnitIntervalNonZeroRational = Rational -> NonZero Rational
forall a. a -> NonZero a
unsafeNonZero (Rational -> NonZero Rational)
-> (PositiveUnitInterval -> Rational)
-> PositiveUnitInterval
-> NonZero Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositiveUnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational