{-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module LiveCoding.Handle
( Handle (..)
, handling
, HandlingState (..)
, HandlingStateT
, isRegistered
, runHandlingState
, runHandlingStateC
, runHandlingStateT
)
where
import Control.Arrow (returnA, arr, (>>>))
import Data.Data
import Data.IntMap
import qualified Data.IntMap as IntMap
import Control.Monad.Trans.Class (MonadTrans(lift))
import Control.Monad.Trans.State.Strict
import LiveCoding.Cell
import LiveCoding.Cell.Monad
import LiveCoding.Cell.Monad.Trans
import LiveCoding.LiveProgram
import LiveCoding.LiveProgram.Monad.Trans
data Handle m h = Handle
{ create :: m h
, destroy :: h -> m ()
}
combineHandles :: Applicative m => Handle m h1 -> Handle m h2 -> Handle m (h1, h2)
combineHandles handle1 handle2 = Handle
{ create = ( , ) <$> create handle1 <*> create handle2
, destroy = \(h1, h2) -> destroy handle2 h2 *> destroy handle1 h1
}
data Handling h where
Handling
:: { id :: Key
, handle :: h
}
-> Handling h
Uninitialized :: Handling h
type Destructors m = IntMap (Destructor m)
data HandlingState m = HandlingState
{ nHandles :: Key
, destructors :: Destructors m
}
deriving Data
type HandlingStateT m = StateT (HandlingState m) m
initHandlingState :: HandlingState m
initHandlingState = HandlingState
{ nHandles = 0
, destructors = IntMap.empty
}
runHandlingStateT
:: Monad m
=> HandlingStateT m a
-> m a
runHandlingStateT = flip evalStateT initHandlingState
runHandlingStateC
:: forall m a b .
(Monad m, Typeable m)
=> Cell (HandlingStateT m) a b
-> Cell m a b
runHandlingStateC cell = flip runStateC_ initHandlingState
$ hoistCellOutput garbageCollected cell
runHandlingState
:: (Monad m, Typeable m)
=> LiveProgram (HandlingStateT m)
-> LiveProgram m
runHandlingState LiveProgram { .. } = flip runStateL initHandlingState LiveProgram
{ liveStep = garbageCollected . liveStep
, ..
}
garbageCollected
:: Monad m
=> HandlingStateT m a
-> HandlingStateT m a
garbageCollected action = unregisterAll >> action <* destroyUnregistered
data Destructor m = Destructor
{ isRegistered :: Bool
, action :: m ()
}
handling
:: ( Typeable h
, Monad m
)
=> Handle m h
-> Cell (HandlingStateT m) arbitrary h
handling handleImpl@Handle { .. } = Cell
{ cellState = Uninitialized
, cellStep = \state input -> case state of
handling@Handling { .. } -> do
reregister handleImpl handling
return (handle, state)
Uninitialized -> do
handle <- lift create
id <- register handleImpl handle
return (handle, Handling { .. })
}
register
:: Monad m
=> Handle m h
-> h
-> HandlingStateT m Key
register handleImpl handle = do
HandlingState { .. } <- get
let id = nHandles + 1
put HandlingState
{ nHandles = id
, destructors = insertDestructor handleImpl id handle destructors
}
return id
reregister
:: Monad m
=> Handle m h
-> Handling h
-> HandlingStateT m ()
reregister handleImpl Handling { .. } = do
HandlingState { .. } <- get
put HandlingState { destructors = insertDestructor handleImpl id handle destructors, .. }
insertDestructor
:: Handle m h
-> Key
-> h
-> Destructors m
-> Destructors m
insertDestructor Handle { .. } id handle destructors =
let destructor = Destructor { isRegistered = True, action = destroy handle }
in insert id destructor destructors
unregisterAll
:: Monad m
=> HandlingStateT m ()
unregisterAll = do
HandlingState { .. } <- get
let newDestructors = IntMap.map (\destructor -> destructor { isRegistered = False }) destructors
put HandlingState { destructors = newDestructors, .. }
destroyUnregistered
:: Monad m
=> HandlingStateT m ()
destroyUnregistered = do
HandlingState { .. } <- get
let
(registered, unregistered) = partition isRegistered destructors
traverse (lift . action) unregistered
put HandlingState { destructors = registered, .. }
dataTypeHandling :: DataType
dataTypeHandling = mkDataType "Handling" [handlingConstr, uninitializedConstr]
handlingConstr :: Constr
handlingConstr = mkConstr dataTypeHandling "Handling" [] Prefix
uninitializedConstr :: Constr
uninitializedConstr = mkConstr dataTypeHandling "Uninitialized" [] Prefix
instance (Typeable h) => Data (Handling h) where
dataTypeOf _ = dataTypeHandling
toConstr Handling { .. } = handlingConstr
toConstr Uninitialized = uninitializedConstr
gunfold _cons nil constructor = nil Uninitialized
dataTypeDestructor :: DataType
dataTypeDestructor = mkDataType "Destructor" [ destructorConstr ]
destructorConstr :: Constr
destructorConstr = mkConstr dataTypeDestructor "Destructor" [] Prefix
instance Typeable m => Data (Destructor m) where
dataTypeOf _ = dataTypeDestructor
toConstr Destructor { .. } = destructorConstr
gunfold _ _ = error "Destructor.gunfold"