[Haskell-cafe] Functor in terms of Arrow

2012-02-18 Thread Tom Schouten
Dear HC, Does AFunctor below have a standard name? It's a generalization of the Functor class in terms of Arrow instead of (-): fmap :: Functor f = (i - o) - f i - f o afmap :: Arrow a, AFunctor f = a i o- a (f i) (f o) It pops up in less general form (AFunctor =

[Haskell-cafe] LLVM: function pointer in global struct

2011-09-29 Thread Tom Schouten
Hi everyone, Using the LLVM bindings, I'm trying to create an initialized global struct variable containing a pointer to a function. {-# LANGUAGE ScopedTypeVariables #-} import LLVM.Core import Data.Word import LLVM.Util.File(writeCodeGenModule) sm_module = do tick :: Function (Word32 -

Re: [Haskell-cafe] Existential question

2011-08-21 Thread Tom Schouten
On 08/21/2011 05:33 AM, Felipe Almeida Lessa wrote: On Sat, Aug 20, 2011 at 6:26 PM, Tom Schoutent...@zwizwa.be wrote: data Kl i o = forall s. Kl s (i -s -(s, o)) This is an Arrow. At first I wondered if there was also an associated Monad, hence the iso function. Given data Kl i

Re: [Haskell-cafe] Existential question

2011-08-20 Thread Tom Schouten
On 08/19/2011 08:50 AM, Ryan Ingram wrote: ki1 :: KI () Int ki1 = KI @Int (\() s - (s+1, s)) ki2 :: KI () Int ki2 = KI @() (\() () - ((), 0)) f :: Bool - KI () Int f x = if x then ki1 else ki2 iso f = KI ?? ?? The problem is that we have multiple possible internal state types! Aha! Nice

Re: [Haskell-cafe] Existential question

2011-08-20 Thread Tom Schouten
On 08/18/2011 07:27 AM, o...@okmij.org wrote: -- Is there a way to make this one work also? data Kl i o = forall s. Kl (i - s - (s, o)) iso :: (i - Kl () o) - Kl i o iso f = Kl $ \i s - (\(Kl kl) - kl () s) (f i) Yes, if you move the quantifier: type Kl i o = i - Kl1 o data Kl1 o =

[Haskell-cafe] Existential question

2011-08-17 Thread Tom Schouten
{-# LANGUAGE ExistentialQuantification #-} -- Dear Cafe, this one works. data Kl' s i o = Kl' (i - s - (s, o)) iso' :: (i - Kl' s () o) - Kl' s i o iso' f = Kl' $ \i s - (\(Kl' kl') - kl' () s) (f i) -- Is there a way to make this one work also? data Kl i o = forall s. Kl (i - s - (s, o)) iso

Re: [Haskell-cafe] Hiding growing state using existentials.

2011-08-16 Thread Tom Schouten
On 08/16/2011 09:23 AM, Stephen Tetley wrote: {- I don't think parametric monads will solve your problem though, as you want a product of the states as the result of bind. Are you really sure you want this behavior?, I'd imagine it breaks the monad laws anyway. -} It seems that the product

[Haskell-cafe] Hiding growing state using existentials.

2011-08-15 Thread Tom Schouten
Dear Cafe, I'm building an abstraction for representing sequences as difference equations, storing initial values and update equation. I have something that resembles a Monad, but has an extra state parameter s that grows on _join or _bind, so I can't simply create an instance Monad (Sig s).