{-#Language OverloadedStrings, FlexibleContexts #-}
{-# LANGUAGE CPP, ExistentialQuantification, FlexibleInstances, ScopedTypeVariables, UndecidableInstances #-}
module Transient.Logged(
Loggable(..), logged, received, param, getLog, exec,wait, emptyLog,
#ifndef ghcjs_HOST_OS
suspend, checkpoint, rerun, restore,
#endif
Log(..), toLazyByteString, byteString, lazyByteString, Raw(..)
) where
import Data.Typeable
import Unsafe.Coerce
import Transient.Internals
import Transient.Indeterminism(choose)
import Transient.Parse
import Control.Applicative
import Control.Monad.State
import System.Directory
import Control.Exception
import qualified Data.ByteString.Lazy.Char8 as BS
import qualified Data.ByteString.Char8 as BSS
import qualified Data.Map as M
import Data.ByteString.Builder
import Data.Monoid
import System.Random
exec= byteString "e/"
wait= byteString "w/"
class (Show a, Read a,Typeable a) => Loggable a where
serialize :: a -> Builder
serialize = byteString . BSS.pack . show
deserializePure :: BS.ByteString -> Maybe(a, BS.ByteString)
deserializePure s = r
where
r= case reads $ BS.unpack s of
[] -> Nothing !> "Nothing"
(r,t): _ -> return (r, BS.pack t)
typeOf1 :: Maybe(a, BS.ByteString) -> a
typeOf1= undefined
deserialize :: TransIO a
deserialize = x
where
x= withGetParseString $ \s -> case deserializePure s of
Nothing -> empty
Just x -> return x
instance Loggable ()
instance Loggable Bool where
serialize b= if b then "t" else "f"
deserialize = withGetParseString $ \s ->
if (BS.head $ BS.tail s) /= '/'
then empty
else
let h= BS.head s
tail= BS.tail s
in if h== 't' then return (True,tail) else if h== 'f' then return (False, tail) else empty
instance Loggable Int
instance Loggable Integer
instance (Typeable a, Loggable a) => Loggable[a]
instance Loggable Char
instance Loggable Float
instance Loggable Double
instance Loggable a => Loggable (Maybe a)
instance (Loggable a,Loggable b) => Loggable (a,b)
instance (Loggable a,Loggable b, Loggable c) => Loggable (a,b,c)
instance (Loggable a,Loggable b, Loggable c,Loggable d) => Loggable (a,b,c,d)
instance (Loggable a,Loggable b, Loggable c,Loggable d,Loggable e) => Loggable (a,b,c,d,e)
instance (Loggable a,Loggable b, Loggable c,Loggable d,Loggable e,Loggable f) => Loggable (a,b,c,d,e,f)
instance (Loggable a,Loggable b, Loggable c,Loggable d,Loggable e,Loggable f,Loggable g) => Loggable (a,b,c,d,e,f,g)
instance (Loggable a,Loggable b, Loggable c,Loggable d,Loggable e,Loggable f,Loggable g,Loggable h) => Loggable (a,b,c,d,e,f,g,h)
instance (Loggable a,Loggable b, Loggable c,Loggable d,Loggable e,Loggable f,Loggable g,Loggable h,Loggable i) => Loggable (a,b,c,d,e,f,g,h,i)
instance (Loggable a, Loggable b) => Loggable (Either a b)
instance (Loggable k, Ord k, Loggable a) => Loggable (M.Map k a) where
serialize v= intDec (M.size v) <> M.foldlWithKey' (\s k x -> s <> "/" <> serialize k <> "/" <> serialize x ) mempty v
deserialize= do
len <- int
list <- replicateM len $
(,) <$> (tChar '/' *> deserialize)
<*> (tChar '/' *> deserialize)
return $ M.fromList list
#ifndef ghcjs_HOST_OS
instance Loggable BS.ByteString where
serialize str = lazyByteString str
deserialize= tTakeWhile (/= '/')
#endif
#ifndef ghcjs_HOST_OS
instance Loggable BSS.ByteString where
serialize str = byteString str
deserialize = tTakeWhile (/= '/') >>= return . BS.toStrict
#endif
instance Loggable SomeException
newtype Raw= Raw BS.ByteString deriving (Read,Show)
instance Loggable Raw where
serialize (Raw str)= lazyByteString str
deserialize= Raw <$> do
s <- notParsed
BS.length s `seq` return s
data Log = Log{ recover :: Bool, buildLog :: Builder, fulLog :: Builder, lengthFull:: Int, hashClosure :: Int}
#ifndef ghcjs_HOST_OS
rerun :: String -> TransIO a -> TransIO a
rerun path proc = do
liftIO $ do
r <- doesDirectoryExist path
when (not r) $ createDirectory path
setCurrentDirectory path
restore' proc False
logs= "logs/"
restore :: TransIO a -> TransIO a
restore proc= restore' proc True
restore' proc delete= do
liftIO $ createDirectory logs `catch` (\(e :: SomeException) -> return ())
list <- liftIO $ getDirectoryContents logs
`catch` (\(e::SomeException) -> return [])
if null list || length list== 2 then proc else do
let list'= filter ((/=) '.' . head) list
file <- choose list'
log <- liftIO $ BS.readFile (logs++file)
let logb= lazyByteString log
setData Log{recover= True,buildLog= logb,fulLog= logb,lengthFull= 0, hashClosure= 0}
setParseString log
when delete $ liftIO $ remove $ logs ++ file
proc
where
remove f= removeFile f `catch` (\(e::SomeException) -> remove f)
suspend :: Typeable a => a -> TransIO a
suspend x= do
log <- getLog
if (recover log) then return x else do
logAll $ fulLog log
exit x
checkpoint :: TransIO ()
checkpoint = do
log <- getLog
if (recover log) then return () else logAll $ fulLog log
logAll log= liftIO $do
newlogfile <- (logs ++) <$> replicateM 7 (randomRIO ('a','z'))
logsExist <- doesDirectoryExist logs
when (not logsExist) $ createDirectory logs
BS.writeFile newlogfile $ toLazyByteString log
#else
rerun :: TransIO a -> TransIO a
rerun = const empty
suspend :: TransIO ()
suspend= empty
checkpoint :: TransIO ()
checkpoint= empty
restore :: TransIO a -> TransIO a
restore= const empty
#endif
getLog :: TransMonad m => m Log
getLog= getData `onNothing` return emptyLog
emptyLog= Log False mempty mempty 0 0
logged :: Loggable a => TransIO a -> TransIO a
logged mx = do
log <- getLog
let full= fulLog log
rest <- giveParseString
if recover log
then
if not $ BS.null rest
then recoverIt log
else do
setData log{buildLog=mempty}
notRecover full log !> "NOTRECOVER"
else notRecover full log
where
notRecover full log= do
let rs = buildLog log
setData $ Log False (rs <> exec) (full <> exec) (lengthFull log +1) (hashClosure log + 1000)
r <- mx <** do setData $ Log False ( rs <> wait) (full <> wait) (lengthFull log +1) (hashClosure log + 100000)
log' <- getLog
let len= lengthFull log'
add= full <> serialize r <> byteString "/"
recoverAfter= recover log'
lognew= buildLog log'
rest <- giveParseString
if recoverAfter && not (BS.null rest)
then do
modify $ \s -> s{execMode= Parallel}
setData $ log'{recover= True, fulLog= lognew <> add, lengthFull= lengthFull log+ len,hashClosure= hashClosure log + 10000000}
else
setData $ Log{recover= False, buildLog=rs <> serialize r <> byteString "/", fulLog= add,lengthFull= len+1, hashClosure=hashClosure log +10000000}
return r
recoverIt log= do
s <- giveParseString
case BS.splitAt 2 s of
("e/",r) -> do
setData $ log{
lengthFull= lengthFull log +1, hashClosure= hashClosure log + 1000}
setParseString r
mx
("w/",r) -> do
setData $ log{
lengthFull= lengthFull log +1, hashClosure= hashClosure log + 100000}
setParseString r
modify $ \s -> s{execMode= Parallel}
empty
_ -> value log
value log= r
where
typeOfr :: TransIO a -> a
typeOfr _= undefined
r= do
x <- deserialize <|> do
psr <- giveParseString
error (show("error parsing",psr,"to",typeOf $ typeOfr r))
tChar '/'
setData $ log{recover= True
,lengthFull= lengthFull log +1,hashClosure= hashClosure log + 10000000}
return x
received :: (Loggable a, Eq a) => a -> TransIO ()
received n= Transient.Internals.try $ do
r <- param
if r == n then return () else empty
param :: (Loggable a, Typeable a) => TransIO a
param = r where
r= do
let t = typeOf $ type1 r
(Transient.Internals.try $ tChar '/' >> return ())<|> return ()
if t == typeOf (undefined :: String) then return . unsafeCoerce . BS.unpack =<< tTakeWhile' (/= '/')
else if t == typeOf (undefined :: BS.ByteString) then return . unsafeCoerce =<< tTakeWhile' (/= '/')
else if t == typeOf (undefined :: BSS.ByteString) then return . unsafeCoerce . BS.toStrict =<< tTakeWhile' (/= '/')
else deserialize
where
type1 :: TransIO x -> x
type1 = undefined