
Hi cafe. On a use case whim, I made the open-union package ( https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality: {-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion type MyUnion = Union (Char :| Int :| [()] :| Void) showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()] If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs. Any thoughts? Is there already something like this around?

In some respects, I think both vinyl and hlist are more general. But I
could be wrong.
On Saturday, June 7, 2014, Ben Foppa
Hi cafe. On a use case whim, I made the open-union package ( https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?

There's also compdata
On Saturday, June 7, 2014, Ben Foppa
Hi cafe. On a use case whim, I made the open-union package ( https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?

Thanks, I wasn't aware of vinyl and compdata. I'll check them out.
I'm not very familiar with HList, but I was under the impression that it
provided intersection, not union, i.e. for every type in { x1 x2 ..}, an
HList has an element vs for SOME type in {x1 x2 ..} a Union has an
element..
On Sat, Jun 7, 2014 at 3:18 PM, Carter Schonwald wrote: There's also compdata On Saturday, June 7, 2014, Ben Foppa Hi cafe. On a use case whim, I made the open-union package (
https://github.com/RobotGymnast/open-union), copying the basic idea from
extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on
the chance that there's already something like this around. Here's the
basic functionality: {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.OpenUnion type MyUnion = Union (Char :| Int :| [()] :| Void) showMyUnion :: MyUnion -> String
showMyUnion
= (\(c :: Char) -> "char: " ++ show c)
@> (\(i :: Int) -> "int: " ++ show i)
@> (\(l :: [()]) -> "list length: " ++ show (length l))
@> typesExhausted main :: IO ()
main = do
putStrLn $ showMyUnion $ liftUnion (4 :: Int)
putStrLn $ showMyUnion $ liftUnion 'a'
putStrLn $ showMyUnion $ liftUnion [(), ()] If any of the (@>) cases is omitted, a compile-time error occurs. If you
try to lift a bad value to the union, a compile-time error occurs. Any thoughts? Is there already something like this around?

Id be surprised if there's not a way to encode a union like structure using
hlist.
On Saturday, June 7, 2014, Ben Foppa
Thanks, I wasn't aware of vinyl and compdata. I'll check them out. I'm not very familiar with HList, but I was under the impression that it provided intersection, not union, i.e. for every type in { x1 x2 ..}, an HList has an element vs for SOME type in {x1 x2 ..} a Union has an element..
On Sat, Jun 7, 2014 at 3:18 PM, Carter Schonwald < carter.schonwald@gmail.com javascript:_e(%7B%7D,'cvml','carter.schonwald@gmail.com');> wrote:
There's also compdata
On Saturday, June 7, 2014, Ben Foppa
javascript:_e(%7B%7D,'cvml','benjamin.foppa@gmail.com');> wrote: Hi cafe. On a use case whim, I made the open-union package ( https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?

Hi Ben,
http://hackage.haskell.org/package/HList-0.3.4.1/docs/Data-HList-TIC.html
is very similar, though it uses -XDataKinds for the type-level list
and has fewer operations. For the next release we're changing the
type-indexed collections (TIP, TIC) to share most of the
implementation with Record and Variant respectively.
I believe it's unnecessary to involve Typeable. Since there's a list
of possible types, you can store (Int, Any), where the Int is an index
into that list, instead of using TypeRep for that index.
http://code.haskell.org/~aavogt/HList/Data/HList/Variant.hs has that
implementation. Leaving out Typeable makes a difference as far as what
is allowed, because Records using promoted strings as the labels do
not have a Typeable instance in ghc-7.8.2.
Regards,
Adam
On Sat, Jun 7, 2014 at 3:47 PM, Ben Foppa
Thanks, I wasn't aware of vinyl and compdata. I'll check them out. I'm not very familiar with HList, but I was under the impression that it provided intersection, not union, i.e. for every type in { x1 x2 ..}, an HList has an element vs for SOME type in {x1 x2 ..} a Union has an element..
On Sat, Jun 7, 2014 at 3:18 PM, Carter Schonwald
wrote: There's also compdata
On Saturday, June 7, 2014, Ben Foppa
wrote: Hi cafe. On a use case whim, I made the open-union package (https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Cool, thanks for the info!
On Jun 7, 2014 9:37 PM, "adam vogt"
Hi Ben,
http://hackage.haskell.org/package/HList-0.3.4.1/docs/Data-HList-TIC.html is very similar, though it uses -XDataKinds for the type-level list and has fewer operations. For the next release we're changing the type-indexed collections (TIP, TIC) to share most of the implementation with Record and Variant respectively.
I believe it's unnecessary to involve Typeable. Since there's a list of possible types, you can store (Int, Any), where the Int is an index into that list, instead of using TypeRep for that index. http://code.haskell.org/~aavogt/HList/Data/HList/Variant.hs has that implementation. Leaving out Typeable makes a difference as far as what is allowed, because Records using promoted strings as the labels do not have a Typeable instance in ghc-7.8.2.
Regards, Adam
On Sat, Jun 7, 2014 at 3:47 PM, Ben Foppa
wrote: Thanks, I wasn't aware of vinyl and compdata. I'll check them out. I'm not very familiar with HList, but I was under the impression that it provided intersection, not union, i.e. for every type in { x1 x2 ..}, an HList has an element vs for SOME type in {x1 x2 ..} a Union has an element..
On Sat, Jun 7, 2014 at 3:18 PM, Carter Schonwald
wrote: There's also compdata
On Saturday, June 7, 2014, Ben Foppa
wrote: Hi cafe. On a use case whim, I made the open-union package (https://github.com/RobotGymnast/open-union), copying the basic idea
from
extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Similar functionality is provided by the `Dynamic` type in Syntactic: https://github.com/emilaxelsson/syntactic/blob/master/src/Data/Syntactic/Typ... (This is in the master branch, which is not on Hackage yet.) For a small showcase, see this reply: http://stackoverflow.com/questions/22876370/combining-data-dynamic-and-type-... One advantage of `Dynamic` in Syntactic is that it has a proper `Show` instance, so you don't need to define functions like `showMyUnion`: instance Witness Show ts ts => Show (Dynamic ts) That is, if you can make a `Show` witness for the types in the open union, then you have a `Show` instance for `Dynamic`. I haven't seen any other implementation where this is possible (but would like to know if there is any). It doesn't hurt to have many alternative solutions on Hackage. I'd say upload your package! / Emil 2014-06-07 21:01, Ben Foppa skrev:
Hi cafe. On a use case whim, I made the open-union package ( https://github.com/RobotGymnast/open-union), copying the basic idea from extensible-effects:Data.OpenUnion1. I haven't uploaded to hackage yet, on the chance that there's already something like this around. Here's the basic functionality:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.OpenUnion
type MyUnion = Union (Char :| Int :| [()] :| Void)
showMyUnion :: MyUnion -> String showMyUnion = (\(c :: Char) -> "char: " ++ show c) @> (\(i :: Int) -> "int: " ++ show i) @> (\(l :: [()]) -> "list length: " ++ show (length l)) @> typesExhausted
main :: IO () main = do putStrLn $ showMyUnion $ liftUnion (4 :: Int) putStrLn $ showMyUnion $ liftUnion 'a' putStrLn $ showMyUnion $ liftUnion [(), ()]
If any of the (@>) cases is omitted, a compile-time error occurs. If you try to lift a bad value to the union, a compile-time error occurs.
Any thoughts? Is there already something like this around?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
adam vogt
-
Ben Foppa
-
Carter Schonwald
-
Emil Axelsson