[Haskell-cafe] Lazy producing a list in the strict ST monad
Ryan Ingram
ryani.spam at gmail.com
Wed Jun 20 00:27:37 CEST 2012
It doesn't work like that by default, and here is why:
-- an infinite tree of values
data InfTree a = Branch a (InfTree a) (InfTree a)
buildTree :: Num a => STRef s a -> ST s (InfTree a)
buildTree ref = do
n <- readSTRef ref
writeSTRef ref $! (n+1)
left <- buildTree ref
right <- buildTree ref
return (Branch n left right)
makeTree :: Num a => ST s (InfTree a)
makeTree = do
ref <- newSTRef 0
buildTree ref
-- should be referentially transparent, i.e. these two expressions should
be equivalent
pureInfTree1, pureInfTree2 :: InfTree Integer
pureInfTree1 = runST makeTree
pureInfTree2 = runST makeTree
element (Branch x _ _) = x
goLeft (Branch _ x _) = x
goRight (Branch _ _ x) = x
test :: IO ()
test = do
let left1 = goLeft pureInfTree1
let right1 = goRight pureInfTree1
let left2 = goLeft pureInfTree2
let right2 = goRight pureInfTree2
evaluate (element left1)
evaluate (element right1)
evaluate (element right2)
evaluate (element left2)
print (element left1 == element left2) -- should be True!
Right now this code diverges, because buildTree diverges. If buildTree was
lazy, test would print False because of the order of evaluation. You can
make buildTree lazy if you want:
import Control.Monad.ST.Unsafe
buildTree :: Num a => STRef s a -> ST s (InfTree a)
buildTree ref = do
n <- readSTRef ref
writeSTRef ref $! (n+1)
left <- unsafeInterleaveST (buildTree ref)
right <- unsafeInterleaveST (buildTree ref)
return (Branch n left right)
In order to safely use unsafeInterleaveST, you need to prove that none of
the references used by the computation passed to unsafeInterleaveST can be
used by any code after the unsafeInterleaveST; so this 'lazy' list
generation is safe:
buildList :: Num a => STRef s a -> ST s [a]
buildList = do
ref <- newSTRef 0
let loop =
n <- readSTRef ref
writeSTRef ref $! (n+1)
rest <- unsafeInterleaveST loop
return (n : rest)
loop
because we are guaranteed that the only reference to ref exists inside the
loop which uses it in a linear fashion. So you may be able to get away
with it... but you have to make a proof manually that the compiler isn't
able to infer for you.
-- ryan
On Sun, Jun 10, 2012 at 5:37 AM, Nicu Ionita <nicu.ionita at acons.at> wrote:
> Hi,
>
> I'm trying to produce a list in the strict ST monad. The documentation of
> ST says that the monad is strict in the state, but not in the values. So I
> expect that, when returning a list, I get back only the Cons (with 2
> unevaluated thunks). Now, when I need the first element (head), this will
> be evaluated (with whatever actions are necessary in the ST universe) and
> the tail is again a Cons with unevaluated parts.
>
> Internally my list is stored in a vector, and the elements are generated
> phasewise, each phase generating 0 or more elements in the vector, and a
> fuction splitMove is driving this process (see code below). I would expect
> that the first phase triggers, generates some moves, then (after these are
> consumed from the list) the next phase triggers generating the next few
> moves and so on.
>
> But when I trace the phases (Debug.Trace.trace) I get all the trace
> messages in front of the first move:
>
> Moves for fen: rnbqkbnr/pp3ppp/4p3/2pp4/3P4/**2NQ4/PPP1PPPP/R1B1KBNR w
> After move generation...
> 0 >= 0 : next phase
> 3 >= 3 : next phase
> 3 >= 3 : next phase
> 42 >= 42 : next phase
> 44 >= 44 : next phase
> d4c5
> g1f3
> g1h3
> c3b1
> ...
>
> This seems not to be just an unhappy combination between trace and ST, as
> also the program without trace is beeing slower than the same implemented
> with plain lists, which is hard to believe (in many cases the move list is
> not consumed to the end).
>
> I wonder if my expectation is wrong, but I don't find a way to do this.
> Here is the (incomplete) code:
>
> produceList ... = runST $ do
> ml <- newMList ...
> listMoves ml
>
> -- Transforms a move list to a list of moves - lazy
> listMoves :: MList s -> ST s [Move]
> listMoves ml = do
> sm <- splitMove ml
> case sm of
> Just (m, ml') -> do
> rest <- listMoves ml'
> return $ m : rest
> Nothing -> return []
>
> -- Split the first move from the move list and return it together with
> -- the new move list (without the first move). Return Nothing if there
> -- is no further move
> splitMove :: MList s -> ST s (Maybe (Move, MList s))
> splitMove ml
> | mlToMove ml >= mlToGen ml = do
> mml <- trace trm $ nextPhase ml
> case mml of
> Nothing -> return Nothing
> Just ml' -> splitMove ml'
> | otherwise = do
> m <- U.unsafeRead (mlVec ml) (mlToMove ml)
> case mlCheck ml ml m of
> Ok -> return $ Just (m, ml1)
> Skip -> splitMove ml1
> Delay -> splitMove ml1 { mlBads = m : mlBads ml }
> where ml1 = ml { mlToMove = mlToMove ml + 1 }
> trm = show (mlToMove ml) ++ " >= " ++ show (mlToGen ml) ++ " :
> next phase"
>
> ______________________________**_________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120619/78f63d2e/attachment.htm>
More information about the Haskell-Cafe
mailing list