locli-1.34: Cardano log analysis CLI
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Util

Synopsis

Documentation

type String = [Char] Source #

A String is a list of characters. String constants in Haskell are values of type String.

See Data.List for operations on lists.

error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a Source #

error stops execution and displays an error message.

head :: HasCallStack => [a] -> a Source #

\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.

>>> head [1, 2, 3]
1
>>> head [1..]
1
>>> head []
*** Exception: Prelude.head: empty list

WARNING: This function is partial. You can use case-matching, uncons or listToMaybe instead.

last :: HasCallStack => [a] -> a Source #

\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.

>>> last [1, 2, 3]
3
>>> last [1..]
* Hangs forever *
>>> last []
*** Exception: Prelude.last: empty list

WARNING: This function is partial. You can use reverse with case-matching, uncons or listToMaybe instead.

type HasCallStack = ?callStack :: CallStack Source #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

type HasDebugCallStack = () Source #

A call stack constraint, but only when isDebugOn.

data Direction Source #

Constructors

Forwards 
Backwards 

dropWhileEndLE :: (a -> Bool) -> [a] -> [a] Source #

ordNub :: Ord a => [a] -> [a] Source #

Remove duplicates but keep elements in order. O(n * log n)

singleton :: a -> [a] Source #

fstOf3 :: (a, b, c) -> a Source #

sndOf3 :: (a, b, c) -> b Source #

count :: (a -> Bool) -> [a] -> Int Source #

lengthAtLeast :: [a] -> Int -> Bool Source #

(lengthAtLeast xs n) = (length xs >= n)

foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a Source #

A strict version of foldl1.

applyWhen :: Bool -> (a -> a) -> a -> a Source #

Apply a function iff some condition is met.

sortWith :: Ord b => (a -> b) -> [a] -> [a] Source #

The sortWith function sorts a list of elements using the user supplied function to project something out of each element

In general if the user supplied function is expensive to compute then you should probably be using sortOn, as it only needs to compute it once for each element. sortWith, on the other hand must compute the mapping function for every comparison that it performs.

mkNoRepType :: String -> DataType Source #

Constructs a non-representation for a non-representable type

spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) Source #

spanEnd p l == reverse (span p (reverse l)). The first list returns actually comes after the second list (when you look at the input list).

compareLength :: [a] -> [b] -> Ordering Source #

dropList :: [b] -> [a] -> [a] Source #

(<&&>) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 Source #

(<||>) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 Source #

unzipWith :: (a -> b -> c) -> [(a, b)] -> [c] Source #

notNull :: Foldable f => f a -> Bool Source #

nubSort :: Ord a => [a] -> [a] Source #

nTimes :: Int -> (a -> a) -> a -> a Source #

Apply a function n times to a given value.

const2 :: a -> b -> c -> a Source #

thdOf3 :: (a, b, c) -> c Source #

filterOut :: (a -> Bool) -> [a] -> [a] Source #

Like filter, only it reverses the sense of the test

partitionWith :: (a -> Either b c) -> [a] -> ([b], [c]) Source #

Uses a function to determine which of two output lists an input element should join

chkAppend :: [a] -> [a] -> [a] Source #

zipEqual :: HasDebugCallStack => String -> [a] -> [b] -> [(a, b)] Source #

zipWithEqual :: HasDebugCallStack => String -> (a -> b -> c) -> [a] -> [b] -> [c] Source #

zipWith3Equal :: HasDebugCallStack => String -> (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

zipWith4Equal :: HasDebugCallStack => String -> (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] Source #

filterByList :: [Bool] -> [a] -> [a] Source #

filterByList takes a list of Bools and a list of some elements and filters out these elements for which the corresponding value in the list of Bools is False. This function does not check whether the lists have equal length.

filterByLists :: [Bool] -> [a] -> [a] -> [a] Source #

filterByLists takes a list of Bools and two lists as input, and outputs a new list consisting of elements from the last two input lists. For each Bool in the list, if it is True, then it takes an element from the former list. If it is False, it takes an element from the latter list. The elements taken correspond to the index of the Bool in its list. For example:

filterByLists [True, False, True, False] "abcd" "wxyz" = "axcz"

This function does not check whether the lists have equal length.

partitionByList :: [Bool] -> [a] -> ([a], [a]) Source #

partitionByList takes a list of Bools and a list of some elements and partitions the list according to the list of Bools. Elements corresponding to True go to the left; elements corresponding to False go to the right. For example, partitionByList [True, False, True] [1,2,3] == ([1,3], [2]) This function does not check whether the lists have equal length; when one list runs out, the function stops.

stretchZipWith :: (a -> Bool) -> b -> (a -> b -> c) -> [a] -> [b] -> [c] Source #

stretchZipWith p z f xs ys stretches ys by inserting z in the places where p returns True

mapFst :: Functor f => (a -> c) -> f (a, b) -> f (c, b) Source #

mapSnd :: Functor f => (b -> c) -> f (a, b) -> f (a, c) Source #

mapAndUnzip :: (a -> (b, c)) -> [a] -> ([b], [c]) Source #

mapAndUnzip3 :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d]) Source #

zipWithAndUnzip :: (a -> b -> (c, d)) -> [a] -> [b] -> ([c], [d]) Source #

zipAndUnzip :: [a] -> [b] -> ([a], [b]) Source #

This has the effect of making the two lists have equal length by dropping the tail of the longer one.

atLength :: ([a] -> b) -> b -> [a] -> Int -> b Source #

atLength atLen atEnd ls n unravels list ls to position n. Precisely:

 atLength atLenPred atEndPred ls n
  | n < 0         = atLenPred ls
  | length ls < n = atEndPred (n - length ls)
  | otherwise     = atLenPred (drop n ls)

lengthExceeds :: [a] -> Int -> Bool Source #

(lengthExceeds xs n) = (length xs > n)

lengthIs :: [a] -> Int -> Bool Source #

(lengthIs xs n) = (length xs == n)

lengthIsNot :: [a] -> Int -> Bool Source #

(lengthIsNot xs n) = (length xs /= n)

lengthAtMost :: [a] -> Int -> Bool Source #

(lengthAtMost xs n) = (length xs <= n)

lengthLessThan :: [a] -> Int -> Bool Source #

(lengthLessThan xs n) == (length xs < n)

equalLength :: [a] -> [b] -> Bool Source #

True if length xs == length ys

leLength :: [a] -> [b] -> Bool Source #

True if length xs <= length ys

ltLength :: [a] -> [b] -> Bool Source #

True if length xs < length ys

only :: [a] -> a Source #

Utility function to go from a singleton list to it's element.

Wether or not the argument is a singleton list is only checked in debug builds.

expectOnly :: HasCallStack => String -> [a] -> a Source #

Extract the single element of a list and panic with the given message if there are more elements or the list was empty. Like expectJust, but for lists.

chunkList :: Int -> [a] -> [[a]] Source #

Split a list into chunks of n elements

holes :: [a] -> [(a, [a])] Source #

Compute all the ways of removing a single element from a list.

holes [1,2,3] = [(1, [2,3]), (2, [1,3]), (3, [1,2])]

changeLast :: [a] -> a -> [a] Source #

Replace the last element of a list with another element.

mapLastM :: Functor f => (a -> f a) -> NonEmpty a -> f (NonEmpty a) Source #

Apply an effectful function to the last list element.

whenNonEmpty :: Applicative m => [a] -> (NonEmpty a -> m ()) -> m () Source #

mergeListsBy :: (a -> a -> Ordering) -> [[a]] -> [a] Source #

Merge an unsorted list of sorted lists, for example:

mergeListsBy compare [ [2,5,15], [1,10,100] ] = [1,2,5,10,15,100]

\( O(n \log{} k) \)

isSortedBy :: (a -> a -> Ordering) -> [a] -> Bool Source #

minWith :: Ord b => (a -> b) -> [a] -> a Source #

ordNubOn :: Ord b => (a -> b) -> [a] -> [a] Source #

Remove duplicates but keep elements in order. O(n * log n)

transitiveClosure :: (a -> [a]) -> (a -> a -> Bool) -> [a] -> [a] Source #

foldl2 :: (acc -> a -> b -> acc) -> acc -> [a] -> [b] -> acc Source #

all2 :: (a -> b -> Bool) -> [a] -> [b] -> Bool Source #

countWhile :: (a -> Bool) -> [a] -> Int Source #

takeList :: [b] -> [a] -> [a] Source #

splitAtList :: [b] -> [a] -> ([a], [a]) Source #

Given two lists xs and ys, return `splitAt (length xs) ys`.

dropTail :: Int -> [a] -> [a] Source #

drop from the end of a list

last2 :: [a] -> Maybe (a, a) Source #

Get the last two elements in a list.

lastMaybe :: [a] -> Maybe a Source #

onJust :: b -> Maybe a -> (a -> b) -> b Source #

onJust x m f applies f to the value inside the Just or returns the default.

snocView :: [a] -> Maybe ([a], a) Source #

Split a list into its last element and the initial part of the list. snocView xs = Just (init xs, last xs) for non-empty lists. snocView xs = Nothing otherwise. Unless both parts of the result are guaranteed to be used prefer separate calls to last + init. If you are guaranteed to use both, this will be more efficient.

capitalise :: String -> String Source #

Convert a word to title case by capitalising the first letter

fuzzyLookup :: String -> [(String, a)] -> [a] Source #

Search for possible matches to the users input in the given list, returning a small number of ranked results

seqList :: [a] -> b -> b Source #

strictMap :: (a -> b) -> [a] -> [b] Source #

strictZipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

strictZipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

exactLog2 :: Integer -> Maybe Integer Source #

Determine the $log_2$ of exact powers of 2

readSignificandExponentPair :: String -> (Integer, Integer) Source #

Parse a string into a significand and exponent. A trivial example might be: ghci> readSignificandExponentPair "1E2" (1,2) In a more complex case we might return a exponent different than that which the user wrote. This is needed in order to use a Integer significand. ghci> readSignificandExponentPair "-1.11E5" (-111,3)

readHexSignificandExponentPair :: String -> (Integer, Integer) Source #

Parse a string into a significand and exponent according to the "Hexadecimal Floats in Haskell" proposal. A trivial example might be: ghci> readHexSignificandExponentPair "0x1p+1" (1,1) Behaves similar to readSignificandExponentPair but the base is 16 and numbers are given in hexadecimal: ghci> readHexSignificandExponentPair "0xAp-4" (10,-4) ghci> readHexSignificandExponentPair "0x1.2p3" (18,-1)

withAtomicRename :: MonadIO m => FilePath -> (FilePath -> m a) -> m a Source #

hashString :: String -> Int32 Source #

A sample hash function for Strings. We keep multiplying by the golden ratio and adding. The implementation is:

hashString = foldl' f golden
  where f m c = fromIntegral (ord c) * magic + hashInt32 m
        magic = 0xdeadbeef

Where hashInt32 works just as hashInt shown above.

Knuth argues that repeated multiplication by the golden ratio will minimize gaps in the hash space, and thus it's a good choice for combining together multiple keys to form one.

Here we know that individual characters c are often small, and this produces frequent collisions if we use ord c alone. A particular problem are the shorter low ASCII and ISO-8859-1 character strings. We pre-multiply by a magic twiddle factor to obtain a good distribution. In fact, given the following test:

testp :: Int32 -> Int
testp k = (n - ) . length . group . sort . map hs . take n $ ls
  where ls = [] : [c : l | l <- ls, c <- ['\0'..'\xff']]
        hs = foldl' f golden
        f m c = fromIntegral (ord c) * k + hashInt32 m
        n = 100000

We discover that testp magic = 0.

mapMaybe' :: Foldable f => (a -> Maybe b) -> f a -> [b] Source #

data Value #

Instances

Instances details
Arbitrary Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

arbitrary :: Gen Value

shrink :: Value -> [Value]

CoArbitrary Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

coarbitrary :: Value -> Gen b -> Gen b

Function Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

function :: (Value -> b) -> Value :-> b

FromJSON Value 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Value -> Value #

toEncoding :: Value -> Encoding #

toJSONList :: [Value] -> Value #

toEncodingList :: [Value] -> Encoding #

omitField :: Value -> Bool #

Data Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value Source #

toConstr :: Value -> Constr Source #

dataTypeOf :: Value -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) Source #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

IsString Value 
Instance details

Defined in Data.Aeson.Types.Internal

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Read Value 
Instance details

Defined in Data.Aeson.Types.Internal

Show Value 
Instance details

Defined in Data.Aeson.Types.Internal

