You can use close type families to do the trick. Here's an example:

    {-# LANGUAGE ScopedTypeVariables, Rank2Types, DataKinds, TypeFamilies, PolyKinds, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-}
    import Data.Proxy

    class ToEither a b k where
        type TheType a b k :: *
        toEither :: proxy k -> TheType a b k -> Either a b

    instance ToEither a b "Left" where
        type TheType a b "Left" = a
        toEither _ = Left

    instance ToEither a b "Right" where
        type TheType a b "Right" = b
        toEither _ = Right

    type family Select a b r where
        Select a a r = "ambiguous"
        Select a b a = "Left"
        Select a b b = "Right"
        Select x y z = "unknown"

    fun :: forall a b r. (ToEither a b (Select a b r), r ~ TheType a b (Select a b r)) => r -> Either a b
    fun = toEither (Proxy :: Proxy (Select a b r))

Note that fun doesn't work well without explicit type signatures.

2016-03-03 7:04 GMT-08:00 Kristoffer Føllesdal <kfollesdal@gmail.com>:
I want a function fun :: q -> Either a b where q is of type a or b.  fun shall work in the following way

fun x    gives    Left x     if x :: a
fun x    gives    Right x   if x :: b

Following is a more precise description of what I want. I have function fun1 and fun2

newtype Vec k b = V [(b,k)] deriving (Eq,Ord,Show)

fun1 :: (Num k) => a -> Either a (Vec k a)
fun1 = Left

fun2 :: (Num k) => Vec k a -> Either a (Vec k a)
fun2 = Right

that work in the following way

{-
>>> fun1 6
Left 6

>>> fun2 (V[(6,1)])
Right (V [(6,1)])
-}

I want a overloaded function ‘fun' such that

{-
>>> fun 6
Left 6

>>> fun (V[(6,1)])
Right (V[(6,1)])
-}

I have tried to use a type class to do this (see code below). But when I try
>>> fun 6

I get the following error

 Could not deduce (Num a0)
    from the context (Num a, Fun a b v)
      bound by the inferred type for ‘it’:
                 (Num a, Fun a b v) => Either b (v b)
      at <interactive>:70:1-5
    The type variable ‘a0’ is ambiguous
    When checking that ‘it’ has the inferred type
      it :: forall a b (v :: * -> *).
            (Num a, Fun a b v) =>
            Either b (v b)
    Probable cause: the inferred type is ambiguous

Is the someone that have know how I can solve this?

Kristoffer

——— CODE ———

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}

newtype Vec k b = V [(b,k)] deriving (Eq,Ord,Show)

fun1 :: (Num k) => a -> Either a (Vec k a)
fun1 = Left

fun2 :: (Num k) => Vec k a -> Either a (Vec k a)
fun2 = Right

class Fun a b v  where
  fun :: a -> Either b (v b)

instance (Num k) => Fun t t (Vec k) where
  fun = fun1

instance (Num k) => Fun (Vec k t) t (Vec k) where
  fun = fun2


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe