Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-14 Thread wren ng thornton

On 3/11/12 11:52 PM, Ben Gamari wrote:

That being said, there are some cases where you really do want to be
able to utilize a mutable data structure inside of an otherwise pure
algorithm. This is precisely the use of the ST monad. ST serves to allow
the use of mutable state inside of a function while hiding the fact from
the outside world.


Do note, however, that in certain cases the ST approach can be much 
slower than the obvious immutable approach (i.e., the State monad--- 
especially when implemented directly via argument passing, rather than 
using the monadic interface). I have some closed-source code where that 
assumption bit me; the ST code was over 4x slower.


One reason this can happen is that, since Haskell is predominantly pure, 
a whole lot of work has gone into optimizing the pure case. Another 
reason is that, if the compiler can see that it's pure, then it knows a 
bunch of safe optimizations the programmer may not have thought about. A 
final major reason is that often the rearrangements necessary to get 
things into state-passing form turn out to optimize the algorithm 
anyways (e.g., by ensuring linear access to inputs, etc)


So don't just assume that ST/mutability == fast.

--
Live well,
~wren

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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-14 Thread Johan Tibell
On Wed, Mar 14, 2012 at 5:50 PM, wren ng thornton w...@freegeek.org wrote:
 Do note, however, that in certain cases the ST approach can be much slower
 than the obvious immutable approach (i.e., the State monad--- especially
 when implemented directly via argument passing, rather than using the
 monadic interface). I have some closed-source code where that assumption bit
 me; the ST code was over 4x slower.

An additional reason is that runST often allocates a closure (as it's
marked NOINLINE) and thus using it e.g. in a tight loop can increase
allocation.

-- Johan

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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-13 Thread Ryan Ingram
On Sun, Mar 11, 2012 at 8:38 PM, E R pc88m...@gmail.com wrote:

 A pure function can allocate and modify memory as long as a) it never
 returns a reference to the memory or b) it never again modifies the
 memory once it returns (i.e. it returns an immutable object).


That's a reasonable first approximation to the problem, yes.  It gets a bit
more complicated due to laziness (what if the mutation gets delayed until
some later part of the output is examined?)

So, again, what is the Haskell philosophy towards using mutable data
 structures in pure functions? Is it:

 1. leave it to the compiler to find these kinds of opportunities
 2. just use the immutable data structures - after all they are just as
 good (at least asymptotically)
 3. you don't want to use mutable data structures because of _
 4. it does happen, and some examples are __


There are two ways in which Haskell encourages the use of mutable data
structures in a pure way.

The first is in the inherent mutation caused by laziness.  For example:

type Positive = Integer

-- trie of binary representation of positive number
-- [1] - tOne
-- x ++ [0] - lookup x . tEven
-- x ++ [1] - lookup x . tOdd
data Trie a = Trie {
tOne :: a,
tEven :: NatTrie a,
tOdd :: NatTrie a
}

lookupTrie :: Trie a - Positive - a
lookupTrie t 1 = tOne t
lookupTrie t n
| even n = lookupTrie (tEven t) (n `div` 2)
| otherwise = lookupTrie (tOdd t) (n `div` 2) -- div drops remainder

makeTrie :: (Positive - a) - Trie a
makeTrie f = Trie (f 1) e o where
e = makeTrie $ \n - f (2*n)
o = makeTrie $ \n - f (2*n + 1)

memoize :: (Positive - a) - (Positive - a)
memoize = lookupTrie . makeTrie

collatz_rec :: (Positive - Integer) - Positive - Integer
collatz_rec f 1 = 0
collatz_rec f n
| even n = 1 + f (n `div` 2)
| otherwise = 1 + f (3*n + 1)

collatz = memoize (collatz_rec collatz)

In this case, makeTrie creates a thunk, and it's only evaluated where
requested by lookupTrie.  You can call collatz at many different values and
later calls will be much faster, as the mutation caused by lazy evaluation
'remembers' the values.

The second is by explicitly documenting that you are using a temporarily
mutable structure, which is the ST monad:

instance Monad (ST s)
newSTRef :: a - ST s (STRef s a)
readSTRef :: STRef s a - ST s a
writeSTRef :: STRef s a - a - ST s ()
-- and similar interface for mutable STArrays

runST :: (forall s. ST s a) - a -- note higher rank type

A computation in the ST monad is an impure computation that can modify
memory, but only memory allocated within that same computation.

The higher rank type in runST makes it safe to do so--references from one
ST computation cannot escape to any other ST computation.  So even though
internally some pure value might rely on an impure computation, it's safe
to do so in a pure context.

