{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Lambdabot.State
(
MonadLBState(..)
, readMS
, writeMS
, modifyMS
, GlobalPrivate
, mkGlobalPrivate
, withPS
, readPS
, writePS
, withGS
, readGS
, writeGS
, readGlobalState
, writeGlobalState
) where
import Lambdabot.File
import Lambdabot.Logging
import Lambdabot.Monad
import Lambdabot.Module
import Lambdabot.Nick
import Lambdabot.Command
import Lambdabot.Util
import Lambdabot.Util.Serial
import Control.Concurrent.Lifted
import Control.Exception.Lifted as E
import Control.Monad.Reader
import Control.Monad.Trans.Control
import qualified Data.ByteString.Char8 as P
import Data.IORef.Lifted
withMWriter :: MonadBaseControl IO m => MVar a -> (a -> (a -> m ()) -> m b) -> m b
withMWriter mvar f = bracket
(do x <- takeMVar mvar; ref <- newIORef x; return (x,ref))
(\(_,ref) -> tryPutMVar mvar =<< readIORef ref)
(\(x,ref) -> f x $ writeIORef ref)
class MonadLB m => MonadLBState m where
type LBState m
withMS :: (LBState m -> (LBState m -> m ()) -> m a) -> m a
instance MonadLB m => MonadLBState (ModuleT st m) where
type LBState (ModuleT st m) = st
withMS f = do
ref <- asks moduleState
withMWriter ref f
instance MonadLBState m => MonadLBState (Cmd m) where
type LBState (Cmd m) = LBState m
withMS f = do
x <- liftWith $ \run ->
withMS $ \st wr ->
run (f st (lift . wr))
restoreT (return x)
readMS :: MonadLBState m => m (LBState m)
readMS = withMS (\st _ -> return st)
modifyMS :: MonadLBState m => (LBState m -> LBState m) -> m ()
modifyMS f = withMS $ \st wr -> wr (f st)
writeMS :: MonadLBState m => LBState m -> m ()
writeMS = modifyMS . const
data GlobalPrivate g p = GP {
global :: !g,
private :: ![(Nick,MVar (Maybe p))],
maxSize :: Int
}
mkGlobalPrivate :: Int -> g -> GlobalPrivate g p
mkGlobalPrivate ms g = GP {
global = g,
private = [],
maxSize = ms
}
withPS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> Nick
-> (Maybe p -> (Maybe p -> LB ()) -> LB a)
-> m a
withPS who f = do
mvar <- accessPS return id who
lb $ withMWriter mvar f
readPS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> Nick -> m (Maybe p)
readPS = accessPS (liftIO . readMVar) (\_ -> return Nothing)
accessPS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> (MVar (Maybe p) -> m a) -> (m (MVar (Maybe p)) -> m a)
-> Nick
-> m a
accessPS success failure who = withMS $ \state writer ->
case lookup who $ private state of
Just mvar -> do
let newPrivate = (who,mvar):
filter ((/=who) . fst) (private state)
length newPrivate `seq` writer (state { private = newPrivate })
success mvar
Nothing -> failure $ do
mvar <- liftIO $ newMVar Nothing
let newPrivate = take (maxSize state) $ (who,mvar): private state
length newPrivate `seq` writer (state { private = newPrivate })
return mvar
withGS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> (g -> (g -> m ()) -> m ()) -> m ()
withGS f = withMS $ \state writer ->
f (global state) $ \g -> writer $ state { global = g }
readGS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> m g
readGS = fmap global readMS
writePS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> Nick -> Maybe p -> m ()
writePS who x = withPS who (\_ writer -> writer x)
writeGS :: (MonadLBState m, LBState m ~ GlobalPrivate g p)
=> g -> m ()
writeGS g = withGS (\_ writer -> writer g)
writeGlobalState :: ModuleT st LB ()
writeGlobalState = do
m <- asks theModule
mName <- asks moduleName
debugM ("saving state for module " ++ show mName)
case moduleSerialize m of
Nothing -> return ()
Just ser -> do
state' <- readMS
case serialize ser state' of
Nothing -> return ()
Just out -> do
stateFile <- lb (findLBFileForWriting mName)
io (P.writeFile stateFile out)
readGlobalState :: Module st -> String -> LB (Maybe st)
readGlobalState module' name = do
debugM ("loading state for module " ++ show name)
case moduleSerialize module' of
Just ser -> do
mbStateFile <- findLBFileForReading name
case mbStateFile of
Nothing -> return Nothing
Just stateFile -> io $ do
state' <- Just `fmap` P.readFile stateFile `E.catch` \SomeException{} -> return Nothing
E.catch (evaluate $ maybe Nothing (Just $!) (deserialize ser =<< state'))
(\e -> do
errorM $ "Error parsing state file for: "
++ name ++ ": " ++ show (e :: SomeException)
errorM $ "Try removing: "++ show stateFile
return Nothing)
Nothing -> return Nothing