ouroboros-consensus-0.1.0.1: Consensus layer for the Ouroboros blockchain protocol
Safe Haskell None
Language Haskell2010

Ouroboros.Consensus.HardFork.Combinator.Util.Match

Description

Intended for qualified import

import Ouroboros.Consensus.HardFork.Combinator.Util.Match (Mismatch(..))
import qualified Ouroboros.Consensus.HardFork.Combinator.Util.Match as Match
Synopsis

Documentation

data Mismatch :: (k -> Type ) -> (k -> Type ) -> [k] -> Type where Source #

Constructors

ML :: f x -> NS g xs -> Mismatch f g (x ': xs)
MR :: NS f xs -> g x -> Mismatch f g (x ': xs)
MS :: Mismatch f g xs -> Mismatch f g (x ': xs)

Instances

Instances details
HAp ( Mismatch f :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

Methods

hap :: forall (f0 :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod ( Mismatch f) (f0 -.-> g) xs -> Mismatch f f0 xs -> Mismatch f g xs Source #

( All ( Compose Eq f) xs, All ( Compose Eq g) xs) => Eq ( Mismatch f g xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

( All ( Compose Eq f) xs, All ( Compose Ord f) xs, All ( Compose Eq g) xs, All ( Compose Ord g) xs) => Ord ( Mismatch f g xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

( All ( Compose Show f) xs, All ( Compose Show g) xs) => Show ( Mismatch f g xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

( All ( Compose NoThunks f) xs, All ( Compose NoThunks g) xs) => NoThunks ( Mismatch f g xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type Prod ( Mismatch f :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type Prod ( Mismatch f :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type SListIN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type SListIN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) = SListI :: [k] -> Constraint
type AllN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type AllN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c

Utilities

mismatchNotEmpty :: Mismatch f g xs -> ( forall x xs'. xs ~ (x ': xs') => Mismatch f g (x ': xs') -> a) -> a Source #

mismatchOne :: Mismatch f g '[x] -> Void Source #

We cannot give a mismatch if we have only one type variable

mismatchToNS :: Mismatch f g xs -> ( NS f xs, NS g xs) Source #

Project two NS from a Mismatch

We should have the property that

uncurry matchNS (mismatchToNS m) == Left m

mismatchTwo :: Mismatch f g '[x, y] -> Either (f x, g y) (f y, g x) Source #

If we only have two eras, only two possibilities for a mismatch

mkMismatchTwo :: Either (f x, g y) (f y, g x) -> Mismatch f g '[x, y] Source #

mustMatchNS :: forall f g xs. HasCallStack => String -> NS f xs -> NS g xs -> NS ( Product f g) xs Source #

Variant of matchNS for when we know the two NS s must match. Otherwise an error, mentioning the given String , is thrown.

SOP operators

bihap :: NP (f -.-> f') xs -> NP (g -.-> g') xs -> Mismatch f g xs -> Mismatch f' g' xs Source #

bihcmap :: All c xs => proxy c -> ( forall x. c x => f x -> f' x) -> ( forall x. c x => g x -> g' x) -> Mismatch f g xs -> Mismatch f' g' xs Source #

Bifunctor analogue of hcmap

bihmap :: SListI xs => ( forall x. f x -> f' x) -> ( forall x. g x -> g' x) -> Mismatch f g xs -> Mismatch f' g' xs Source #