Stateful nondeterminism

From HaskellWiki
Revision as of 05:31, 9 March 2021 by Atravers (talk | contribs) (Added nondeterminism category)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

From New monads


If you want to do nondeterministic computation with local states for each of your threads and a global state shared by all your threads, use this monad:

newtype SuperState s t a = SuperState { runSuperState :: (s -> t -> (t,[(a,s)])) } 
                                    
instance Monad (SuperState s t) where 
    return a        = SuperState $ \s t -> (t,[(a,s)])
    (SuperState x) >>= f = SuperState $ \s t -> let (t',stateList) = x s t
                                                in  foldl (\(newt,sofar) (v,s) -> let (t'',lst) = runSuperState (f v) s newt
                                                                               in
                                                                                 (t'',sofar++lst)) (t',[]) stateList



instance MonadPlus (SuperState s t) where
    mzero = mz
    mplus = mp


getGlobal = SuperState $ \s t-> (t,[(t,s)])
getLocal = SuperState $ \s t -> (t,[(s,s)])

putLocal s = SuperState $ \_ t -> (t,[((),s)])
putGlobal t = SuperState $ \s _ -> (t,[((),s)])

mz = SuperState $ \_ t -> (t,[])
mp (SuperState a) (SuperState b) = 
    SuperState $ \s t ->
        let
            (t',stateList) = a s t
            (t'',stateList') = b s t'
        in
          (t'',stateList++stateList')