Copyright | Dennis Gosnell 2017 |
---|---|
License | BSD3 |
Maintainer | Dennis Gosnell (cdep.illabout@gmail.com) |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
This package defines a type called OpenUnion
. This represents an open union
of possible types (also called an open sum type).
Here is an example of taking a String
, and lifting it up into an open union
of a String
and Int
:
let int = 3 ::Int
let o =openUnionLift
int ::OpenUnion
'[String
,Int
]
There are a couple different ways to pattern match on a OpenUnion
.
The easiest one is to use catchesOpenUnion
, which takes a tuple of handlers for
each possible type in the OpenUnion
:
let strHandler = (str -> "got a String: "++
str) ::String
->String
intHandler = (int -> "got an Int: "++
show
int) ::Int
->String
incatchesOpenUnion
(strHandler, intHandler) u ::String
The above will print got an Int: 3
.
There is also the openUnionMatch
function, as well as fromOpenUnion
and
openUnion
. Read the documentation below for more information.
Synopsis
- type OpenUnion = Union Identity
- openUnion :: (OpenUnion as -> c) -> (a -> c) -> OpenUnion (a ': as) -> c
- fromOpenUnion :: (OpenUnion as -> a) -> OpenUnion (a ': as) -> a
- fromOpenUnionOr :: OpenUnion (a ': as) -> (OpenUnion as -> a) -> a
- openUnionPrism :: forall a as. IsMember a as => Prism' (OpenUnion as) a
- openUnionLift :: forall a as. IsMember a as => a -> OpenUnion as
- openUnionMatch :: forall a as. IsMember a as => OpenUnion as -> Maybe a
- catchesOpenUnion :: ToOpenProduct tuple (ReturnX x as) => tuple -> OpenUnion as -> x
- relaxOpenUnion :: Contains as bs => OpenUnion as -> OpenUnion bs
- openUnionRemove :: forall a as. ElemRemove a as => OpenUnion as -> Either (OpenUnion (Remove a as)) a
- openUnionHandle :: ElemRemove a as => (OpenUnion (Remove a as) -> b) -> (a -> b) -> OpenUnion as -> b
- type IsMember (a :: u) (as :: [u]) = UElem a as (RIndex a as)
- type family Contains (as :: [k]) (bs :: [k]) :: Constraint where ...
- data Union (f :: u -> *) (as :: [u]) where
- union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c
- absurdUnion :: Union f '[] -> a
- umap :: (forall a. f a -> g a) -> Union f as -> Union g as
- catchesUnion :: (Applicative f, ToProduct tuple f (ReturnX x as)) => tuple -> Union f as -> f x
- relaxUnion :: Contains as bs => Union f as -> Union f bs
- unionRemove :: forall a as f. ElemRemove a as => Union f as -> Either (Union f (Remove a as)) (f a)
- unionHandle :: ElemRemove a as => (Union f (Remove a as) -> b) -> (f a -> b) -> Union f as -> b
- _This :: Prism (Union f (a ': as)) (Union f (b ': as)) (f a) (f b)
- _That :: Prism (Union f (a ': as)) (Union f (a ': bs)) (Union f as) (Union f bs)
- type ElemRemove a as = ElemRemove' a as (RemoveCase a as)
- type family Remove (a :: k) (as :: [k]) :: [k] where ...
- data Nat
- type family RIndex (r :: k) (rs :: [k]) :: Nat where ...
- class i ~ RIndex a as => UElem (a :: k) (as :: [k]) (i :: Nat) where
- unionPrism :: Prism' (Union f as) (f a)
- unionLift :: f a -> Union f as
- unionMatch :: Union f as -> Maybe (f a)
- type OpenProduct = Product Identity
- data Product (f :: u -> *) (as :: [u]) where
- class ToOpenProduct (tuple :: *) (as :: [*]) | as -> tuple
- tupleToOpenProduct :: ToOpenProduct t as => t -> OpenProduct as
- class ToProduct (tuple :: *) (f :: u -> *) (as :: [u]) | f as -> tuple
- tupleToProduct :: ToProduct t f as => t -> Product f as
- type family ReturnX x as where ...
OpenUnion
OpenUnion
Helpers
openUnion :: (OpenUnion as -> c) -> (a -> c) -> OpenUnion (a ': as) -> c Source #
Case analysis for OpenUnion
.
Examples
Here is an example of successfully matching:
>>>
let string = "hello" :: String
>>>
let o = openUnionLift string :: OpenUnion '[String, Int]
>>>
openUnion (const "not a String") id o
"hello"
Here is an example of unsuccessfully matching:
>>>
let double = 3.5 :: Double
>>>
let p = openUnionLift double :: OpenUnion '[String, Double, Int]
>>>
openUnion (const "not a String") id p
"not a String"
fromOpenUnion :: (OpenUnion as -> a) -> OpenUnion (a ': as) -> a Source #
This is similar to fromMaybe
for an OpenUnion
.
Examples
Here is an example of successfully matching:
>>>
let string = "hello" :: String
>>>
let o = openUnionLift string :: OpenUnion '[String, Int]
>>>
fromOpenUnion (const "not a String") o
"hello"
Here is an example of unsuccessfully matching:
>>>
let double = 3.5 :: Double
>>>
let p = openUnionLift double :: OpenUnion '[String, Double, Int]
>>>
fromOpenUnion (const "not a String") p
"not a String"
fromOpenUnionOr :: OpenUnion (a ': as) -> (OpenUnion as -> a) -> a Source #
Flipped version of fromOpenUnion
.
openUnionPrism :: forall a as. IsMember a as => Prism' (OpenUnion as) a Source #
Just like unionPrism
but for OpenUnion
.
openUnionLift :: forall a as. IsMember a as => a -> OpenUnion as Source #
openUnionMatch :: forall a as. IsMember a as => OpenUnion as -> Maybe a Source #
Just like unionMatch
but for OpenUnion
.
Examples
Successful matching:
>>>
let string = "hello" :: String
>>>
let o = openUnionLift string :: OpenUnion '[Double, String, Int]
>>>
openUnionMatch o :: Maybe String
Just "hello"
Failure matching:
>>>
let double = 3.5 :: Double
>>>
let p = openUnionLift double :: OpenUnion '[Double, String]
>>>
openUnionMatch p :: Maybe String
Nothing
catchesOpenUnion :: ToOpenProduct tuple (ReturnX x as) => tuple -> OpenUnion as -> x Source #
An alternate case anaylsis for an OpenUnion
. This method uses a tuple
containing handlers for each potential value of the OpenUnion
. This is
somewhat similar to the catches
function.
When working with large OpenUnion
s, it can be easier to use
catchesOpenUnion
than openUnion
.
Examples
Here is an example of handling an OpenUnion
with two possible values.
Notice that a normal tuple is used:
>>>
let u = openUnionLift (3 :: Int) :: OpenUnion '[Int, String]
>>>
let intHandler = (\int -> show int) :: Int -> String
>>>
let strHandler = (\str -> str) :: String -> String
>>>
catchesOpenUnion (intHandler, strHandler) u :: String
"3"
Given an OpenUnion
like
, the type of
OpenUnion
'[Int
, String
]catchesOpenUnion
becomes the following:
catchesOpenUnion
:: (Int
-> x,String
-> x) ->OpenUnion
'[Int
,String
] -> x
Here is an example of handling an OpenUnion
with three possible values:
>>>
let u = openUnionLift ("hello" :: String) :: OpenUnion '[Int, String, Double]
>>>
let intHandler = (\int -> show int) :: Int -> String
>>>
let strHandler = (\str -> str) :: String -> String
>>>
let dblHandler = (\dbl -> "got a double") :: Double -> String
>>>
catchesOpenUnion (intHandler, strHandler, dblHandler) u :: String
"hello"
Here is an example of handling an OpenUnion
with only one possible value.
Notice how a tuple is not used, just a single value:
>>>
let u = openUnionLift (2.2 :: Double) :: OpenUnion '[Double]
>>>
let dblHandler = (\dbl -> "got a double") :: Double -> String
>>>
catchesOpenUnion dblHandler u :: String
"got a double"
relaxOpenUnion :: Contains as bs => OpenUnion as -> OpenUnion bs Source #
Just like relaxUnion
but for OpenUnion
.
>>>
let u = openUnionLift (3.5 :: Double) :: Union Identity '[Double, String]
>>>
relaxOpenUnion u :: Union Identity '[Char, Double, Int, String, Float]
Identity 3.5
openUnionRemove :: forall a as. ElemRemove a as => OpenUnion as -> Either (OpenUnion (Remove a as)) a Source #
This function allows you to try to remove individual types from an
OpenUnion
.
This can be used to handle only certain types in an OpenUnion
, instead of
having to handle all of them at the same time. This can be more convenient
than a function like catchesOpenUnion
.
Examples
Handling a type in an OpenUnion
:
>>>
let u = openUnionLift ("hello" :: String) :: OpenUnion '[String, Double]
>>>
openUnionRemove u :: Either (OpenUnion '[Double]) String
Right "hello"
Failing to handle a type in an OpenUnion
:
>>>
let u = openUnionLift (3.5 :: Double) :: OpenUnion '[String, Double]
>>>
openUnionRemove u :: Either (OpenUnion '[Double]) String
Left (Identity 3.5)
Note that if you have an OpenUnion
with multiple of the same type, they will
all be handled at the same time:
>>>
let u = That (This (Identity 3.5)) :: OpenUnion '[String, Double, Char, Double]
>>>
openUnionRemove u :: Either (OpenUnion '[String, Char]) Double
Right 3.5
openUnionHandle :: ElemRemove a as => (OpenUnion (Remove a as) -> b) -> (a -> b) -> OpenUnion as -> b Source #
Handle a single case in an OpenUnion
. This is similar to openUnion
but lets you handle any case within the OpenUnion
, not just the first one.
Examples
Handling the first item in an OpenUnion
:
>>>
let u = This 3.5 :: OpenUnion '[Double, Int]
>>>
let printDouble = print :: Double -> IO ()
>>>
let printUnion = print :: OpenUnion '[Int] -> IO ()
>>>
openUnionHandle printUnion printDouble u
3.5
Handling a middle item in an OpenUnion
:
>>>
let u2 = openUnionLift (3.5 :: Double) :: OpenUnion '[Char, Double, Int]
>>>
let printUnion = print :: OpenUnion '[Char, Int] -> IO ()
>>>
openUnionHandle printUnion printDouble u2
3.5
Failing to handle an item in an OpenUnion
. In the following example, the
printUnion
function is called:
>>>
let u2 = openUnionLift 'c' :: OpenUnion '[Char, Double, Int]
>>>
let printUnion = print :: OpenUnion '[Char, Int] -> IO ()
>>>
openUnionHandle printUnion printDouble u2
Identity 'c'
If you have duplicates in your OpenUnion
, they will both get handled with
a single call to openUnionHandle
.
>>>
let u3 = That (This 3.5) :: OpenUnion '[Double, Double, Int]
>>>
let printUnion = print :: OpenUnion '[Int] -> IO ()
>>>
openUnionHandle printUnion printDouble u3
3.5
Use absurdOpenUnion
to handle an empty OpenUnion
:
>>>
let u4 = This 3.5 :: OpenUnion '[Double]
>>>
openUnionHandle (absurdUnion :: OpenUnion '[] -> IO ()) printDouble u4
3.5
type IsMember (a :: u) (as :: [u]) = UElem a as (RIndex a as) Source #
This is a helpful Constraint
synonym to assert that a
is a member of
as
. You can see how it is used in functions like openUnionLift
.
type family Contains (as :: [k]) (bs :: [k]) :: Constraint where ... Source #
A type family to assert that all of the types in a list are contained within another list.
>>>
Refl :: Contains '[String] '[String, Char] :~: (IsMember String '[String, Char], (() :: Constraint))
Refl
>>>
Refl :: Contains '[] '[Int, Char] :~: (() :: Constraint)
Refl
Union
(used by OpenUnion
)
OpenUnion
is a type synonym around Union
. Most users will be able to
work directly with OpenUnion
and ignore this Union
type.
data Union (f :: u -> *) (as :: [u]) where Source #
A Union
is parameterized by a universe u
, an interpretation f
and a list of labels as
. The labels of the union are given by
inhabitants of the kind u
; the type of values at any label a ::
u
is given by its interpretation f a :: *
.
What does this mean in practice? It means that a type like
can be _either_ an
Union
Identity
'[String
, Int
]
or an Identity
String
.Identity
Int
You need to pattern match on the This
and That
constructors to figure
out whether you are holding a String
or Int
:
>>>
let u = That (This (Identity 1)) :: Union Identity '[String, Int]
>>>
:{
case u of This (Identity str) -> "we got a string: " ++ str That (This (Identity int)) -> "we got an int: " ++ show int :} "we got an int: 1"
There are multiple functions that let you perform this pattern matching
easier: union
, catchesUnion
, unionMatch
There is also a type synonym OpenUnion
for the common case of
, as well as helper functions for working with it.Union
Indentity
Instances
(Eq (f a2), Eq (Union f as)) => Eq (Union f (a2 ': as)) Source # | |
Eq (Union f ([] :: [u])) Source # | |
(Ord (f a2), Ord (Union f as)) => Ord (Union f (a2 ': as)) Source # | |
Defined in Data.WorldPeace.Union compare :: Union f (a2 ': as) -> Union f (a2 ': as) -> Ordering # (<) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (<=) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (>) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (>=) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # max :: Union f (a2 ': as) -> Union f (a2 ': as) -> Union f (a2 ': as) # min :: Union f (a2 ': as) -> Union f (a2 ': as) -> Union f (a2 ': as) # | |
Ord (Union f ([] :: [u])) Source # | |
(Read (f a2), Read (Union f as)) => Read (Union f (a2 ': as)) Source # | This is only a valid instance when the For instance, imagine we are working with a
However, imagine are we working with a
If the order of the types is flipped around, we are are able to read
|
Read (Union f ([] :: [u])) Source # | This will always fail, since |
(Show (f a2), Show (Union f as)) => Show (Union f (a2 ': as)) Source # | |
Show (Union f ([] :: [u])) Source # | |
(ToJSON (f a2), ToJSON (Union f as)) => ToJSON (Union f (a2 ': as)) Source # | |
Defined in Data.WorldPeace.Union | |
ToJSON (Union f ([] :: [u])) Source # | |
Defined in Data.WorldPeace.Union | |
(FromJSON (f a2), FromJSON (Union f as)) => FromJSON (Union f (a2 ': as)) Source # | This is only a valid instance when the This is similar to the |
FromJSON (Union f ([] :: [u])) Source # | This will always fail, since |
(NFData (f a2), NFData (Union f as)) => NFData (Union f (a2 ': as)) Source # | |
Defined in Data.WorldPeace.Union | |
NFData (Union f ([] :: [u])) Source # | |
Defined in Data.WorldPeace.Union |
Union helpers
union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c Source #
Case analysis for Union
.
See unionHandle
for a more flexible version of this.
Examples
Here is an example of matching on a This
:
>>>
let u = This (Identity "hello") :: Union Identity '[String, Int]
>>>
let runIdent = runIdentity :: Identity String -> String
>>>
union (const "not a String") runIdent u
"hello"
Here is an example of matching on a That
:
>>>
let v = That (This (Identity 3.5)) :: Union Identity '[String, Double, Int]
>>>
union (const "not a String") runIdent v
"not a String"
absurdUnion :: Union f '[] -> a Source #
Since a union with an empty list of labels is uninhabited, we can recover any type from it.
catchesUnion :: (Applicative f, ToProduct tuple f (ReturnX x as)) => tuple -> Union f as -> f x Source #
An alternate case anaylsis for a Union
. This method uses a tuple
containing handlers for each potential value of the Union
. This is
somewhat similar to the catches
function.
Examples
Here is an example of handling a Union
with two possible values. Notice
that a normal tuple is used:
>>>
let u = This $ Identity 3 :: Union Identity '[Int, String]
>>>
let intHandler = (Identity $ \int -> show int) :: Identity (Int -> String)
>>>
let strHandler = (Identity $ \str -> str) :: Identity (String -> String)
>>>
catchesUnion (intHandler, strHandler) u :: Identity String
Identity "3"
Given a Union
like
, the type of
Union
Identity
'[Int
, String
]catchesUnion
becomes the following:
catchesUnion
:: (Identity
(Int
->String
),Identity
(String
->String
)) ->Union
Identity
'[Int
,String
] ->Identity
String
Checkout catchesOpenUnion
for more examples.
relaxUnion :: Contains as bs => Union f as -> Union f bs Source #
Relaxes a Union
to a larger set of types.
Note that the result types have to completely contain the input types.
>>>
let u = This (Identity 3.5) :: Union Identity '[Double, String]
>>>
relaxUnion u :: Union Identity '[Char, Double, Int, String, Float]
Identity 3.5
The original types can be in a different order in the result Union
:
>>>
let u = That (This (Identity 3.5)) :: Union Identity '[String, Double]
>>>
relaxUnion u :: Union Identity '[Char, Double, Int, String, Float]
Identity 3.5
unionRemove :: forall a as f. ElemRemove a as => Union f as -> Either (Union f (Remove a as)) (f a) Source #
This function allows you to try to remove individual types from a Union
.
This can be used to handle only certain types in a Union
, instead of
having to handle all of them at the same time.
Examples
Handling a type in a Union
:
>>>
let u = This (Identity "hello") :: Union Identity '[String, Double]
>>>
unionRemove u :: Either (Union Identity '[Double]) (Identity String)
Right (Identity "hello")
Failing to handle a type in a Union
:
>>>
let u = That (This (Identity 3.5)) :: Union Identity '[String, Double]
>>>
unionRemove u :: Either (Union Identity '[Double]) (Identity String)
Left (Identity 3.5)
Note that if you have a Union
with multiple of the same type, they will
all be handled at the same time:
>>>
let u = That (This (Identity 3.5)) :: Union Identity '[String, Double, Char, Double]
>>>
unionRemove u :: Either (Union Identity '[String, Char]) (Identity Double)
Right (Identity 3.5)
unionHandle :: ElemRemove a as => (Union f (Remove a as) -> b) -> (f a -> b) -> Union f as -> b Source #
Handle a single case on a Union
. This is similar to union
but lets
you handle any case within the Union
.
Examples
Handling the first item in a Union
.
>>>
let u = This 3.5 :: Union Identity '[Double, Int]
>>>
let printDouble = print :: Identity Double -> IO ()
>>>
let printUnion = print :: Union Identity '[Int] -> IO ()
>>>
unionHandle printUnion printDouble u
Identity 3.5
Handling a middle item in a Union
.
>>>
let u2 = That (This 3.5) :: Union Identity '[Char, Double, Int]
>>>
let printUnion = print :: Union Identity '[Char, Int] -> IO ()
>>>
unionHandle printUnion printDouble u2
Identity 3.5
If you have duplicates in your Union
, they will both get handled with
a single call to unionHandle
.
>>>
let u3 = That (This 3.5) :: Union Identity '[Double, Double, Int]
>>>
let printUnion = print :: Union Identity '[Int] -> IO ()
>>>
unionHandle printUnion printDouble u3
Identity 3.5
Use absurdUnion
to handle an empty Union
.
>>>
let u4 = This 3.5 :: Union Identity '[Double]
>>>
unionHandle (absurdUnion :: Union Identity '[] -> IO ()) printDouble u4
Identity 3.5
Union optics
_This :: Prism (Union f (a ': as)) (Union f (b ': as)) (f a) (f b) Source #
Lens-compatible Prism
for This
.
Examples
Use _This
to construct a Union
:
>>>
review _This (Just "hello") :: Union Maybe '[String]
Just "hello"
Use _This
to try to destruct a Union
into a f a
:
>>>
let u = This (Identity "hello") :: Union Identity '[String, Int]
>>>
preview _This u :: Maybe (Identity String)
Just (Identity "hello")
Use _This
to try to destruct a Union
into a f a
(unsuccessfully):
>>>
let v = That (This (Identity 3.5)) :: Union Identity '[String, Double, Int]
>>>
preview _This v :: Maybe (Identity String)
Nothing
_That :: Prism (Union f (a ': as)) (Union f (a ': bs)) (Union f as) (Union f bs) Source #
Lens-compatible Prism
for That
.
Examples
Use _That
to construct a Union
:
>>>
let u = This (Just "hello") :: Union Maybe '[String]
>>>
review _That u :: Union Maybe '[Double, String]
Just "hello"
Use _That
to try to peel off a That
from a Union
:
>>>
let v = That (This (Identity "hello")) :: Union Identity '[Int, String]
>>>
preview _That v :: Maybe (Union Identity '[String])
Just (Identity "hello")
Use _That
to try to peel off a That
from a Union
(unsuccessfully):
>>>
let w = This (Identity 3.5) :: Union Identity '[Double, String]
>>>
preview _That w :: Maybe (Union Identity '[String])
Nothing
Typeclasses used with Union
type ElemRemove a as = ElemRemove' a as (RemoveCase a as) Source #
This type alias is a Constraint
that is used when working with
functions like unionRemove
or unionHandle
.
ElemRemove
gives you a way to specific types from a Union
.
Note that
doesn't force ElemRemove
a asa
to be in as
. We are able
to try to pull out a Double
from a
:Union
Identity
'[Double
]
>>>
let u = This (Identity 3.5) :: Union Identity '[Double]
>>>
unionRemove u :: Either (Union Identity '[Double]) (Identity String)
Left (Identity 3.5)
When writing your own functions using unionRemove
, in order to make sure
the a
is in as
, you should combine ElemRemove
with IsMember
.
ElemRemove
uses some tricks to work correctly, so the underlying 'ElemRemove\''typeclass
is not exported.
type family Remove (a :: k) (as :: [k]) :: [k] where ... Source #
This type family removes a type from a type-level list.
This is used to compute the type of the returned Union
in unionRemove
.
Examples
>>>
Refl :: Remove Double '[Double, String] :~: '[String]
Refl
If the list contains multiple of the type, then they are all removed.
>>>
Refl :: Remove Double '[Char, Double, String, Double] :~: '[Char, String]
Refl
If the list is empty, then nothing is removed.
>>>
Refl :: Remove Double '[] :~: '[]
Refl
A mere approximation of the natural numbers. And their image as lifted by
-XDataKinds
corresponds to the actual natural numbers.
type family RIndex (r :: k) (rs :: [k]) :: Nat where ... Source #
A partial relation that gives the index of a value in a list.
Examples
Find the first item:
>>>
Refl :: RIndex String '[String, Int] :~: 'Z
Refl
Find the third item:
>>>
Refl :: RIndex Char '[String, Int, Char] :~: 'S ('S 'Z)
Refl
class i ~ RIndex a as => UElem (a :: k) (as :: [k]) (i :: Nat) where Source #
provides a way to potentially get an UElem
a as if a
out of a
(Union
f asunionMatch
). It also provides a way to create a
from an Union
f asf a
(unionLift
).
This is safe because of the RIndex
contraint. This RIndex
constraint
tells us that there actually is an a
in as
at index i
.
As an end-user, you should never need to implement an additional instance of this typeclass.
unionPrism :: Prism' (Union f as) (f a) Source #
This is implemented as
.prism'
unionLift
unionMatch
unionLift :: f a -> Union f as Source #
This is implemented as
.review
unionPrism
unionMatch :: Union f as -> Maybe (f a) Source #
This is implemented as
.preview
unionPrism
OpenProduct
This OpenProduct
type is used to easily create a case-analysis for
Union
s. You can see it being used in catchesOpenUnion
and
The ToProduct
type class makes it easy to convert a
tuple to a Product
. This class is used so that the end user only has to worry
about working with tuples, and can mostly ignore this Product
type.
type OpenProduct = Product Identity Source #
data Product (f :: u -> *) (as :: [u]) where Source #
An extensible product type. This is similar to
Union
, except a product type
instead of a sum type.
class ToOpenProduct (tuple :: *) (as :: [*]) | as -> tuple Source #
ToOpenProduct
gives us a way to convert a tuple to an OpenProduct
.
See tupleToOpenProduct
.
Instances
ToOpenProduct a (a ': ([] :: [Type])) Source # | Convert a single value into an |
Defined in Data.WorldPeace.Product toOpenProduct :: a -> OpenProduct (a ': []) Source # | |
ToOpenProduct (a, b) (a ': (b ': ([] :: [Type]))) Source # | Convert a tuple into an |
Defined in Data.WorldPeace.Product toOpenProduct :: (a, b) -> OpenProduct (a ': (b ': [])) Source # | |
ToOpenProduct (a, b, c) (a ': (b ': (c ': ([] :: [Type])))) Source # | Convert a 3-tuple into an |
Defined in Data.WorldPeace.Product toOpenProduct :: (a, b, c) -> OpenProduct (a ': (b ': (c ': []))) Source # | |
ToOpenProduct (a, b, c, d) (a ': (b ': (c ': (d ': ([] :: [Type]))))) Source # | Convert a 4-tuple into an |
Defined in Data.WorldPeace.Product toOpenProduct :: (a, b, c, d) -> OpenProduct (a ': (b ': (c ': (d ': [])))) Source # |
tupleToOpenProduct :: ToOpenProduct t as => t -> OpenProduct as Source #
Turn a tuple into an OpenProduct
.
Examples
Turn a triple into an OpenProduct
:
>>>
tupleToOpenProduct (1, 2.0, "hello") :: OpenProduct '[Int, Double, String]
Cons (Identity 1) (Cons (Identity 2.0) (Cons (Identity "hello") Nil))
Turn a single value into an OpenProduct
:
>>>
tupleToOpenProduct 'c' :: OpenProduct '[Char]
Cons (Identity 'c') Nil
class ToProduct (tuple :: *) (f :: u -> *) (as :: [u]) | f as -> tuple Source #
This type class provides a way to turn a tuple into a Product
.
Instances
ToProduct (f a) (f :: u -> Type) (a ': ([] :: [u]) :: [u]) Source # | Convert a single value into a |
Defined in Data.WorldPeace.Product | |
ToProduct (f a, f b) (f :: u -> Type) (a ': (b ': ([] :: [u])) :: [u]) Source # | Convert a tuple into a |
Defined in Data.WorldPeace.Product | |
ToProduct (f a, f b, f c) (f :: u -> Type) (a ': (b ': (c ': ([] :: [u]))) :: [u]) Source # | Convert a 3-tuple into a |
Defined in Data.WorldPeace.Product | |
ToProduct (f a, f b, f c, f d) (f :: u -> Type) (a ': (b ': (c ': (d ': ([] :: [u])))) :: [u]) Source # | Convert a 4-tuple into a |
Defined in Data.WorldPeace.Product |
tupleToProduct :: ToProduct t f as => t -> Product f as Source #
Turn a tuple into a Product
.
>>>
tupleToProduct (Identity 1, Identity 2.0) :: Product Identity '[Int, Double]
Cons (Identity 1) (Cons (Identity 2.0) Nil)