[Haskell-cafe] Associated Types and several Classes

Martin Hofmann martin.hofmann at uni-bamberg.de
Mon Oct 13 11:25:15 EDT 2008


> {-# 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
   



More information about the Haskell-Cafe mailing list