[Haskell-cafe] "data" and classes question
Chaim Friedman
cfriedman at z-combinator.net
Tue Jan 29 11:26:25 EST 2008
Hello,
I had a question about type classes and data types. I want to create one
class that has a function which depends upon a parameter from another
class. I would assume that this can be done, but I can't seem to write
code that does it. Can anybody tell me what is wrong? Here is an example
of what I want to work:
module Main where
class Change c
class State st where
transitions :: (Change c) => st -> [(c, st)]
data BinState = On | Off
data BinChange = OnToOff | OffToOn
-- get a list of (transition, newState) pairs:
--binTransitions :: BinState -> [(BinChange, BinState)] -- doesn't work
--binTransitions :: (State state, Change change) => state ->
-- [(change, state)] -- doesn't work
--binTransitions :: (State state1, State state2, Change change) =>
-- state1 -> [(change, state2)] -- doesn't work
binTransitions On = [(OnToOff, Off)]
binTransitions Off = [(OffToOn, On)]
instance Change BinChange
instance State BinState where
transitions = binTransitions
main = putStrLn "success."
-- Thanks,
-- -Chaim
More information about the Haskell-Cafe
mailing list