[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

ross at soi.city.ac.uk ross at soi.city.ac.uk
Sat Mar 19 19:35:46 EST 2005


On Sat, Mar 19, 2005 at 12:17:46PM -0700, Kevin Atkinson wrote:
> On Sat, 19 Mar 2005 ross at soi.city.ac.uk wrote:
> > I would also have expected loopFG to have been defined using fixIO.
> 
> Could you be more specific.  Ie How?

For the type definitions

	newtype FG' a b = FG' (Control -> a -> IO (Control, b))
	newtype FG a b = FG (FGState -> IO (FG' a b, FGState))
	newtype Container a b = Container (FG ([WidgetP], a) b)

the usual instances would be (give or take a ~):

	instance Arrow FG' where
		arr f = FG' $ \ c x -> return (c, f x)
		FG' f >>> FG' g = FG' $ \ c x -> do
			(c', x') <- f c x
			g c' x'
		first (FG' f) = FG' $ \ c (x, y) -> do
			(c', x') <- f c x
			return (c', (x', y))

	instance ArrowLoop FG' where
		loop (FG' f) = FG' $ \ c x -> do
			(c', x', _) <- mfix $ \ ~(_, _, y) -> do
				~(c', ~(x', y')) <- f c (x, y)
				return (c', x', y')
			return (c', x')

	instance Arrow FG where
		arr f = FG $ \ s -> return (arr f, s)
		FG f >>> FG g = FG $ \ s -> do
			(f', s') <- f s
			(g', s'') <- g s
			return (f' >>> g', s'')
		first (FG f) = FG $ \ s -> do
			(f', s') <- f s
			return (first f', s')

	instance ArrowLoop FG where
		loop (FG f) = FG $ \ s -> do
			(f', s') <- f s
			return (loop f', s')

	instance Arrow Container where
		arr f = Container (arr (f . snd))
		Container f >>> Container g = Container $
			arr (\ (ws, a) -> (ws, (ws, a))) >>> second f >>> g
		first (Container f) = Container $
			arr (\ ~(ws,~(x,y)) -> ((ws,x),y)) >>> first f

	instance ArrowLoop Container where
		loop (Container f) = Container $
			loop (arr (\ ((ws,x),y) -> (ws,(x,y))) >>> f)

The FG instances seem to match yours, except for ArrowLoop.


More information about the Haskell-Cafe mailing list