[Haskell-cafe] open-union

Ben Foppa benjamin.foppa at gmail.com
Sat Jun 7 19:47:32 UTC 2014


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 at gmail.com
> wrote:

> There's also compdata
>
>
> On Saturday, June 7, 2014, Ben Foppa <benjamin.foppa at 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?
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140607/c80c2c53/attachment.html>


More information about the Haskell-Cafe mailing list