[Haskell-cafe] State monad exit
p75213 at gmail.com
p75213 at gmail.com
Sat Apr 8 01:44:08 UTC 2017
Hi,
I am playing around with the State monad and queues. At the moment I
have the following code:
{-# LANGUAGE ViewPatterns, FlexibleContexts #-}
module Main where
import Criterion.Main
import Control.Monad.State.Lazy
import Data.Maybe (fromJust)
import Data.Sequence ((<|), ViewR ((:>)))
import qualified Data.Sequence as S
--------------------------------------------------------
data Queue a = Queue { enqueue :: [a], dequeue :: [a] }
deriving (Eq, Show)
-- adds an item
push :: a -> Queue a -> Queue a
push a q = Queue (a:enqueue q) (dequeue q)
pop :: Queue a -> Maybe (a, Queue a)
pop q = if null (dequeue q) then
go $ Queue [] (reverse (enqueue q))
else
go q
where go (Queue _ []) = Nothing
go (Queue en (x:de)) = Just (x, Queue en de)
queueTst :: Int -> Queue Int -> Queue Int
queueTst 0 q = q
queueTst n q | even n = queueTst (n - 1) (push (100 + n) q)
| otherwise = queueTst (n - 1)
(if popped == Nothing then q
else snd (fromJust popped))
where popped = pop q
-------------------------------------------------------------
pushS :: a -> S.Seq a -> S.Seq a
pushS a s = a <| s
pushS' :: a -> State (S.Seq a) (Maybe a)
pushS' a = do
s <- get
put (a <| s)
return Nothing
pushS'' :: a -> State (S.Seq a) (Maybe a)
pushS'' a = get >>= (\g -> put (a <| g)) >> return Nothing
popS :: S.Seq a -> Maybe (a, S.Seq a)
popS (S.viewr -> S.EmptyR) = Nothing
popS (S.viewr -> s:>r) = Just (r,s)
popS' :: State (S.Seq a) (Maybe a)
popS' = do
se <- get
let sl = popS'' se
put $ snd sl
return $ fst sl
where popS'' (S.viewr -> S.EmptyR) = (Nothing, S.empty)
popS'' (S.viewr -> beg:>r) = (Just r, beg)
queueTstS :: Int -> S.Seq Int -> S.Seq Int
queueTstS 0 s = s
queueTstS n s | even n = queueTstS (n - 1) (pushS (100 + n) s)
| otherwise = queueTstS (n - 1)
(if popped == Nothing then s
else snd (fromJust popped))
where popped = popS s
queueTstST :: Int -> State (S.Seq Int) (Maybe Int)
queueTstST n =
if (n > 0) then
if even n then
pushS' (100 + n) >> queueTstST (n - 1)
else
popS' >> queueTstST (n - 1)
else return Nothing
main1 :: IO ()
main1 = defaultMain
[ bench "Twin Queue" $ whnf (queueTst 550) (Queue [500,499..1] [])
, bench "Sequence Queue" $ whnf (queueTstS 550) (S.fromList [500,499..1])
, bench "State Queue" $ whnf
(runState (queueTstST 550)) (S.fromList [500,499..1])
]
--------------------------------------------------------------------------------------------------------------------------------------------------
In the function "queueTstST" is there a way to exit while retaining the
last "Maybe value" rather than with "Nothing"?
More information about the Haskell-Cafe
mailing list