3

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
josejuan
  • 9,338
  • 24
  • 31
  • I think your best bet is probably the `reflection` package (don't use `Given` to preserve your sanity). – dfeuer Jun 24 '15 at 19:12
  • I get that `WithBehavior` is of type `String -> WithBehavior`. What is the type of `withBehavior`? what is `makeWithBehavior`? It sort of fell apart at the end with the intended operation falling into undefined and untyped symbols. – Thomas M. DuBuisson Jun 24 '15 at 19:45
  • @dfeuer using `data BehaviorWrapper where { BehaviorWrapper :: Behavior b => b -> BehaviorWrapper }` could be made but I want avoid type wrappers :) – josejuan Jun 24 '15 at 20:19
  • @ThomasM.DuBuisson is not real code, `withBehavior x` construct the application data (`WithBehavior` containing the final `Behavior` instance) using some `x` runtime configuration (eg. sys.args). `makeWithBehavior` could be directly `WithBehavior "fooString" bee`. Thk! – josejuan Jun 24 '15 at 20:27
  • If `IBehavior` really has only one method... just pass a function to anybody that needs it. You don't need to "define a class" and then "construct instances of it" just to pass a function around. – MathematicalOrchid Jun 24 '15 at 20:28
  • No @MathematicalOrchid (see `class Behavior`) I want include a full, configurable, with state, ... behavior selectable at runtime (excuse my poorly explanation). – josejuan Jun 24 '15 at 20:44
  • 2
    Oh look it's our old friend the [existential typeclass antipattern](https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/). The answerers are right here -- ditch the class, use a record instead. Your aversion is based on intuition from other languages. Haskell is quite different. Give it a try and see how it goes. – luqui Jun 24 '15 at 22:45
  • Thank you @luqui I'll follow your tip – josejuan Jun 25 '15 at 06:57
  • possible duplicate of ["Strategy Pattern" in Haskell](http://stackoverflow.com/questions/21677201/strategy-pattern-in-haskell) – josejuan Jun 25 '15 at 08:54

2 Answers2

6

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.

bheklilr
  • 53,530
  • 6
  • 107
  • 163
  • Yes @bheklilr I know these direct OOP aproach (and works!) it remember me C-style OOP pattern :D But yours `k` are the same type (`String`) and `selectBehavior` returns only one fixed type (then, with `class`works well too) – josejuan Jun 24 '15 at 20:36
  • @josejuan Correct, if you need it to be more flexible then you'll have to apply other techniques, I included those data type parameters because you had them in some places in your example code, but not in others. You will have to return the exact same type there, this is a restriction but not that bad of one, there are ways around it. However, your main problem here comes from trying to directly translate OOP to FP using typeclasses, and that's just not what typeclasses are for. – bheklilr Jun 24 '15 at 20:44
4

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.)

Reid Barton
  • 14,951
  • 3
  • 39
  • 49
  • Excuse me @ReidBarton (and others) is my fault (I explain poorly). Each behavior instance (alternative) has their own context (data type). `Database.Persist` may be a good example I'm looking for but is too complex to me. – josejuan Jun 24 '15 at 20:40
  • That doesn't actually matter. You can add type parameters to `Behavior` if necessary, or just use the context in the implementation of your `Behavior` in a way that it does not appear in the type. Type classes provide convenience and coherence, and neither is relevant here when you don't even know how to write your program at all. – Reid Barton Jun 24 '15 at 21:14
  • @josejuan, the better way than the version using GADTs in the edit is the version in my answer or bheklilr's answer (with the type parameter(s) of `Behavior` removed, since you do not use them). They are equivalent. – Reid Barton Jun 24 '15 at 21:24
  • Thank you very much @ReidBarton, both answers are great. I'll take your way :) – josejuan Jun 25 '15 at 07:01