
Yes, closed type families *can* be used to achieve the same result even now, but it tends to be fairly verbose. There are a number of minor variations in how it can be done, but here's one example: {-# LANGUAGE TypeFamilies, DataKinds, MultiParamTypeClasses, FlexibleInstances, FlexibleInstances, ScopedTypeVariables, UndecidableInstances #-} import Data.Proxy class Closed a b where fun :: a -> b -> Int -- Names for the instances data InstanceChoice = ChooseFirst | ChooseSecond | IgnoreBoth -- Determine which instance should be used type family Choose a b where Choose Int y = 'ChooseFirst Choose x Int = 'ChooseSecond Choose x y = 'IgnoreBoth -- Auxiliary class with instance-choice parameter class Closed' (choice :: InstanceChoice) a b where fun' :: proxy choice -> a -> b -> Int -- The actual instances instance Closed' 'ChooseFirst Int y where fun' _ x _ = x instance Closed' 'ChooseSecond x Int where fun' _ _ y = y instance Closed' 'IgnoreBoth x y where fun' _ _ _ = 0 -- Note that ScopedTypeVariables is necessary to make this typecheck. instance (choice ~ Choose a b, Closed' choice a b) => Closed a b where fun = fun' (Proxy :: Proxy choice) Then
fun (3 :: Int) 'a' 3 fun 'a' (4 :: Int) 4 fun 'a' 'b' 0
On Wed, Feb 17, 2016 at 7:21 PM, Imants Cekusins
This would be very useful indeed.
Can closed type families not be used to achieve the same result even now, already?
I tried to use type families recently to explicitly pick an (otherwise overlapping) instance in specified order but could not figure out, how.
If someone could give a complete simple example of primary intended use of closed type families with class instances, this would help a lot.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe