module Control.SessionTypes.Visualize (
visualize,
visualizeP,
MkDiagram
) where
import Control.SessionTypes.MonadSession
import Control.SessionTypes.Types as ST
import Diagrams.Prelude hiding (Coordinates, loc)
import Diagrams.Backend.SVG.CmdLine
import Control.Monad.State
import qualified Data.Vector as V
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable, typeRep)
visualize :: forall m ctx s r a. (MonadSession m, MkDiagram s) => m ('Cap ctx s) r a -> IO ()
visualize _ = mainWith $ mkDiagram (Proxy :: Proxy s)
visualizeP :: forall s. MkDiagram s => Proxy s -> IO ()
visualizeP p = mainWith $ mkDiagram p
type Grid = V.Vector (V.Vector Node)
newGrid :: Int -> Int -> Grid
newGrid x y = V.map (\_ -> V.replicate (x + 1) empNode) $ V.replicate (y + 1) V.empty
gridIndex :: Grid -> (Int, Int) -> Maybe Node
gridIndex g (x,y) = g V.!? y >>= \v -> v V.!? x
gridIndex' :: Grid -> (Int, Int) -> Node
gridIndex' g (x,y) = g V.! y V.! x
data Node = Node {name :: String, nodeType :: NodeType, nodeDiag :: Diagram B }
data NodeType = N_Send | N_Recv | N_B | N_Anch | N_CR | N_End | N_Emp | T | N_R | N_V | N_W deriving (Eq, Show)
data Orientation = Horizontal | Vertical
diagSize :: Double
diagSize = 1
newDiag :: String -> Diagram B
newDiag s = (text s <> circle diagSize) # fontSize (local diagSize)
pointDiag :: Diagram B
pointDiag = circle 0.01 # lw none
arrBetween_noHead :: String -> String -> Diagram B -> Diagram B
arrBetween_noHead s1 s2 d = (connectOutside' (with & arrowHead .~ noHead )) s1 s2 d
sendNode, recvNode, endNode, empNode, crNode, anchNode, offNode, selNode, rNode, vNode, wNode :: Node
sendNode = Node "" N_Send $ newDiag ":!>"
recvNode = Node "" N_Recv $ newDiag ":?>"
endNode = Node "end" N_End $ newDiag "End"
empNode = Node "" N_Emp $ newDiag "" # lw none
crNode = Node "" N_CR $ pointDiag
anchNode = Node "" N_Anch $ pointDiag
offNode = Node "" N_B $ newDiag "Off"
selNode = Node "" N_B $ newDiag "Sel"
rNode = Node "" N_R $ newDiag "R"
vNode = Node "" N_V $ newDiag "V"
wNode = Node "" N_W $ newDiag "Wk"
encase :: Node -> Node
encase (Node n nt d) = Node n nt (d <> (circle diagSize # lw none))
typeBox :: String -> Node
typeBox s = Node "" T $ newDiag s # lw none
data DState = DState {
counter :: Int,
weakenN :: Int,
loc :: (Int, Int),
diag :: Diagram B,
grid :: Grid
}
newDState :: Grid -> DState
newDState = DState 0 0 (0,0) mempty
type DiagramM a = StateT DState IO a
runDiagramM :: DState -> DiagramM a -> IO (a, DState)
runDiagramM state m = runStateT m state
gridToDiagram :: Grid -> Diagram B
gridToDiagram g = vsep (2 * diagSize) $ V.toList $ V.map (hsep (2 * diagSize) . map nodeDiag . V.toList) g
newName :: DiagramM String
newName = do
(DState n w xy d g) <- get
put (DState (n + 1) w xy d g)
return $ show n
nameNode :: Node -> DiagramM Node
nameNode (Node _ t d) = do
name <- newName
return $ Node name t $ d # named name
getNameAtCurr :: DiagramM String
getNameAtCurr = do
loc <- getLoc
grid <- getGrid
let (Node name _ _) = gridIndex' grid loc
return name
getLoc :: DiagramM (Int, Int)
getLoc = fmap loc get
saveLoc :: (Int, Int) -> DiagramM ()
saveLoc (x,y) = modify $ \(DState n w _ d g) -> DState n w (x,y) d g
incrLocY :: DiagramM ()
incrLocY = modify $ \(DState n w (x,y) d g) -> DState n w (x, y + 1) d g
decrLocY :: DiagramM ()
decrLocY = modify $ \(DState n w (x,y) d g) -> DState n w (x, y 1) d g
incrLocX :: DiagramM ()
incrLocX = modify $ \(DState n w (x,y) d g) -> DState n w (x + 1, y) d g
incrLocXWhile :: (Node -> Bool) -> DiagramM ()
incrLocXWhile f = do
incrLocX
loc <- getLoc
grid <- getGrid
let mn = gridIndex grid loc
case mn of
Nothing -> return ()
Just n | f n -> incrLocXWhile f
| otherwise -> return ()
incrWk :: DiagramM ()
incrWk = modify $ \(DState n w loc d g) -> DState n (w + 1) loc d g
decrWk :: DiagramM ()
decrWk = modify $ \(DState n w loc d g) -> DState n (w 1) loc d g
getWk :: DiagramM Int
getWk = fmap weakenN get
saveWk :: Int -> DiagramM ()
saveWk w = modify $ \(DState n _ loc d g) -> DState n w loc d g
getGrid :: DiagramM Grid
getGrid = fmap grid get
saveGrid :: Grid -> DiagramM ()
saveGrid g = modify $ \(DState n w loc d _) -> DState n w loc d g
getDiag :: DiagramM (Diagram B)
getDiag = fmap diag get
saveDiag :: Diagram B -> DiagramM ()
saveDiag d = modify $ \(DState n w loc _ g) -> DState n w loc d g
placeAtCurrM :: Node -> DiagramM ()
placeAtCurrM sn = do
loc <- getLoc
placeAtLocM sn loc
placeAtLocM :: Node -> (Int, Int) -> DiagramM ()
placeAtLocM sn loc = do
grid <- getGrid
saveGrid $ placeAtLoc sn loc grid
placeAtLoc :: Node -> (Int, Int) -> Grid -> Grid
placeAtLoc sn (x,y) grid = grid V.// [(y, (grid V.! y) V.// [(x, sn)])]
printGrid :: Grid -> IO ()
printGrid g = forM_ g $ \hv -> do
forM_ hv (\(Node n t _) -> putStr (show (n, t) ++ " "))
putStrLn ""
class MkDiagram (s :: ST k) where
mkDiagram :: Proxy s -> IO (Diagram B)
default mkDiagram :: (Coordinates s, PlaceNodes s) => Proxy s -> IO (Diagram B)
mkDiagram p = do
dstate <- dstateWNodesIO
(diag, DState n _ _ d g) <- runStateT connectGrid dstate
fmap fst $ runStateT connectRecursions (DState n 0 (0,0) diag g)
where
dstateWNodesIO = fmap snd $ runStateT (placeNodes p) (newDState $ newGrid (getX p) (getY p))
instance (Coordinates s, PlaceNodes s) => MkDiagram s
class Coordinates (s :: ST k) where
getX :: Proxy s -> Int
getY :: Proxy s -> Int
instance Coordinates r => Coordinates (a :!> r) where
getY Proxy = 2 + getY (Proxy :: Proxy r)
getX Proxy = getX (Proxy :: Proxy r)
instance Coordinates r => Coordinates (a :?> r) where
getY Proxy = 2 + getY (Proxy :: Proxy r)
getX Proxy = getX (Proxy :: Proxy r)
instance Coordinates t => Coordinates (Sel '[t]) where
getY Proxy = getY (Proxy :: Proxy t)
getX Proxy = getX (Proxy :: Proxy t)
instance (Coordinates s, Coordinates (Sel (t ': xs))) => Coordinates (Sel (s ': t ': xs)) where
getY Proxy = 1 + getY (Proxy :: Proxy s) `max` getY (Proxy :: Proxy (Sel (t ': xs)))
getX Proxy = 1 + getX (Proxy :: Proxy s) + getX (Proxy :: Proxy (Sel (t ': xs)))
instance Coordinates t => Coordinates (Off '[t]) where
getY Proxy = getY (Proxy :: Proxy t)
getX Proxy = getX (Proxy :: Proxy t)
instance (Coordinates s, Coordinates (Off (t ': xs))) => Coordinates (Off (s ': t ': xs)) where
getY Proxy = 1 + getY (Proxy :: Proxy s) `max` getY (Proxy :: Proxy (Off (t ': xs)))
getX Proxy = 1 + getX (Proxy :: Proxy s) + getX (Proxy :: Proxy (Off (t ': xs)))
instance Coordinates s => Coordinates (R s) where
getY _ = 1 + getY (Proxy :: Proxy s)
getX _ = getX (Proxy :: Proxy s)
instance Coordinates ST.V where
getY _ = 0
getX _ = 1
instance Coordinates s => Coordinates (Wk s) where
getY _ = 1 + getY (Proxy :: Proxy s)
getX _ = getX (Proxy :: Proxy s)
instance Coordinates 'Eps where
getY _ = 0
getX _ = 0
class PlaceNodes (s :: ST k) where
placeNodes :: Proxy s -> DiagramM ()
instance (Typeable a, PlaceNodes r) => PlaceNodes (a :!> r) where
placeNodes Proxy = operationDiagram sendNode (Proxy :: Proxy a) (Proxy :: Proxy r)
instance (Typeable a, PlaceNodes r) => PlaceNodes (a :?> r) where
placeNodes Proxy = operationDiagram recvNode (Proxy :: Proxy a) (Proxy :: Proxy r)
instance PlaceNodes s => PlaceNodes (Sel '[s]) where
placeNodes _ = placeNodes (Proxy :: Proxy s)
instance (Coordinates s, PlaceNodes s, PlaceNodes (Sel (t ': xs))) => PlaceNodes (Sel (s ': t ': xs)) where
placeNodes _ = branchDiagram selNode (Proxy :: Proxy s) (Proxy :: Proxy (Sel (t ': xs)))
instance PlaceNodes s => PlaceNodes (Off '[s]) where
placeNodes _ = placeNodes (Proxy :: Proxy s)
instance (Coordinates s, PlaceNodes s, PlaceNodes (Off (t ': xs))) => PlaceNodes (Off (s ': t ': xs)) where
placeNodes _ = branchDiagram offNode (Proxy :: Proxy s) (Proxy :: Proxy (Off (t ': xs)))
instance PlaceNodes s => PlaceNodes (R s) where
placeNodes p = do
rnode' <- nameNode rNode
loc <- getLoc
placeAtCurrM rnode'
incrLocY
placeNodes (Proxy :: Proxy s)
saveLoc loc
incrLocX
placeAnchors (\(x,y) -> (x + 1, y))
instance PlaceNodes ST.V where
placeNodes _ = do
vnode <- nameNode vNode
placeAtCurrM vnode
incrLocX
anchnode <- nameNode anchNode
placeAtCurrM $ encase anchnode
instance PlaceNodes s => PlaceNodes (Wk s) where
placeNodes _ = do
wnode <- nameNode wNode
placeAtCurrM wnode
incrLocY
placeNodes (Proxy :: Proxy s)
instance PlaceNodes 'Eps where
placeNodes Proxy = do
end <- nameNode endNode
placeAtCurrM end
return ()
operationDiagram :: (Typeable a, PlaceNodes r) => Node -> Proxy a -> Proxy r -> DiagramM ()
operationDiagram node pr1 pr2 = do
tb <- nameNode $ typeBox $ show $ typeRep pr1
nnode <- nameNode node
placeAtCurrM tb
incrLocY
placeAtCurrM nnode
incrLocY
placeNodes pr2
branchDiagram :: (Coordinates s, PlaceNodes s, PlaceNodes r) => Node -> Proxy s -> Proxy r -> DiagramM ()
branchDiagram n pr1 pr2 = do
br <- nameNode n
cr <- nameNode crNode
placeAtCurrM br
(x,y) <- getLoc
incrLocY
placeNodes pr1
saveLoc (x + getX pr1 + 1, y)
placeAtCurrM (encase cr)
incrLocY
placeNodes pr2
placeAnchors :: ((Int, Int) -> (Int, Int)) -> DiagramM ()
placeAnchors move = do
loc <- getLoc
g <- getGrid
let mn = gridIndex g loc
case mn of
Nothing -> return ()
Just n | nodeType n == N_Emp -> do
nn <- nameNode anchNode
placeAtCurrM (encase nn)
saveLoc (move loc)
placeAnchors move
| otherwise -> return ()
connectGrid :: DiagramM (Diagram B)
connectGrid = do
grid <- getGrid
addConn $ gridToDiagram grid
where
addConn d = do
grid <- getGrid
walkGrid (0,0) connectNodes grid d
connectNodes :: Node -> Node -> Orientation -> Diagram B -> DiagramM (Diagram B)
connectNodes (Node n1 t1 d1) (Node n2 t2 d2) Horizontal d
| t1 == N_B && t2 == N_CR = return $ (d # arrBetween_noHead n1 n2)
| otherwise = return d
connectNodes (Node n1 t1 _) (Node n2 t2 _) Vertical d
| t2 /= N_CR
&& t1 /= N_Emp = return $ d # connectOutside n1 n2
| otherwise = return d
walkGrid :: (Int, Int) -> (Node -> Node -> Orientation -> Diagram B -> DiagramM (Diagram B)) -> Grid -> Diagram B -> DiagramM (Diagram B)
walkGrid (x,y) f g d = tryVertical d >>= tryHorizontal (x,y)
where
currNode = gridIndex' g (x,y)
tryHorizontal (x',y') d = do
case gridIndex g (x' + 1,y') of
Nothing -> return d
Just sn | nodeType sn == N_Anch || nodeType sn == N_Emp -> tryHorizontal (x' + 1, y) d
| nodeType sn == N_CR -> do
d' <- f currNode sn Horizontal d
walkGrid (x' + 1, y') f g d'
| otherwise -> return d
tryVertical d = case gridIndex g (x, y + 1) of
Nothing -> return d
Just sn -> do
d' <- f currNode sn Vertical d
walkGrid (x, y + 1) f g d'
connectRecursions :: DiagramM (Diagram B)
connectRecursions = do
pos <- getLoc
grid <- getGrid
let (Node name nt _) = gridIndex' grid pos
case nt of
N_V -> do
incrLocX
backTrack name
getDiag
N_B -> do
incrLocY
d <- connectRecursions
saveDiag d
saveLoc pos
incrLocXWhile (\(Node _ nt _) -> nt /= N_CR)
connectRecursions
N_W -> do
incrLocY
incrWk
wk <- getWk
connectRecursions
decrWk
getDiag
N_End -> getDiag
_ -> do
incrLocY
connectRecursions
backTrack :: String -> DiagramM ()
backTrack name = do
grid <- getGrid
pos <- getLoc
cname <- getNameAtCurr
goUp cname
saveLoc pos
where
goUp cname = do
ms <- rToLeft
case ms of
Nothing -> do
decrLocY
goUp cname
Just rname -> do
wkC <- getWk
if wkC == 0
then do
cname' <- getNameAtCurr
d <- getDiag
saveDiag (d # arrBetween_noHead name cname
# arrBetween_noHead cname cname'
# connectOutside cname' rname)
else do
decrWk
decrLocY
goUp cname
saveWk wkC
rToLeft :: DiagramM (Maybe String)
rToLeft = do
(x,y) <- getLoc
grid <- getGrid
let mnode = gridIndex grid (x,y)
mn <- case mnode of
Nothing -> return Nothing
Just (Node name nt _)
| nt == N_R -> return $ Just name
| nt == N_Anch || nt == N_Emp -> do
saveLoc (x1, y)
ms <- rToLeft
return ms
| otherwise -> return Nothing
saveLoc (x, y)
return mn