[Haskell-cafe] Associated Types and several Classes

Ryan Ingram ryani.spam at gmail.com
Mon Oct 13 13:10:16 EDT 2008


First, a comment.  I don't understand why you have so many classes!
What proof invariants are they helping you enforce?  Do you really a
constraint that says that something is a "Rule"?  Are you going to
write functions that are polymorphic over CRule?  How can you do so
when CRule has no methods?

Now, to the explanation.  You're partially running into the
monomorphism restriction here, but that's not the whole story.

If you comment out ahypo, this module compiles.  Then, in ghci:

*Test> :t hypo rules rule1
hypo rules rule1 :: (S.Set Rule ~ CHypoRules h, Rule ~ CHypoRule h, CHypo h) =>
                    h

So the reason you are failing to compile is that "ahypo", as a plain
value, needs to have a monomorphic type, so we need to figure out how
to instantiate "h".  In the absence of other information, the compiler
can't figure out what to select for "h"; I'm free to come by after the
fact and define a new instance for CHypo over another data type that
has CHypoRules = S.Set Rule, and CHypoRule = Rule, and then ahypo
could be either type.

It's possible that the compiler should be extended to "default" in the
case that only one possible type is in scope (although that search
might be tricky!), but right now it just gives up because it can't
choose an "h".

You can turn this off with "-fno-monomorphism-restriction", but I
don't really recommend that.  Instead, here are some suggestions, in
order of "goodness" (from best to worst!)

1) First of all, you don't need to use typeclasses at all, if your
goal is to just hide the implementation and change the underlying
representation.  Instead, just export your data types abstractly:

> module Hypo (
>    Rules,
>    Rule,
>    Hypo,
>    hypo,
>    -- other functions
> ) where

Now nobody can construct values of Hypo except by using the "hypo"
function you provide, and nobody can pattern match on them or use them
except via whatever additional interface you provide.  Similar
constraints apply for Rule and Rules.  Problem solved!

> import qualified Set as S
>
> data Rule = Rule Int
> newtype Rules = HRs { unHRs :: S.Set Rule }
>
> data Hypo = Hypo { open :: S.Set Rule, closed :: S.Set Rule }
>
> hypo :: HypoRules -> HypoRule -> Hypo
> hypo hrs hr = Hypo (unHRs hrs) (S.singleton hr)

A good guideline: if you aren't planning to use overloading, you don't
want a typeclass!

2) If you really want to use typeclasses, you can put a type signature on ahypo:

> ahypo :: Hypo
> ahypo = hypo rules rule1

This compiles; you are telling the compiler what instance to choose for "hypo".

3) Another option is to use data families instead.  Data families are
injective; that is, if you have t ~ CHypoRule r1, and r1 /~ r2, then t
/~ CHypoRule r2.  This means that as soon as you apply hypo to a
single argument, you've "locked in" the correct instance to apply.
Here's an example:

> class CHypo h where
>    data CHypoRules h
>    data CHypoRule h
>    hypo :: CHypoRules h -> CHypoRule h -> h
>
> type Rule = CHypoRule Hypo
>    -- note reference to applied data family here
>    -- we could define Rule as you did and newtype it inside the
>    -- class definition, but that seems way more complicated!
>
> type Rules = S.Set Rule
>    -- here, on the other hand, we don't reference the newtype
>    -- this is so we can use the un-newtyped version inside the
>    -- data structure to make manipulating it easier!
>
> data Hypo = Hypo { open :: Rules, closed :: Rules }
>
> instance CHypo Hypo where
>    data CHypoRule Hypo = Rule Int deriving (Eq, Ord)
>    newtype CHypoRules Hypo = HRules { unHRules :: Rules }
>    hypo o c = Hypo { open = unHRules o, closed = S.singleton c }

Now, your test code works with just one tiny change: we add the
constructor "HRules" to the definition of "rules":

> rule1 = Rule 1
> rule2 = Rule 2
> rule3 = Rule 3
> rules = HRules $ S.fromList [rule1,rule2,rule3]
> ahypo = hypo rules rule1

I really recommend option 1, though.  The simplest solution is best
and you'll be happier when you can stop banging your head over weird
typechecking errors.  You're really giving the compiler more freedom
than you need to!

  -- ryan

On Mon, Oct 13, 2008 at 4:25 PM, Martin Hofmann
<martin.hofmann at uni-bamberg.de> wrote:
>> {-# OPTIONS_GHC -fglasgow-exts #-}
>> module Test where
>>import qualified Data.Set as S
>
> Hi. I try to model the following: Hypotheses are build up from Rules,
> which itself are made of the type Rule. Because I may change the
> implementation later, I want to use type classes, which define the
> signature of my functions I will use in other modules.
>
>>class CRule r
>
>>class (CRule (CRulesRule r) ) => CRules r where
>>    type CRulesRule r
>
>>class (CRule (CHypoRule h), CRules (CHypoRules h) ) => CHypo h where
>>    type CHypoRules h
>>    type CHypoRule h
>>    hypo ::
>>        CHypoRules h ->
>>        CHypoRule h ->
>>        h
>
> -- | Rule
>
>>data Rule = Rule Int deriving(Eq,Ord)
>>instance CRule Rule
>
>
> -- | Rules
>
>>type Rules = S.Set Rule
>>instance CRules (S.Set Rule) where
>>    type CRulesRule (S.Set Rule) = Rule
>
> -- | Hypothese
>
>>data Hypo  = Hypo { open   :: Rules
>>                  , closed :: Rules
>>                  }
>
>
>>instance CHypo Hypo where
>>    type CHypoRules Hypo = Rules
>>    type CHypoRule Hypo = Rule
>
>>    hypo ro rc = Hypo { open=ro, closed=(S.singleton rc)}
>
> So far so good. But why does now the last of the following lines not
> type check?
> It says:
>
>    Couldn't match expected type `CHypoRules h'
>           against inferred type `S.Set Rule'
>
>    Couldn't match expected type `CHypoRule h'
>           against inferred type `Rule'
>
>>rule1 = Rule 1
>>rule2 = Rule 2
>>rule3 = Rule 3
>>rules = S.fromList [rule1,rule2,rule3]
>>ahypo = hypo rules rule1
>
> Shouldn't be (CHypoRules Hypo) be associated with Rules and similar
> (CHypoRule)
> with Rule?
>
> Thanks a lot,
>
> Martin
>
>
> --
> ---------------------------------------------------------------
> Dipl.-Wirtsch.Inf. (E.M.B.Sc.) Martin Hofmann
> Cognitive Systems Group
> Faculty Information Systems and Applied Computer Science
> University of Bamberg
> http://www.cogsys.wiai.uni-bamberg.de/members/hofmann
> http://www.inductive-programming.org
>
>
> _______________________________________________
> 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