Re: [Haskell-cafe] Configuration Problem and Plugins

2011-09-06 Thread Ryan Ingram
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
technopolit...@gmail.comwrote:

 On Sat, Sep 3, 2011 at 12:33 AM, Max Rabkin max.rab...@gmail.com wrote:
  On Sat, Sep 3, 2011 at 03:15, M. George Hansen technopolit...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Configuration Problem and Plugins

2011-09-03 Thread M. George Hansen
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 ()
}

The program loads plugins at the start and runs the initialize
function, and then enters the main loop where it repeatedly calls the
render function with output to display. When the program exits the
main loop, it calls the destroy function to clean up any resources
used by the plugin. You can probably already see my problem: how do I
pass initialization information created in the initialize function to
the render function?

I'm vaguely aware of some solutions to the typical configuration
problem, such as implicit arguments or explicitly passing the
configuration data through the function call hierarchy. As far as I
can tell, neither of these approaches would work because the program
can't know at compile time what, if any, configuration data is used by
the plugin.

I suppose I could pass a Dynamic up the call chain and let the plugin
decode it in the render function, but that seems a little kludgy to
me.

Any thoughts would be greatly appreciated.

--
  M. George Hansen

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


Re: [Haskell-cafe] Configuration Problem and Plugins

2011-09-03 Thread MigMit
data Renderer = Renderer {destroy :: IO (); render :: SystemOutput - IO ()}
newtype Initializer = Initializer {initialize :: IO Renderer}

Отправлено с iPad

03.09.2011, в 14:15, M. George Hansen technopolit...@gmail.com написал(а):

 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 ()
 }
 
 The program loads plugins at the start and runs the initialize
 function, and then enters the main loop where it repeatedly calls the
 render function with output to display. When the program exits the
 main loop, it calls the destroy function to clean up any resources
 used by the plugin. You can probably already see my problem: how do I
 pass initialization information created in the initialize function to
 the render function?
 
 I'm vaguely aware of some solutions to the typical configuration
 problem, such as implicit arguments or explicitly passing the
 configuration data through the function call hierarchy. As far as I
 can tell, neither of these approaches would work because the program
 can't know at compile time what, if any, configuration data is used by
 the plugin.
 
 I suppose I could pass a Dynamic up the call chain and let the plugin
 decode it in the render function, but that seems a little kludgy to
 me.
 
 Any thoughts would be greatly appreciated.
 
 --
   M. George Hansen
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Configuration Problem and Plugins

2011-09-03 Thread M. George Hansen
On Sat, Sep 3, 2011 at 12:33 AM, Max Rabkin max.rab...@gmail.com wrote:
 On Sat, Sep 3, 2011 at 03:15, M. George Hansen technopolit...@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe