Safe Haskell | None |
---|---|
Language | Haskell2010 |
NP with optional values
Intended for qualified import
import Ouroboros.Consensus.Util.OptNP (OptNP (..), ViewOptNP (..)) import qualified Ouroboros.Consensus.Util.OptNP as OptNP
Synopsis
- type NonEmptyOptNP = OptNP ' False
- data OptNP (empty :: Bool ) (f :: k -> Type ) (xs :: [k]) where
- at :: SListI xs => f x -> Index xs x -> NonEmptyOptNP f xs
- empty :: forall f xs. SListI xs => OptNP ' True f xs
- fromNP :: ( forall empty. OptNP empty f xs -> r) -> NP f xs -> r
- fromNonEmptyNP :: forall f xs. IsNonEmpty xs => NP f xs -> NonEmptyOptNP f xs
- fromSingleton :: NonEmptyOptNP f '[x] -> f x
- singleton :: f x -> NonEmptyOptNP f '[x]
- toNP :: OptNP empty f xs -> NP ( Maybe :.: f) xs
-
data
ViewOptNP
f xs
where
- OptNP_ExactlyOne :: f x -> ViewOptNP f '[x]
- OptNP_AtLeastTwo :: ViewOptNP f (x ': (y ': zs))
- view :: forall f xs. NonEmptyOptNP f xs -> ViewOptNP f xs
- combine :: forall (f :: Type -> Type ) xs. ( SListI xs, HasCallStack ) => Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs)
- combineWith :: SListI xs => ( forall a. These1 f g a -> h a) -> Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP g xs) -> Maybe ( NonEmptyOptNP h xs)
- zipWith :: forall f g h xs. ( forall a. These1 f g a -> h a) -> NonEmptyOptNP f xs -> NonEmptyOptNP g xs -> NonEmptyOptNP h xs
Documentation
type NonEmptyOptNP = OptNP ' False Source #
data OptNP (empty :: Bool ) (f :: k -> Type ) (xs :: [k]) where Source #
Like an
NP
, but with optional values
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
HAp ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source # | |
HSequence ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source # | |
Defined in Ouroboros.Consensus.Util.OptNP 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 # | |
All ( Compose Show f) xs => Show ( OptNP empty f xs) Source # | |
type Prod ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source # | |
type SListIN ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source # | |
Defined in Ouroboros.Consensus.Util.OptNP |
|
type AllN ( OptNP empty :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source # | |
Defined in Ouroboros.Consensus.Util.OptNP |
fromNonEmptyNP :: forall f xs. IsNonEmpty xs => NP f xs -> NonEmptyOptNP f xs Source #
fromSingleton :: NonEmptyOptNP f '[x] -> f x Source #
If
OptNP
is not empty, it must contain at least one value
singleton :: f x -> NonEmptyOptNP f '[x] Source #
View
data ViewOptNP f xs where Source #
OptNP_ExactlyOne :: f x -> ViewOptNP f '[x] | |
OptNP_AtLeastTwo :: ViewOptNP f (x ': (y ': zs)) |
view :: forall f xs. NonEmptyOptNP f xs -> ViewOptNP f xs Source #
Combining
combine :: forall (f :: Type -> Type ) xs. ( SListI xs, HasCallStack ) => Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP f xs) Source #
combineWith :: SListI xs => ( forall a. These1 f g a -> h a) -> Maybe ( NonEmptyOptNP f xs) -> Maybe ( NonEmptyOptNP g xs) -> Maybe ( NonEmptyOptNP h xs) Source #
zipWith :: forall f g h xs. ( forall a. These1 f g a -> h a) -> NonEmptyOptNP f xs -> NonEmptyOptNP g xs -> NonEmptyOptNP h xs Source #