FW: Haskell accumulator

John Meacham john@repetae.net
Thu, 13 Jun 2002 16:14:58 -0700


I am thinking one of the following...
(the first needs a type signature due to the monomorphism restriction..
i think.)

foo :: Num a => a -> a -> a
foo = (+)

foo n = (n +)

foo n i = n + i



On Fri, Jun 14, 2002 at 08:29:55AM +1000, Dominic Cooney wrote:
> Paul Graham is collecting canonical accumulator generators at
> http://www.paulgraham.com/accgen.html , and has Dylan, E, JavaScript,
> various dialects Lisp, Lua, Rebol, Ruby, Perl, Python and Smalltalk.
> 
> Could the serious Haskellers comment on this attempt of mine?
> 
> foo n = do
>   n' <- newIORef n
>   return (\i -> do { modifyIORef n' (i+); readIORef n' })
> 
> This is all related to arguments about the benefits of succinctness and
> expressivity in programming languages.
> 
> Dominic Cooney
> 
> -----Original Message-----
> From: Paul Graham [mailto:pg@archub.org] 
> Sent: Thursday, 13 June 2002 11:17 PM
> To: dominic@dcooney.com
> Subject: Re: Haskell accumulator
> 
> Would this (if the type signature is unnecc) then be the
> canonical def in Haskell?
> 
> foo n = do
>   n' <- newIORef n
>   return (\i -> do { modifyIORef n' (i+); readIORef n' })
> 
> 
> --Dominic Cooney wrote:
> > This is a multi-part message in MIME format.
> > 
> > ------=_NextPart_000_0001_01C212A8.F2F6A010
> > Content-Type: text/plain;
> > 	charset="us-ascii"
> > Content-Transfer-Encoding: 7bit
> > 
> > If you are still collecting these Revenge of the Nerds accumulators,
> > here it is in literate Haskell:
> > 
> > > mkAccum :: (Num a) => a -> IO (a -> IO a)
> > > mkAccum n = do
> > >     n' <- newIORef n
> > >     return (\i -> do { modifyIORef n' (i+); readIORef n' })
> > 
> > There are a couple of interesting things here; firstly the (Num a) =>
> is
> > an example of Haskell's type classes.
> > 
> > The second is the 'IO' written everywhere. Haskell is pure, and IO is
> > the library-sanctioned state monad. Thus mkAccum and the accumulator
> > itself evaluate to "IO things" since they involve mutable state.
> > 
> > The only other interesting thing about the type signature is that it
> is
> > completely unnecessary. The compiler infers the most general type. The
> > programmer can write explicit type signatures to narrow the type of a
> > function, or (more commonly) have the compiler provide a sanity check.
> > 
> > 'Return' is unusual too-- it wraps things in the IO monad. Ordinarily
> it
> > is not required, e.g.
> > 
> > > incr n = \x -> n + x
> > 
> > Although this could simply be written as a partial application, like:
> > 
> > > incr n = (+) n
> > 
> > A whole test program is attached re: the accumulator.
> > 
> > On another note, I am eagerly awaiting the arrival of ANSI Common Lisp
> > from Amazon. I may be converted yet.
> > 
> > Dominic Cooney
> > 
> > 
> > ------=_NextPart_000_0001_01C212A8.F2F6A010
> > Content-Type: application/octet-stream;
> > 	name="accum.lhs"
> > Content-Transfer-Encoding: 7bit
> > Content-Disposition: attachment;
> > 	filename="accum.lhs"
> > 
> > This can be built with:
> > 
> > ghc -fglasgow-exts -package lang --make accum.lhs -o accum
> > 
> > GHC is available from http://www.haskell.org/ghc .
> > 
> > 
> > > module Main (main) where
> > 
> > Haskell is pure-- the state of the world is in the IO monad. Hence
> > the accumulator requires these imports.
> > 
> > > import IOExts (IORef, newIORef, readIORef, modifyIORef)
> > 
> > 
> > The accumulator.
> > 
> > > mkAccum :: (Num a) => a -> IO (a -> IO a)
> > > mkAccum n = do
> > >     n' <- newIORef n
> > >     return (\i -> do { modifyIORef n' (i+); readIORef n' })
> > 
> > 
> > Small test program.
> > 
> > > main :: IO ()
> > > main = do
> > >     acc <- mkAccum 42
> > >     x <- acc 1
> > >     put x
> > >     x <- acc 2
> > >     put x
> > 
> > 
> > Put is a small function that prints something.
> > 
> > > put :: (Show a) => a -> IO ()
> > > put = putStrLn.show
> > ------=_NextPart_000_0001_01C212A8.F2F6A010--
> > 
> 
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 

-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john@foo.net
---------------------------------------------------------------------------