On Mon, Feb 26, 2007 at 01:22:57PM -0600, Thomas Nelson wrote:
> I'm brand new to haskell and I'm having trouble using classes.  The basic 
> idea is I want two classes, Sine and MetaSine, that are both instances of 
> ISine. This way I can use the act method and recurse through the metasines 
> and sines. Here's my code:
> 
> module Main
>     where
> 
> class ISine a where
>     period :: a -> Integer
>     offset :: a -> Integer
>     threshold :: a -> Integer
>     act :: (ISine b) => Integer -> a -> b
>     on :: Integer -> a -> Bool
>     --on needs offset, period, threshold
>     on time self = (mod (time-(offset self)) (period self)) < (threshold 
>     self)
> 
> data Sine =
>     Sine {
>         period :: Integer,
>         offset :: Integer,
>         threshold :: Integer,
>         letter :: String
>         }
> 
> instance Sine ISine where
 The other way round: instance class type where

Your errors have nothing to do with classes. Just try

        module Main where
        data MetaSine = MetaSine {period :: Integer }
        data Sine = Sine { period :: Integer }
        main = print "test"
which won't compile and show the same error

Solution? 
1) single module solution:

        a) using records: Use prefixes
        data MetaSine = MetaSine {msPeriod :: Integer }
        data Sine = Sine { sPeriod :: Integer }

        b) using the same accessor function "period" requires classes
           I think this is what you had in mind when introducing ISine
           Of course you can add this to a), too.

        data MetaSine = MetaSine Integer
        data Sine = Sine sPeriod

        class Period where
                period :: Integer
        instance Period Sine where period (Sine p) = p
        instance Period MetaSine where period (MetaSine p) = p

2) use for each datatype another module. Then you can define record name
period more than once. But you have to access them using
ModuleSine.period or ModuleMetaSine.period which is not what you want I
think.

HTH Marc
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to