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

Ouroboros.Consensus.Util.OptNP

Description

NP with optional values

Intended for qualified import

import           Ouroboros.Consensus.Util.OptNP (OptNP (..), ViewOptNP (..))
import qualified Ouroboros.Consensus.Util.OptNP as OptNP
Synopsis

Documentation

data OptNP (empty :: Bool ) (f :: k -> Type ) (xs :: [k]) where Source #

Like an NP , but with optional values

Constructors

OptNil :: OptNP ' True f '[]
OptCons :: !(f x) -> !( OptNP empty f xs) -> OptNP ' False f (x ': xs)
OptSkip :: !( OptNP empty f xs) -> OptNP empty f (x ': xs)

Instances

Instances details
HAp ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

Methods

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

HSequence ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN ( OptNP empty) xs, Applicative f) => OptNP empty (f :.: g) xs -> f ( OptNP empty g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN ( OptNP empty) c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> OptNP empty f xs -> g ( OptNP empty f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN ( OptNP empty) xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> OptNP empty f xs -> g ( OptNP empty f' xs) Source #

All ( Compose Eq f) xs => Eq ( OptNP empty f xs) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

Methods

(==) :: OptNP empty f xs -> OptNP empty f xs -> Bool Source #

(/=) :: OptNP empty f xs -> OptNP empty f xs -> Bool Source #

All ( Compose Show f) xs => Show ( OptNP empty f xs) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

type Prod ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

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

Defined in Ouroboros.Consensus.Util.OptNP

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

Defined in Ouroboros.Consensus.Util.OptNP

type AllN ( OptNP empty :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c

fromNP :: ( forall empty. OptNP empty f xs -> r) -> NP f xs -> r Source #

fromSingleton :: NonEmptyOptNP f '[x] -> f x Source #

If OptNP is not empty, it must contain at least one value

View

data ViewOptNP f xs where Source #

Constructors

OptNP_ExactlyOne :: f x -> ViewOptNP f '[x]
OptNP_AtLeastTwo :: ViewOptNP f (x ': (y ': zs))

Combining

combine :: forall (f :: Type -> Type ) xs. ( SListI xs, HasCallStack ) => Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs) Source #

Precondition: there is no overlap between the two given lists: if there is a Just at a given position in one, it must be Nothing at the same position in the other.

zipWith :: forall f g h xs. ( forall a. These1 f g a -> h a) -> NonEmptyOptNP f xs -> NonEmptyOptNP g xs -> NonEmptyOptNP h xs Source #