nooby question on typing

Hi, I have a question about types in Haskell. I feel that I am overlooking some obvious solution, but I do not manage to get it right. Here is the plot: I have got 4 different types of 'rules', each with it's own constructor. So i defined:
type Rules = [Rule] data Rule = RuRule | SgRule | GcRule | FrRule deriving (Eq,Show) data RuRule = Ru { rrsrt :: Char , rrant :: Expression , rrfps :: FilePos } deriving (Eq,Show) data SgRule = Sg { srfps :: FilePos , srsig :: Rule , srxpl :: String , srtyp :: (Concept,Concept) } deriving (Eq,Show) data GcRule = Gc { grfps :: FilePos , grspe :: Morphism , grgen :: Expression } deriving (Eq,Show) data FrRule = Fr { fraut :: AutType , frdec :: Declaration , frcmp :: Expression , frpat :: String } deriving (Eq,Show)
Now I would like to be able to use these rules without knowing what kind they are, in lists, however i get errors like Couldn't match expected type `Rule' against inferred type `SgRule'. Is there any other (even trivial?) way to get this done? I know Haskell well enough to know that it is possible, but I don not know Haskell well enough to know how to do it :teeth: Any help is kindly appreciated! Han Joosten -- View this message in context: http://www.nabble.com/nooby-question-on-typing-tp19470727p19470727.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Sat, Sep 13, 2008 at 2:49 PM, Han Joosten
Hi,
I have a question about types in Haskell. I feel that I am overlooking some obvious solution, but I do not manage to get it right. Here is the plot:
I have got 4 different types of 'rules', each with it's own constructor. So i defined:
type Rules = [Rule] data Rule = RuRule | SgRule | GcRule | FrRule deriving (Eq,Show)
This effectively creates an enum type. I.e. each case here doesn't contain any data other than the "tag". I think you're getting confused because the constructor is named the same as the type you're expecting to store. Try something like:
type Rules = [Rule] data Rule = RuRule | MkSgRule SgRule | MkGcRule GcRule | MkFrRule FrRule deriving (Eq,Show)
So MkSgRule is a "tag" or a "label" deciding which version of Rule you're building, and it also has a value of type SgRule. Now you can create a list or Rule like so:
mylist :: [Rule] mylist = [ MkSgRule mysgrule, MkGcRule mygcrule ]
where mysgrule :: SgRule and mygcrule :: GcRule. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Saturday September 13 2008, Han Joosten wrote:
data Rule = RuRule | SgRule | GcRule | FrRule deriving (Eq,Show)
Here, Rule is a type constructor, whereas RuRule and others are data constructors. Just like:
data Bool = False | True
The type of RuRule is Rule and is not related to the RuRule type you are defining afterwards. What you want to do is probably this:
type Rules = [Rule] data Rule = Ru RuRule | Sg SgRule | Gc GcRule | Fr FrRule deriving (Eq,Show)
data RuRule = RuRule { rrsrt :: Char , rrant :: Expression , rrfps :: FilePos } deriving (Eq,Show)
data SgRule = SgRule { srfps :: FilePos , srsig :: Rule , srxpl :: String , srtyp :: (Concept,Concept) } deriving (Eq,Show)
... You can now form a Rules list and use pattern matching on its members. -- Gokhan

So it sounds like what you want to do is this: rulesList = [ Ru 'a' someExpr someFilePos , Sg someFilePos (Gc someOtherFilePos someMorphism someExpr) "hello" (a,b) ] (This won't compile because Ru and Sg construct different types.) You have a few options to do this: 1) Move the constructors into the "Rule" type. This means you don't get functions that only apply to "RuRule", or any of the other types without them being partial and subject to runtime error, so this may not be safe enough for you. But it is the simplest answer.
data Rule = Ru { rrst :: Char, other stuff... } | Sg { ... } | ...
2) Smart constructors!
data Rule = MkRu RuRule | MkSg SgRule | ... ru a b c = MkRu (Ru a b c) ...
Now just use the lowercase "ru" instead of "Ru" to construct a "Rule" (instead of the specific rule type). rulesList = [ ru 'a' someExpr someFilePos , sg someFilePos (Gc someOtherFilePos someMorphism someExpr) "hello" (a,b) ] This will work! You will still need the "MkRu (Ru a b c)" if you pattern match on Rule, though. 3) dynamic typing and/or existential types, with smart constructors
{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable, PatternGuards #-} import Data.Typeable
data RuRule = Ru { ... } deriving (Eq, Show, Typeable) ...
class Typeable a => IsRule a instance IsRule RuRule instance IsRule GcRule ...
data Rule = forall a. IsRule a => Rule a
ru a b c = Rule (Ru a b c)
unRu :: Rule -> Maybe RuRule unRu (Rule x) = cast x ...
-- example of pattern matching using pattern guards as "views" test :: Rule -> Bool test x | Just (Ru _ _ _) <- unRu x = True | Just (Sg _ x2 _ _) <- unSg x, Just (Ru a _ _) <- unRu x2 = a == 'h' | otherwise = False
Hopefully one of these will suit your needs!
-- ryan
On Sat, Sep 13, 2008 at 6:49 AM, Han Joosten
Hi,
I have a question about types in Haskell. I feel that I am overlooking some obvious solution, but I do not manage to get it right. Here is the plot:
I have got 4 different types of 'rules', each with it's own constructor. So i defined:
type Rules = [Rule] data Rule = RuRule | SgRule | GcRule | FrRule deriving (Eq,Show) data RuRule = Ru { rrsrt :: Char , rrant :: Expression , rrfps :: FilePos } deriving (Eq,Show) data SgRule = Sg { srfps :: FilePos , srsig :: Rule , srxpl :: String , srtyp :: (Concept,Concept) } deriving (Eq,Show) data GcRule = Gc { grfps :: FilePos , grspe :: Morphism , grgen :: Expression } deriving (Eq,Show) data FrRule = Fr { fraut :: AutType , frdec :: Declaration , frcmp :: Expression , frpat :: String } deriving (Eq,Show)
Now I would like to be able to use these rules without knowing what kind they are, in lists, however i get errors like Couldn't match expected type `Rule' against inferred type `SgRule'. Is there any other (even trivial?) way to get this done? I know Haskell well enough to know that it is possible, but I don not know Haskell well enough to know how to do it :teeth:
Any help is kindly appreciated!
Han Joosten -- View this message in context: http://www.nabble.com/nooby-question-on-typing-tp19470727p19470727.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Gökhan San
-
Han Joosten
-
Ryan Ingram
-
Sebastian Sylvan