Here's a sample implementation of ST:

-- DO NOT EXPORT THESE CONSTRUCTORS
newtype ST s a = ST (IO a)
newtype STRef s a = STRef { getRef :: IORef a }

runST :: (forall s. ST s a) - a
runST (ST act) = unsafePerformIO act -- Actually safe!

newSTRef :: a - ST s (STRef s a)
newSTRef a  = ST $ liftM STRef (newIORef a)

readSTRef :: STRef s a - ST s a
readSTRef (STRef r) = ST $ readIORef r

writeSTRef :: STRef s a - a - ST s ()
writeSTRef (STRef r) a = ST $ writeIORef r a

There's some usage examples at http://www.haskell.org/haskellwiki/Monad/ST

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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-12 Thread Stephen Tetley
There is a trick to `nub` where you couldn't implement the internal
lookup list with an (assumed faster) search tree anyway.

`nub` only mandates equality not ordering, so building a ordered
structure like a binary tree is impossible. In practice i would be
hard to beat list as the intermediate structure in this case.

On 12 March 2012 03:38, E R pc88m...@gmail.com wrote:
[Chop]

 For example, consider the definition of Data.List.nub:

 nub l                   = nub' l []
  where
    nub' [] _           = []
    nub' (x:xs) ls
        | x `elem` ls   = nub' xs ls
        | otherwise     = x : nub' xs (x:ls)

 Clearly the memory allocated to ls never escapes nub', so it seems
 that ls could be replaced with a mutable data structure (with an eye
 towards improving performance in special cases).

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


[Haskell-cafe] using mutable data structures in pure functions

2012-03-11 Thread E R
Consider the following idea for implementing pure functions:

A pure function can allocate and modify memory as long as a) it never
returns a reference to the memory or b) it never again modifies the
memory once it returns (i.e. it returns an immutable object).

This is based on the idea of value objects in object-oriented
languages - the only mutation of a value object occurs in the
constructor. Once the constructor is finished initializing the object
it becomes immutable.

My first question is whether or not this is accurate or does it need
some qualifications / fixing up.

Secondly, where does this idea fit into the Haskell philosophy?

For example, consider the definition of Data.List.nub:

nub l   = nub' l []
  where
nub' [] _   = []
nub' (x:xs) ls
| x `elem` ls   = nub' xs ls
| otherwise = x : nub' xs (x:ls)

Clearly the memory allocated to ls never escapes nub', so it seems
that ls could be replaced with a mutable data structure (with an eye
towards improving performance in special cases).

For another example, consider Data.Map.fromList. I kind of expected
fromList to build up the map using a mutable data structure and then
seal it up before returning it, but it seems to call the same insert
that one would call to add to the map after it has been constructed.

So, again, what is the Haskell philosophy towards using mutable data
structures in pure functions? Is it:

1. leave it to the compiler to find these kinds of opportunities
2. just use the immutable data structures - after all they are just as
good (at least asymptotically)
3. you don't want to use mutable data structures because of _
4. it does happen, and some examples are __

Thanks,
ER

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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-11 Thread Ben Gamari
I'm sure others will want to chime in here, but I'll offer my two cents.

On Sun, 11 Mar 2012 22:38:56 -0500, E R pc88m...@gmail.com wrote:
snip
 
 So, again, what is the Haskell philosophy towards using mutable data
 structures in pure functions? Is it:
 
 1. leave it to the compiler to find these kinds of opportunities
 2. just use the immutable data structures - after all they are just as
 good (at least asymptotically)
 3. you don't want to use mutable data structures because of _
 4. it does happen, and some examples are __
 
You will find that a surprising amount of the time this will be
sufficient. After all, programmer time is frequently more expensive than
processor time.

That being said, there are some cases where you really do want to be
able to utilize a mutable data structure inside of an otherwise pure
algorithm. This is precisely the use of the ST monad. ST serves to allow
the use of mutable state inside of a function while hiding the fact from
the outside world.

Cheers,

- Ben


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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-11 Thread Johan Tibell
On Sun, Mar 11, 2012 at 8:38 PM, E R pc88m...@gmail.com wrote:
 1. leave it to the compiler to find these kinds of opportunities
 2. just use the immutable data structures - after all they are just as
 good (at least asymptotically)
 3. you don't want to use mutable data structures because of _
 4. it does happen, and some examples are __

5. There's no substitute for thinking and understanding the trade-offs
that you are making.

:)

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