[Haskell-cafe] open-union

Emil Axelsson emax at chalmers.se
Mon Jun 9 07:55:53 UTC 2014


Similar functionality is provided by the `Dynamic` type in Syntactic:

 
https://github.com/emilaxelsson/syntactic/blob/master/src/Data/Syntactic/TypeUniverse/TypeUniverse.hs

(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-classes/22989262#22989262

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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list