NFData Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Value -> () Source #

Quote Value 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

quote :: Id -> Int -> Value -> Term Source #

Unquote Value 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

unquote :: Id -> Int -> Term -> Result Value Source #

Eq Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

(==) :: Value -> Value -> Bool Source #

(/=) :: Value -> Value -> Bool Source #

Ord Value 
Instance details

Defined in Data.Aeson.Types.Internal

Hashable Value 
Instance details

Defined in Data.Aeson.Types.Internal

KeyValue Encoding Series 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> Series #

explicitToField :: (v -> Encoding) -> Key -> v -> Series

KeyValueOmit Encoding Series 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.?=) :: ToJSON v => Key -> v -> Series

explicitToFieldOmit :: (v -> Bool) -> (v -> Encoding) -> Key -> v -> Series

Lift Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

lift :: Quote m => Value -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Value -> Code m Value Source #

(GToJSON' Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

sumToJSON' :: Options -> ToArgs Encoding arity a0 -> C1 c a a0 -> Tagged TwoElemArray Encoding

(GToJSON' Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

sumToJSON' :: Options -> ToArgs Value arity a0 -> C1 c a a0 -> Tagged TwoElemArray Value

GToJSON' Encoding arity (U1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding

GToJSON' Encoding arity (V1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> V1 a -> Encoding

GToJSON' Value arity (U1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> U1 a -> Value

GToJSON' Value arity (V1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> V1 a -> Value

ToJSON1 f => GToJSON' Encoding One (Rec1 f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding

ToJSON1 f => GToJSON' Value One (Rec1 f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> Rec1 f a -> Value

(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding

ToJSON a => GToJSON' Encoding arity (K1 i a :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> K1 i a a0 -> Encoding

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> (a :*: b) a0 -> Value

ToJSON a => GToJSON' Value arity (K1 i a :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> K1 i a a0 -> Value

(ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> (f :.: g) a -> Encoding

(ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> (f :.: g) a -> Value

FromPairs Value (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromPairs :: DList Pair -> Value

value ~ Value => KeyValue Value (KeyMap value) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> KeyMap value #

explicitToField :: (v -> Value) -> Key -> v -> KeyMap value

value ~ Value => KeyValueOmit Value (KeyMap value) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.?=) :: ToJSON v => Key -> v -> KeyMap value

explicitToFieldOmit :: (v -> Bool) -> (v -> Value) -> Key -> v -> KeyMap value

v ~ Value => KeyValuePair v (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

pair :: Key -> v -> DList Pair

(key ~ Key, value ~ Value) => KeyValue Value (key, value) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> (key, value) #

explicitToField :: (v -> Value) -> Key -> v -> (key, value)

Quote (KeyMap Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

quote :: Id -> Int -> KeyMap Value -> Term Source #

Quote (Vector Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

quote :: Id -> Int -> Vector Value -> Term Source #

Quote [Value] 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

quote :: Id -> Int -> [Value] -> Term Source #

Unquote (KeyMap Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

unquote :: Id -> Int -> Term -> Result (KeyMap Value) Source #

Unquote (Vector Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

unquote :: Id -> Int -> Term -> Result (Vector Value) Source #

AnsiPretty (PP Value) 
Instance details

Defined in Text.EDE.Internal.Types

Quote (HashMap Text Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

quote :: Id -> Int -> HashMap Text Value -> Term Source #

Unquote (HashMap Text Value) 
Instance details

Defined in Text.EDE.Internal.Quoting

Methods

unquote :: Id -> Int -> Term -> Result (HashMap Text Value) Source #

type Rep Value 
Instance details

Defined in Data.Aeson.Types.Internal

type Object = KeyMap Value #

class FromJSON a where #

Minimal complete definition

Nothing

Instances

Instances details
FromJSON Key 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Key #

parseJSONList :: Value -> Parser [Key] #

omittedField :: Maybe Key #

FromJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DotNetTime #

parseJSONList :: Value -> Parser [DotNetTime] #

omittedField :: Maybe DotNetTime #

FromJSON Value 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Version 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Void 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ByteString64 
Instance details

Defined in Data.ByteString.Base64.Type

Methods

parseJSON :: Value -> Parser ByteString64 #

parseJSONList :: Value -> Parser [ByteString64] #

omittedField :: Maybe ByteString64 #

FromJSON ProtocolMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

FromJSON ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

FromJSON RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

FromJSON CompactRedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Compact

FromJSON RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

FromJSON VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

FromJSON DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON NonNegativeInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON Port 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON PositiveInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON UnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

FromJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

FromJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

FromJSON RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

FromJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

FromJSON IntSet 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Ordering 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON SlotStart Source # 
Instance details

Defined in Cardano.Analysis.API.Chain

FromJSON BlockCond Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

FromJSON ChainFilter Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

FromJSON FilterName Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

FromJSON SlotCond Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

FromJSON Branch Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON Commit Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON ComponentInfo Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON GeneratorProfile Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON Genesis Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON GenesisSpec Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON Manifest Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON Metadata Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON PParams Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON PlutusParams Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON Version Source # 
Instance details

Defined in Cardano.Analysis.API.Context

FromJSON DictEntry Source # 
Instance details

Defined in Cardano.Analysis.API.Dictionary

FromJSON Dictionary Source # 
Instance details

Defined in Cardano.Analysis.API.Dictionary

FromJSON EpochSafeInt Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON EpochSlot Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON FieldName Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON Hash Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON Host Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON JsonLogfile Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON TId Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

FromJSON LocliVersion Source # 
Instance details

Defined in Cardano.Analysis.API.LocliVersion

FromJSON RunPartial Source # 
Instance details

Defined in Cardano.Analysis.API.Run

FromJSON BPError Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON BPErrorKind Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON BlockEvents Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON BlockForge Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON BlockObservation Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON HostBlockStats Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON MultiClusterPerf Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON Phase Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON SomeBlockProp Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON SomeSummary Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON MachView Source # 
Instance details

Defined in Cardano.Analysis.BlockProp

FromJSON Author Source # 
Instance details

Defined in Cardano.Report

FromJSON ShortId Source # 
Instance details

Defined in Cardano.Report

FromJSON Tag Source # 
Instance details

Defined in Cardano.Report

FromJSON LogObject Source # 
Instance details

Defined in Cardano.Unlog.LogObject

FromJSON RUTCTime Source # 
Instance details

Defined in Cardano.Util

FromJSON Centile Source # 
Instance details

Defined in Data.CDF

FromJSON URI 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser URI #

parseJSONList :: Value -> Parser [URI] #

omittedField :: Maybe URI #

FromJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

FromJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

FromJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

FromJSON SatInt 
Instance details

Defined in Data.SatInt

FromJSON CovLoc 
Instance details

Defined in PlutusTx.Coverage

FromJSON CoverageAnnotation 
Instance details

Defined in PlutusTx.Coverage

FromJSON CoverageData 
Instance details

Defined in PlutusTx.Coverage

FromJSON CoverageIndex 
Instance details

Defined in PlutusTx.Coverage

FromJSON CoverageMetadata 
Instance details

Defined in PlutusTx.Coverage

FromJSON CoverageReport 
Instance details

Defined in PlutusTx.Coverage

FromJSON Metadata 
Instance details

Defined in PlutusTx.Coverage

FromJSON Rational

This mimics the behaviour of Aeson's instance for Rational.

Instance details

Defined in PlutusTx.Ratio

FromJSON Scientific 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON StudentT 
Instance details

Defined in Statistics.Distribution.StudentT

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ShortText 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Day 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Month 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Quarter 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ConfigOptionRep 
Instance details

Defined in Cardano.Logging.ConfigurationParser

Methods

parseJSON :: Value -> Parser ConfigOptionRep #

parseJSONList :: Value -> Parser [ConfigOptionRep] #

omittedField :: Maybe ConfigOptionRep #

FromJSON ConfigRepresentation 
Instance details

Defined in Cardano.Logging.ConfigurationParser

Methods

parseJSON :: Value -> Parser ConfigRepresentation #

parseJSONList :: Value -> Parser [ConfigRepresentation] #

omittedField :: Maybe ConfigRepresentation #

FromJSON BackendConfig 
Instance details

Defined in Cardano.Logging.Types

FromJSON DetailLevel 
Instance details

Defined in Cardano.Logging.Types

FromJSON ForwarderAddr 
Instance details

Defined in Cardano.Logging.Types

FromJSON ForwarderMode 
Instance details

Defined in Cardano.Logging.Types

FromJSON SeverityF 
Instance details

Defined in Cardano.Logging.Types

FromJSON SeverityS 
Instance details

Defined in Cardano.Logging.Types

FromJSON TraceOptionForwarder 
Instance details

Defined in Cardano.Logging.Types

FromJSON Verbosity 
Instance details

Defined in Cardano.Logging.Types

FromJSON UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser UUID #

parseJSONList :: Value -> Parser [UUID] #

omittedField :: Maybe UUID #

FromJSON Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON () 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Bool 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Char 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Double 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Float 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON v => FromJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (KeyMap v) #

parseJSONList :: Value -> Parser [KeyMap v] #

omittedField :: Maybe (KeyMap v) #

FromJSON a => FromJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Down a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON a, Integral a) => FromJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (RedeemSignature a) 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Signature

FromJSON (Signature w) 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Crypto c => FromJSON (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Crypto c => FromJSON (BlocksMade c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Crypto c => FromJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c => FromJSON (GenDelegPair c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Crypto c => FromJSON (GenDelegs c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

FromJSON a => FromJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

FromJSON a => FromJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

FromJSON a => FromJSON (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

FromJSON a => FromJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Ord a, FromJSON a) => FromJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON v => FromJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON1 f => FromJSON (Fix f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Fix f) #

parseJSONList :: Value -> Parser [Fix f] #

omittedField :: Maybe (Fix f) #

(FromJSON1 f, Functor f) => FromJSON (Mu f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Mu f) #

parseJSONList :: Value -> Parser [Mu f] #

omittedField :: Maybe (Mu f) #

(FromJSON1 f, Functor f) => FromJSON (Nu f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Nu f) #

parseJSONList :: Value -> Parser [Nu f] #

omittedField :: Maybe (Nu f) #

FromJSON a => FromJSON (DNonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Interval a) Source # 
Instance details

Defined in Cardano.Util

FromJSON (JsonInputFile a) Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

(forall a. FromJSON a => FromJSON (f a), FromJSON (CDFList f (DataDomain I SlotNo)), FromJSON (CDFList f (DataDomain I BlockNo))) => FromJSON (BlockProp f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON a => FromJSON (ForgerEvents a) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

(forall a. FromJSON a => FromJSON (f a), FromJSON (CDFList f (DataDomain I SlotNo))) => FromJSON (MachPerf f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

(forall a. FromJSON a => FromJSON (f a)) => FromJSON (Summary f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

FromJSON a => FromJSON (HostLogs a) Source # 
Instance details

Defined in Cardano.Unlog.LogObject

FromJSON a => FromJSON (RunLogs a) Source # 
Instance details

Defined in Cardano.Unlog.LogObject

(forall a. FromJSON a => FromJSON (f a)) => FromJSON (ProfileEntry f) Source # 
Instance details

Defined in Data.Profile

(forall a. FromJSON a => FromJSON (f a)) => FromJSON (ProfilingData f) Source # 
Instance details

Defined in Data.Profile

FromJSON (BuiltinCostModelBase CostingFun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

parseJSON :: Value -> Parser (BuiltinCostModelBase CostingFun) #

parseJSONList :: Value -> Parser [BuiltinCostModelBase CostingFun] #

omittedField :: Maybe (BuiltinCostModelBase CostingFun) #

FromJSON (CekMachineCostsBase Identity) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Methods

parseJSON :: Value -> Parser (CekMachineCostsBase Identity) #

parseJSONList :: Value -> Parser [CekMachineCostsBase Identity] #

omittedField :: Maybe (CekMachineCostsBase Identity) #

FromJSON a => FromJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Array a) #

parseJSONList :: Value -> Parser [Array a] #

omittedField :: Maybe (Array a) #

(Prim a, FromJSON a) => FromJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (PrimArray a) #

parseJSONList :: Value -> Parser [PrimArray a] #

omittedField :: Maybe (PrimArray a) #

FromJSON a => FromJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (SmallArray a) #

parseJSONList :: Value -> Parser [SmallArray a] #

omittedField :: Maybe (SmallArray a) #

FromJSON a => FromJSON (I a) Source # 
Instance details

Defined in Cardano.Util

Methods

parseJSON :: Value -> Parser (I a) #

parseJSONList :: Value -> Parser [I a] #

omittedField :: Maybe (I a) #

FromJSON d => FromJSON (LinearTransform d) 
Instance details

Defined in Statistics.Distribution.Transform

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Maybe a) #

parseJSONList :: Value -> Parser [Maybe a] #

omittedField :: Maybe0 (Maybe a) #

FromJSON a => FromJSON (Resources a) 
Instance details

Defined in Cardano.Logging.Resources.Types

(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Prim a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Storable a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a) #

parseJSONList :: Value -> Parser [(a)] #

omittedField :: Maybe (a) #

FromJSON a => FromJSON [a] 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser [a] #

parseJSONList :: Value -> Parser [[a]] #

omittedField :: Maybe [a] #

(FromJSON a, FromJSON b) => FromJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

HasResolution a => FromJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

HashAlgorithm h => FromJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

parseJSON :: Value -> Parser (Hash h a) #

parseJSONList :: Value -> Parser [Hash h a] #

omittedField :: Maybe (Hash h a) #

HashAlgorithm algo => FromJSON (AbstractHash algo a) 
Instance details

Defined in Cardano.Crypto.Hashing

FromJSON b => FromJSON (Annotated b ()) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Bounded (BoundedRatio b Word64) => FromJSON (BoundedRatio b Word64) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser (BoundedRatio b Word64) #

parseJSONList :: Value -> Parser [BoundedRatio b Word64] #

omittedField :: Maybe (BoundedRatio b Word64) #

Crypto c => FromJSON (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

parseJSON :: Value -> Parser (KeyHash disc c) #

parseJSONList :: Value -> Parser [KeyHash disc c] #

omittedField :: Maybe (KeyHash disc c) #

Crypto c => FromJSON (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

parseJSON :: Value -> Parser (SafeHash c index) #

parseJSONList :: Value -> Parser [SafeHash c index] #

omittedField :: Maybe (SafeHash c index) #

(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

omittedField :: Maybe (Map k v) #

FromJSON (Count a) Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

(FromJSON (p a), FromJSON (p Double), FromJSON a) => FromJSON (CDF p a) Source # 
Instance details

Defined in Data.CDF

Methods

parseJSON :: Value -> Parser (CDF p a) #

parseJSONList :: Value -> Parser [CDF p a] #

omittedField :: Maybe (CDF p a) #

(forall b. FromJSON b => FromJSON (f b), FromJSON a) => FromJSON (DataDomain f a) Source # 
Instance details

Defined in Data.DataDomain

(FromJSONKey k, Ord k, FromJSON a) => FromJSON (MonoidalMap k a) 
Instance details

Defined in Data.Map.Monoidal

Methods

parseJSON :: Value -> Parser (MonoidalMap k a) #

parseJSONList :: Value -> Parser [MonoidalMap k a] #

omittedField :: Maybe (MonoidalMap k a) #

(FromJSON a, FromJSON b) => FromJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

omittedField :: Maybe (Either a b) #

(FromJSON a, FromJSON b) => FromJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These a b) #

parseJSONList :: Value -> Parser [These a b] #

omittedField :: Maybe (These a b) #

(FromJSON a, FromJSON b) => FromJSON (Pair a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Pair a b) #

parseJSONList :: Value -> Parser [Pair a b] #

omittedField :: Maybe (Pair a b) #

(FromJSON a, FromJSON b) => FromJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These a b) #

parseJSONList :: Value -> Parser [These a b] #

omittedField :: Maybe (These a b) #

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON a, FromJSON b) => FromJSON (a, b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b) #

parseJSONList :: Value -> Parser [(a, b)] #

omittedField :: Maybe (a, b) #

FromJSON a => FromJSON (Const a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON b => FromJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Tagged a b) #

parseJSONList :: Value -> Parser [Tagged a b] #

omittedField :: Maybe (Tagged a b) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (These1 f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These1 f g a) #

parseJSONList :: Value -> Parser [These1 f g a] #

omittedField :: Maybe (These1 f g a) #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c) #

parseJSONList :: Value -> Parser [(a, b, c)] #

omittedField :: Maybe (a, b, c) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Product f g a) #

parseJSONList :: Value -> Parser [Product f g a] #

omittedField :: Maybe (Product f g a) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Sum f g a) #

parseJSONList :: Value -> Parser [Sum f g a] #

omittedField :: Maybe (Sum f g a) #

(Vector vk k, Vector vv v, Ord k, FromJSONKey k, FromJSON v) => FromJSON (VMap vk vv k v) 
Instance details

Defined in Data.VMap

Methods

parseJSON :: Value -> Parser (VMap vk vv k v) #

parseJSONList :: Value -> Parser [VMap vk vv k v] #

omittedField :: Maybe (VMap vk vv k v) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d) #

parseJSONList :: Value -> Parser [(a, b, c, d)] #

omittedField :: Maybe (a, b, c, d) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Compose f g a) #

parseJSONList :: Value -> Parser [Compose f g a] #

omittedField :: Maybe (Compose f g a) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e) #

parseJSONList :: Value -> Parser [(a, b, c, d, e)] #

omittedField :: Maybe (a, b, c, d, e) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f)] #

omittedField :: Maybe (a, b, c, d, e, f) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)] #

omittedField :: Maybe (a, b, c, d, e, f, g) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

class ToJSON a where #

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value #

toEncoding :: a -> Encoding #

toJSONList :: [a] -> Value #

toEncodingList :: [a] -> Encoding #

omitField :: a -> Bool #

Instances

Instances details
ToJSON Key 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Key -> Value #

toEncoding :: Key -> Encoding #

toJSONList :: [Key] -> Value #

toEncodingList :: [Key] -> Encoding #

omitField :: Key -> Bool #

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DotNetTime -> Value #

toEncoding :: DotNetTime -> Encoding #

toJSONList :: [DotNetTime] -> Value #

toEncodingList :: [DotNetTime] -> Encoding #

omitField :: DotNetTime -> Bool #

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Value -> Value #

toEncoding :: Value -> Encoding #

toJSONList :: [Value] -> Value #

toEncodingList :: [Value] -> Encoding #

omitField :: Value -> Bool #

ToJSON Version 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Version -> Value #

toEncoding :: Version -> Encoding #

toJSONList :: [Version] -> Value #

toEncodingList :: [Version] -> Encoding #

omitField :: Version -> Bool #

ToJSON CTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: CTime -> Value #

toEncoding :: CTime -> Encoding #

toJSONList :: [CTime] -> Value #

toEncodingList :: [CTime] -> Encoding #

omitField :: CTime -> Bool #

ToJSON Void 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Void -> Value #

toEncoding :: Void -> Encoding #

toJSONList :: [Void] -> Value #

toEncodingList :: [Void] -> Encoding #

omitField :: Void -> Bool #

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int16 -> Value #

toEncoding :: Int16 -> Encoding #

toJSONList :: [Int16] -> Value #

toEncodingList :: [Int16] -> Encoding #

omitField :: Int16 -> Bool #

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int32 -> Value #

toEncoding :: Int32 -> Encoding #

toJSONList :: [Int32] -> Value #

toEncodingList :: [Int32] -> Encoding #

omitField :: Int32 -> Bool #

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int64 -> Value #

toEncoding :: Int64 -> Encoding #

toJSONList :: [Int64] -> Value #

toEncodingList :: [Int64] -> Encoding #

omitField :: Int64 -> Bool #

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int8 -> Value #

toEncoding :: Int8 -> Encoding #

toJSONList :: [Int8] -> Value #

toEncodingList :: [Int8] -> Encoding #

omitField :: Int8 -> Bool #

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word16 -> Value #

toEncoding :: Word16 -> Encoding #

toJSONList :: [Word16] -> Value #

toEncodingList :: [Word16] -> Encoding #

omitField :: Word16 -> Bool #

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word32 -> Value #

toEncoding :: Word32 -> Encoding #

toJSONList :: [Word32] -> Value #

toEncodingList :: [Word32] -> Encoding #

omitField :: Word32 -> Bool #

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word64 -> Value #

toEncoding :: Word64 -> Encoding #

toJSONList :: [Word64] -> Value #

toEncodingList :: [Word64] -> Encoding #

omitField :: Word64 -> Bool #

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word8 -> Value #

toEncoding :: Word8 -> Encoding #

toJSONList :: [Word8] -> Value #

toEncodingList :: [Word8] -> Encoding #

omitField :: Word8 -> Bool #

ToJSON ByteString64 
Instance details

Defined in Data.ByteString.Base64.Type

Methods

toJSON :: ByteString64 -> Value #

toEncoding :: ByteString64 -> Encoding #

toJSONList :: [ByteString64] -> Value #

toEncodingList :: [ByteString64] -> Encoding #

omitField :: ByteString64 -> Bool #

ToJSON ProtocolMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

ToJSON ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

ToJSON RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

ToJSON CompactRedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Compact

ToJSON RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

ToJSON VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

ToJSON ByteSpan 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

toJSON :: ByteSpan -> Value #

toEncoding :: ByteSpan -> Encoding #

toJSONList :: [ByteSpan] -> Value #

toEncodingList :: [ByteSpan] -> Encoding #

omitField :: ByteSpan -> Bool #

ToJSON AddrAttributes 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

ToJSON HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

ToJSON AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

toJSON :: AddrType -> Value #

toEncoding :: AddrType -> Encoding #

toJSONList :: [AddrType] -> Value #

toEncodingList :: [AddrType] -> Encoding #

omitField :: AddrType -> Bool #

ToJSON Address 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toJSON :: Address -> Value #

toEncoding :: Address -> Encoding #

toJSONList :: [Address] -> Value #

toEncodingList :: [Address] -> Encoding #

omitField :: Address -> Bool #

ToJSON UnparsedFields 
Instance details

Defined in Cardano.Chain.Common.Attributes

ToJSON ChainDifficulty 
Instance details

Defined in Cardano.Chain.Common.ChainDifficulty

ToJSON Lovelace 
Instance details

Defined in Cardano.Chain.Common.Lovelace

Methods

toJSON :: Lovelace -> Value #

toEncoding :: Lovelace -> Encoding #

toJSONList :: [Lovelace] -> Value #

toEncodingList :: [Lovelace] -> Encoding #

omitField :: Lovelace -> Bool #

ToJSON LovelacePortion 
Instance details

Defined in Cardano.Chain.Common.LovelacePortion

ToJSON NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

ToJSON TxFeePolicy 
Instance details

Defined in Cardano.Chain.Common.TxFeePolicy

ToJSON TxSizeLinear 
Instance details

Defined in Cardano.Chain.Common.TxSizeLinear

ToJSON CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: CertIx -> Value #

toEncoding :: CertIx -> Encoding #

toJSONList :: [CertIx] -> Value #

toEncodingList :: [CertIx] -> Encoding #

omitField :: CertIx -> Bool #

ToJSON DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: DnsName -> Value #

toEncoding :: DnsName -> Encoding #

toJSONList :: [DnsName] -> Value #

toEncodingList :: [DnsName] -> Encoding #

omitField :: DnsName -> Bool #

ToJSON EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Network -> Value #

toEncoding :: Network -> Encoding #

toJSONList :: [Network] -> Value #

toEncodingList :: [Network] -> Encoding #

omitField :: Network -> Bool #

ToJSON NonNegativeInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Nonce -> Value #

toEncoding :: Nonce -> Encoding #

toJSONList :: [Nonce] -> Value #

toEncodingList :: [Nonce] -> Encoding #

omitField :: Nonce -> Bool #

ToJSON Port 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Port -> Value #

toEncoding :: Port -> Encoding #

toJSONList :: [Port] -> Value #

toEncodingList :: [Port] -> Encoding #

omitField :: Port -> Bool #

ToJSON PositiveInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToJSON PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: ProtVer -> Value #

toEncoding :: ProtVer -> Encoding #

toJSONList :: [ProtVer] -> Value #

toEncodingList :: [ProtVer] -> Encoding #

omitField :: ProtVer -> Bool #

ToJSON TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: TxIx -> Value #

toEncoding :: TxIx -> Encoding #

toJSONList :: [TxIx] -> Value #

toEncodingList :: [TxIx] -> Encoding #

omitField :: TxIx -> Bool #

ToJSON UnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Url -> Value #

toEncoding :: Url -> Encoding #

toJSONList :: [Url] -> Value #

toEncodingList :: [Url] -> Encoding #

omitField :: Url -> Bool #

ToJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toJSON :: BlockNo -> Value #

toEncoding :: BlockNo -> Encoding #

toJSONList :: [BlockNo] -> Value #

toEncodingList :: [BlockNo] -> Encoding #

omitField :: BlockNo -> Bool #

ToJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: EpochNo -> Value #

toEncoding :: EpochNo -> Encoding #

toJSONList :: [EpochNo] -> Value #

toEncodingList :: [EpochNo] -> Encoding #

omitField :: EpochNo -> Bool #

ToJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: SlotNo -> Value #

toEncoding :: SlotNo -> Encoding #

toJSONList :: [SlotNo] -> Value #

toEncodingList :: [SlotNo] -> Encoding #

omitField :: SlotNo -> Bool #

ToJSON RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

ToJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

ToJSON IntSet 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntSet -> Value #

toEncoding :: IntSet -> Encoding #

toJSONList :: [IntSet] -> Value #

toEncodingList :: [IntSet] -> Encoding #

omitField :: IntSet -> Bool #

ToJSON Ordering 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ordering -> Value #

toEncoding :: Ordering -> Encoding #

toJSONList :: [Ordering] -> Value #

toEncodingList :: [Ordering] -> Encoding #

omitField :: Ordering -> Bool #

ToJSON SlotStart Source # 
Instance details

Defined in Cardano.Analysis.API.Chain

ToJSON BlockCond Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

ToJSON ChainFilter Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

ToJSON FilterName Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

ToJSON SlotCond Source # 
Instance details

Defined in Cardano.Analysis.API.ChainFilter

Methods

toJSON :: SlotCond -> Value #

toEncoding :: SlotCond -> Encoding #

toJSONList :: [SlotCond] -> Value #

toEncodingList :: [SlotCond] -> Encoding #

omitField :: SlotCond -> Bool #

ToJSON Branch Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Branch -> Value #

toEncoding :: Branch -> Encoding #

toJSONList :: [Branch] -> Value #

toEncodingList :: [Branch] -> Encoding #

omitField :: Branch -> Bool #

ToJSON Commit Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Commit -> Value #

toEncoding :: Commit -> Encoding #

toJSONList :: [Commit] -> Value #

toEncodingList :: [Commit] -> Encoding #

omitField :: Commit -> Bool #

ToJSON ComponentInfo Source # 
Instance details

Defined in Cardano.Analysis.API.Context

ToJSON GeneratorProfile Source # 
Instance details

Defined in Cardano.Analysis.API.Context

ToJSON Genesis Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Genesis -> Value #

toEncoding :: Genesis -> Encoding #

toJSONList :: [Genesis] -> Value #

toEncodingList :: [Genesis] -> Encoding #

omitField :: Genesis -> Bool #

ToJSON GenesisSpec Source # 
Instance details

Defined in Cardano.Analysis.API.Context

ToJSON Manifest Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Manifest -> Value #

toEncoding :: Manifest -> Encoding #

toJSONList :: [Manifest] -> Value #

toEncodingList :: [Manifest] -> Encoding #

omitField :: Manifest -> Bool #

ToJSON Metadata Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Metadata -> Value #

toEncoding :: Metadata -> Encoding #

toJSONList :: [Metadata] -> Value #

toEncodingList :: [Metadata] -> Encoding #

omitField :: Metadata -> Bool #

ToJSON PParams Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: PParams -> Value #

toEncoding :: PParams -> Encoding #

toJSONList :: [PParams] -> Value #

toEncodingList :: [PParams] -> Encoding #

omitField :: PParams -> Bool #

ToJSON PlutusParams Source # 
Instance details

Defined in Cardano.Analysis.API.Context

ToJSON Version Source # 
Instance details

Defined in Cardano.Analysis.API.Context

Methods

toJSON :: Version -> Value #

toEncoding :: Version -> Encoding #

toJSONList :: [Version] -> Value #

toEncodingList :: [Version] -> Encoding #

omitField :: Version -> Bool #

ToJSON DictEntry Source # 
Instance details

Defined in Cardano.Analysis.API.Dictionary

ToJSON Dictionary Source # 
Instance details

Defined in Cardano.Analysis.API.Dictionary

ToJSON EpochSafeInt Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

ToJSON EpochSlot Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

ToJSON FieldName Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

ToJSON Hash Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

Methods

toJSON :: Hash -> Value #

toEncoding :: Hash -> Encoding #

toJSONList :: [Hash] -> Value #

toEncodingList :: [Hash] -> Encoding #

omitField :: Hash -> Bool #

ToJSON Host Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

Methods

toJSON :: Host -> Value #

toEncoding :: Host -> Encoding #

toJSONList :: [Host] -> Value #

toEncodingList :: [Host] -> Encoding #

omitField :: Host -> Bool #

ToJSON JsonLogfile Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

ToJSON TId Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

Methods

toJSON :: TId -> Value #

toEncoding :: TId -> Encoding #

toJSONList :: [TId] -> Value #

toEncodingList :: [TId] -> Encoding #

omitField :: TId -> Bool #

ToJSON LocliVersion Source # 
Instance details

Defined in Cardano.Analysis.API.LocliVersion

ToJSON BPError Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: BPError -> Value #

toEncoding :: BPError -> Encoding #

toJSONList :: [BPError] -> Value #

toEncodingList :: [BPError] -> Encoding #

omitField :: BPError -> Bool #

ToJSON BPErrorKind Source # 
Instance details

Defined in Cardano.Analysis.API.Types

ToJSON BlockEvents Source # 
Instance details

Defined in Cardano.Analysis.API.Types

ToJSON BlockForge Source # 
Instance details

Defined in Cardano.Analysis.API.Types

ToJSON BlockObservation Source # 
Instance details

Defined in Cardano.Analysis.API.Types

ToJSON HostBlockStats Source # 
Instance details

Defined in Cardano.Analysis.API.Types

ToJSON MultiClusterPerf Source # 
Instance details

Defined in Cardano.Analysis.API.Metrics

ToJSON Phase Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: Phase -> Value #

toEncoding :: Phase -> Encoding #

toJSONList :: [Phase] -> Value #

toEncodingList :: [Phase] -> Encoding #

omitField :: Phase -> Bool #

ToJSON MachView Source # 
Instance details

Defined in Cardano.Analysis.BlockProp

Methods

toJSON :: MachView -> Value #

toEncoding :: MachView -> Encoding #

toJSONList :: [MachView] -> Value #

toEncodingList :: [MachView] -> Encoding #

omitField :: MachView -> Bool #

ToJSON Author Source # 
Instance details

Defined in Cardano.Report

Methods

toJSON :: Author -> Value #

toEncoding :: Author -> Encoding #

toJSONList :: [Author] -> Value #

toEncodingList :: [Author] -> Encoding #

omitField :: Author -> Bool #

ToJSON ReportMeta Source # 
Instance details

Defined in Cardano.Report

ToJSON ShortId Source # 
Instance details

Defined in Cardano.Report

Methods

toJSON :: ShortId -> Value #

toEncoding :: ShortId -> Encoding #

toJSONList :: [ShortId] -> Value #

toEncodingList :: [ShortId] -> Encoding #

omitField :: ShortId -> Bool #

ToJSON Tag Source # 
Instance details

Defined in Cardano.Report

Methods

toJSON :: Tag -> Value #

toEncoding :: Tag -> Encoding #

toJSONList :: [Tag] -> Value #

toEncodingList :: [Tag] -> Encoding #

omitField :: Tag -> Bool #

ToJSON TmplRun Source # 
Instance details

Defined in Cardano.Report

Methods

toJSON :: TmplRun -> Value #

toEncoding :: TmplRun -> Encoding #

toJSONList :: [TmplRun] -> Value #

toEncodingList :: [TmplRun] -> Encoding #

omitField :: TmplRun -> Bool #

ToJSON TmplSection Source # 
Instance details

Defined in Cardano.Report

ToJSON Workload Source # 
Instance details

Defined in Cardano.Report

Methods

toJSON :: Workload -> Value #

toEncoding :: Workload -> Encoding #

toJSONList :: [Workload] -> Value #

toEncodingList :: [Workload] -> Encoding #

omitField :: Workload -> Bool #

ToJSON LOAnyType Source # 
Instance details

Defined in Cardano.Unlog.LogObject

ToJSON LOBody Source # 
Instance details

Defined in Cardano.Unlog.LogObject

Methods

toJSON :: LOBody -> Value #

toEncoding :: LOBody -> Encoding #

toJSONList :: [LOBody] -> Value #

toEncodingList :: [LOBody] -> Encoding #

omitField :: LOBody -> Bool #

ToJSON LogObject Source # 
Instance details

Defined in Cardano.Unlog.LogObject

ToJSON RUTCTime Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: RUTCTime -> Value #

toEncoding :: RUTCTime -> Encoding #

toJSONList :: [RUTCTime] -> Value #

toEncodingList :: [RUTCTime] -> Encoding #

omitField :: RUTCTime -> Bool #

ToJSON Centile Source # 
Instance details

Defined in Data.CDF

Methods

toJSON :: Centile -> Value #

toEncoding :: Centile -> Encoding #

toJSONList :: [Centile] -> Value #

toEncodingList :: [Centile] -> Encoding #

omitField :: Centile -> Bool #

ToJSON URI 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: URI -> Value #

toEncoding :: URI -> Encoding #

toJSONList :: [URI] -> Value #

toEncodingList :: [URI] -> Encoding #

omitField :: URI -> Bool #

ToJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

toJSON :: ExBudget -> Value #

toEncoding :: ExBudget -> Encoding #

toJSONList :: [ExBudget] -> Value #

toEncodingList :: [ExBudget] -> Encoding #

omitField :: ExBudget -> Bool #

ToJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

toJSON :: ExCPU -> Value #

toEncoding :: ExCPU -> Encoding #

toJSONList :: [ExCPU] -> Value #

toEncodingList :: [ExCPU] -> Encoding #

omitField :: ExCPU -> Bool #

ToJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

toJSON :: ExMemory -> Value #

toEncoding :: ExMemory -> Encoding #

toJSONList :: [ExMemory] -> Value #

toEncodingList :: [ExMemory] -> Encoding #

omitField :: ExMemory -> Bool #

ToJSON SatInt 
Instance details

Defined in Data.SatInt

Methods

toJSON :: SatInt -> Value #

toEncoding :: SatInt -> Encoding #

toJSONList :: [SatInt] -> Value #

toEncodingList :: [SatInt] -> Encoding #

omitField :: SatInt -> Bool #

ToJSON CovLoc 
Instance details

Defined in PlutusTx.Coverage

Methods

toJSON :: CovLoc -> Value #

toEncoding :: CovLoc -> Encoding #

toJSONList :: [CovLoc] -> Value #

toEncodingList :: [CovLoc] -> Encoding #

omitField :: CovLoc -> Bool #

ToJSON CoverageAnnotation 
Instance details

Defined in PlutusTx.Coverage

ToJSON CoverageData 
Instance details

Defined in PlutusTx.Coverage

ToJSON CoverageIndex 
Instance details

Defined in PlutusTx.Coverage

ToJSON CoverageMetadata 
Instance details

Defined in PlutusTx.Coverage

ToJSON CoverageReport 
Instance details

Defined in PlutusTx.Coverage

ToJSON Metadata 
Instance details

Defined in PlutusTx.Coverage

Methods

toJSON :: Metadata -> Value #

toEncoding :: Metadata -> Encoding #

toJSONList :: [Metadata] -> Value #

toEncodingList :: [Metadata] -> Encoding #

omitField :: Metadata -> Bool #

ToJSON Rational

This mimics the behaviour of Aeson's instance for Rational.

Instance details

Defined in PlutusTx.Ratio

Methods

toJSON :: Rational -> Value #

toEncoding :: Rational -> Encoding #

toJSONList :: [Rational] -> Value #

toEncodingList :: [Rational] -> Encoding #

omitField :: Rational -> Bool #

ToJSON Scientific 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON StudentT 
Instance details

Defined in Statistics.Distribution.StudentT

Methods

toJSON :: StudentT -> Value #

toEncoding :: StudentT -> Encoding #

toJSONList :: [StudentT] -> Value #

toEncodingList :: [StudentT] -> Encoding #

omitField :: StudentT -> Bool #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value #

toEncoding :: Text -> Encoding #

toJSONList :: [Text] -> Value #

toEncodingList :: [Text] -> Encoding #

omitField :: Text -> Bool #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value #

toEncoding :: Text -> Encoding #

toJSONList :: [Text] -> Value #

toEncodingList :: [Text] -> Encoding #

omitField :: Text -> Bool #

ToJSON ShortText 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Day 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Day -> Value #

toEncoding :: Day -> Encoding #

toJSONList :: [Day] -> Value #

toEncodingList :: [Day] -> Encoding #

omitField :: Day -> Bool #

ToJSON Month 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Month -> Value #

toEncoding :: Month -> Encoding #

toJSONList :: [Month] -> Value #

toEncodingList :: [Month] -> Encoding #

omitField :: Month -> Bool #

ToJSON Quarter 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Quarter -> Value #

toEncoding :: Quarter -> Encoding #

toJSONList :: [Quarter] -> Value #

toEncodingList :: [Quarter] -> Encoding #

omitField :: Quarter -> Bool #

ToJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DiffTime -> Value #

toEncoding :: DiffTime -> Encoding #

toJSONList :: [DiffTime] -> Value #

toEncodingList :: [DiffTime] -> Encoding #

omitField :: DiffTime -> Bool #

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UTCTime -> Value #

toEncoding :: UTCTime -> Encoding #

toJSONList :: [UTCTime] -> Value #

toEncodingList :: [UTCTime] -> Encoding #

omitField :: UTCTime -> Bool #

ToJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ConfigOptionRep 
Instance details

Defined in Cardano.Logging.ConfigurationParser

Methods

toJSON :: ConfigOptionRep -> Value #

toEncoding :: ConfigOptionRep -> Encoding #

toJSONList :: [ConfigOptionRep] -> Value #

toEncodingList :: [ConfigOptionRep] -> Encoding #

omitField :: ConfigOptionRep -> Bool #

ToJSON ConfigRepresentation 
Instance details

Defined in Cardano.Logging.ConfigurationParser

Methods

toJSON :: ConfigRepresentation -> Value #

toEncoding :: ConfigRepresentation -> Encoding #

toJSONList :: [ConfigRepresentation] -> Value #

toEncodingList :: [ConfigRepresentation] -> Encoding #

omitField :: ConfigRepresentation -> Bool #

ToJSON BackendConfig 
Instance details

Defined in Cardano.Logging.Types

ToJSON DetailLevel 
Instance details

Defined in Cardano.Logging.Types

ToJSON SeverityF 
Instance details

Defined in Cardano.Logging.Types

ToJSON SeverityS 
Instance details

Defined in Cardano.Logging.Types

ToJSON TraceOptionForwarder 
Instance details

Defined in Cardano.Logging.Types

ToJSON Verbosity 
Instance details

Defined in Cardano.Logging.Types

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UUID -> Value #

toEncoding :: UUID -> Encoding #

toJSONList :: [UUID] -> Value #

toEncodingList :: [UUID] -> Encoding #

omitField :: UUID -> Bool #

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Integer -> Value #

toEncoding :: Integer -> Encoding #

toJSONList :: [Integer] -> Value #

toEncodingList :: [Integer] -> Encoding #

omitField :: Integer -> Bool #

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Natural -> Value #

toEncoding :: Natural -> Encoding #

toJSONList :: [Natural] -> Value #

toEncodingList :: [Natural] -> Encoding #

omitField :: Natural -> Bool #

ToJSON () 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

omitField :: () -> Bool #

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Bool -> Value #

toEncoding :: Bool -> Encoding #

toJSONList :: [Bool] -> Value #

toEncodingList :: [Bool] -> Encoding #

omitField :: Bool -> Bool #

ToJSON Char 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Char -> Value #

toEncoding :: Char -> Encoding #

toJSONList :: [Char] -> Value #

toEncodingList :: [Char] -> Encoding #

omitField :: Char -> Bool #

ToJSON Double 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Double -> Value #

toEncoding :: Double -> Encoding #

toJSONList :: [Double] -> Value #

toEncodingList :: [Double] -> Encoding #

omitField :: Double -> Bool #

ToJSON Float 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Float -> Value #

toEncoding :: Float -> Encoding #

toJSONList :: [Float] -> Value #

toEncodingList :: [Float] -> Encoding #

omitField :: Float -> Bool #

ToJSON Int 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int -> Value #

toEncoding :: Int -> Encoding #

toJSONList :: [Int] -> Value #

toEncodingList :: [Int] -> Encoding #

omitField :: Int -> Bool #

ToJSON Word 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word -> Value #

toEncoding :: Word -> Encoding #

toJSONList :: [Word] -> Value #

toEncodingList :: [Word] -> Encoding #

omitField :: Word -> Bool #

ToJSON v => ToJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: KeyMap v -> Value #

toEncoding :: KeyMap v -> Encoding #

toJSONList :: [KeyMap v] -> Value #

toEncodingList :: [KeyMap v] -> Encoding #

omitField :: KeyMap v -> Bool #

ToJSON a => ToJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Identity a -> Value #

toEncoding :: Identity a -> Encoding #

toJSONList :: [Identity a] -> Value #

toEncodingList :: [Identity a] -> Encoding #

omitField :: Identity a -> Bool #

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value #

toEncoding :: First a -> Encoding #

toJSONList :: [First a] -> Value #

toEncodingList :: [First a] -> Encoding #

omitField :: First a -> Bool #

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value #

toEncoding :: Last a -> Encoding #

toJSONList :: [Last a] -> Value #

toEncodingList :: [Last a] -> Encoding #

omitField :: Last a -> Bool #

ToJSON a => ToJSON (Down a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Down a -> Value #

toEncoding :: Down a -> Encoding #

toJSONList :: [Down a] -> Value #

toEncodingList :: [Down a] -> Encoding #

omitField :: Down a -> Bool #

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value #

toEncoding :: First a -> Encoding #

toJSONList :: [First a] -> Value #

toEncodingList :: [First a] -> Encoding #

omitField :: First a -> Bool #

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value #

toEncoding :: Last a -> Encoding #

toJSONList :: [Last a] -> Value #

toEncodingList :: [Last a] -> Encoding #

omitField :: Last a -> Bool #

ToJSON a => ToJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

omitField :: Max a -> Bool #

ToJSON a => ToJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

omitField :: Min a -> Bool #

ToJSON a => ToJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Dual a -> Value #

toEncoding :: Dual a -> Encoding #

toJSONList :: [Dual a] -> Value #

toEncodingList :: [Dual a] -> Encoding #

omitField :: Dual a -> Bool #

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: NonEmpty a -> Value #

toEncoding :: NonEmpty a -> Encoding #

toJSONList :: [NonEmpty a] -> Value #

toEncodingList :: [NonEmpty a] -> Encoding #

omitField :: NonEmpty a -> Bool #

(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Generically a -> Value #

toEncoding :: Generically a -> Encoding #

toJSONList :: [Generically a] -> Value #

toEncodingList :: [Generically a] -> Encoding #

omitField :: Generically a -> Bool #

(ToJSON a, Integral a) => ToJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ratio a -> Value #

toEncoding :: Ratio a -> Encoding #

toJSONList :: [Ratio a] -> Value #

toEncodingList :: [Ratio a] -> Encoding #

omitField :: Ratio a -> Bool #

ToJSON a => ToJSON (RedeemSignature a) 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Signature

ToJSON (Signature w) 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

toJSON :: Signature w -> Value #

toEncoding :: Signature w -> Encoding #

toJSONList :: [Signature w] -> Value #

toEncodingList :: [Signature w] -> Encoding #

omitField :: Signature w -> Bool #

ToJSON a => ToJSON (Attributes a) 
Instance details

Defined in Cardano.Chain.Common.Attributes

Methods

toJSON :: Attributes a -> Value #

toEncoding :: Attributes a -> Encoding #

toJSONList :: [Attributes a] -> Value #

toEncodingList :: [Attributes a] -> Encoding #

omitField :: Attributes a -> Bool #

ToJSON a => ToJSON (MerkleRoot a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

Methods

toJSON :: MerkleRoot a -> Value #

toEncoding :: MerkleRoot a -> Encoding #

toJSONList :: [MerkleRoot a] -> Value #

toEncodingList :: [MerkleRoot a] -> Encoding #

omitField :: MerkleRoot a -> Bool #

Crypto c => ToJSON (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Anchor c -> Value #

toEncoding :: Anchor c -> Encoding #

toJSONList :: [Anchor c] -> Value #

toEncodingList :: [Anchor c] -> Encoding #

omitField :: Anchor c -> Bool #

Crypto c => ToJSON (BlocksMade c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: BlocksMade c -> Value #

toEncoding :: BlocksMade c -> Encoding #

toJSONList :: [BlocksMade c] -> Value #

toEncodingList :: [BlocksMade c] -> Encoding #

omitField :: BlocksMade c -> Bool #

Crypto c => ToJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toJSON :: ScriptHash c -> Value #

toEncoding :: ScriptHash c -> Encoding #

toJSONList :: [ScriptHash c] -> Value #

toEncodingList :: [ScriptHash c] -> Encoding #

omitField :: ScriptHash c -> Bool #

Crypto c => ToJSON (GenDelegPair c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Crypto c => ToJSON (GenDelegs c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toJSON :: GenDelegs c -> Value #

toEncoding :: GenDelegs c -> Encoding #

toJSONList :: [GenDelegs c] -> Value #

toEncodingList :: [GenDelegs c] -> Encoding #

omitField :: GenDelegs c -> Bool #

ToJSON a => ToJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: WithOrigin a -> Value #

toEncoding :: WithOrigin a -> Encoding #

toJSONList :: [WithOrigin a] -> Value #

toEncodingList :: [WithOrigin a] -> Encoding #

omitField :: WithOrigin a -> Bool #

ToJSON a => ToJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

toJSON :: StrictMaybe a -> Value #

toEncoding :: StrictMaybe a -> Encoding #

toJSONList :: [StrictMaybe a] -> Value #

toEncodingList :: [StrictMaybe a] -> Encoding #

omitField :: StrictMaybe a -> Bool #

ToJSON a => ToJSON (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

Methods

toJSON :: StrictSeq a -> Value #

toEncoding :: StrictSeq a -> Encoding #

toJSONList :: [StrictSeq a] -> Value #

toEncodingList :: [StrictSeq a] -> Encoding #

omitField :: StrictSeq a -> Bool #

ToJSON a => ToJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntMap a -> Value #

toEncoding :: IntMap a -> Encoding #

toJSONList :: [IntMap a] -> Value #

toEncodingList :: [IntMap a] -> Encoding #

omitField :: IntMap a -> Bool #

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

omitField :: Seq a -> Bool #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

omitField :: Set a -> Bool #

ToJSON v => ToJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tree v -> Value #

toEncoding :: Tree v -> Encoding #

toJSONList :: [Tree v] -> Value #

toEncodingList :: [Tree v] -> Encoding #

omitField :: Tree v -> Bool #

ToJSON1 f => ToJSON (Fix f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fix f -> Value #

toEncoding :: Fix f -> Encoding #

toJSONList :: [Fix f] -> Value #

toEncodingList :: [Fix f] -> Encoding #

omitField :: Fix f -> Bool #

(ToJSON1 f, Functor f) => ToJSON (Mu f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Mu f -> Value #

toEncoding :: Mu f -> Encoding #

toJSONList :: [Mu f] -> Value #

toEncodingList :: [Mu f] -> Encoding #

omitField :: Mu f -> Bool #

(ToJSON1 f, Functor f) => ToJSON (Nu f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Nu f -> Value #

toEncoding :: Nu f -> Encoding #

toJSONList :: [Nu f] -> Value #

toEncodingList :: [Nu f] -> Encoding #

omitField :: Nu f -> Bool #

ToJSON a => ToJSON (DNonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DNonEmpty a -> Value #

toEncoding :: DNonEmpty a -> Encoding #

toJSONList :: [DNonEmpty a] -> Value #

toEncodingList :: [DNonEmpty a] -> Encoding #

omitField :: DNonEmpty a -> Bool #

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DList a -> Value #

toEncoding :: DList a -> Encoding #

toJSONList :: [DList a] -> Value #

toEncodingList :: [DList a] -> Encoding #

omitField :: DList a -> Bool #

ToJSON a => ToJSON (Interval a) Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: Interval a -> Value #

toEncoding :: Interval a -> Encoding #

toJSONList :: [Interval a] -> Value #

toEncodingList :: [Interval a] -> Encoding #

omitField :: Interval a -> Bool #

ToJSON (JsonInputFile a) Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

ToJSON a => ToJSON (ARunWith a) Source # 
Instance details

Defined in Cardano.Analysis.API.Run

Methods

toJSON :: ARunWith a -> Value #

toEncoding :: ARunWith a -> Encoding #

toJSONList :: [ARunWith a] -> Value #

toEncodingList :: [ARunWith a] -> Encoding #

omitField :: ARunWith a -> Bool #

(forall a. ToJSON a => ToJSON (f a), ToJSON (CDFList f (DataDomain I SlotNo)), ToJSON (CDFList f (DataDomain I BlockNo))) => ToJSON (BlockProp f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: BlockProp f -> Value #

toEncoding :: BlockProp f -> Encoding #

toJSONList :: [BlockProp f] -> Value #

toEncodingList :: [BlockProp f] -> Encoding #

omitField :: BlockProp f -> Bool #

ToJSON a => ToJSON (ForgerEvents a) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

(forall a. ToJSON a => ToJSON (f a), ToJSON (CDFList f (DataDomain I SlotNo))) => ToJSON (MachPerf f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: MachPerf f -> Value #

toEncoding :: MachPerf f -> Encoding #

toJSONList :: [MachPerf f] -> Value #

toEncodingList :: [MachPerf f] -> Encoding #

omitField :: MachPerf f -> Bool #

ToJSON a => ToJSON (SlotStats a) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: SlotStats a -> Value #

toEncoding :: SlotStats a -> Encoding #

toJSONList :: [SlotStats a] -> Value #

toEncodingList :: [SlotStats a] -> Encoding #

omitField :: SlotStats a -> Bool #

(forall a. ToJSON a => ToJSON (f a)) => ToJSON (Summary f) Source # 
Instance details

Defined in Cardano.Analysis.API.Types

Methods

toJSON :: Summary f -> Value #

toEncoding :: Summary f -> Encoding #

toJSONList :: [Summary f] -> Value #

toEncodingList :: [Summary f] -> Encoding #

omitField :: Summary f -> Bool #

ToJSON a => ToJSON (HostLogs a) Source # 
Instance details

Defined in Cardano.Unlog.LogObject

Methods

toJSON :: HostLogs a -> Value #

toEncoding :: HostLogs a -> Encoding #

toJSONList :: [HostLogs a] -> Value #

toEncodingList :: [HostLogs a] -> Encoding #

omitField :: HostLogs a -> Bool #

ToJSON a => ToJSON (RunLogs a) Source # 
Instance details

Defined in Cardano.Unlog.LogObject

Methods

toJSON :: RunLogs a -> Value #

toEncoding :: RunLogs a -> Encoding #

toJSONList :: [RunLogs a] -> Value #

toEncodingList :: [RunLogs a] -> Encoding #

omitField :: RunLogs a -> Bool #

(forall a. ToJSON a => ToJSON (f a)) => ToJSON (ProfileEntry f) Source # 
Instance details

Defined in Data.Profile

(forall a. ToJSON a => ToJSON (f a)) => ToJSON (ProfilingData f) Source # 
Instance details

Defined in Data.Profile

ToJSON (BuiltinCostModelBase MCostingFun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

toJSON :: BuiltinCostModelBase MCostingFun -> Value #

toEncoding :: BuiltinCostModelBase MCostingFun -> Encoding #

toJSONList :: [BuiltinCostModelBase MCostingFun] -> Value #

toEncodingList :: [BuiltinCostModelBase MCostingFun] -> Encoding #

omitField :: BuiltinCostModelBase MCostingFun -> Bool #

ToJSON (BuiltinCostModelBase CostingFun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

toJSON :: BuiltinCostModelBase CostingFun -> Value #

toEncoding :: BuiltinCostModelBase CostingFun -> Encoding #

toJSONList :: [BuiltinCostModelBase CostingFun] -> Value #

toEncodingList :: [BuiltinCostModelBase CostingFun] -> Encoding #

omitField :: BuiltinCostModelBase CostingFun -> Bool #

ToJSON a => ToJSON (MCostingFun a) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

toJSON :: MCostingFun a -> Value #

toEncoding :: MCostingFun a -> Encoding #

toJSONList :: [MCostingFun a] -> Value #

toEncodingList :: [MCostingFun a] -> Encoding #

omitField :: MCostingFun a -> Bool #

ToJSON (CekMachineCostsBase Identity) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Methods

toJSON :: CekMachineCostsBase Identity -> Value #

toEncoding :: CekMachineCostsBase Identity -> Encoding #

toJSONList :: [CekMachineCostsBase Identity] -> Value #

toEncodingList :: [CekMachineCostsBase Identity] -> Encoding #

omitField :: CekMachineCostsBase Identity -> Bool #

ToJSON (CekMachineCostsBase Maybe) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Methods

toJSON :: CekMachineCostsBase Maybe -> Value #

toEncoding :: CekMachineCostsBase Maybe -> Encoding #

toJSONList :: [CekMachineCostsBase Maybe] -> Value #

toEncodingList :: [CekMachineCostsBase Maybe] -> Encoding #

omitField :: CekMachineCostsBase Maybe -> Bool #

ToJSON a => ToJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Array a -> Value #

toEncoding :: Array a -> Encoding #

toJSONList :: [Array a] -> Value #

toEncodingList :: [Array a] -> Encoding #

omitField :: Array a -> Bool #

(Prim a, ToJSON a) => ToJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: PrimArray a -> Value #

toEncoding :: PrimArray a -> Encoding #

toJSONList :: [PrimArray a] -> Value #

toEncodingList :: [PrimArray a] -> Encoding #

omitField :: PrimArray a -> Bool #

ToJSON a => ToJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: SmallArray a -> Value #

toEncoding :: SmallArray a -> Encoding #

toJSONList :: [SmallArray a] -> Value #

toEncodingList :: [SmallArray a] -> Encoding #

omitField :: SmallArray a -> Bool #

ToJSON a => ToJSON (I a) Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: I a -> Value #

toEncoding :: I a -> Encoding #

toJSONList :: [I a] -> Value #

toEncodingList :: [I a] -> Encoding #

omitField :: I a -> Bool #

ToJSON d => ToJSON (LinearTransform d) 
Instance details

Defined in Statistics.Distribution.Transform

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Maybe a -> Value #

toEncoding :: Maybe a -> Encoding #

toJSONList :: [Maybe a] -> Value #

toEncodingList :: [Maybe a] -> Encoding #

omitField :: Maybe a -> Bool #

ToJSON a => ToJSON (Resources a) 
Instance details

Defined in Cardano.Logging.Resources.Types

Methods

toJSON :: Resources a -> Value #

toEncoding :: Resources a -> Encoding #

toJSONList :: [Resources a] -> Value #

toEncodingList :: [Resources a] -> Encoding #

omitField :: Resources a -> Bool #

ToJSON a => ToJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashSet a -> Value #

toEncoding :: HashSet a -> Encoding #

toJSONList :: [HashSet a] -> Value #

toEncodingList :: [HashSet a] -> Encoding #

omitField :: HashSet a -> Bool #

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Prim a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Storable a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Maybe a -> Value #

toEncoding :: Maybe a -> Encoding #

toJSONList :: [Maybe a] -> Value #

toEncodingList :: [Maybe a] -> Encoding #

omitField :: Maybe a -> Bool #

ToJSON a => ToJSON (a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a) -> Value #

toEncoding :: (a) -> Encoding #

toJSONList :: [(a)] -> Value #

toEncodingList :: [(a)] -> Encoding #

omitField :: (a) -> Bool #

ToJSON a => ToJSON [a] 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

toJSONList :: [[a]] -> Value #

toEncodingList :: [[a]] -> Encoding #

omitField :: [a] -> Bool #

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

omitField :: Either a b -> Bool #

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fixed a -> Value #

toEncoding :: Fixed a -> Encoding #

toJSONList :: [Fixed a] -> Value #

toEncodingList :: [Fixed a] -> Encoding #

omitField :: Fixed a -> Bool #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Proxy a -> Value #

toEncoding :: Proxy a -> Encoding #

toJSONList :: [Proxy a] -> Value #

toEncodingList :: [Proxy a] -> Encoding #

omitField :: Proxy a -> Bool #

HashAlgorithm h => ToJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toJSON :: Hash h a -> Value #

toEncoding :: Hash h a -> Encoding #

toJSONList :: [Hash h a] -> Value #

toEncodingList :: [Hash h a] -> Encoding #

omitField :: Hash h a -> Bool #

ToJSON (AbstractHash algo a) 
Instance details

Defined in Cardano.Crypto.Hashing

Methods

toJSON :: AbstractHash algo a -> Value #

toEncoding :: AbstractHash algo a -> Encoding #

toJSONList :: [AbstractHash algo a] -> Value #

toEncodingList :: [AbstractHash algo a] -> Encoding #

omitField :: AbstractHash algo a -> Bool #

ToJSON b => ToJSON (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

toJSON :: Annotated b a -> Value #

toEncoding :: Annotated b a -> Encoding #

toJSONList :: [Annotated b a] -> Value #

toEncodingList :: [Annotated b a] -> Encoding #

omitField :: Annotated b a -> Bool #

ToJSON (BoundedRatio b Word64) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: BoundedRatio b Word64 -> Value #

toEncoding :: BoundedRatio b Word64 -> Encoding #

toJSONList :: [BoundedRatio b Word64] -> Value #

toEncodingList :: [BoundedRatio b Word64] -> Encoding #

omitField :: BoundedRatio b Word64 -> Bool #

Crypto c => ToJSON (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toJSON :: KeyHash disc c -> Value #

toEncoding :: KeyHash disc c -> Encoding #

toJSONList :: [KeyHash disc c] -> Value #

toEncodingList :: [KeyHash disc c] -> Encoding #

omitField :: KeyHash disc c -> Bool #

Crypto c => ToJSON (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

toJSON :: SafeHash c index -> Value #

toEncoding :: SafeHash c index -> Encoding #

toJSONList :: [SafeHash c index] -> Value #

toEncodingList :: [SafeHash c index] -> Encoding #

omitField :: SafeHash c index -> Bool #

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

omitField :: Map k v -> Bool #

ToJSON (Count a) Source # 
Instance details

Defined in Cardano.Analysis.API.Ground

Methods

toJSON :: Count a -> Value #

toEncoding :: Count a -> Encoding #

toJSONList :: [Count a] -> Value #

toEncodingList :: [Count a] -> Encoding #

omitField :: Count a -> Bool #

(ToJSON (p a), ToJSON (p Double), ToJSON a) => ToJSON (CDF p a) Source # 
Instance details

Defined in Data.CDF

Methods

toJSON :: CDF p a -> Value #

toEncoding :: CDF p a -> Encoding #

toJSONList :: [CDF p a] -> Value #

toEncodingList :: [CDF p a] -> Encoding #

omitField :: CDF p a -> Bool #

(forall b. ToJSON b => ToJSON (f b), ToJSON a) => ToJSON (DataDomain f a) Source # 
Instance details

Defined in Data.DataDomain

Methods

toJSON :: DataDomain f a -> Value #

toEncoding :: DataDomain f a -> Encoding #

toJSONList :: [DataDomain f a] -> Value #

toEncodingList :: [DataDomain f a] -> Encoding #

omitField :: DataDomain f a -> Bool #

(ToJSON a, ToJSONKey k) => ToJSON (MonoidalMap k a) 
Instance details

Defined in Data.Map.Monoidal

Methods

toJSON :: MonoidalMap k a -> Value #

toEncoding :: MonoidalMap k a -> Encoding #

toJSONList :: [MonoidalMap k a] -> Value #

toEncodingList :: [MonoidalMap k a] -> Encoding #

omitField :: MonoidalMap k a -> Bool #

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

omitField :: Either a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

omitField :: These a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (Pair a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Pair a b -> Value #

toEncoding :: Pair a b -> Encoding #

toJSONList :: [Pair a b] -> Value #

toEncodingList :: [Pair a b] -> Encoding #

omitField :: Pair a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

omitField :: These a b -> Bool #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashMap k v -> Value #

toEncoding :: HashMap k v -> Encoding #

toJSONList :: [HashMap k v] -> Value #

toEncodingList :: [HashMap k v] -> Encoding #

omitField :: HashMap k v -> Bool #

(ToJSON a, ToJSON b) => ToJSON (a, b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b) -> Value #

toEncoding :: (a, b) -> Encoding #

toJSONList :: [(a, b)] -> Value #

toEncodingList :: [(a, b)] -> Encoding #

omitField :: (a, b) -> Bool #

ToJSON a => ToJSON (Const a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Const a b -> Value #

toEncoding :: Const a b -> Encoding #

toJSONList :: [Const a b] -> Value #

toEncodingList :: [Const a b] -> Encoding #

omitField :: Const a b -> Bool #

ToJSON b => ToJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tagged a b -> Value #

toEncoding :: Tagged a b -> Encoding #

toJSONList :: [Tagged a b] -> Value #

toEncodingList :: [Tagged a b] -> Encoding #

omitField :: Tagged a b -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These1 f g a -> Value #

toEncoding :: These1 f g a -> Encoding #

toJSONList :: [These1 f g a] -> Value #

toEncodingList :: [These1 f g a] -> Encoding #

omitField :: These1 f g a -> Bool #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c) -> Value #

toEncoding :: (a, b, c) -> Encoding #

toJSONList :: [(a, b, c)] -> Value #

toEncodingList :: [(a, b, c)] -> Encoding #

omitField :: (a, b, c) -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Product f g a -> Value #

toEncoding :: Product f g a -> Encoding #

toJSONList :: [Product f g a] -> Value #

toEncodingList :: [Product f g a] -> Encoding #

omitField :: Product f g a -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Sum f g a -> Value #

toEncoding :: Sum f g a -> Encoding #

toJSONList :: [Sum f g a] -> Value #

toEncodingList :: [Sum f g a] -> Encoding #

omitField :: Sum f g a -> Bool #

(Vector vk k, Vector vv v, ToJSONKey k, ToJSON v) => ToJSON (VMap vk vv k v) 
Instance details

Defined in Data.VMap

Methods

toJSON :: VMap vk vv k v -> Value #

toEncoding :: VMap vk vv k v -> Encoding #

toJSONList :: [VMap vk vv k v] -> Value #

toEncodingList :: [VMap vk vv k v] -> Encoding #

omitField :: VMap vk vv k v -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d) -> Value #

toEncoding :: (a, b, c, d) -> Encoding #

toJSONList :: [(a, b, c, d)] -> Value #

toEncodingList :: [(a, b, c, d)] -> Encoding #

omitField :: (a, b, c, d) -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Compose f g a -> Value #

toEncoding :: Compose f g a -> Encoding #

toJSONList :: [Compose f g a] -> Value #

toEncodingList :: [Compose f g a] -> Encoding #

omitField :: Compose f g a -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e) -> Value #

toEncoding :: (a, b, c, d, e) -> Encoding #

toJSONList :: [(a, b, c, d, e)] -> Value #

toEncodingList :: [(a, b, c, d, e)] -> Encoding #

omitField :: (a, b, c, d, e) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f) -> Value #

toEncoding :: (a, b, c, d, e, f) -> Encoding #

toJSONList :: [(a, b, c, d, e, f)] -> Value #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding #

omitField :: (a, b, c, d, e, f) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value #

toEncoding :: (a, b, c, d, e, f, g) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding #

omitField :: (a, b, c, d, e, f, g) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

(.:) :: FromJSON a => Object -> Key -> Parser a #

object :: [Pair] -> Value #

(.!=) :: Parser (Maybe a) -> a -> Parser a #

(.:?) :: FromJSON a => Object -> Key -> Parser (Maybe a) #

withObject :: String -> (Object -> Parser a) -> Value -> Parser a #

data Interval v Source #

A closed interval. The lower bound should be less than or equal to the upper bound.

Constructors

Interval v v

Lower and upper bounds of the interval.

Instances

Instances details
Functor Interval Source # 
Instance details

Defined in Cardano.Util

Methods

fmap :: (a -> b) -> Interval a -> Interval b Source #

(<$) :: a -> Interval b -> Interval a Source #

FromJSON a => FromJSON (Interval a) Source # 
Instance details

Defined in Cardano.Util

ToJSON a => ToJSON (Interval a) Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: Interval a -> Value #

toEncoding :: Interval a -> Encoding #

toJSONList :: [Interval a] -> Value #

toEncodingList :: [Interval a] -> Encoding #

omitField :: Interval a -> Bool #

Generic (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

Associated Types

type Rep (Interval v) :: Type -> Type Source #

Methods

from :: Interval v -> Rep (Interval v) x Source #

to :: Rep (Interval v) x -> Interval v Source #

Read v => Read (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

Show v => Show (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

NFData a => NFData (Interval a) Source # 
Instance details

Defined in Cardano.Util

Methods

rnf :: Interval a -> () Source #

Eq v => Eq (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

Methods

(==) :: Interval v -> Interval v -> Bool Source #

(/=) :: Interval v -> Interval v -> Bool Source #

Ord v => Ord (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

type Rep (Interval v) 
Instance details

Defined in Data.IntervalMap.FingerTree

type Rep (Interval v) = D1 ('MetaData "Interval" "Data.IntervalMap.FingerTree" "fingertree-0.1.5.0-4A0Okgv02lgEkSU40NJaKW" 'False) (C1 ('MetaCons "Interval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)))

low :: Interval v -> v Source #

Lower bound of the interval

high :: Interval v -> v Source #

Upper bound of the interval

point :: v -> Interval v Source #

An interval in which the lower and upper bounds are equal.

newtype I a Source #

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 

Instances

Instances details
Foldable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => I m -> m Source #

foldMap :: Monoid m => (a -> m) -> I a -> m Source #

foldMap' :: Monoid m => (a -> m) -> I a -> m Source #

foldr :: (a -> b -> b) -> b -> I a -> b Source #

foldr' :: (a -> b -> b) -> b -> I a -> b Source #

foldl :: (b -> a -> b) -> b -> I a -> b Source #

foldl' :: (b -> a -> b) -> b -> I a -> b Source #

foldr1 :: (a -> a -> a) -> I a -> a Source #

foldl1 :: (a -> a -> a) -> I a -> a Source #

toList :: I a -> [a] Source #

null :: I a -> Bool Source #

length :: I a -> Int Source #

elem :: Eq a => a -> I a -> Bool Source #

maximum :: Ord a => I a -> a Source #

minimum :: Ord a => I a -> a Source #

sum :: Num a => I a -> a Source #

product :: Num a => I a -> a Source #

Eq1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> I a -> I b -> Bool Source #

Ord1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> I a -> I b -> Ordering Source #

Read1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (I a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [I a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (I a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [I a] Source #

Show1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> I a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [I a] -> ShowS Source #

Traversable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a -> f b) -> I a -> f (I b) Source #

sequenceA :: Applicative f => I (f a) -> f (I a) Source #

mapM :: Monad m => (a -> m b) -> I a -> m (I b) Source #

sequence :: Monad m => I (m a) -> m (I a) Source #

Applicative I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a -> I a Source #

(<*>) :: I (a -> b) -> I a -> I b Source #

liftA2 :: (a -> b -> c) -> I a -> I b -> I c Source #

(*>) :: I a -> I b -> I b Source #

(<*) :: I a -> I b -> I a Source #

Functor I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> I a -> I b Source #

(<$) :: a -> I b -> I a Source #

Monad I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(>>=) :: I a -> (a -> I b) -> I b Source #

(>>) :: I a -> I b -> I b Source #

return :: a -> I a Source #

NFData1 I

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> I a -> () Source #

KnownCDF I Source # 
Instance details

Defined in Data.CDF

Methods

cdfIx :: CDFIx I Source #

FromJSON a => FromJSON (I a) Source # 
Instance details

Defined in Cardano.Util

Methods

parseJSON :: Value -> Parser (I a) #

parseJSONList :: Value -> Parser [I a] #

omittedField :: Maybe (I a) #

ToJSON a => ToJSON (I a) Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: I a -> Value #

toEncoding :: I a -> Encoding #

toJSONList :: [I a] -> Value #

toEncodingList :: [I a] -> Encoding #

omitField :: I a -> Bool #

Monoid a => Monoid (I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: I a Source #

mappend :: I a -> I a -> I a Source #

mconcat :: [I a] -> I a Source #

Semigroup a => Semigroup (I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: I a -> I a -> I a Source #

sconcat :: NonEmpty (I a) -> I a Source #

stimes :: Integral b => b -> I a -> I a Source #

Generic (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (I a) :: Type -> Type Source #

Methods

from :: I a -> Rep (I a) x Source #

to :: Rep (I a) x -> I a Source #

Num (I Int) Source # 
Instance details

Defined in Cardano.Analysis.Summary

Methods

(+) :: I Int -> I Int -> I Int Source #

(-) :: I Int -> I Int -> I Int Source #

(*) :: I Int -> I Int -> I Int Source #

negate :: I Int -> I Int Source #

abs :: I Int -> I Int Source #

signum :: I Int -> I Int Source #

fromInteger :: Integer -> I Int Source #

Read a => Read (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Show a => Show (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> I a -> ShowS Source #

show :: I a -> String Source #

showList :: [I a] -> ShowS Source #

NFData a => NFData (I a)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: I a -> () Source #

Eq a => Eq (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: I a -> I a -> Bool Source #

(/=) :: I a -> I a -> Bool Source #

Ord a => Ord (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: I a -> I a -> Ordering Source #

(<) :: I a -> I a -> Bool Source #

(<=) :: I a -> I a -> Bool Source #

(>) :: I a -> I a -> Bool Source #

(>=) :: I a -> I a -> Bool Source #

max :: I a -> I a -> I a Source #

min :: I a -> I a -> I a Source #

KnownCDF (CDF I) Source # 
Instance details

Defined in Data.CDF

Methods

cdfIx :: CDFIx (CDF I) Source #

type Rep (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (I a) = D1 ('MetaData "I" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-6frQFsrp1xOFEhJrxT1beu" 'True) (C1 ('MetaCons "I" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

unI :: I a -> a Source #

Extract the contents of an I value.

chunksOf :: Int -> [e] -> [[e]] Source #

chunksOf n splits a list into length-n pieces. The last piece will be shorter if n does not evenly divide the length of the list. If n <= 0, chunksOf n l returns an infinite list of empty lists.

>>> chunksOf 3 [1..12]
[[1,2,3],[4,5,6],[7,8,9],[10,11,12]]
>>> chunksOf 3 "Hello there"
["Hel","lo ","the","re"]
>>> chunksOf 3 ([] :: [Int])
[]

Note that chunksOf n [] is [], not [[]]. This is intentional, and satisfies the property that

chunksOf n xs ++ chunksOf n ys == chunksOf n (xs ++ ys)

whenever n evenly divides the length of xs.

data UTCTime Source #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Constructors

UTCTime 

Fields

Instances

Instances details
FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction UTCTime

fromJSONKeyList :: FromJSONKeyFunction [UTCTime]

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UTCTime -> Value #

toEncoding :: UTCTime -> Encoding #

toJSONList :: [UTCTime] -> Value #

toEncodingList :: [UTCTime] -> Encoding #

omitField :: UTCTime -> Bool #

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction UTCTime

toJSONKeyList :: ToJSONKeyFunction [UTCTime]

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime Source #

toConstr :: UTCTime -> Constr Source #

dataTypeOf :: UTCTime -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) Source #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime Source #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () Source #

Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

data NominalDiffTime Source #

This is a length of time, as measured by UTC. It has a precision of 10^-12 s.

Conversion functions such as fromInteger and realToFrac will treat it as seconds. For example, (0.010 :: NominalDiffTime) corresponds to 10 milliseconds.

It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.

It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.

Instances

Instances details
FromJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NominalDiffTime -> c NominalDiffTime Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NominalDiffTime Source #

toConstr :: NominalDiffTime -> Constr Source #

dataTypeOf :: NominalDiffTime -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NominalDiffTime) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NominalDiffTime) Source #

gmapT :: (forall b. Data b => b -> b) -> NominalDiffTime -> NominalDiffTime Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NominalDiffTime -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NominalDiffTime -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime Source #

Enum NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Num NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Read NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Fractional NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Real NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

RealFrac NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Show NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

NFData NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

rnf :: NominalDiffTime -> () Source #

Eq NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Ord NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Divisible NominalDiffTime Source # 
Instance details

Defined in Data.CDF

Show (TimelineComments (SlotStats NominalDiffTime)) Source # 
Instance details

Defined in Cardano.Analysis.API.Metrics

TimelineFields (SlotStats NominalDiffTime) Source # 
Instance details

Defined in Cardano.Analysis.API.Metrics

data TimelineComments (SlotStats NominalDiffTime) Source # 
Instance details

Defined in Cardano.Analysis.API.Metrics

addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime Source #

addUTCTime a b = a + b

diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime Source #

diffUTCTime a b = a - b

data StrictMaybe a Source #

Constructors

SNothing 
SJust !a 

Instances

Instances details
MonadFail StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

fail :: String -> StrictMaybe a Source #

Foldable StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

fold :: Monoid m => StrictMaybe m -> m Source #

foldMap :: Monoid m => (a -> m) -> StrictMaybe a -> m Source #

foldMap' :: Monoid m => (a -> m) -> StrictMaybe a -> m Source #

foldr :: (a -> b -> b) -> b -> StrictMaybe a -> b Source #

foldr' :: (a -> b -> b) -> b -> StrictMaybe a -> b Source #

foldl :: (b -> a -> b) -> b -> StrictMaybe a -> b Source #

foldl' :: (b -> a -> b) -> b -> StrictMaybe a -> b Source #

foldr1 :: (a -> a -> a) -> StrictMaybe a -> a Source #

foldl1 :: (a -> a -> a) -> StrictMaybe a -> a Source #

toList :: StrictMaybe a -> [a] Source #

null :: StrictMaybe a -> Bool Source #

length :: StrictMaybe a -> Int Source #

elem :: Eq a => a -> StrictMaybe a -> Bool Source #

maximum :: Ord a => StrictMaybe a -> a Source #

minimum :: Ord a => StrictMaybe a -> a Source #

sum :: Num a => StrictMaybe a -> a Source #

product :: Num a => StrictMaybe a -> a Source #

Traversable StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

traverse :: Applicative f => (a -> f b) -> StrictMaybe a -> f (StrictMaybe b) Source #

sequenceA :: Applicative f => StrictMaybe (f a) -> f (StrictMaybe a) Source #

mapM :: Monad m => (a -> m b) -> StrictMaybe a -> m (StrictMaybe b) Source #

sequence :: Monad m => StrictMaybe (m a) -> m (StrictMaybe a) Source #

Alternative StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Applicative StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Functor StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

fmap :: (a -> b) -> StrictMaybe a -> StrictMaybe b Source #

(<$) :: a -> StrictMaybe b -> StrictMaybe a Source #

Monad StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

FromJSON a => FromJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

ToJSON a => ToJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

toJSON :: StrictMaybe a -> Value #

toEncoding :: StrictMaybe a -> Encoding #

toJSONList :: [StrictMaybe a] -> Value #

toEncodingList :: [StrictMaybe a] -> Encoding #

omitField :: StrictMaybe a -> Bool #

Semigroup a => Monoid (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Semigroup a => Semigroup (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Generic (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Associated Types

type Rep (StrictMaybe a) :: Type -> Type Source #

Show a => Show (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

FromCBOR a => FromCBOR (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

ToCBOR a => ToCBOR (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

toCBOR :: StrictMaybe a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size Source #

Default (StrictMaybe t) 
Instance details

Defined in Data.Maybe.Strict

Methods

def :: StrictMaybe t Source #

NFData a => NFData (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

rnf :: StrictMaybe a -> () Source #

Eq a => Eq (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Ord a => Ord (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

NoThunks a => NoThunks (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

type Rep (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

type Rep (StrictMaybe a) = D1 ('MetaData "StrictMaybe" "Data.Maybe.Strict" "cardano-strict-containers-0.1.3.0-86c2IVFj8yvJB1TAEwUmlH" 'False) (C1 ('MetaCons "SNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

fromSMaybe :: a -> StrictMaybe a -> a Source #

Same as fromMaybe

(***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') infixr 3 Source #

Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

(&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') infixr 3 Source #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 Source #

An associative binary operation

mapConcurrently :: Traversable t => (a -> IO b) -> t a -> IO (t b) Source #

Maps an IO-performing function over any Traversable data type, performing all the IO actions concurrently, and returning the original data structure with the arguments replaced by the results.

If any of the actions throw an exception, then all other actions are cancelled and the exception is re-thrown.

For example, mapConcurrently works with lists:

pages <- mapConcurrently getURL ["url1", "url2", "url3"]

Take into account that async will try to immediately spawn a thread for each element of the Traversable, so running this on large inputs without care may lead to resource exhaustion (of memory, file descriptors, or other limited resources).

forConcurrently :: Traversable t => t a -> (a -> IO b) -> IO (t b) Source #

forConcurrently is mapConcurrently with its arguments flipped

pages <- forConcurrently ["url1", "url2", "url3"] $ \url -> getURL url

Since: async-2.1.0

mapConcurrently_ :: Foldable f => (a -> IO b) -> f a -> IO () Source #

mapConcurrently_ is mapConcurrently with the return value discarded; a concurrent equivalent of mapM_.

forConcurrently_ :: Foldable f => f a -> (a -> IO b) -> IO () Source #

forConcurrently_ is forConcurrently with the return value discarded; a concurrent equivalent of forM_.

newExceptT :: m (Either x a) -> ExceptT x m a Source #

Constructor for computations in the ExceptT monad. (The inverse of runExceptT).

firstExceptT :: forall (m :: Type -> Type) x y a. Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a Source #

Map the Left unwrapped computation using the given function.

printf :: PrintfType r => String -> r Source #

Format a variable number of arguments with the C-style formatting string.

>>> printf "%s, %d, %.4f" "hello" 123 pi
hello, 123, 3.1416

The return value is either String or (IO a) (which should be (IO ()), but Haskell's type system makes this hard).

The format string consists of ordinary characters and conversion specifications, which specify how to format one of the arguments to printf in the output string. A format specification is introduced by the % character; this character can be self-escaped into the format string using %%. A format specification ends with a format character that provides the primary information about how to format the value. The rest of the conversion specification is optional. In order, one may have flag characters, a width specifier, a precision specifier, and type-specific modifier characters.

Unlike C printf(3), the formatting of this printf is driven by the argument type; formatting is type specific. The types formatted by printf "out of the box" are:

printf is also extensible to support other types: see below.

A conversion specification begins with the character %, followed by zero or more of the following flags:

-      left adjust (default is right adjust)
+      always use a sign (+ or -) for signed conversions
space  leading space for positive numbers in signed conversions
0      pad with zeros rather than spaces
#      use an \"alternate form\": see below

When both flags are given, - overrides 0 and + overrides space. A negative width specifier in a * conversion is treated as positive but implies the left adjust flag.

The "alternate form" for unsigned radix conversions is as in C printf(3):

%o           prefix with a leading 0 if needed
%x           prefix with a leading 0x if nonzero
%X           prefix with a leading 0X if nonzero
%b           prefix with a leading 0b if nonzero
%[eEfFgG]    ensure that the number contains a decimal point

Any flags are followed optionally by a field width:

num    field width
*      as num, but taken from argument list

The field width is a minimum, not a maximum: it will be expanded as needed to avoid mutilating a value.

Any field width is followed optionally by a precision:

.num   precision
.      same as .0
.*     as num, but taken from argument list

Negative precision is taken as 0. The meaning of the precision depends on the conversion type.

Integral    minimum number of digits to show
RealFloat   number of digits after the decimal point
String      maximum number of characters

The precision for Integral types is accomplished by zero-padding. If both precision and zero-pad are given for an Integral field, the zero-pad is ignored.

Any precision is followed optionally for Integral types by a width modifier; the only use of this modifier being to set the implicit size of the operand for conversion of a negative operand to unsigned:

hh     Int8
h      Int16
l      Int32
ll     Int64
L      Int64

The specification ends with a format character:

c      character               Integral
d      decimal                 Integral
o      octal                   Integral
x      hexadecimal             Integral
X      hexadecimal             Integral
b      binary                  Integral
u      unsigned decimal        Integral
f      floating point          RealFloat
F      floating point          RealFloat
g      general format float    RealFloat
G      general format float    RealFloat
e      exponent format float   RealFloat
E      exponent format float   RealFloat
s      string                  String
v      default format          any type

The "%v" specifier is provided for all built-in types, and should be provided for user-defined type formatters as well. It picks a "best" representation for the given type. For the built-in types the "%v" specifier is converted as follows:

c      Char
u      other unsigned Integral
d      other signed Integral
g      RealFloat
s      String

Mismatch between the argument types and the format string, as well as any other syntactic or semantic errors in the format string, will cause an exception to be thrown at runtime.

Note that the formatting for RealFloat types is currently a bit different from that of C printf(3), conforming instead to showEFloat, showFFloat and showGFloat (and their alternate versions showFFloatAlt and showGFloatAlt). This is hard to fix: the fixed versions would format in a backward-incompatible way. In any case the Haskell behavior is generally more sensible than the C behavior. A brief summary of some key differences:

  • Haskell printf never uses the default "6-digit" precision used by C printf.
  • Haskell printf treats the "precision" specifier as indicating the number of digits after the decimal point.
  • Haskell printf prints the exponent of e-format numbers without a gratuitous plus sign, and with the minimum possible number of digits.
  • Haskell printf will place a zero after a decimal point when possible.

data F Source #

Constructors

R String 
Q String 
L [String] 
forall a.ToJSON a => J a 

newtype RUTCTime Source #

Constructors

RUTCTime 

Instances

Instances details
FromJSON RUTCTime Source # 
Instance details

Defined in Cardano.Util

ToJSON RUTCTime Source # 
Instance details

Defined in Cardano.Util

Methods

toJSON :: RUTCTime -> Value #

toEncoding :: RUTCTime -> Encoding #

toJSONList :: [RUTCTime] -> Value #

toEncodingList :: [RUTCTime] -> Encoding #

omitField :: RUTCTime -> Bool #

Num RUTCTime Source # 
Instance details

Defined in Cardano.Util

Real RUTCTime Source # 
Instance details

Defined in Cardano.Util

Show RUTCTime Source # 
Instance details

Defined in Cardano.Util

NFData RUTCTime Source # 
Instance details

Defined in Cardano.Util

Methods

rnf :: RUTCTime -> () Source #

Eq RUTCTime Source # 
Instance details

Defined in Cardano.Util

Ord RUTCTime Source # 
Instance details

Defined in Cardano.Util

Divisible RUTCTime Source # 
Instance details

Defined in Data.CDF

spans :: forall a. (a -> Bool) -> [a] -> [Vector a] Source #

showText :: Show a => a -> Text Source #

renderIntv :: (a -> Text) -> Interval a -> Text Source #

smaybe :: b -> (a -> b) -> StrictMaybe a -> b Source #

catSMaybes :: [SMaybe a] -> [a] Source #

mapSMaybe :: (a -> StrictMaybe b) -> [a] -> [b] Source #

mapSMaybeFB :: (b -> r -> r) -> (a -> StrictMaybe b) -> a -> r -> r Source #

mapConcurrentlyPure :: NFData b => (a -> b) -> [a] -> IO [b] Source #

mapHead :: (a -> a) -> [a] -> [a] Source #

mapLast :: (a -> a) -> [a] -> [a] Source #

redistribute :: (a, (b, c)) -> ((a, b), (a, c)) Source #

toDouble :: forall a. Real a => a -> Double Source #

progress :: MonadIO m => String -> F -> m () Source #

norm2Tuple :: ((a, b), c) -> (a, (b, c)) Source #

foldEmpty :: r -> ([a] -> r) -> [a] -> r Source #

zeroUTCTime :: UTCTime Source #

A tweaked version of UTCTime that is able to have more instances. Structurally equivalent to difftime from zeroUTCTime

Orphan instances

Functor Interval Source # 
Instance details

Methods

fmap :: (a -> b) -> Interval a -> Interval b Source #

(<$) :: a -> Interval b -> Interval a Source #

FromJSON a => FromJSON (Interval a) Source # 
Instance details

FromJSON a => FromJSON (I a) Source # 
Instance details

Methods

parseJSON :: Value -> Parser (I a) #

parseJSONList :: Value -> Parser [I a] #

omittedField :: Maybe (I a) #

ToJSON a => ToJSON (Interval a) Source # 
Instance details

Methods

toJSON :: Interval a -> Value #

toEncoding :: Interval a -> Encoding #

toJSONList :: [Interval a] -> Value #

toEncodingList :: [Interval a] -> Encoding #

omitField :: Interval a -> Bool #

ToJSON a => ToJSON (I a) Source # 
Instance details

Methods

toJSON :: I a -> Value #

toEncoding :: I a -> Encoding #

toJSONList :: [I a] -> Value #

toEncodingList :: [I a] -> Encoding #

omitField :: I a -> Bool #

NFData a => NFData (Interval a) Source # 
Instance details

Methods

rnf :: Interval a -> () Source #