问题
I'm stuck trying to select one instance from many at runtime. Really is a kind of Backend
.
I'm able to do it if I select one instance or other at compile time.
UPDATED probably I want some similar to Database.Persist (it define a fully behavior but many instances: mongodb, sqlite, postgresql, ...). But is too complex to me.
UPDATED using GADTs
works but I think exist a better way (full code at the bottom).
In some OOP language my problem is more or less
interface IBehavior { void foo(); }
class AppObject { IBehavior bee; void run(); }
...
var app = new AppObject { bee = makeOneOrOtherBehavior(); }
....
I've tried many ways (and lots of extensions :D) but none works.
Informally I want to define one class
with certain behavior and use this generic definition into some application, after it, select at runtime one instance
from some.
The generic behavior (not real code)
class Behavior k a where
behavior :: k -> IO ()
foo :: k -> a -> Bool
...
(I think k
is needed since each instance
could need their own context/data; other restrictions like key
/value
may be exist)
Two instances
data BehaviorA
instance Behavior BehaviorA where
behavior _ = print "Behavior A!"
data BehaviorB
instance Behavior BehaviorB where
behavior _ = print "Behavior B!"
my application use that behavior (here begin the chaos)
data WithBehavior =
WithBehavior { foo :: String
, bee :: forall b . Behavior b => b
}
run :: WithBehavior -> IO ()
run (WithBehavior {..}) = print foo >> behavior bee
I wish select at runtime
selectedBee x = case x of
"A" -> makeBehaviorA
"B" -> makeBehaviorB
...
withBehavior x = makeWithBehavior (selectedBee x)
but I'm lost into a maze of extensions, type dependencies and others :(
I cannot set the proper type for selectedBee
function.
Any help will be appreciated! :)
(Using GADTs
, but without additional a
type parameters!)
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE GADTs #-}
import System.Environment
import Control.Applicative
class Behavior k where
behavior' :: k -> IO ()
data BehaviorInstance where
BehaviorInstance :: Behavior b => b -> BehaviorInstance
behavior :: BehaviorInstance -> IO ()
behavior (BehaviorInstance b) = behavior' b
data BehaviorA = BehaviorA
instance Behavior BehaviorA where
behavior' _ = print "Behavior A!"
makeBehaviorA :: BehaviorInstance
makeBehaviorA = BehaviorInstance BehaviorA
data BehaviorB = BehaviorB
instance Behavior BehaviorB where
behavior' _ = print "Behavior B!"
makeBehaviorB :: BehaviorInstance
makeBehaviorB = BehaviorInstance BehaviorB
data WithBehavior =
WithBehavior { foo :: String
, bee :: BehaviorInstance
}
run :: WithBehavior -> IO ()
run (WithBehavior {..}) = print foo >> behavior bee
main = do
n <- head <$> getArgs
let be = case n of
"A" -> makeBehaviorA
_ -> makeBehaviorB
run $ WithBehavior "Foo Message!" be
回答1:
Why use a typeclass? Instead, represent the typeclass as a record type, with "instances" being values of that type:
data Behavior k a = Behavior
{ behavior :: IO ()
, foo :: k -> a -> Bool
}
behaviorA :: Behavior String Int
behaviorA = Behavior
{ behavior = putStrLn "Behavior A!"
, foo = \a b -> length a < b
}
behaviorB :: Behavior String Int
behaviorB = Behavior
{ behavior = putStrLn "Behavior B!"
, foo = \a b -> length a > b
}
selectBehavior :: String -> Maybe (Behavior String Int)
selectBehavior "A" = Just behaviorA
selectBehavior "B" = Just behaviorB
selectBehavior _ = Nothing
main :: IO ()
main = do
putStrLn "Which behavior (A or B)?"
selection <- getLine
let selected = selectBehavior selection
maybe (return ()) behavior selected
putStrLn "What is your name?"
name <- getLine
putStrLn "What is your age?"
age <- readLn -- Don't use in real code, you should actually parse things
maybe (return ()) (\bhvr -> print $ foo bhvr name age) selected
(I haven't compiled this code, but it should work)
Typeclasses are meant to be resolved fully at compile time. You're trying to force them to be resolved at runtime. Instead, think about how you're really specifying it in OOP: you have a type and a function that returns some value of that type based on its arguments. You then call a method on that type. The only difference is that with the OOP solution the values returned from the selection function don't have the exact type that the function says it should, so you're returning a BehaviorA
or BehaviorB
instead of an IBehavior
. With Haskell you have to actually return a value that exactly matches the return type.
The only thing that the OOP version lets you do that Haskell doesn't is cast your IBehavior
back to a BehaviorA
or BehaviorB
, and this is often considered unsafe anyway. If you receive a value whose type is specified by an interface, you should always restrict yourself to only what that interface allows. Haskell forces this, while OOP uses it merely by convention. For a more complete explanation of this pattern check out this post.
回答2:
Why are you introducing these types BehaviorA
, BehaviorB
to dispatch on? It looks like a bad translation from Java unless there is some specific advantage to dispatching based on types rather than values; but it just seems to be causing you problems here.
Instead, how about ditching the type class and just using a record of "methods"?
data Behavior a = Behavior { behavior :: IO (), ... }
behaviorA = Behavior { behavior = print "Behavior A!" }
behaviorB = Behavior { behavior = print "Behavior B!" }
selectedBee x = case x of
"A" -> behaviorA
"B" -> behaviorB
data WithBehavior a = WithBehavior { foo :: String
, bee :: Behavior a }
run :: WithBehavior a -> IO ()
run (WithBehavior {..}) = print foo >> behavior bee
(I'm not sure exactly what you intended with WithBehavior
, since your Behavior
class lost one of its two arguments somewhere along the way. Maybe you want a universally or existentially quantified type instead.)
来源:https://stackoverflow.com/questions/31034826/select-instance-behavior-at-runtime