{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Cardano.Ledger.BaseTypes
( ProtVer (..),
FixedPoint,
(==>),
(⭒),
Network (..),
networkToWord8,
word8ToNetwork,
Nonce (..),
Seed (..),
UnitInterval,
PositiveUnitInterval,
PositiveInterval,
NonNegativeInterval,
BoundedRational (..),
boundedRationalFromCBOR,
boundedRationalToCBOR,
fpPrecision,
promoteRatio,
invalidKey,
mkNonceFromOutputVRF,
mkNonceFromNumber,
Url,
urlToText,
textToUrl,
DnsName,
dnsToText,
textToDns,
Port (..),
ActiveSlotCoeff,
mkActiveSlotCoeff,
activeSlotVal,
activeSlotLog,
module Data.Maybe.Strict,
BlocksMade (..),
TxIx (..),
txIxToInt,
txIxFromIntegral,
mkTxIxPartial,
CertIx (..),
certIxToInt,
certIxFromIntegral,
mkCertIxPartial,
Globals (..),
epochInfoPure,
ShelleyBase,
)
where
import Cardano.Binary
( Decoder,
DecoderError (..),
Encoding,
FromCBOR (fromCBOR),
ToCBOR (toCBOR),
encodeListLen,
encodedSizeExpr,
)
import Cardano.Crypto.Hash
import Cardano.Crypto.Util (SignableRepresentation (..))
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import Cardano.Ledger.NonIntegral (ln')
import Cardano.Ledger.Serialization
( CBORGroup (..),
FromCBORGroup (..),
ToCBORGroup (..),
decodeRecordSum,
ratioFromCBOR,
ratioToCBOR,
)
import Cardano.Slotting.EpochInfo (EpochInfo, hoistEpochInfo)
import Cardano.Slotting.Time (SystemStart)
import Control.DeepSeq (NFData)
import Control.Exception (throw)
import Control.Monad (when, (<=<))
import Control.Monad.Trans.Reader (ReaderT)
import Data.Aeson (FromJSON (..), ToJSON (..), (.:), (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Binary.Put as B
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Data.Coders (cborError, invalidKey)
import Data.Default.Class (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.Ratio (Ratio, denominator, numerator, (%))
import Data.Scientific (Scientific, base10Exponent, coefficient, normalize, scientific)
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))
data ProtVer = ProtVer {ProtVer -> Natural
pvMajor :: !Natural, 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
showList :: [ProtVer] -> ShowS
$cshowList :: [ProtVer] -> ShowS
show :: ProtVer -> String
$cshow :: ProtVer -> String
showsPrec :: Int -> ProtVer -> ShowS
$cshowsPrec :: Int -> ProtVer -> ShowS
Show, ProtVer -> ProtVer -> Bool
(ProtVer -> ProtVer -> Bool)
-> (ProtVer -> ProtVer -> Bool) -> Eq ProtVer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProtVer -> ProtVer -> Bool
$c/= :: ProtVer -> ProtVer -> Bool
== :: ProtVer -> ProtVer -> Bool
$c== :: ProtVer -> ProtVer -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep ProtVer x -> ProtVer
$cfrom :: forall x. ProtVer -> Rep ProtVer x
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
min :: ProtVer -> ProtVer -> ProtVer
$cmin :: ProtVer -> ProtVer -> ProtVer
max :: ProtVer -> ProtVer -> ProtVer
$cmax :: ProtVer -> ProtVer -> ProtVer
>= :: ProtVer -> ProtVer -> Bool
$c>= :: ProtVer -> ProtVer -> Bool
> :: ProtVer -> ProtVer -> Bool
$c> :: ProtVer -> ProtVer -> Bool
<= :: ProtVer -> ProtVer -> Bool
$c<= :: ProtVer -> ProtVer -> Bool
< :: ProtVer -> ProtVer -> Bool
$c< :: ProtVer -> ProtVer -> Bool
compare :: ProtVer -> ProtVer -> Ordering
$ccompare :: ProtVer -> ProtVer -> Ordering
$cp1Ord :: Eq ProtVer
Ord, ProtVer -> ()
(ProtVer -> ()) -> NFData ProtVer
forall a. (a -> ()) -> NFData a
rnf :: ProtVer -> ()
$crnf :: ProtVer -> ()
NFData)
deriving (Typeable ProtVer
Typeable ProtVer
-> (ProtVer -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy ProtVer -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [ProtVer] -> Size)
-> ToCBOR ProtVer
ProtVer -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
toCBOR :: ProtVer -> Encoding
$ctoCBOR :: ProtVer -> Encoding
$cp1ToCBOR :: Typeable ProtVer
ToCBOR) via (CBORGroup ProtVer)
deriving (Typeable ProtVer
Decoder s ProtVer
Typeable ProtVer
-> (forall s. Decoder s ProtVer)
-> (Proxy ProtVer -> Text)
-> FromCBOR ProtVer
Proxy ProtVer -> Text
forall s. Decoder s ProtVer
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy ProtVer -> Text
$clabel :: Proxy ProtVer -> Text
fromCBOR :: Decoder s ProtVer
$cfromCBOR :: forall s. Decoder s ProtVer
$cp1FromCBOR :: Typeable ProtVer
FromCBOR) via (CBORGroup ProtVer)
instance NoThunks ProtVer
instance ToJSON ProtVer where
toJSON :: ProtVer -> Value
toJSON (ProtVer Natural
major Natural
minor) =
[Pair] -> Value
Aeson.object
[ Key
"major" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
major,
Key
"minor" Key -> Natural -> Pair
forall kv v. (KeyValue 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
Aeson.withObject String
"ProtVer" ((Object -> Parser ProtVer) -> Value -> Parser ProtVer)
-> (Object -> Parser ProtVer) -> Value -> Parser ProtVer
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
Natural -> Natural -> ProtVer
ProtVer
(Natural -> Natural -> ProtVer)
-> Parser Natural -> Parser (Natural -> ProtVer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser Natural
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"major"
Parser (Natural -> ProtVer) -> Parser Natural -> Parser ProtVer
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser Natural
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"minor"
instance ToCBORGroup ProtVer where
toCBORGroup :: ProtVer -> Encoding
toCBORGroup (ProtVer Natural
x Natural
y) = Natural -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Natural
x Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Natural -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Natural
y
encodedGroupSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size
encodedGroupSizeExpr forall t. ToCBOR t => Proxy t -> Size
l Proxy ProtVer
proxy =
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word -> Size
forall a.
ToCBOR a =>
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
l ((\(ProtVer Natural
x Natural
_) -> Natural -> Word
toWord Natural
x) (ProtVer -> Word) -> Proxy ProtVer -> Proxy Word
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. ToCBOR t => Proxy t -> Size) -> Proxy Word -> Size
forall a.
ToCBOR a =>
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
l ((\(ProtVer Natural
_ Natural
y) -> Natural -> Word
toWord Natural
y) (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 FromCBORGroup ProtVer where
fromCBORGroup :: Decoder s ProtVer
fromCBORGroup = Natural -> Natural -> ProtVer
ProtVer (Natural -> Natural -> ProtVer)
-> Decoder s Natural -> Decoder s (Natural -> ProtVer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Natural
forall a s. FromCBOR a => Decoder s a
fromCBOR Decoder s (Natural -> ProtVer)
-> Decoder s Natural -> Decoder s ProtVer
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Natural
forall a s. FromCBOR a => Decoder s a
fromCBOR
data E34
instance FP.HasResolution E34 where
resolution :: 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)
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
/= :: BoundedRatio b a -> BoundedRatio b a -> Bool
$c/= :: forall b a. Eq a => BoundedRatio b a -> BoundedRatio b a -> Bool
== :: BoundedRatio b a -> BoundedRatio b a -> Bool
$c== :: forall b a. Eq a => BoundedRatio b a -> BoundedRatio b a -> Bool
Eq, (forall 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
$cto :: forall b a x. Rep (BoundedRatio b a) x -> BoundedRatio b a
$cfrom :: forall b a x. BoundedRatio b a -> Rep (BoundedRatio b a) x
Generic)
deriving newtype (Int -> BoundedRatio b a -> ShowS
[BoundedRatio b a] -> ShowS
BoundedRatio b a -> String
(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
showList :: [BoundedRatio b a] -> ShowS
$cshowList :: forall b a. Show a => [BoundedRatio b a] -> ShowS
show :: BoundedRatio b a -> String
$cshow :: forall b a. Show a => BoundedRatio b a -> String
showsPrec :: Int -> BoundedRatio b a -> ShowS
$cshowsPrec :: forall b a. Show a => Int -> BoundedRatio b a -> ShowS
Show, Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
Proxy (BoundedRatio b a) -> String
(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
showTypeOf :: Proxy (BoundedRatio b a) -> String
$cshowTypeOf :: forall b a. NoThunks a => Proxy (BoundedRatio b a) -> String
wNoThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
noThunks :: Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
$cnoThunks :: forall b a.
NoThunks a =>
Context -> BoundedRatio b a -> IO (Maybe ThunkInfo)
NoThunks, BoundedRatio b a -> ()
(BoundedRatio b a -> ()) -> NFData (BoundedRatio b a)
forall a. (a -> ()) -> NFData a
forall b a. NFData a => BoundedRatio b a -> ()
rnf :: BoundedRatio b a -> ()
$crnf :: forall b a. NFData a => BoundedRatio b a -> ()
NFData)
instance Integral a => Ord (BoundedRatio b a) where
compare :: BoundedRatio b a -> BoundedRatio b a -> Ordering
compare (BoundedRatio Ratio a
a) (BoundedRatio Ratio a
b) = 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 :: 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)
class Bounded r => BoundedRational r where
boundRational :: Rational -> Maybe r
unboundRational :: r -> Rational
instance
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
BoundedRational (BoundedRatio b a)
where
boundRational :: Rational -> Maybe (BoundedRatio b a)
boundRational = 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 :: 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 :: 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
| Bool
otherwise = Ratio a -> Maybe (BoundedRatio b a)
forall b 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
fromRatioBoundedRatio ::
forall b a.
(Bounded (BoundedRatio b a), Integral a) =>
Ratio a ->
Maybe (BoundedRatio b a)
fromRatioBoundedRatio :: 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 a b. Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio BoundedRatio b a
lowerBound
Bool -> Bool -> Bool
|| Rational
r Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
> BoundedRatio b a -> Rational
forall a b. Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio BoundedRatio b a
upperBound =
Maybe (BoundedRatio b a)
forall a. Maybe a
Nothing
| 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, Typeable a) => ToCBOR (BoundedRatio b a) where
toCBOR :: BoundedRatio b a -> Encoding
toCBOR (BoundedRatio Ratio a
u) = Ratio a -> Encoding
forall a. ToCBOR a => Ratio a -> Encoding
ratioToCBOR Ratio a
u
instance
(FromCBOR a, Bounded (BoundedRatio b a), Bounded a, Integral a, Typeable b, Typeable a, Show a) =>
FromCBOR (BoundedRatio b a)
where
fromCBOR :: Decoder s (BoundedRatio b a)
fromCBOR = do
Ratio a
r <- Decoder s (Ratio a)
forall a s.
(Bounded a, Integral a, FromCBOR a) =>
Decoder s (Ratio a)
ratioFromCBOR
case Ratio a -> Maybe (BoundedRatio b a)
forall b a.
(Bounded (BoundedRatio b a), Integral a) =>
Ratio a -> Maybe (BoundedRatio b a)
fromRatioBoundedRatio Ratio a
r of
Maybe (BoundedRatio b a)
Nothing ->
DecoderError -> Decoder s (BoundedRatio b a)
forall e s a. Buildable e => e -> Decoder s 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
$ Ratio a -> String
forall a. Show a => a -> String
show Ratio a
r)
Just BoundedRatio b a
u -> BoundedRatio b a -> Decoder s (BoundedRatio b a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure BoundedRatio b a
u
boundedRationalToCBOR :: BoundedRational r => r -> Encoding
boundedRationalToCBOR :: r -> Encoding
boundedRationalToCBOR = Rational -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Rational -> Encoding) -> (r -> Rational) -> r -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational
boundedRationalFromCBOR :: BoundedRational r => Decoder s r
boundedRationalFromCBOR :: Decoder s r
boundedRationalFromCBOR = do
Rational
r <- Decoder s Rational
forall a s. FromCBOR a => Decoder s a
fromCBOR
case Rational -> Maybe r
forall r. BoundedRational r => Rational -> Maybe r
boundRational Rational
r of
Maybe r
Nothing ->
DecoderError -> Decoder s r
forall e s a. Buildable e => e -> Decoder s a
cborError (DecoderError -> Decoder s r) -> DecoderError -> Decoder s r
forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"BoundedRational" (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 r
u -> r -> Decoder s r
forall (f :: * -> *) a. Applicative f => a -> f a
pure r
u
instance ToJSON (BoundedRatio b Word64) where
toJSON :: BoundedRatio b Word64 -> Value
toJSON = Scientific -> Value
forall a. ToJSON a => a -> Value
toJSON (Scientific -> Value)
-> (BoundedRatio b Word64 -> Scientific)
-> BoundedRatio b Word64
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BoundedRatio b Word64 -> Scientific
forall b. BoundedRatio b Word64 -> Scientific
toScientificBoundedRatioWord64WithRounding
toScientificBoundedRatioWord64WithRounding :: BoundedRatio b Word64 -> Scientific
toScientificBoundedRatioWord64WithRounding :: BoundedRatio b Word64 -> Scientific
toScientificBoundedRatioWord64WithRounding (BoundedRatio b Word64 -> Rational
forall a b. Integral a => BoundedRatio b a -> Rational
toRationalBoundedRatio -> Rational
ur) =
Integer -> Int -> Scientific
scientific Integer
q Int
0 Scientific -> Scientific -> Scientific
forall a. Num a => a -> a -> a
+ Integer -> Int -> Scientific
scientific ((Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
scale) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
d) (Int -> Int
forall a. Num a => a -> a
negate Int
exp10)
where
n :: Integer
n = Rational -> Integer
forall a. Ratio a -> a
numerator Rational
ur
d :: Integer
d = Rational -> Integer
forall a. Ratio a -> a
denominator Rational
ur
(Integer
q, Integer
r) = Integer
n Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
d
exp10 :: Int
exp10 = Int
19 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
19 (Integer -> Int
numDigits Integer
q)
scale :: Integer
scale = Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
exp10
numDigits :: Integer -> Int
numDigits :: Integer -> Int
numDigits = Int -> Integer -> Int
forall t t. (Num t, Integral t) => t -> t -> t
go Int
0
where
go :: t -> t -> t
go t
ds t
0 = t
ds
go t
ds t
i = t
ds t -> t -> t
`seq` t -> t -> t
go (t
ds t -> t -> t
forall a. Num a => a -> a -> a
+ t
1) (t
i t -> t -> t
forall a. Integral a => a -> a -> a
`quot` t
10)
instance Bounded (BoundedRatio b Word64) => FromJSON (BoundedRatio b Word64) where
parseJSON :: Value -> Parser (BoundedRatio b Word64)
parseJSON = (String -> Parser (BoundedRatio b Word64))
-> (BoundedRatio b Word64 -> Parser (BoundedRatio b Word64))
-> Either String (BoundedRatio b Word64)
-> Parser (BoundedRatio b Word64)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser (BoundedRatio b Word64)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail BoundedRatio b Word64 -> Parser (BoundedRatio b Word64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String (BoundedRatio b Word64)
-> Parser (BoundedRatio b Word64))
-> (Scientific -> Either String (BoundedRatio b Word64))
-> Scientific
-> Parser (BoundedRatio b Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Either String (BoundedRatio b Word64)
forall b.
Bounded (BoundedRatio b Word64) =>
Scientific -> Either String (BoundedRatio b Word64)
fromScientificBoundedRatioWord64 (Scientific -> Parser (BoundedRatio b Word64))
-> (Value -> Parser Scientific)
-> Value
-> Parser (BoundedRatio b Word64)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser Scientific
forall a. FromJSON a => Value -> Parser a
parseJSON
fromScientificBoundedRatioWord64 ::
Bounded (BoundedRatio b Word64) =>
Scientific ->
Either String (BoundedRatio b Word64)
fromScientificBoundedRatioWord64 :: 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 -> Either String (BoundedRatio b Word64)
forall a. String -> Either String a
failWith String
"negative"
| 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
19) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a. String -> Either String a
failWith String
"too precise"
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
19 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 -> Either String ()
forall a. String -> Either String a
failWith String
"too big"
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
failWith :: String -> Either String a
failWith :: String -> Either String a
failWith String
msg = String -> Either String a
forall a b. a -> Either a b
Left (String -> Either String a) -> String -> Either String a
forall a b. (a -> b) -> a -> b
$ String
"Value is " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
sci
fromRationalEither :: Rational -> Either String (BoundedRatio b Word64)
fromRationalEither =
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 -> Either String (BoundedRatio b Word64)
forall a. String -> Either String a
failWith String
"outside of bounds") 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))
-> (Rational -> Maybe (BoundedRatio b Word64))
-> Rational
-> Either String (BoundedRatio b Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Maybe (BoundedRatio b Word64)
forall b a.
(Bounded (BoundedRatio b a), Bounded a, Integral a) =>
Rational -> Maybe (BoundedRatio b a)
fromRationalBoundedRatio
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
min :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
$cmin :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
max :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
$cmax :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval
>= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c>= :: NonNegativeInterval -> NonNegativeInterval -> Bool
> :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c> :: NonNegativeInterval -> NonNegativeInterval -> Bool
<= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c<= :: NonNegativeInterval -> NonNegativeInterval -> Bool
< :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c< :: NonNegativeInterval -> NonNegativeInterval -> Bool
compare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
$ccompare :: NonNegativeInterval -> NonNegativeInterval -> Ordering
$cp1Ord :: Eq NonNegativeInterval
Ord, NonNegativeInterval -> NonNegativeInterval -> Bool
(NonNegativeInterval -> NonNegativeInterval -> Bool)
-> (NonNegativeInterval -> NonNegativeInterval -> Bool)
-> Eq NonNegativeInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c/= :: NonNegativeInterval -> NonNegativeInterval -> Bool
== :: NonNegativeInterval -> NonNegativeInterval -> Bool
$c== :: NonNegativeInterval -> NonNegativeInterval -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep NonNegativeInterval x -> NonNegativeInterval
$cfrom :: forall x. NonNegativeInterval -> Rep NonNegativeInterval x
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
showList :: [NonNegativeInterval] -> ShowS
$cshowList :: [NonNegativeInterval] -> ShowS
show :: NonNegativeInterval -> String
$cshow :: NonNegativeInterval -> String
showsPrec :: Int -> NonNegativeInterval -> ShowS
$cshowsPrec :: Int -> NonNegativeInterval -> ShowS
Show,
NonNegativeInterval
NonNegativeInterval
-> NonNegativeInterval -> Bounded NonNegativeInterval
forall a. a -> a -> Bounded a
maxBound :: NonNegativeInterval
$cmaxBound :: NonNegativeInterval
minBound :: NonNegativeInterval
$cminBound :: 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
unboundRational :: NonNegativeInterval -> Rational
$cunboundRational :: NonNegativeInterval -> Rational
boundRational :: Rational -> Maybe NonNegativeInterval
$cboundRational :: Rational -> Maybe NonNegativeInterval
$cp1BoundedRational :: Bounded NonNegativeInterval
BoundedRational,
Typeable NonNegativeInterval
Typeable NonNegativeInterval
-> (NonNegativeInterval -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size)
-> ToCBOR NonNegativeInterval
NonNegativeInterval -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonNegativeInterval] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonNegativeInterval -> Size
toCBOR :: NonNegativeInterval -> Encoding
$ctoCBOR :: NonNegativeInterval -> Encoding
$cp1ToCBOR :: Typeable NonNegativeInterval
ToCBOR,
Typeable NonNegativeInterval
Decoder s NonNegativeInterval
Typeable NonNegativeInterval
-> (forall s. Decoder s NonNegativeInterval)
-> (Proxy NonNegativeInterval -> Text)
-> FromCBOR NonNegativeInterval
Proxy NonNegativeInterval -> Text
forall s. Decoder s NonNegativeInterval
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy NonNegativeInterval -> Text
$clabel :: Proxy NonNegativeInterval -> Text
fromCBOR :: Decoder s NonNegativeInterval
$cfromCBOR :: forall s. Decoder s NonNegativeInterval
$cp1FromCBOR :: Typeable NonNegativeInterval
FromCBOR,
[NonNegativeInterval] -> Encoding
[NonNegativeInterval] -> Value
NonNegativeInterval -> Encoding
NonNegativeInterval -> Value
(NonNegativeInterval -> Value)
-> (NonNegativeInterval -> Encoding)
-> ([NonNegativeInterval] -> Value)
-> ([NonNegativeInterval] -> Encoding)
-> ToJSON NonNegativeInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NonNegativeInterval] -> Encoding
$ctoEncodingList :: [NonNegativeInterval] -> Encoding
toJSONList :: [NonNegativeInterval] -> Value
$ctoJSONList :: [NonNegativeInterval] -> Value
toEncoding :: NonNegativeInterval -> Encoding
$ctoEncoding :: NonNegativeInterval -> Encoding
toJSON :: NonNegativeInterval -> Value
$ctoJSON :: NonNegativeInterval -> Value
ToJSON,
Value -> Parser [NonNegativeInterval]
Value -> Parser NonNegativeInterval
(Value -> Parser NonNegativeInterval)
-> (Value -> Parser [NonNegativeInterval])
-> FromJSON NonNegativeInterval
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NonNegativeInterval]
$cparseJSONList :: Value -> Parser [NonNegativeInterval]
parseJSON :: Value -> Parser NonNegativeInterval
$cparseJSON :: Value -> Parser NonNegativeInterval
FromJSON,
Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
Proxy NonNegativeInterval -> String
(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
showTypeOf :: Proxy NonNegativeInterval -> String
$cshowTypeOf :: Proxy NonNegativeInterval -> String
wNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo)
NoThunks,
NonNegativeInterval -> ()
(NonNegativeInterval -> ()) -> NFData NonNegativeInterval
forall a. (a -> ()) -> NFData a
rnf :: NonNegativeInterval -> ()
$crnf :: 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)
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
min :: PositiveInterval -> PositiveInterval -> PositiveInterval
$cmin :: PositiveInterval -> PositiveInterval -> PositiveInterval
max :: PositiveInterval -> PositiveInterval -> PositiveInterval
$cmax :: PositiveInterval -> PositiveInterval -> PositiveInterval
>= :: PositiveInterval -> PositiveInterval -> Bool
$c>= :: PositiveInterval -> PositiveInterval -> Bool
> :: PositiveInterval -> PositiveInterval -> Bool
$c> :: PositiveInterval -> PositiveInterval -> Bool
<= :: PositiveInterval -> PositiveInterval -> Bool
$c<= :: PositiveInterval -> PositiveInterval -> Bool
< :: PositiveInterval -> PositiveInterval -> Bool
$c< :: PositiveInterval -> PositiveInterval -> Bool
compare :: PositiveInterval -> PositiveInterval -> Ordering
$ccompare :: PositiveInterval -> PositiveInterval -> Ordering
$cp1Ord :: Eq PositiveInterval
Ord, PositiveInterval -> PositiveInterval -> Bool
(PositiveInterval -> PositiveInterval -> Bool)
-> (PositiveInterval -> PositiveInterval -> Bool)
-> Eq PositiveInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveInterval -> PositiveInterval -> Bool
$c/= :: PositiveInterval -> PositiveInterval -> Bool
== :: PositiveInterval -> PositiveInterval -> Bool
$c== :: PositiveInterval -> PositiveInterval -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep PositiveInterval x -> PositiveInterval
$cfrom :: forall x. PositiveInterval -> Rep PositiveInterval x
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
showList :: [PositiveInterval] -> ShowS
$cshowList :: [PositiveInterval] -> ShowS
show :: PositiveInterval -> String
$cshow :: PositiveInterval -> String
showsPrec :: Int -> PositiveInterval -> ShowS
$cshowsPrec :: Int -> PositiveInterval -> ShowS
Show,
PositiveInterval
PositiveInterval -> PositiveInterval -> Bounded PositiveInterval
forall a. a -> a -> Bounded a
maxBound :: PositiveInterval
$cmaxBound :: PositiveInterval
minBound :: PositiveInterval
$cminBound :: 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
unboundRational :: PositiveInterval -> Rational
$cunboundRational :: PositiveInterval -> Rational
boundRational :: Rational -> Maybe PositiveInterval
$cboundRational :: Rational -> Maybe PositiveInterval
$cp1BoundedRational :: Bounded PositiveInterval
BoundedRational,
Typeable PositiveInterval
Typeable PositiveInterval
-> (PositiveInterval -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size)
-> ToCBOR PositiveInterval
PositiveInterval -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveInterval] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveInterval -> Size
toCBOR :: PositiveInterval -> Encoding
$ctoCBOR :: PositiveInterval -> Encoding
$cp1ToCBOR :: Typeable PositiveInterval
ToCBOR,
Typeable PositiveInterval
Decoder s PositiveInterval
Typeable PositiveInterval
-> (forall s. Decoder s PositiveInterval)
-> (Proxy PositiveInterval -> Text)
-> FromCBOR PositiveInterval
Proxy PositiveInterval -> Text
forall s. Decoder s PositiveInterval
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy PositiveInterval -> Text
$clabel :: Proxy PositiveInterval -> Text
fromCBOR :: Decoder s PositiveInterval
$cfromCBOR :: forall s. Decoder s PositiveInterval
$cp1FromCBOR :: Typeable PositiveInterval
FromCBOR,
[PositiveInterval] -> Encoding
[PositiveInterval] -> Value
PositiveInterval -> Encoding
PositiveInterval -> Value
(PositiveInterval -> Value)
-> (PositiveInterval -> Encoding)
-> ([PositiveInterval] -> Value)
-> ([PositiveInterval] -> Encoding)
-> ToJSON PositiveInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PositiveInterval] -> Encoding
$ctoEncodingList :: [PositiveInterval] -> Encoding
toJSONList :: [PositiveInterval] -> Value
$ctoJSONList :: [PositiveInterval] -> Value
toEncoding :: PositiveInterval -> Encoding
$ctoEncoding :: PositiveInterval -> Encoding
toJSON :: PositiveInterval -> Value
$ctoJSON :: PositiveInterval -> Value
ToJSON,
Value -> Parser [PositiveInterval]
Value -> Parser PositiveInterval
(Value -> Parser PositiveInterval)
-> (Value -> Parser [PositiveInterval])
-> FromJSON PositiveInterval
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PositiveInterval]
$cparseJSONList :: Value -> Parser [PositiveInterval]
parseJSON :: Value -> Parser PositiveInterval
$cparseJSON :: Value -> Parser PositiveInterval
FromJSON,
Context -> PositiveInterval -> IO (Maybe ThunkInfo)
Proxy PositiveInterval -> String
(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
showTypeOf :: Proxy PositiveInterval -> String
$cshowTypeOf :: Proxy PositiveInterval -> String
wNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PositiveInterval -> IO (Maybe ThunkInfo)
NoThunks,
PositiveInterval -> ()
(PositiveInterval -> ()) -> NFData PositiveInterval
forall a. (a -> ()) -> NFData a
rnf :: PositiveInterval -> ()
$crnf :: 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)
positiveIntervalEpsilon :: BoundedRatio b Word64
positiveIntervalEpsilon :: 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
19 :: Int))
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
min :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
$cmin :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
max :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
$cmax :: PositiveUnitInterval
-> PositiveUnitInterval -> PositiveUnitInterval
>= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c>= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
> :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c> :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
<= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c<= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
< :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c< :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
compare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
$ccompare :: PositiveUnitInterval -> PositiveUnitInterval -> Ordering
$cp1Ord :: Eq PositiveUnitInterval
Ord, PositiveUnitInterval -> PositiveUnitInterval -> Bool
(PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> (PositiveUnitInterval -> PositiveUnitInterval -> Bool)
-> Eq PositiveUnitInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c/= :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
$c== :: PositiveUnitInterval -> PositiveUnitInterval -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep PositiveUnitInterval x -> PositiveUnitInterval
$cfrom :: forall x. PositiveUnitInterval -> Rep PositiveUnitInterval x
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
showList :: [PositiveUnitInterval] -> ShowS
$cshowList :: [PositiveUnitInterval] -> ShowS
show :: PositiveUnitInterval -> String
$cshow :: PositiveUnitInterval -> String
showsPrec :: Int -> PositiveUnitInterval -> ShowS
$cshowsPrec :: Int -> PositiveUnitInterval -> ShowS
Show,
PositiveUnitInterval
PositiveUnitInterval
-> PositiveUnitInterval -> Bounded PositiveUnitInterval
forall a. a -> a -> Bounded a
maxBound :: PositiveUnitInterval
$cmaxBound :: PositiveUnitInterval
minBound :: PositiveUnitInterval
$cminBound :: 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
unboundRational :: PositiveUnitInterval -> Rational
$cunboundRational :: PositiveUnitInterval -> Rational
boundRational :: Rational -> Maybe PositiveUnitInterval
$cboundRational :: Rational -> Maybe PositiveUnitInterval
$cp1BoundedRational :: Bounded PositiveUnitInterval
BoundedRational,
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
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [PositiveUnitInterval] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy PositiveUnitInterval -> Size
toCBOR :: PositiveUnitInterval -> Encoding
$ctoCBOR :: PositiveUnitInterval -> Encoding
$cp1ToCBOR :: Typeable PositiveUnitInterval
ToCBOR,
Typeable PositiveUnitInterval
Decoder s 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
label :: Proxy PositiveUnitInterval -> Text
$clabel :: Proxy PositiveUnitInterval -> Text
fromCBOR :: Decoder s PositiveUnitInterval
$cfromCBOR :: forall s. Decoder s PositiveUnitInterval
$cp1FromCBOR :: Typeable PositiveUnitInterval
FromCBOR,
[PositiveUnitInterval] -> Encoding
[PositiveUnitInterval] -> Value
PositiveUnitInterval -> Encoding
PositiveUnitInterval -> Value
(PositiveUnitInterval -> Value)
-> (PositiveUnitInterval -> Encoding)
-> ([PositiveUnitInterval] -> Value)
-> ([PositiveUnitInterval] -> Encoding)
-> ToJSON PositiveUnitInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PositiveUnitInterval] -> Encoding
$ctoEncodingList :: [PositiveUnitInterval] -> Encoding
toJSONList :: [PositiveUnitInterval] -> Value
$ctoJSONList :: [PositiveUnitInterval] -> Value
toEncoding :: PositiveUnitInterval -> Encoding
$ctoEncoding :: PositiveUnitInterval -> Encoding
toJSON :: PositiveUnitInterval -> Value
$ctoJSON :: PositiveUnitInterval -> Value
ToJSON,
Value -> Parser [PositiveUnitInterval]
Value -> Parser PositiveUnitInterval
(Value -> Parser PositiveUnitInterval)
-> (Value -> Parser [PositiveUnitInterval])
-> FromJSON PositiveUnitInterval
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PositiveUnitInterval]
$cparseJSONList :: Value -> Parser [PositiveUnitInterval]
parseJSON :: Value -> Parser PositiveUnitInterval
$cparseJSON :: Value -> Parser PositiveUnitInterval
FromJSON,
Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
Proxy PositiveUnitInterval -> String
(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
showTypeOf :: Proxy PositiveUnitInterval -> String
$cshowTypeOf :: Proxy PositiveUnitInterval -> String
wNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PositiveUnitInterval -> IO (Maybe ThunkInfo)
NoThunks,
PositiveUnitInterval -> ()
(PositiveUnitInterval -> ()) -> NFData PositiveUnitInterval
forall a. (a -> ()) -> NFData a
rnf :: PositiveUnitInterval -> ()
$crnf :: 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)
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
min :: UnitInterval -> UnitInterval -> UnitInterval
$cmin :: UnitInterval -> UnitInterval -> UnitInterval
max :: UnitInterval -> UnitInterval -> UnitInterval
$cmax :: UnitInterval -> UnitInterval -> UnitInterval
>= :: UnitInterval -> UnitInterval -> Bool
$c>= :: UnitInterval -> UnitInterval -> Bool
> :: UnitInterval -> UnitInterval -> Bool
$c> :: UnitInterval -> UnitInterval -> Bool
<= :: UnitInterval -> UnitInterval -> Bool
$c<= :: UnitInterval -> UnitInterval -> Bool
< :: UnitInterval -> UnitInterval -> Bool
$c< :: UnitInterval -> UnitInterval -> Bool
compare :: UnitInterval -> UnitInterval -> Ordering
$ccompare :: UnitInterval -> UnitInterval -> Ordering
$cp1Ord :: Eq UnitInterval
Ord, UnitInterval -> UnitInterval -> Bool
(UnitInterval -> UnitInterval -> Bool)
-> (UnitInterval -> UnitInterval -> Bool) -> Eq UnitInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnitInterval -> UnitInterval -> Bool
$c/= :: UnitInterval -> UnitInterval -> Bool
== :: UnitInterval -> UnitInterval -> Bool
$c== :: UnitInterval -> UnitInterval -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep UnitInterval x -> UnitInterval
$cfrom :: forall x. UnitInterval -> Rep UnitInterval x
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
showList :: [UnitInterval] -> ShowS
$cshowList :: [UnitInterval] -> ShowS
show :: UnitInterval -> String
$cshow :: UnitInterval -> String
showsPrec :: Int -> UnitInterval -> ShowS
$cshowsPrec :: Int -> UnitInterval -> ShowS
Show,
UnitInterval
UnitInterval -> UnitInterval -> Bounded UnitInterval
forall a. a -> a -> Bounded a
maxBound :: UnitInterval
$cmaxBound :: UnitInterval
minBound :: UnitInterval
$cminBound :: 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
unboundRational :: UnitInterval -> Rational
$cunboundRational :: UnitInterval -> Rational
boundRational :: Rational -> Maybe UnitInterval
$cboundRational :: Rational -> Maybe UnitInterval
$cp1BoundedRational :: Bounded UnitInterval
BoundedRational,
Typeable UnitInterval
Typeable UnitInterval
-> (UnitInterval -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size)
-> ToCBOR UnitInterval
UnitInterval -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [UnitInterval] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy UnitInterval -> Size
toCBOR :: UnitInterval -> Encoding
$ctoCBOR :: UnitInterval -> Encoding
$cp1ToCBOR :: Typeable UnitInterval
ToCBOR,
Typeable UnitInterval
Decoder s UnitInterval
Typeable UnitInterval
-> (forall s. Decoder s UnitInterval)
-> (Proxy UnitInterval -> Text)
-> FromCBOR UnitInterval
Proxy UnitInterval -> Text
forall s. Decoder s UnitInterval
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy UnitInterval -> Text
$clabel :: Proxy UnitInterval -> Text
fromCBOR :: Decoder s UnitInterval
$cfromCBOR :: forall s. Decoder s UnitInterval
$cp1FromCBOR :: Typeable UnitInterval
FromCBOR,
[UnitInterval] -> Encoding
[UnitInterval] -> Value
UnitInterval -> Encoding
UnitInterval -> Value
(UnitInterval -> Value)
-> (UnitInterval -> Encoding)
-> ([UnitInterval] -> Value)
-> ([UnitInterval] -> Encoding)
-> ToJSON UnitInterval
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UnitInterval] -> Encoding
$ctoEncodingList :: [UnitInterval] -> Encoding
toJSONList :: [UnitInterval] -> Value
$ctoJSONList :: [UnitInterval] -> Value
toEncoding :: UnitInterval -> Encoding
$ctoEncoding :: UnitInterval -> Encoding
toJSON :: UnitInterval -> Value
$ctoJSON :: UnitInterval -> Value
ToJSON,
Value -> Parser [UnitInterval]
Value -> Parser UnitInterval
(Value -> Parser UnitInterval)
-> (Value -> Parser [UnitInterval]) -> FromJSON UnitInterval
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UnitInterval]
$cparseJSONList :: Value -> Parser [UnitInterval]
parseJSON :: Value -> Parser UnitInterval
$cparseJSON :: Value -> Parser UnitInterval
FromJSON,
Context -> UnitInterval -> IO (Maybe ThunkInfo)
Proxy UnitInterval -> String
(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
showTypeOf :: Proxy UnitInterval -> String
$cshowTypeOf :: Proxy UnitInterval -> String
wNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
noThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo)
NoThunks,
UnitInterval -> ()
(UnitInterval -> ()) -> NFData UnitInterval
forall a. (a -> ()) -> NFData a
rnf :: UnitInterval -> ()
$crnf :: 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
data Nonce
= Nonce !(Hash Blake2b_256 Nonce)
|
NeutralNonce
deriving (Nonce -> Nonce -> Bool
(Nonce -> Nonce -> Bool) -> (Nonce -> Nonce -> Bool) -> Eq Nonce
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Nonce -> Nonce -> Bool
$c/= :: Nonce -> Nonce -> Bool
== :: Nonce -> Nonce -> Bool
$c== :: Nonce -> Nonce -> Bool
Eq, (forall x. 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
$cto :: forall x. Rep Nonce x -> Nonce
$cfrom :: forall x. Nonce -> Rep Nonce x
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
min :: Nonce -> Nonce -> Nonce
$cmin :: Nonce -> Nonce -> Nonce
max :: Nonce -> Nonce -> Nonce
$cmax :: Nonce -> Nonce -> Nonce
>= :: Nonce -> Nonce -> Bool
$c>= :: Nonce -> Nonce -> Bool
> :: Nonce -> Nonce -> Bool
$c> :: Nonce -> Nonce -> Bool
<= :: Nonce -> Nonce -> Bool
$c<= :: Nonce -> Nonce -> Bool
< :: Nonce -> Nonce -> Bool
$c< :: Nonce -> Nonce -> Bool
compare :: Nonce -> Nonce -> Ordering
$ccompare :: Nonce -> Nonce -> Ordering
$cp1Ord :: Eq 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
showList :: [Nonce] -> ShowS
$cshowList :: [Nonce] -> ShowS
show :: Nonce -> String
$cshow :: Nonce -> String
showsPrec :: Int -> Nonce -> ShowS
$cshowsPrec :: Int -> Nonce -> ShowS
Show, Nonce -> ()
(Nonce -> ()) -> NFData Nonce
forall a. (a -> ()) -> NFData a
rnf :: Nonce -> ()
$crnf :: Nonce -> ()
NFData)
instance NoThunks 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 :: Decoder s Nonce
fromCBOR = String -> (Word -> Decoder s (Int, Nonce)) -> Decoder s Nonce
forall s a. String -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum String
"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 (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 a s. FromCBOR a => Decoder s a
fromCBOR
(Int, Nonce) -> Decoder s (Int, Nonce)
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 s a. Word -> Decoder s a
invalidKey Word
k
deriving anyclass instance ToJSON Nonce
deriving anyclass instance FromJSON 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
mkNonceFromOutputVRF :: VRF.OutputVRF v -> Nonce
mkNonceFromOutputVRF :: 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
. (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
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)
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
/= :: Seed -> Seed -> Bool
$c/= :: Seed -> Seed -> Bool
== :: Seed -> Seed -> Bool
$c== :: 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
min :: Seed -> Seed -> Seed
$cmin :: Seed -> Seed -> Seed
max :: Seed -> Seed -> Seed
$cmax :: Seed -> Seed -> Seed
>= :: Seed -> Seed -> Bool
$c>= :: Seed -> Seed -> Bool
> :: Seed -> Seed -> Bool
$c> :: Seed -> Seed -> Bool
<= :: Seed -> Seed -> Bool
$c<= :: Seed -> Seed -> Bool
< :: Seed -> Seed -> Bool
$c< :: Seed -> Seed -> Bool
compare :: Seed -> Seed -> Ordering
$ccompare :: Seed -> Seed -> Ordering
$cp1Ord :: Eq 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
showList :: [Seed] -> ShowS
$cshowList :: [Seed] -> ShowS
show :: Seed -> String
$cshow :: Seed -> String
showsPrec :: Int -> Seed -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep Seed x -> Seed
$cfrom :: forall x. Seed -> Rep Seed x
Generic)
deriving newtype (Context -> Seed -> IO (Maybe ThunkInfo)
Proxy Seed -> String
(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
showTypeOf :: Proxy Seed -> String
$cshowTypeOf :: Proxy Seed -> String
wNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
noThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Seed -> IO (Maybe ThunkInfo)
NoThunks, Typeable Seed
Typeable Seed
-> (Seed -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Seed -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Seed] -> Size)
-> ToCBOR Seed
Seed -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Seed] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Seed -> Size
toCBOR :: Seed -> Encoding
$ctoCBOR :: Seed -> Encoding
$cp1ToCBOR :: Typeable Seed
ToCBOR)
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 ==>
text64 :: Text -> Maybe Text
text64 :: Text -> Maybe Text
text64 Text
t =
if (ByteString -> Int
BS.length (ByteString -> Int) -> (Text -> ByteString) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8) Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
64
then Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
else Maybe Text
forall a. Maybe a
Nothing
text64FromCBOR :: Decoder s Text
text64FromCBOR :: Decoder s Text
text64FromCBOR = do
Text
t <- Decoder s Text
forall a s. FromCBOR a => Decoder s a
fromCBOR
if (ByteString -> Int
BS.length (ByteString -> Int) -> (Text -> ByteString) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8) Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
64
then DecoderError -> Decoder s Text
forall e s a. Buildable e => e -> Decoder s a
cborError (DecoderError -> Decoder s Text) -> DecoderError -> Decoder s Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"text exceeds 64 bytes:" Text
t
else Text -> Decoder s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
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
/= :: Url -> Url -> Bool
$c/= :: Url -> Url -> Bool
== :: Url -> Url -> Bool
$c== :: 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
min :: Url -> Url -> Url
$cmin :: Url -> Url -> Url
max :: Url -> Url -> Url
$cmax :: Url -> Url -> Url
>= :: Url -> Url -> Bool
$c>= :: Url -> Url -> Bool
> :: Url -> Url -> Bool
$c> :: Url -> Url -> Bool
<= :: Url -> Url -> Bool
$c<= :: Url -> Url -> Bool
< :: Url -> Url -> Bool
$c< :: Url -> Url -> Bool
compare :: Url -> Url -> Ordering
$ccompare :: Url -> Url -> Ordering
$cp1Ord :: Eq 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
$cto :: forall x. Rep Url x -> Url
$cfrom :: forall x. Url -> Rep Url x
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
showList :: [Url] -> ShowS
$cshowList :: [Url] -> ShowS
show :: Url -> String
$cshow :: Url -> String
showsPrec :: Int -> Url -> ShowS
$cshowsPrec :: Int -> Url -> ShowS
Show)
deriving newtype (Typeable Url
Typeable Url
-> (Url -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Url -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size)
-> ToCBOR Url
Url -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Url -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Url -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Url -> Size
toCBOR :: Url -> Encoding
$ctoCBOR :: Url -> Encoding
$cp1ToCBOR :: Typeable Url
ToCBOR, Url -> ()
(Url -> ()) -> NFData Url
forall a. (a -> ()) -> NFData a
rnf :: Url -> ()
$crnf :: 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
showTypeOf :: Proxy Url -> String
$cshowTypeOf :: Proxy Url -> String
wNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
noThunks :: Context -> Url -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Url -> IO (Maybe ThunkInfo)
NoThunks, Value -> Parser [Url]
Value -> Parser Url
(Value -> Parser Url) -> (Value -> Parser [Url]) -> FromJSON Url
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Url]
$cparseJSONList :: Value -> Parser [Url]
parseJSON :: Value -> Parser Url
$cparseJSON :: Value -> Parser Url
FromJSON, [Url] -> Encoding
[Url] -> Value
Url -> Encoding
Url -> Value
(Url -> Value)
-> (Url -> Encoding)
-> ([Url] -> Value)
-> ([Url] -> Encoding)
-> ToJSON Url
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Url] -> Encoding
$ctoEncodingList :: [Url] -> Encoding
toJSONList :: [Url] -> Value
$ctoJSONList :: [Url] -> Value
toEncoding :: Url -> Encoding
$ctoEncoding :: Url -> Encoding
toJSON :: Url -> Value
$ctoJSON :: Url -> Value
ToJSON)
textToUrl :: Text -> Maybe Url
textToUrl :: Text -> Maybe Url
textToUrl Text
t = Text -> Url
Url (Text -> Url) -> Maybe Text -> Maybe Url
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
text64 Text
t
instance FromCBOR Url where
fromCBOR :: Decoder s Url
fromCBOR = Text -> Url
Url (Text -> Url) -> Decoder s Text -> Decoder s Url
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Text
forall s. Decoder s Text
text64FromCBOR
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
/= :: DnsName -> DnsName -> Bool
$c/= :: DnsName -> DnsName -> Bool
== :: DnsName -> DnsName -> Bool
$c== :: 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
min :: DnsName -> DnsName -> DnsName
$cmin :: DnsName -> DnsName -> DnsName
max :: DnsName -> DnsName -> DnsName
$cmax :: DnsName -> DnsName -> DnsName
>= :: DnsName -> DnsName -> Bool
$c>= :: DnsName -> DnsName -> Bool
> :: DnsName -> DnsName -> Bool
$c> :: DnsName -> DnsName -> Bool
<= :: DnsName -> DnsName -> Bool
$c<= :: DnsName -> DnsName -> Bool
< :: DnsName -> DnsName -> Bool
$c< :: DnsName -> DnsName -> Bool
compare :: DnsName -> DnsName -> Ordering
$ccompare :: DnsName -> DnsName -> Ordering
$cp1Ord :: Eq 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
$cto :: forall x. Rep DnsName x -> DnsName
$cfrom :: forall x. DnsName -> Rep DnsName x
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
showList :: [DnsName] -> ShowS
$cshowList :: [DnsName] -> ShowS
show :: DnsName -> String
$cshow :: DnsName -> String
showsPrec :: Int -> DnsName -> ShowS
$cshowsPrec :: Int -> DnsName -> ShowS
Show)
deriving newtype (Typeable DnsName
Typeable DnsName
-> (DnsName -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy DnsName -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [DnsName] -> Size)
-> ToCBOR DnsName
DnsName -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size
toCBOR :: DnsName -> Encoding
$ctoCBOR :: DnsName -> Encoding
$cp1ToCBOR :: Typeable DnsName
ToCBOR, 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
showTypeOf :: Proxy DnsName -> String
$cshowTypeOf :: Proxy DnsName -> String
wNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
noThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)
NoThunks, DnsName -> ()
(DnsName -> ()) -> NFData DnsName
forall a. (a -> ()) -> NFData a
rnf :: DnsName -> ()
$crnf :: DnsName -> ()
NFData, Value -> Parser [DnsName]
Value -> Parser DnsName
(Value -> Parser DnsName)
-> (Value -> Parser [DnsName]) -> FromJSON DnsName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DnsName]
$cparseJSONList :: Value -> Parser [DnsName]
parseJSON :: Value -> Parser DnsName
$cparseJSON :: Value -> Parser DnsName
FromJSON, [DnsName] -> Encoding
[DnsName] -> Value
DnsName -> Encoding
DnsName -> Value
(DnsName -> Value)
-> (DnsName -> Encoding)
-> ([DnsName] -> Value)
-> ([DnsName] -> Encoding)
-> ToJSON DnsName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DnsName] -> Encoding
$ctoEncodingList :: [DnsName] -> Encoding
toJSONList :: [DnsName] -> Value
$ctoJSONList :: [DnsName] -> Value
toEncoding :: DnsName -> Encoding
$ctoEncoding :: DnsName -> Encoding
toJSON :: DnsName -> Value
$ctoJSON :: DnsName -> Value
ToJSON)
textToDns :: Text -> Maybe DnsName
textToDns :: Text -> Maybe DnsName
textToDns Text
t = Text -> DnsName
DnsName (Text -> DnsName) -> Maybe Text -> Maybe DnsName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
text64 Text
t
instance FromCBOR DnsName where
fromCBOR :: Decoder s DnsName
fromCBOR = Text -> DnsName
DnsName (Text -> DnsName) -> Decoder s Text -> Decoder s DnsName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Text
forall s. Decoder s Text
text64FromCBOR
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
/= :: Port -> Port -> Bool
$c/= :: Port -> Port -> Bool
== :: Port -> Port -> Bool
$c== :: 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
min :: Port -> Port -> Port
$cmin :: Port -> Port -> Port
max :: Port -> Port -> Port
$cmax :: Port -> Port -> Port
>= :: Port -> Port -> Bool
$c>= :: Port -> Port -> Bool
> :: Port -> Port -> Bool
$c> :: Port -> Port -> Bool
<= :: Port -> Port -> Bool
$c<= :: Port -> Port -> Bool
< :: Port -> Port -> Bool
$c< :: Port -> Port -> Bool
compare :: Port -> Port -> Ordering
$ccompare :: Port -> Port -> Ordering
$cp1Ord :: Eq 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
$cto :: forall x. Rep Port x -> Port
$cfrom :: forall x. Port -> Rep Port x
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
showList :: [Port] -> ShowS
$cshowList :: [Port] -> ShowS
show :: Port -> String
$cshow :: Port -> String
showsPrec :: Int -> Port -> ShowS
$cshowsPrec :: Int -> Port -> ShowS
Show)
deriving newtype (Integer -> Port
Port -> Port
Port -> Port -> Port
(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
fromInteger :: Integer -> Port
$cfromInteger :: Integer -> Port
signum :: Port -> Port
$csignum :: Port -> Port
abs :: Port -> Port
$cabs :: Port -> Port
negate :: Port -> Port
$cnegate :: Port -> Port
* :: Port -> Port -> Port
$c* :: Port -> Port -> Port
- :: Port -> Port -> Port
$c- :: Port -> Port -> Port
+ :: Port -> Port -> Port
$c+ :: Port -> Port -> Port
Num, Typeable Port
Decoder s Port
Typeable Port
-> (forall s. Decoder s Port)
-> (Proxy Port -> Text)
-> FromCBOR Port
Proxy Port -> Text
forall s. Decoder s Port
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy Port -> Text
$clabel :: Proxy Port -> Text
fromCBOR :: Decoder s Port
$cfromCBOR :: forall s. Decoder s Port
$cp1FromCBOR :: Typeable Port
FromCBOR, Typeable Port
Typeable Port
-> (Port -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy Port -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Port] -> Size)
-> ToCBOR Port
Port -> Encoding
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy Port -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Port] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Port -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Port -> Size
toCBOR :: Port -> Encoding
$ctoCBOR :: Port -> Encoding
$cp1ToCBOR :: Typeable Port
ToCBOR, Port -> ()
(Port -> ()) -> NFData Port
forall a. (a -> ()) -> NFData a
rnf :: Port -> ()
$crnf :: 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
showTypeOf :: Proxy Port -> String
$cshowTypeOf :: Proxy Port -> String
wNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
noThunks :: Context -> Port -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Port -> IO (Maybe ThunkInfo)
NoThunks, [Port] -> Encoding
[Port] -> Value
Port -> Encoding
Port -> Value
(Port -> Value)
-> (Port -> Encoding)
-> ([Port] -> Value)
-> ([Port] -> Encoding)
-> ToJSON Port
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Port] -> Encoding
$ctoEncodingList :: [Port] -> Encoding
toJSONList :: [Port] -> Value
$ctoJSONList :: [Port] -> Value
toEncoding :: Port -> Encoding
$ctoEncoding :: Port -> Encoding
toJSON :: Port -> Value
$ctoJSON :: Port -> Value
ToJSON, Value -> Parser [Port]
Value -> Parser Port
(Value -> Parser Port) -> (Value -> Parser [Port]) -> FromJSON Port
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Port]
$cparseJSONList :: Value -> Parser [Port]
parseJSON :: Value -> Parser Port
$cparseJSON :: Value -> Parser Port
FromJSON)
data ActiveSlotCoeff = ActiveSlotCoeff
{ ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal :: !PositiveUnitInterval,
ActiveSlotCoeff -> Integer
unActiveSlotLog :: !Integer
}
deriving (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
(ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> (ActiveSlotCoeff -> ActiveSlotCoeff -> Bool)
-> Eq ActiveSlotCoeff
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c/= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c== :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
Eq, Eq ActiveSlotCoeff
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
min :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
$cmin :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
max :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
$cmax :: ActiveSlotCoeff -> ActiveSlotCoeff -> ActiveSlotCoeff
>= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c>= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
> :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c> :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
<= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c<= :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
< :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
$c< :: ActiveSlotCoeff -> ActiveSlotCoeff -> Bool
compare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
$ccompare :: ActiveSlotCoeff -> ActiveSlotCoeff -> Ordering
$cp1Ord :: Eq 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
showList :: [ActiveSlotCoeff] -> ShowS
$cshowList :: [ActiveSlotCoeff] -> ShowS
show :: ActiveSlotCoeff -> String
$cshow :: ActiveSlotCoeff -> String
showsPrec :: Int -> ActiveSlotCoeff -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep ActiveSlotCoeff x -> ActiveSlotCoeff
$cfrom :: forall x. ActiveSlotCoeff -> Rep ActiveSlotCoeff x
Generic)
instance NoThunks ActiveSlotCoeff
instance NFData ActiveSlotCoeff
instance FromCBOR ActiveSlotCoeff where
fromCBOR :: 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 a s. FromCBOR a => Decoder s a
fromCBOR
instance ToCBOR ActiveSlotCoeff where
toCBOR :: ActiveSlotCoeff -> Encoding
toCBOR
ActiveSlotCoeff
{ unActiveSlotVal :: ActiveSlotCoeff -> PositiveUnitInterval
unActiveSlotVal = PositiveUnitInterval
slotVal,
unActiveSlotLog :: ActiveSlotCoeff -> Integer
unActiveSlotLog = Integer
_logVal
} =
PositiveUnitInterval -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR PositiveUnitInterval
slotVal
mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff :: PositiveUnitInterval -> ActiveSlotCoeff
mkActiveSlotCoeff PositiveUnitInterval
v =
ActiveSlotCoeff :: PositiveUnitInterval -> Integer -> ActiveSlotCoeff
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
Integer
0
else
FixedPoint -> Integer
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
data Globals = Globals
{ Globals -> EpochInfo (Either Text)
epochInfo :: !(EpochInfo (Either Text)),
Globals -> Word64
slotsPerKESPeriod :: !Word64,
Globals -> Word64
stabilityWindow :: !Word64,
Globals -> Word64
randomnessStabilisationWindow :: !Word64,
Globals -> Word64
securityParameter :: !Word64,
Globals -> Word64
maxKESEvo :: !Word64,
Globals -> Word64
quorum :: !Word64,
Globals -> Natural
maxMajorPV :: !Natural,
Globals -> Word64
maxLovelaceSupply :: !Word64,
Globals -> ActiveSlotCoeff
activeSlotCoeff :: !ActiveSlotCoeff,
Globals -> Network
networkId :: !Network,
Globals -> SystemStart
systemStart :: !SystemStart
}
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
showList :: [Globals] -> ShowS
$cshowList :: [Globals] -> ShowS
show :: Globals -> String
$cshow :: Globals -> String
showsPrec :: Int -> Globals -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep Globals x -> Globals
$cfrom :: forall x. Globals -> Rep Globals x
Generic)
instance NoThunks Globals
type ShelleyBase = ReaderT Globals Identity
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 (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
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
/= :: Network -> Network -> Bool
$c/= :: Network -> Network -> Bool
== :: Network -> Network -> Bool
$c== :: 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
min :: Network -> Network -> Network
$cmin :: Network -> Network -> Network
max :: Network -> Network -> Network
$cmax :: Network -> Network -> Network
>= :: Network -> Network -> Bool
$c>= :: Network -> Network -> Bool
> :: Network -> Network -> Bool
$c> :: Network -> Network -> Bool
<= :: Network -> Network -> Bool
$c<= :: Network -> Network -> Bool
< :: Network -> Network -> Bool
$c< :: Network -> Network -> Bool
compare :: Network -> Network -> Ordering
$ccompare :: Network -> Network -> Ordering
$cp1Ord :: Eq 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
enumFromThenTo :: Network -> Network -> Network -> [Network]
$cenumFromThenTo :: Network -> Network -> Network -> [Network]
enumFromTo :: Network -> Network -> [Network]
$cenumFromTo :: Network -> Network -> [Network]
enumFromThen :: Network -> Network -> [Network]
$cenumFromThen :: Network -> Network -> [Network]
enumFrom :: Network -> [Network]
$cenumFrom :: Network -> [Network]
fromEnum :: Network -> Int
$cfromEnum :: Network -> Int
toEnum :: Int -> Network
$ctoEnum :: Int -> Network
pred :: Network -> Network
$cpred :: Network -> Network
succ :: Network -> Network
$csucc :: Network -> Network
Enum, Network
Network -> Network -> Bounded Network
forall a. a -> a -> Bounded a
maxBound :: Network
$cmaxBound :: Network
minBound :: Network
$cminBound :: 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
showList :: [Network] -> ShowS
$cshowList :: [Network] -> ShowS
show :: Network -> String
$cshow :: Network -> String
showsPrec :: Int -> Network -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep Network x -> Network
$cfrom :: forall x. Network -> Rep Network x
Generic, Network -> ()
(Network -> ()) -> NFData Network
forall a. (a -> ()) -> NFData a
rnf :: Network -> ()
$crnf :: Network -> ()
NFData, [Network] -> Encoding
[Network] -> Value
Network -> Encoding
Network -> Value
(Network -> Value)
-> (Network -> Encoding)
-> ([Network] -> Value)
-> ([Network] -> Encoding)
-> ToJSON Network
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Network] -> Encoding
$ctoEncodingList :: [Network] -> Encoding
toJSONList :: [Network] -> Value
$ctoJSONList :: [Network] -> Value
toEncoding :: Network -> Encoding
$ctoEncoding :: Network -> Encoding
toJSON :: Network -> Value
$ctoJSON :: Network -> Value
ToJSON, Value -> Parser [Network]
Value -> Parser Network
(Value -> Parser Network)
-> (Value -> Parser [Network]) -> FromJSON Network
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Network]
$cparseJSONList :: Value -> Parser [Network]
parseJSON :: Value -> Parser Network
$cparseJSON :: Value -> Parser Network
FromJSON, Context -> Network -> IO (Maybe ThunkInfo)
Proxy Network -> String
(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
showTypeOf :: Proxy Network -> String
$cshowTypeOf :: Proxy Network -> String
wNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
noThunks :: Context -> Network -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> Network -> IO (Maybe ThunkInfo)
NoThunks)
networkToWord8 :: Network -> Word8
networkToWord8 :: Network -> Word8
networkToWord8 = 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 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 FromCBOR Network where
fromCBOR :: Decoder s Network
fromCBOR =
Word8 -> Maybe Network
word8ToNetwork (Word8 -> Maybe Network)
-> Decoder s Word8 -> Decoder s (Maybe Network)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Word8
forall a s. FromCBOR a => Decoder s a
fromCBOR Decoder s (Maybe Network)
-> (Maybe Network -> Decoder s Network) -> Decoder s Network
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Network
Nothing -> DecoderError -> Decoder s Network
forall e s a. Buildable e => e -> Decoder s 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 (f :: * -> *) a. Applicative f => a -> f a
pure Network
n
newtype BlocksMade crypto = BlocksMade
{ BlocksMade crypto -> Map (KeyHash 'StakePool crypto) Natural
unBlocksMade :: Map (KeyHash 'StakePool crypto) Natural
}
deriving (BlocksMade crypto -> BlocksMade crypto -> Bool
(BlocksMade crypto -> BlocksMade crypto -> Bool)
-> (BlocksMade crypto -> BlocksMade crypto -> Bool)
-> Eq (BlocksMade crypto)
forall crypto. BlocksMade crypto -> BlocksMade crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlocksMade crypto -> BlocksMade crypto -> Bool
$c/= :: forall crypto. BlocksMade crypto -> BlocksMade crypto -> Bool
== :: BlocksMade crypto -> BlocksMade crypto -> Bool
$c== :: forall crypto. BlocksMade crypto -> BlocksMade crypto -> Bool
Eq, (forall x. BlocksMade crypto -> Rep (BlocksMade crypto) x)
-> (forall x. Rep (BlocksMade crypto) x -> BlocksMade crypto)
-> Generic (BlocksMade crypto)
forall x. Rep (BlocksMade crypto) x -> BlocksMade crypto
forall x. BlocksMade crypto -> Rep (BlocksMade crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (BlocksMade crypto) x -> BlocksMade crypto
forall crypto x. BlocksMade crypto -> Rep (BlocksMade crypto) x
$cto :: forall crypto x. Rep (BlocksMade crypto) x -> BlocksMade crypto
$cfrom :: forall crypto x. BlocksMade crypto -> Rep (BlocksMade crypto) x
Generic)
deriving (Int -> BlocksMade crypto -> ShowS
[BlocksMade crypto] -> ShowS
BlocksMade crypto -> String
(Int -> BlocksMade crypto -> ShowS)
-> (BlocksMade crypto -> String)
-> ([BlocksMade crypto] -> ShowS)
-> Show (BlocksMade crypto)
forall crypto. Int -> BlocksMade crypto -> ShowS
forall crypto. [BlocksMade crypto] -> ShowS
forall crypto. BlocksMade crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlocksMade crypto] -> ShowS
$cshowList :: forall crypto. [BlocksMade crypto] -> ShowS
show :: BlocksMade crypto -> String
$cshow :: forall crypto. BlocksMade crypto -> String
showsPrec :: Int -> BlocksMade crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> BlocksMade crypto -> ShowS
Show) via Quiet (BlocksMade crypto)
deriving newtype (Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
Proxy (BlocksMade crypto) -> String
(Context -> BlocksMade crypto -> IO (Maybe ThunkInfo))
-> (Context -> BlocksMade crypto -> IO (Maybe ThunkInfo))
-> (Proxy (BlocksMade crypto) -> String)
-> NoThunks (BlocksMade crypto)
forall crypto. Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
forall crypto. Proxy (BlocksMade crypto) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (BlocksMade crypto) -> String
$cshowTypeOf :: forall crypto. Proxy (BlocksMade crypto) -> String
wNoThunks :: Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall crypto. Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
$cnoThunks :: forall crypto. Context -> BlocksMade crypto -> IO (Maybe ThunkInfo)
NoThunks, BlocksMade crypto -> ()
(BlocksMade crypto -> ()) -> NFData (BlocksMade crypto)
forall crypto. BlocksMade crypto -> ()
forall a. (a -> ()) -> NFData a
rnf :: BlocksMade crypto -> ()
$crnf :: forall crypto. BlocksMade crypto -> ()
NFData, [BlocksMade crypto] -> Encoding
[BlocksMade crypto] -> Value
BlocksMade crypto -> Encoding
BlocksMade crypto -> Value
(BlocksMade crypto -> Value)
-> (BlocksMade crypto -> Encoding)
-> ([BlocksMade crypto] -> Value)
-> ([BlocksMade crypto] -> Encoding)
-> ToJSON (BlocksMade crypto)
forall crypto. Crypto crypto => [BlocksMade crypto] -> Encoding
forall crypto. Crypto crypto => [BlocksMade crypto] -> Value
forall crypto. Crypto crypto => BlocksMade crypto -> Encoding
forall crypto. Crypto crypto => BlocksMade crypto -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BlocksMade crypto] -> Encoding
$ctoEncodingList :: forall crypto. Crypto crypto => [BlocksMade crypto] -> Encoding
toJSONList :: [BlocksMade crypto] -> Value
$ctoJSONList :: forall crypto. Crypto crypto => [BlocksMade crypto] -> Value
toEncoding :: BlocksMade crypto -> Encoding
$ctoEncoding :: forall crypto. Crypto crypto => BlocksMade crypto -> Encoding
toJSON :: BlocksMade crypto -> Value
$ctoJSON :: forall crypto. Crypto crypto => BlocksMade crypto -> Value
ToJSON, Value -> Parser [BlocksMade crypto]
Value -> Parser (BlocksMade crypto)
(Value -> Parser (BlocksMade crypto))
-> (Value -> Parser [BlocksMade crypto])
-> FromJSON (BlocksMade crypto)
forall crypto. Crypto crypto => Value -> Parser [BlocksMade crypto]
forall crypto. Crypto crypto => Value -> Parser (BlocksMade crypto)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BlocksMade crypto]
$cparseJSONList :: forall crypto. Crypto crypto => Value -> Parser [BlocksMade crypto]
parseJSON :: Value -> Parser (BlocksMade crypto)
$cparseJSON :: forall crypto. Crypto crypto => Value -> Parser (BlocksMade crypto)
FromJSON, Typeable (BlocksMade crypto)
Typeable (BlocksMade crypto)
-> (BlocksMade crypto -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade crypto) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade crypto] -> Size)
-> ToCBOR (BlocksMade crypto)
BlocksMade crypto -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade crypto] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade crypto) -> 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
forall crypto. Crypto crypto => Typeable (BlocksMade crypto)
forall crypto. Crypto crypto => BlocksMade crypto -> Encoding
forall crypto.
Crypto crypto =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade crypto] -> Size
forall crypto.
Crypto crypto =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade crypto) -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade crypto] -> Size
$cencodedListSizeExpr :: forall crypto.
Crypto crypto =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [BlocksMade crypto] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade crypto) -> Size
$cencodedSizeExpr :: forall crypto.
Crypto crypto =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (BlocksMade crypto) -> Size
toCBOR :: BlocksMade crypto -> Encoding
$ctoCBOR :: forall crypto. Crypto crypto => BlocksMade crypto -> Encoding
$cp1ToCBOR :: forall crypto. Crypto crypto => Typeable (BlocksMade crypto)
ToCBOR, Typeable (BlocksMade crypto)
Decoder s (BlocksMade crypto)
Typeable (BlocksMade crypto)
-> (forall s. Decoder s (BlocksMade crypto))
-> (Proxy (BlocksMade crypto) -> Text)
-> FromCBOR (BlocksMade crypto)
Proxy (BlocksMade crypto) -> Text
forall s. Decoder s (BlocksMade crypto)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
forall crypto. Crypto crypto => Typeable (BlocksMade crypto)
forall crypto. Crypto crypto => Proxy (BlocksMade crypto) -> Text
forall crypto s. Crypto crypto => Decoder s (BlocksMade crypto)
label :: Proxy (BlocksMade crypto) -> Text
$clabel :: forall crypto. Crypto crypto => Proxy (BlocksMade crypto) -> Text
fromCBOR :: Decoder s (BlocksMade crypto)
$cfromCBOR :: forall crypto s. Crypto crypto => Decoder s (BlocksMade crypto)
$cp1FromCBOR :: forall crypto. Crypto crypto => Typeable (BlocksMade crypto)
FromCBOR)
newtype TxIx = TxIx Word64
deriving stock (TxIx -> TxIx -> Bool
(TxIx -> TxIx -> Bool) -> (TxIx -> TxIx -> Bool) -> Eq TxIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxIx -> TxIx -> Bool
$c/= :: TxIx -> TxIx -> Bool
== :: TxIx -> TxIx -> Bool
$c== :: TxIx -> TxIx -> Bool
Eq, Eq TxIx
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
min :: TxIx -> TxIx -> TxIx
$cmin :: TxIx -> TxIx -> TxIx
max :: TxIx -> TxIx -> TxIx
$cmax :: TxIx -> TxIx -> TxIx
>= :: TxIx -> TxIx -> Bool
$c>= :: TxIx -> TxIx -> Bool
> :: TxIx -> TxIx -> Bool
$c> :: TxIx -> TxIx -> Bool
<= :: TxIx -> TxIx -> Bool
$c<= :: TxIx -> TxIx -> Bool
< :: TxIx -> TxIx -> Bool
$c< :: TxIx -> TxIx -> Bool
compare :: TxIx -> TxIx -> Ordering
$ccompare :: TxIx -> TxIx -> Ordering
$cp1Ord :: Eq 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
showList :: [TxIx] -> ShowS
$cshowList :: [TxIx] -> ShowS
show :: TxIx -> String
$cshow :: TxIx -> String
showsPrec :: Int -> TxIx -> ShowS
$cshowsPrec :: Int -> TxIx -> ShowS
Show)
deriving newtype (TxIx -> ()
(TxIx -> ()) -> NFData TxIx
forall a. (a -> ()) -> NFData a
rnf :: TxIx -> ()
$crnf :: TxIx -> ()
NFData, Int -> TxIx
TxIx -> Int
TxIx -> [TxIx]
TxIx -> TxIx
TxIx -> TxIx -> [TxIx]
TxIx -> TxIx -> TxIx -> [TxIx]
(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
enumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
$cenumFromThenTo :: TxIx -> TxIx -> TxIx -> [TxIx]
enumFromTo :: TxIx -> TxIx -> [TxIx]
$cenumFromTo :: TxIx -> TxIx -> [TxIx]
enumFromThen :: TxIx -> TxIx -> [TxIx]
$cenumFromThen :: TxIx -> TxIx -> [TxIx]
enumFrom :: TxIx -> [TxIx]
$cenumFrom :: TxIx -> [TxIx]
fromEnum :: TxIx -> Int
$cfromEnum :: TxIx -> Int
toEnum :: Int -> TxIx
$ctoEnum :: Int -> TxIx
pred :: TxIx -> TxIx
$cpred :: TxIx -> TxIx
succ :: TxIx -> TxIx
$csucc :: TxIx -> TxIx
Enum, TxIx
TxIx -> TxIx -> Bounded TxIx
forall a. a -> a -> Bounded a
maxBound :: TxIx
$cmaxBound :: TxIx
minBound :: TxIx
$cminBound :: 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
showTypeOf :: Proxy TxIx -> String
$cshowTypeOf :: Proxy TxIx -> String
wNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> TxIx -> IO (Maybe ThunkInfo)
NoThunks, Typeable TxIx
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
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size
toCBOR :: TxIx -> Encoding
$ctoCBOR :: TxIx -> Encoding
$cp1ToCBOR :: Typeable TxIx
ToCBOR, Typeable TxIx
Decoder s 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
label :: Proxy TxIx -> Text
$clabel :: Proxy TxIx -> Text
fromCBOR :: Decoder s TxIx
$cfromCBOR :: forall s. Decoder s TxIx
$cp1FromCBOR :: Typeable TxIx
FromCBOR)
txIxToInt :: TxIx -> Int
txIxToInt :: TxIx -> Int
txIxToInt (TxIx Word64
w16) = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w16
txIxFromIntegral :: Integral a => a -> Maybe TxIx
txIxFromIntegral :: a -> Maybe TxIx
txIxFromIntegral = (Word16 -> TxIx) -> Maybe Word16 -> Maybe TxIx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word64 -> TxIx
TxIx (Word64 -> TxIx) -> (Word16 -> Word64) -> Word16 -> TxIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Maybe Word16 -> Maybe TxIx)
-> (a -> Maybe Word16) -> a -> Maybe TxIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Maybe Word16
word16FromInteger (Integer -> Maybe Word16) -> (a -> Integer) -> a -> Maybe Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a. Integral a => a -> Integer
toInteger
mkTxIxPartial :: HasCallStack => Integer -> TxIx
mkTxIxPartial :: 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. Integral a => a -> Maybe TxIx
txIxFromIntegral Integer
i
newtype CertIx = CertIx Word64
deriving stock (CertIx -> CertIx -> Bool
(CertIx -> CertIx -> Bool)
-> (CertIx -> CertIx -> Bool) -> Eq CertIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertIx -> CertIx -> Bool
$c/= :: CertIx -> CertIx -> Bool
== :: CertIx -> CertIx -> Bool
$c== :: CertIx -> CertIx -> Bool
Eq, Eq CertIx
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
min :: CertIx -> CertIx -> CertIx
$cmin :: CertIx -> CertIx -> CertIx
max :: CertIx -> CertIx -> CertIx
$cmax :: CertIx -> CertIx -> CertIx
>= :: CertIx -> CertIx -> Bool
$c>= :: CertIx -> CertIx -> Bool
> :: CertIx -> CertIx -> Bool
$c> :: CertIx -> CertIx -> Bool
<= :: CertIx -> CertIx -> Bool
$c<= :: CertIx -> CertIx -> Bool
< :: CertIx -> CertIx -> Bool
$c< :: CertIx -> CertIx -> Bool
compare :: CertIx -> CertIx -> Ordering
$ccompare :: CertIx -> CertIx -> Ordering
$cp1Ord :: Eq 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
showList :: [CertIx] -> ShowS
$cshowList :: [CertIx] -> ShowS
show :: CertIx -> String
$cshow :: CertIx -> String
showsPrec :: Int -> CertIx -> ShowS
$cshowsPrec :: Int -> CertIx -> ShowS
Show)
deriving newtype (CertIx -> ()
(CertIx -> ()) -> NFData CertIx
forall a. (a -> ()) -> NFData a
rnf :: CertIx -> ()
$crnf :: CertIx -> ()
NFData, Int -> CertIx
CertIx -> Int
CertIx -> [CertIx]
CertIx -> CertIx
CertIx -> CertIx -> [CertIx]
CertIx -> CertIx -> CertIx -> [CertIx]
(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
enumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
$cenumFromThenTo :: CertIx -> CertIx -> CertIx -> [CertIx]
enumFromTo :: CertIx -> CertIx -> [CertIx]
$cenumFromTo :: CertIx -> CertIx -> [CertIx]
enumFromThen :: CertIx -> CertIx -> [CertIx]
$cenumFromThen :: CertIx -> CertIx -> [CertIx]
enumFrom :: CertIx -> [CertIx]
$cenumFrom :: CertIx -> [CertIx]
fromEnum :: CertIx -> Int
$cfromEnum :: CertIx -> Int
toEnum :: Int -> CertIx
$ctoEnum :: Int -> CertIx
pred :: CertIx -> CertIx
$cpred :: CertIx -> CertIx
succ :: CertIx -> CertIx
$csucc :: CertIx -> CertIx
Enum, CertIx
CertIx -> CertIx -> Bounded CertIx
forall a. a -> a -> Bounded a
maxBound :: CertIx
$cmaxBound :: CertIx
minBound :: CertIx
$cminBound :: 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
showTypeOf :: Proxy CertIx -> String
$cshowTypeOf :: Proxy CertIx -> String
wNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CertIx -> IO (Maybe ThunkInfo)
NoThunks, Typeable CertIx
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
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size
toCBOR :: CertIx -> Encoding
$ctoCBOR :: CertIx -> Encoding
$cp1ToCBOR :: Typeable CertIx
ToCBOR, Typeable CertIx
Decoder s 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
label :: Proxy CertIx -> Text
$clabel :: Proxy CertIx -> Text
fromCBOR :: Decoder s CertIx
$cfromCBOR :: forall s. Decoder s CertIx
$cp1FromCBOR :: Typeable CertIx
FromCBOR)
certIxToInt :: CertIx -> Int
certIxToInt :: CertIx -> Int
certIxToInt (CertIx Word64
w16) = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w16
certIxFromIntegral :: Integral a => a -> Maybe CertIx
certIxFromIntegral :: a -> Maybe CertIx
certIxFromIntegral = (Word16 -> CertIx) -> Maybe Word16 -> Maybe CertIx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word64 -> CertIx
CertIx (Word64 -> CertIx) -> (Word16 -> Word64) -> Word16 -> CertIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Maybe Word16 -> Maybe CertIx)
-> (a -> Maybe Word16) -> a -> Maybe CertIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Maybe Word16
word16FromInteger (Integer -> Maybe Word16) -> (a -> Integer) -> a -> Maybe Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a. Integral a => a -> Integer
toInteger
mkCertIxPartial :: HasCallStack => Integer -> CertIx
mkCertIxPartial :: 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. Integral a => a -> Maybe CertIx
certIxFromIntegral Integer
i
word16FromInteger :: Integer -> Maybe Word16
word16FromInteger :: Integer -> Maybe Word16
word16FromInteger Integer
i
| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Word16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16
forall a. Bounded a => a
minBound :: Word16) Bool -> Bool -> Bool
|| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Word16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16
forall a. Bounded a => a
maxBound :: Word16) = Maybe Word16
forall a. Maybe a
Nothing
| Bool
otherwise = Word16 -> Maybe Word16
forall a. a -> Maybe a
Just (Integer -> Word16
forall a. Num a => Integer -> a
fromInteger Integer
i)