
I was thinking about ~two notions of "closed class" yesterday, and I'm curious if anyone's done any work on either concept. In each case, the class definition is followed by *all* of its instances, and the instances are checked *in order* (rather than based on specificity and OVERLAPS/OVERLAPPABLE pragmas). No backtracking: If the instance head matches, GHC commits to it. Associated types are treated as closed type families, and would work just the same (I don't think any significant extension to the closed type family mechanism would be required). This seems to make a very nice parallel to the usual open classes with open associated types. And it lets you combine overlapping instances with associated types without (I believe) risking type safety. Backtracking: GHC does not commit to the instance until it has satisfied the instance constraints. This lets instance writers offer multiple alternative instance constraints. Associated types would be a good bit trickier. One option would be to require all instances with the same head to share a type/data instance. The other (much more invasive) option would be to allow the instance chosen to guide the type selection, which would push the backtracking into the type checker.

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.

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

For the sake of completeness, I'd love to be able to write this, instead, as
{-# LANGUAGE ClosedClasses #-}
-- The "closed" keyword indicates that
-- only instances in this module will be
-- permitted.
closed class Closed a b where
fun :: a -> b -> Int
-- Necessarily in the same module, and in
-- this order. Ideally, other definitions would
-- be allowed to appear between them.
-- The "closed" keyword is a reminder of
-- order-dependence.
closed instance Closed Int y where fun x _ = x
closed instance Closed x Int where fun _ y = y
closed instance Closed x y where fun _ _ = 0
On Wed, Feb 17, 2016 at 10:44 PM, David Feuer
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
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

Hi. For consistency reasons, I'd love to write the following, possibly even omiting the closed keyword.
{-# LANGUAGE ClosedClasses #-} closed class Closed a b where fun :: a -> b -> Int instance Closed Int y where fun x _ = x instance Closed x Int where fun _ y = y instance Closed x y where fun _ _ = 0
I guess, that's already bikeshedding. Cheers, Tobias Florek

That is more consistent, but it leaves no room to intersperse auxiliary
definitions, which strikes me as unfortunate for practical reasons.
On Feb 18, 2016 5:43 AM, "Tobias Florek"
Hi.
For consistency reasons, I'd love to write the following, possibly even omiting the closed keyword.
{-# LANGUAGE ClosedClasses #-} closed class Closed a b where fun :: a -> b -> Int instance Closed Int y where fun x _ = x instance Closed x Int where fun _ y = y instance Closed x y where fun _ _ = 0
I guess, that's already bikeshedding.
Cheers, Tobias Florek _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The work on instance chains[1] seems related, but I'm not very familiar with it, so it might just be superficial. [1]: http://web.cecs.pdx.edu/~mpj/pubs/instancechains.pdf On Wed, Feb 17, 2016, at 14:21, David Feuer wrote:
I was thinking about ~two notions of "closed class" yesterday, and I'm curious if anyone's done any work on either concept. In each case, the class definition is followed by *all* of its instances, and the instances are checked *in order* (rather than based on specificity and OVERLAPS/OVERLAPPABLE pragmas).
No backtracking:
If the instance head matches, GHC commits to it. Associated types are treated as closed type families, and would work just the same (I don't think any significant extension to the closed type family mechanism would be required). This seems to make a very nice parallel to the usual open classes with open associated types. And it lets you combine overlapping instances with associated types without (I believe) risking type safety.
Backtracking:
GHC does not commit to the instance until it has satisfied the instance constraints. This lets instance writers offer multiple alternative instance constraints. Associated types would be a good bit trickier. One option would be to require all instances with the same head to share a type/data instance. The other (much more invasive) option would be to allow the instance chosen to guide the type selection, which would push the backtracking into the type checker. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

It seems *highly* related, and, to my untrained eye, very carefully
considered indeed. Unfortunately, based on the fact that its website has
not updated since 2010, it appears that the entire HASP project has died a
quiet death.
One thing that's not clear to me is whether the instance chain approach
(including explicit failure and backtracking) can interact well with
associated types. My understanding is that backtracking in instance
resolution cannot be allowed to infect unification, on pain of impossibly
bad performance. Thus I imagine there would have to be some restrictions on
the use of associated types in instance and/or class contexts; I don't know
if it would be possible to make that work out cleanly and flexibly.
On Thu, Feb 18, 2016 at 12:34 AM, Eric Seidel
The work on instance chains[1] seems related, but I'm not very familiar with it, so it might just be superficial.
[1]: http://web.cecs.pdx.edu/~mpj/pubs/instancechains.pdf
On Wed, Feb 17, 2016, at 14:21, David Feuer wrote:
I was thinking about ~two notions of "closed class" yesterday, and I'm curious if anyone's done any work on either concept. In each case, the class definition is followed by *all* of its instances, and the instances are checked *in order* (rather than based on specificity and OVERLAPS/OVERLAPPABLE pragmas).
No backtracking:
If the instance head matches, GHC commits to it. Associated types are treated as closed type families, and would work just the same (I don't think any significant extension to the closed type family mechanism would be required). This seems to make a very nice parallel to the usual open classes with open associated types. And it lets you combine overlapping instances with associated types without (I believe) risking type safety.
Backtracking:
GHC does not commit to the instance until it has satisfied the instance constraints. This lets instance writers offer multiple alternative instance constraints. Associated types would be a good bit trickier. One option would be to require all instances with the same head to share a type/data instance. The other (much more invasive) option would be to allow the instance chosen to guide the type selection, which would push the backtracking into the type checker. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The backtracking approach would be useful. It would be nice to say:
instance (A t) => C t where ...
instance (B t) => C t where ...
in the case where you can define a C instance if you've already got a B
instance or an A instance. Indeed (aside from efficiency) you don't really
care which one.
Yes, this means if someone else defines and instance of A somewhere else in
the program then suddenly you're silently calling a different instance.
Indeed you could be using different instances in different parts of the
program. But as long as they have the same effect that shouldn't be an
issue. If they have different effects it's likely one is wrong anyway.
For (perhaps a silly) example:
class DrawRhombus drawerT where
drawRhombus :: drawerT -> Sidelength -> Angle -> Shape
class DrawRectangle drawerT where
drawRectangle :: drawerT -> Sidelength -> Sidelength -> Shape
class DrawSquare t where
drawSquare :: drawerT -> Sidelength -> Shape
instance (DrawRhombus drawerT) => DrawSquare drawerT where
drawSquare d l = drawRhombus d l (Angle 0)
instance (DrawRectangle drawerT) => DrawSquare drawerT where
drawSquare d l = drawRectangle d l l
On Thu, Feb 18, 2016 at 9:21 AM, David Feuer
I was thinking about ~two notions of "closed class" yesterday, and I'm curious if anyone's done any work on either concept. In each case, the class definition is followed by *all* of its instances, and the instances are checked *in order* (rather than based on specificity and OVERLAPS/OVERLAPPABLE pragmas).
No backtracking:
If the instance head matches, GHC commits to it. Associated types are treated as closed type families, and would work just the same (I don't think any significant extension to the closed type family mechanism would be required). This seems to make a very nice parallel to the usual open classes with open associated types. And it lets you combine overlapping instances with associated types without (I believe) risking type safety.
Backtracking:
GHC does not commit to the instance until it has satisfied the instance constraints. This lets instance writers offer multiple alternative instance constraints. Associated types would be a good bit trickier. One option would be to require all instances with the same head to share a type/data instance. The other (much more invasive) option would be to allow the instance chosen to guide the type selection, which would push the backtracking into the type checker.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

David, thank you very much for the examples. They are very clear. Would it be difficult to post the first one (working in current setup) on Wiki? either https://wiki.haskell.org/GHC/Type_families or https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/type-familie... ? expanding your and Clinton's suggestions, here is one more version. Not sure if this may work however this may be intuitive to C#, Java users: -- 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 class Closed a b where fun :: a -> b -> Int instance (Choose Int y) => Closed Int y where fun x _ = x instance (Choose x Int) => Closed x Int where fun _ y = y instance (Choose x y) => Closed x y where fun _ _ = 0 the differences: no need to use new keyword "closed" no need for new language pragma non-type family instances may still be defined instances may be defined in other modules (if possible:) multiple type families may be used with the same class. Instance constraint would hint, which (if any) type family to apply in selecting an instance how does this sound?

.. and one more option: -- Enum order specifies the order instances are tried data InstanceChoice = ChooseFirst | ChooseSecond | IgnoreBoth deriving Enum type family Choose a b where Choose Int y = ChooseFirst Choose x Int = ChooseSecond Choose x y = IgnoreBoth class (Choose a b) => Closed a b where fun :: a -> b -> Int instance Closed Int y where fun x _ = x instance Closed x Int where fun _ y = y instance Closed x y where fun _ _ = 0
participants (5)
-
Clinton Mead
-
David Feuer
-
Eric Seidel
-
Imants Cekusins
-
Tobias Florek