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
    act time (Sine self)
        |on time self = [letter self]
        |otherwise = []


data MetaSine =
    MetaSine {
        period :: Integer,
        offset :: Integer,
        threshold :: Integer,
        sines :: (ISine a) => [a]
        }

instance MetaSine ISine where
    act time (MetaSine self)
        |on time self  = foldr (++) (map (act time) (sines self))
        |otherwise = []

The errors I get involve multiple declarations of period, offset, and threshold.

Any help would be greatly appreciated.
-Thomas

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

Reply via email to