[Haskell-cafe] Configuration Problem and Plugins

Ryan Ingram ryani.spam at gmail.com
Tue Sep 6 20:59:39 CEST 2011


The other option is

{-# LANGUAGE ExistentialQuantification #-}

data Renderer s = Renderer {
    initialize :: IO s,
    destroy :: IO (),
    renderS :: SystemOutput -> s -> IO s
 }

-- Now, you need to hold the state somewhere, which you can do with an
existential:

data InitializedRenderer = forall s. IRenderer s (Renderer s)

initRenderer :: Renderer s -> IO InitializedRenderer
initRenderer r = do
    s <- initialize r
    return (IRenderer s r)

render :: InitializedRenderer -> SystemOutput -> IO InitializedRenderer
render (IRenderer s r) o = do
   s' <- renderS r o s
   return (IRenderer s' r)




On Sat, Sep 3, 2011 at 10:44 PM, M. George Hansen
<technopolitica at gmail.com>wrote:

> On Sat, Sep 3, 2011 at 12:33 AM, Max Rabkin <max.rabkin at gmail.com> wrote:
> > On Sat, Sep 3, 2011 at 03:15, M. George Hansen <technopolitica at gmail.com>
> wrote:
> >> Greetings,
> >>
> >> I'm a Python programmer who is relatively new to Haskell, so go easy on
> me :)
> >>
> >> I have a program that uses (or will use) plugins to render output to
> >> the user in a generic way. I'm basing the design of the plugin
> >> infrastructure on the Plugins library, and have the following
> >> interface:
> >>
> >> data Renderer = Renderer {
> >>     initialize :: IO (),
> >>     destroy :: IO (),
> >>    render :: SystemOutput -> IO ()
> >> }
> >
> > How about having initialize return the render (and destroy, if
> > necessary) functions:
> >
> > initialize :: IO (SystemOutput -> IO ())
> >
> > or
> >
> > initialize :: IO (SystemOutput -> IO (), IO())
> >
>
> Thanks for your reply. That does seem like the best solution, I'll
> give it a try.
>
> --
>   M. George Hansen
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110906/2cd8773b/attachment.htm>


More information about the Haskell-Cafe mailing list