Choose Int y = 'ChooseFirstYes, 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.Proxyclass Closed a b wherefun :: a -> b -> Int-- Names for the instancesdata InstanceChoice = ChooseFirst | ChooseSecond | IgnoreBoth-- Determine which instance should be usedtype family Choose a b whereChoose x Int = 'ChooseSecondChoose x y = 'IgnoreBoth-- Auxiliary class with instance-choice parameterclass Closed' (choice :: InstanceChoice) a b where
fun' :: proxy choice -> a -> b -> Int-- The actual instancesinstance Closed' 'ChooseFirst Int y where fun' _ x _ = xinstance Closed' 'ChooseSecond x Int where fun' _ _ y = yinstance 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'
0On Wed, Feb 17, 2016 at 7:21 PM, Imants Cekusins <imantc@gmail.com> wrote:_______________________________________________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