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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to