2016-02-04 11:19:08 +03:00
|
|
|
{-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, TypeFamilies #-}
|
|
|
|
module Translate(
|
|
|
|
translateString
|
|
|
|
) where
|
|
|
|
|
|
|
|
import qualified Diagrams.Prelude as DIA
|
2016-02-05 08:53:21 +03:00
|
|
|
import Diagrams.Prelude((<>))
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-19 09:51:16 +03:00
|
|
|
import Language.Haskell.Exts(Decl(..), parseDecl, Name(..), Pat(..), Rhs(..),
|
|
|
|
Exp(..), QName(..), fromParseResult, Match(..), QOp(..), GuardedRhs(..),
|
2016-02-21 05:47:56 +03:00
|
|
|
Stmt(..), Binds(..))
|
2016-02-19 07:34:08 +03:00
|
|
|
import qualified Language.Haskell.Exts as Exts
|
2016-02-06 08:07:06 +03:00
|
|
|
import Control.Monad.State(State, evalState)
|
2016-02-18 04:31:11 +03:00
|
|
|
import Data.List(partition)
|
2016-02-18 05:51:03 +03:00
|
|
|
import qualified Control.Arrow
|
2016-02-21 05:47:56 +03:00
|
|
|
import Debug.Trace
|
2016-02-22 02:15:16 +03:00
|
|
|
import Data.Either(partitionEithers)
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-08 05:01:57 +03:00
|
|
|
import Types(Icon, Edge(..), Drawing(..), NameAndPort(..), IDState,
|
2016-02-06 08:07:06 +03:00
|
|
|
initialIdState, getId)
|
2016-02-08 05:01:57 +03:00
|
|
|
import Util(toNames, noEnds, nameAndPort, justName, fromMaybeError)
|
2016-02-04 11:19:08 +03:00
|
|
|
import Icons(Icon(..))
|
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
type Reference = Either String NameAndPort
|
2016-02-21 07:15:40 +03:00
|
|
|
-- | An IconGraph is a normal Drawing (Icons, Edges, and sub Drawings) with two additional fields:
|
|
|
|
-- unconected sink ports (varible usage), and unconnected source ports (varible definition).
|
|
|
|
data IconGraph = IconGraph [(DIA.Name, Icon)] [Edge] [(DIA.Name, Drawing)] [(String, NameAndPort)] [(String, Reference)]
|
2016-02-21 05:47:56 +03:00
|
|
|
deriving (Show)
|
2016-02-08 05:01:57 +03:00
|
|
|
|
|
|
|
type EvalContext = [String]
|
2016-02-21 06:22:09 +03:00
|
|
|
type GraphAndRef = (IconGraph, Reference)
|
2016-02-05 08:53:21 +03:00
|
|
|
|
|
|
|
instance DIA.Semigroup IconGraph where
|
2016-02-21 07:15:40 +03:00
|
|
|
(IconGraph icons1 edges1 subDrawings1 sinks1 sources1) <> (IconGraph icons2 edges2 subDrawings2 sinks2 sources2) =
|
|
|
|
IconGraph (icons1 <> icons2) (edges1 <> edges2) (subDrawings1 <> subDrawings2) (sinks1 <> sinks2) (sources1 <> sources2)
|
2016-02-05 08:53:21 +03:00
|
|
|
|
|
|
|
instance Monoid IconGraph where
|
2016-02-21 07:15:40 +03:00
|
|
|
mempty = IconGraph mempty mempty mempty mempty mempty
|
2016-02-05 08:53:21 +03:00
|
|
|
mappend = (<>)
|
|
|
|
|
2016-02-21 07:15:40 +03:00
|
|
|
iconGraphFromIcons :: [(DIA.Name, Icon)] -> IconGraph
|
|
|
|
iconGraphFromIcons icons = IconGraph icons mempty mempty mempty mempty
|
|
|
|
|
|
|
|
iconGraphFromIconsEdges :: [(DIA.Name, Icon)] -> [Edge] -> IconGraph
|
|
|
|
iconGraphFromIconsEdges icons edges = IconGraph icons edges mempty mempty mempty
|
|
|
|
|
2016-02-18 10:14:14 +03:00
|
|
|
getUniqueName :: String -> State IDState String
|
|
|
|
getUniqueName base = fmap ((base ++). show) getId
|
|
|
|
|
2016-02-05 08:53:21 +03:00
|
|
|
nameToString :: Language.Haskell.Exts.Name -> String
|
2016-02-04 11:19:08 +03:00
|
|
|
nameToString (Ident s) = s
|
|
|
|
nameToString (Symbol s) = s
|
|
|
|
|
2016-02-23 00:26:47 +03:00
|
|
|
evalPApp :: QName -> [Pat] -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalPApp name patterns = do
|
|
|
|
patName <- DIA.toName <$> getUniqueName "pat"
|
|
|
|
let
|
|
|
|
context = mempty
|
|
|
|
evaledPatterns <- mapM evalPattern patterns
|
|
|
|
let
|
|
|
|
constructorName = evalQName name context
|
|
|
|
gr = makeApplyGraph True patName constructorName evaledPatterns (length evaledPatterns)
|
|
|
|
pure gr
|
2016-02-22 07:26:12 +03:00
|
|
|
|
2016-02-23 00:26:47 +03:00
|
|
|
|
|
|
|
evalPattern :: Pat -> State IDState GraphAndRef
|
2016-02-04 11:19:08 +03:00
|
|
|
evalPattern p = case p of
|
2016-02-23 00:26:47 +03:00
|
|
|
PVar n -> pure (mempty, Left $ nameToString n)
|
|
|
|
PApp name patterns -> fmap Right <$> evalPApp name patterns
|
|
|
|
PParen pat -> evalPattern pat
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalQName :: QName -> EvalContext -> (IconGraph, Reference)
|
2016-02-08 05:01:57 +03:00
|
|
|
evalQName (UnQual n) context = result where
|
2016-02-05 08:53:21 +03:00
|
|
|
nameString = nameToString n
|
2016-02-21 07:15:40 +03:00
|
|
|
graph = iconGraphFromIcons [(DIA.toName nameString, TextBoxIcon nameString)]
|
2016-02-08 05:01:57 +03:00
|
|
|
result = if nameString `elem` context
|
2016-02-21 06:22:09 +03:00
|
|
|
then (mempty, Left nameString)
|
|
|
|
else (graph, Right $ justName nameString)
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalQOp :: QOp -> EvalContext -> (IconGraph, Reference)
|
2016-02-19 09:07:38 +03:00
|
|
|
evalQOp (QVarOp n) = evalQName n
|
|
|
|
evalQOp (QConOp n) = evalQName n
|
|
|
|
|
2016-02-23 00:26:47 +03:00
|
|
|
combineExpressions :: Bool -> [((IconGraph, Reference), NameAndPort)] -> IconGraph
|
|
|
|
combineExpressions inPattern portExpPairs = mconcat $ fmap mkGraph portExpPairs where
|
2016-02-21 06:22:09 +03:00
|
|
|
mkGraph ((graph, ref), port) = graph <> case ref of
|
2016-02-23 00:26:47 +03:00
|
|
|
Left str -> if inPattern
|
|
|
|
then IconGraph mempty mempty mempty mempty [(str, Right port)]
|
|
|
|
else IconGraph mempty mempty mempty [(str, port)] mempty
|
2016-02-21 07:15:40 +03:00
|
|
|
Right resultPort -> IconGraph mempty [Edge (resultPort, port) noEnds] mempty mempty mempty
|
2016-02-18 02:36:57 +03:00
|
|
|
|
2016-02-23 00:26:47 +03:00
|
|
|
makeApplyGraph :: Bool -> DIA.Name -> (IconGraph, Reference) -> [(IconGraph, Reference)] -> Int -> (IconGraph, NameAndPort)
|
|
|
|
makeApplyGraph inPattern applyIconName funVal argVals numArgs = (newGraph <> combinedGraph, nameAndPort applyIconName 1)
|
2016-02-19 09:07:38 +03:00
|
|
|
where
|
|
|
|
argumentPorts = map (nameAndPort applyIconName) [2,3..]
|
|
|
|
functionPort = nameAndPort applyIconName 0
|
2016-02-23 00:26:47 +03:00
|
|
|
combinedGraph = combineExpressions inPattern $ zip (funVal:argVals) (functionPort:argumentPorts)
|
2016-02-19 09:07:38 +03:00
|
|
|
icons = [(applyIconName, Apply0NIcon numArgs)]
|
2016-02-21 07:15:40 +03:00
|
|
|
newGraph = iconGraphFromIcons icons
|
2016-02-19 09:07:38 +03:00
|
|
|
|
2016-02-19 02:03:31 +03:00
|
|
|
evalApp :: (Exp, [Exp]) -> EvalContext -> State IDState (IconGraph, NameAndPort)
|
2016-02-18 07:59:43 +03:00
|
|
|
evalApp (funExp, argExps) c = do
|
2016-02-10 05:58:28 +03:00
|
|
|
funVal <- evalExp c funExp
|
|
|
|
argVals <- mapM (evalExp c) argExps
|
2016-02-18 10:14:14 +03:00
|
|
|
applyIconName <- DIA.toName <$> getUniqueName "app0"
|
2016-02-23 00:26:47 +03:00
|
|
|
pure $ makeApplyGraph False applyIconName funVal argVals (length argExps)
|
2016-02-19 09:07:38 +03:00
|
|
|
|
|
|
|
evalInfixApp :: EvalContext -> Exp -> QOp -> Exp -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalInfixApp c e1 op e2 = do
|
|
|
|
argVals <- mapM (evalExp c) [e1, e2]
|
|
|
|
applyIconName <- DIA.toName <$> getUniqueName "app0"
|
|
|
|
let funVal = evalQOp op c
|
2016-02-23 00:26:47 +03:00
|
|
|
pure $ makeApplyGraph False applyIconName funVal argVals 2
|
2016-02-10 05:58:28 +03:00
|
|
|
|
|
|
|
-- TODO add test for this function
|
|
|
|
simplifyApp :: Exp -> (Exp, [Exp])
|
|
|
|
simplifyApp (App exp1 exp2) = (funExp, args <> [exp2])
|
|
|
|
where
|
|
|
|
(funExp, args) = simplifyApp exp1
|
|
|
|
simplifyApp e = (e, [])
|
2016-02-06 08:07:06 +03:00
|
|
|
|
2016-02-18 10:14:14 +03:00
|
|
|
evalIf :: EvalContext -> Exp -> Exp -> Exp -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalIf c e1 e2 e3 = do
|
|
|
|
e1Val <- evalExp c e1
|
|
|
|
e2Val <- evalExp c e2
|
|
|
|
e3Val <- evalExp c e3
|
|
|
|
guardName <- DIA.toName <$> getUniqueName "if"
|
|
|
|
let
|
|
|
|
icons = [(guardName, GuardIcon 2)]
|
|
|
|
combinedGraph =
|
2016-02-23 00:26:47 +03:00
|
|
|
combineExpressions False $ zip [e1Val, e2Val, e3Val] (map (nameAndPort guardName) [3, 2, 4])
|
2016-02-21 07:15:40 +03:00
|
|
|
newGraph = iconGraphFromIcons icons <> combinedGraph
|
2016-02-18 10:14:14 +03:00
|
|
|
pure (newGraph, NameAndPort guardName (Just 0))
|
2016-02-18 02:36:57 +03:00
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalStmt :: EvalContext -> Stmt -> State IDState GraphAndRef
|
2016-02-19 09:51:16 +03:00
|
|
|
evalStmt c (Qualifier e) = evalExp c e
|
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalStmts :: EvalContext -> [Stmt] -> State IDState GraphAndRef
|
2016-02-19 09:51:16 +03:00
|
|
|
evalStmts c [stmt] = evalStmt c stmt
|
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalGuaredRhs :: EvalContext -> GuardedRhs -> State IDState (GraphAndRef, GraphAndRef)
|
2016-02-19 09:51:16 +03:00
|
|
|
evalGuaredRhs c (GuardedRhs _ stmts e) = do
|
|
|
|
expVal <- evalExp c e
|
|
|
|
stmtsVal <- evalStmts c stmts
|
|
|
|
pure (stmtsVal, expVal)
|
|
|
|
|
|
|
|
evalGuardedRhss :: EvalContext -> [GuardedRhs] -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalGuardedRhss c rhss = do
|
|
|
|
guardName <- DIA.toName <$> getUniqueName "guard"
|
|
|
|
evaledRhss <- mapM (evalGuaredRhs c) rhss
|
|
|
|
let
|
|
|
|
(bools, exps) = unzip evaledRhss
|
|
|
|
expsWithPorts = zip exps $ map (nameAndPort guardName) [2,4..]
|
|
|
|
boolsWithPorts = zip bools $ map (nameAndPort guardName) [3,5..]
|
2016-02-23 00:26:47 +03:00
|
|
|
combindedGraph = combineExpressions False $ expsWithPorts <> boolsWithPorts
|
2016-02-19 09:51:16 +03:00
|
|
|
icons = [(guardName, GuardIcon (length rhss))]
|
2016-02-21 07:15:40 +03:00
|
|
|
newGraph = iconGraphFromIcons icons <> combindedGraph
|
2016-02-19 09:51:16 +03:00
|
|
|
pure (newGraph, NameAndPort guardName (Just 0))
|
|
|
|
|
2016-02-20 00:46:14 +03:00
|
|
|
makeLiteral :: (Show x) => x -> State IDState (IconGraph, NameAndPort)
|
|
|
|
makeLiteral x = do
|
2016-02-19 07:34:08 +03:00
|
|
|
let str = show x
|
|
|
|
name <- DIA.toName <$> getUniqueName str
|
2016-02-21 07:15:40 +03:00
|
|
|
let graph = iconGraphFromIcons [(DIA.toName name, TextBoxIcon str)]
|
2016-02-19 07:34:08 +03:00
|
|
|
pure (graph, justName name)
|
|
|
|
|
2016-02-20 00:46:14 +03:00
|
|
|
evalLit :: Exts.Literal -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalLit (Exts.Int x) = makeLiteral x
|
|
|
|
evalLit (Exts.Char x) = makeLiteral x
|
|
|
|
evalLit (Exts.String x) = makeLiteral x
|
|
|
|
-- TODO: Print the Rational as a floating point.
|
|
|
|
evalLit (Exts.Frac x) = makeLiteral x
|
|
|
|
-- TODO: Test the unboxed literals
|
|
|
|
evalLit (Exts.PrimInt x) = makeLiteral x
|
|
|
|
evalLit (Exts.PrimWord x) = makeLiteral x
|
|
|
|
evalLit (Exts.PrimFloat x) = makeLiteral x
|
|
|
|
evalLit (Exts.PrimDouble x) = makeLiteral x
|
|
|
|
evalLit (Exts.PrimChar x) = makeLiteral x
|
|
|
|
evalLit (Exts.PrimString x) = makeLiteral x
|
|
|
|
|
2016-02-22 07:26:12 +03:00
|
|
|
namesInPattern :: GraphAndRef -> [String]
|
2016-02-23 00:26:47 +03:00
|
|
|
namesInPattern (_, Left str) = [str]
|
|
|
|
namesInPattern (IconGraph _ _ _ _ bindings, Right _) = fmap fst bindings
|
2016-02-22 07:26:12 +03:00
|
|
|
|
|
|
|
getBoundVarName :: Decl -> [String]
|
2016-02-23 00:26:47 +03:00
|
|
|
-- TODO Should evalState be used here?
|
|
|
|
getBoundVarName (PatBind _ pat _ _) = namesInPattern $ evalState (evalPattern pat) initialIdState
|
2016-02-22 07:26:12 +03:00
|
|
|
getBoundVarName (FunBind [Match _ name _ _ _ _]) = [nameToString name]
|
2016-02-21 05:47:56 +03:00
|
|
|
|
2016-02-22 02:15:16 +03:00
|
|
|
--TODO: Should this call makeEdges?
|
2016-02-21 09:35:13 +03:00
|
|
|
evalBinds :: EvalContext -> Binds -> State IDState (IconGraph, EvalContext)
|
2016-02-21 05:47:56 +03:00
|
|
|
evalBinds c (BDecls decls) = do
|
|
|
|
let
|
2016-02-22 07:26:12 +03:00
|
|
|
boundNames = concatMap getBoundVarName decls
|
2016-02-21 05:47:56 +03:00
|
|
|
augmentedContext = boundNames <> c
|
2016-02-21 09:35:13 +03:00
|
|
|
evaledDecl <- mconcat <$> mapM (evalDecl augmentedContext) decls
|
|
|
|
pure (evaledDecl, augmentedContext)
|
2016-02-21 05:47:56 +03:00
|
|
|
|
|
|
|
printSelf :: (Show a) => a -> a
|
|
|
|
printSelf a = Debug.Trace.trace (show a ++ "\n\n") a
|
|
|
|
|
2016-02-21 10:07:46 +03:00
|
|
|
-- | Recursivly find the matching reference in a list of bindings.
|
2016-02-21 11:38:06 +03:00
|
|
|
-- TODO: Might want to present some indication if there is a reference cycle.
|
2016-02-21 09:35:13 +03:00
|
|
|
lookupReference :: [(String, Reference)] -> Reference -> Reference
|
2016-02-22 02:15:16 +03:00
|
|
|
lookupReference _ ref@(Right _) = ref
|
2016-02-21 11:38:06 +03:00
|
|
|
lookupReference bindings ref@(Left originalS) = lookupHelper ref where
|
2016-02-22 02:15:16 +03:00
|
|
|
lookupHelper newRef@(Right _) = newRef
|
|
|
|
lookupHelper newRef@(Left s)= case lookup s bindings of
|
2016-02-21 11:38:06 +03:00
|
|
|
Just r -> failIfCycle r $ lookupHelper r
|
2016-02-22 02:15:16 +03:00
|
|
|
Nothing -> newRef
|
2016-02-21 11:38:06 +03:00
|
|
|
where
|
|
|
|
failIfCycle r@(Left newStr) res = if newStr == originalS then r else res
|
|
|
|
failIfCycle _ res = res
|
2016-02-21 09:35:13 +03:00
|
|
|
|
|
|
|
deleteBindings :: IconGraph -> IconGraph
|
|
|
|
deleteBindings (IconGraph a b c d _) = IconGraph a b c d mempty
|
|
|
|
|
2016-02-22 02:15:16 +03:00
|
|
|
makeEdges :: IconGraph -> IconGraph
|
|
|
|
makeEdges (IconGraph icons edges c sinks bindings) = newGraph where
|
|
|
|
(newSinks, newEdges) = partitionEithers $ fmap renameOrMakeEdge sinks
|
|
|
|
newGraph = IconGraph icons (newEdges <> edges) c newSinks bindings
|
|
|
|
|
|
|
|
renameOrMakeEdge :: (String, NameAndPort) -> Either (String, NameAndPort) Edge
|
|
|
|
renameOrMakeEdge orig@(s, destPort) = case lookup s bindings of
|
2016-02-21 10:07:46 +03:00
|
|
|
Just ref -> case lookupReference bindings ref of
|
2016-02-22 02:15:16 +03:00
|
|
|
(Right sourcePort) -> Right $ Edge (sourcePort, destPort) noEnds
|
|
|
|
(Left newStr) -> Left (newStr, destPort)
|
|
|
|
Nothing -> Left orig
|
|
|
|
|
2016-02-22 06:34:33 +03:00
|
|
|
evalGeneralLet :: (EvalContext -> State IDState (IconGraph, Reference)) -> EvalContext -> Binds -> State IDState (IconGraph, Reference)
|
|
|
|
evalGeneralLet expOrRhsEvaler c bs = do
|
2016-02-21 09:35:13 +03:00
|
|
|
(bindGraph, bindContext) <- evalBinds c bs
|
2016-02-22 06:34:33 +03:00
|
|
|
expVal <- expOrRhsEvaler bindContext
|
2016-02-21 05:47:56 +03:00
|
|
|
let
|
2016-02-21 09:35:13 +03:00
|
|
|
(expGraph, expResult) = expVal
|
2016-02-22 02:15:16 +03:00
|
|
|
newGraph = deleteBindings . makeEdges $ expGraph <> bindGraph
|
|
|
|
(IconGraph _ _ _ _ bindings) = bindGraph
|
|
|
|
pure $ printSelf (newGraph, lookupReference bindings expResult)
|
2016-02-20 00:46:14 +03:00
|
|
|
|
2016-02-22 06:34:33 +03:00
|
|
|
evalLet :: EvalContext -> Binds -> Exp -> State IDState (IconGraph, Reference)
|
|
|
|
evalLet context binds e = evalGeneralLet (`evalExp` e) context binds
|
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
evalExp :: EvalContext -> Exp -> State IDState (IconGraph, Reference)
|
2016-02-10 05:58:28 +03:00
|
|
|
evalExp c x = case x of
|
2016-02-08 05:01:57 +03:00
|
|
|
Var n -> pure $ evalQName n c
|
2016-02-23 00:26:47 +03:00
|
|
|
Con n -> pure $ evalQName n c
|
2016-02-21 06:22:09 +03:00
|
|
|
Lit l -> fmap Right <$> evalLit l
|
|
|
|
InfixApp e1 op e2 -> fmap Right <$> evalInfixApp c e1 op e2
|
|
|
|
e@App{} -> fmap Right <$> evalApp (simplifyApp e) c
|
|
|
|
Lambda _ patterns e -> fmap Right <$> evalLambda c patterns e
|
2016-02-21 09:35:13 +03:00
|
|
|
Let bs e -> evalLet c bs e
|
2016-02-21 06:22:09 +03:00
|
|
|
If e1 e2 e3 -> fmap Right <$> evalIf c e1 e2 e3
|
2016-02-21 05:47:56 +03:00
|
|
|
Paren e -> evalExp c e
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-10 09:29:07 +03:00
|
|
|
-- | This is used by the rhs for identity (eg. y x = x)
|
|
|
|
makeDummyRhs :: String -> (IconGraph, NameAndPort)
|
|
|
|
makeDummyRhs s = (graph, port) where
|
2016-02-21 07:15:40 +03:00
|
|
|
graph = IconGraph icons mempty mempty [(s, justName s)] mempty
|
2016-02-10 09:29:07 +03:00
|
|
|
icons = [(DIA.toName s, BranchIcon)]
|
|
|
|
port = justName s
|
|
|
|
|
2016-02-21 06:22:09 +03:00
|
|
|
coerceExpressionResult :: (IconGraph, Reference) -> (IconGraph, NameAndPort)
|
|
|
|
coerceExpressionResult (_, Left str) = makeDummyRhs str
|
|
|
|
coerceExpressionResult (g, Right x) = (g, x)
|
2016-02-18 02:36:57 +03:00
|
|
|
|
2016-02-08 05:01:57 +03:00
|
|
|
-- | First argument is the right hand side.
|
|
|
|
-- The second arugement is a list of strings that are bound in the environment.
|
2016-02-21 06:22:09 +03:00
|
|
|
evalRhs :: Rhs -> EvalContext -> State IDState (IconGraph, Reference)
|
2016-02-21 05:47:56 +03:00
|
|
|
evalRhs (UnGuardedRhs e) c = evalExp c e
|
2016-02-21 06:22:09 +03:00
|
|
|
evalRhs (GuardedRhss rhss) c = fmap Right <$> evalGuardedRhss c rhss
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-21 05:47:56 +03:00
|
|
|
evalPatBind :: EvalContext -> Decl -> State IDState IconGraph
|
2016-02-23 00:26:47 +03:00
|
|
|
evalPatBind c (PatBind _ pat rhs maybeWhereBinds) = do
|
|
|
|
patternNames <- printSelf . namesInPattern <$> evalPattern pat
|
|
|
|
let
|
2016-02-22 07:26:12 +03:00
|
|
|
rhsContext = patternNames <> c
|
2016-02-23 00:26:47 +03:00
|
|
|
(rhsGraph, rhsRef) <- case maybeWhereBinds of
|
|
|
|
Nothing -> evalRhs rhs rhsContext
|
|
|
|
Just b -> evalGeneralLet (evalRhs rhs) rhsContext b
|
2016-02-08 05:01:57 +03:00
|
|
|
|
2016-02-23 00:26:47 +03:00
|
|
|
(patGraph, patRef) <- evalPattern pat
|
|
|
|
let
|
|
|
|
(newEdges, newSinks, bindings) = case patRef of
|
|
|
|
(Left s) -> (mempty, mempty, [(s, rhsRef)])
|
|
|
|
(Right patPort) -> case rhsRef of
|
|
|
|
(Left rhsStr) -> (mempty, [(rhsStr, patPort)], mempty)
|
|
|
|
-- TODO: This edge should be special to indicate that one side is a pattern.
|
|
|
|
(Right rhsPort) -> ([Edge (rhsPort, patPort) noEnds], mempty, mempty)
|
|
|
|
gr = IconGraph mempty newEdges mempty newSinks bindings
|
|
|
|
pure .printSelf. makeEdges $ (gr <> rhsGraph <> patGraph)
|
2016-02-22 06:34:33 +03:00
|
|
|
|
2016-02-08 05:01:57 +03:00
|
|
|
iconGraphToDrawing :: IconGraph -> Drawing
|
2016-02-21 07:15:40 +03:00
|
|
|
iconGraphToDrawing (IconGraph icons edges subDrawings _ _) = Drawing icons edges subDrawings
|
2016-02-08 05:01:57 +03:00
|
|
|
|
2016-02-18 05:51:03 +03:00
|
|
|
--processPatterns :: DIA.IsName a => a -> [Pat] -> ([(String, NameAndPort)], [String], Int)
|
|
|
|
processPatterns :: DIA.IsName a => a -> [Pat] -> [(String, NameAndPort)] -> ([(String, NameAndPort)], [String], Int)
|
|
|
|
processPatterns lambdaName patterns extraVars =
|
|
|
|
(patternStringMap, patternStrings, numParameters)
|
|
|
|
where
|
|
|
|
lambdaPorts = map (nameAndPort lambdaName) [0,1..]
|
2016-02-22 07:26:12 +03:00
|
|
|
-- TODO this is wrong and must be rewritten for more complex patterns. (perhaps use makeEdges)
|
2016-02-23 00:26:47 +03:00
|
|
|
patternStringMap = extraVars <> zip (map (head . namesInPattern. (`evalState` initialIdState) .evalPattern) patterns) lambdaPorts
|
2016-02-18 05:51:03 +03:00
|
|
|
patternStrings = map fst patternStringMap
|
|
|
|
numParameters = length patterns
|
|
|
|
|
|
|
|
makeRhsDrawing :: DIA.IsName a => a -> (IconGraph, NameAndPort) -> Drawing
|
|
|
|
makeRhsDrawing resultIconName (rhsGraph, rhsResult)= rhsDrawing where
|
|
|
|
rhsNewIcons = toNames [(resultIconName, ResultIcon)]
|
|
|
|
rhsNewEdges = [Edge (rhsResult, justName resultIconName) noEnds]
|
2016-02-21 07:15:40 +03:00
|
|
|
rhsGraphWithResult = rhsGraph <> iconGraphFromIconsEdges rhsNewIcons rhsNewEdges
|
2016-02-18 05:51:03 +03:00
|
|
|
rhsDrawing = iconGraphToDrawing rhsGraphWithResult
|
|
|
|
|
|
|
|
qualifyNameAndPort :: String -> NameAndPort -> NameAndPort
|
|
|
|
qualifyNameAndPort s (NameAndPort n p) = NameAndPort (s DIA..> n) p
|
|
|
|
|
|
|
|
boundVarsToEdge :: Eq a => [(a, NameAndPort)] -> (a, NameAndPort) -> Edge
|
|
|
|
boundVarsToEdge patternStringMap (s, np) = Edge (source, np) noEnds where
|
|
|
|
source = fromMaybeError "boundVarsToEdge: bound var not found" $ lookup s patternStringMap
|
|
|
|
|
2016-02-21 05:47:56 +03:00
|
|
|
--TODO: I think this will loop on recursive references (eg. ("a", Left "a"))
|
|
|
|
-- simplifyReferences :: [(String, Reference)] -> [(String, Reference)] -> [(String, NameAndPort)]
|
|
|
|
-- simplifyReferences extraBounds ls = map lookupReference ls where
|
|
|
|
-- augmentedLs = extraBounds <> ls
|
|
|
|
-- lookupReference (str, Right n@(NameAndPort _ _)) = (str, n)
|
|
|
|
-- lookupReference v@(str, Left n) = case lookup n augmentedLs of
|
|
|
|
-- Just x -> lookupReference (str, x)
|
|
|
|
-- Nothing -> error $ "Could not find reference. ls =" ++ show ls ++ "\nv=" ++ show v
|
|
|
|
|
2016-02-18 05:51:03 +03:00
|
|
|
makeInternalEdges :: Foldable t => String -> IconGraph -> t String -> [(String, NameAndPort)] -> ([Edge], [(String, NameAndPort)])
|
|
|
|
makeInternalEdges lambdaName rhsGraph patternStrings patternStringMap = (internalEdges, unmatchedBoundVars) where
|
2016-02-21 07:15:40 +03:00
|
|
|
(IconGraph _ _ _ boundVars _) = rhsGraph
|
2016-02-18 05:51:03 +03:00
|
|
|
qualifiedBoundVars =
|
|
|
|
fmap (Control.Arrow.second (qualifyNameAndPort lambdaName)) boundVars
|
|
|
|
(matchedBoundVars, unmatchedBoundVars) = partition (\(s, _) -> s `elem` patternStrings) qualifiedBoundVars
|
|
|
|
internalEdges = fmap (boundVarsToEdge patternStringMap) matchedBoundVars
|
|
|
|
|
|
|
|
evalLambda :: EvalContext -> [Pat] -> Exp -> State IDState (IconGraph, NameAndPort)
|
|
|
|
evalLambda c patterns e = do
|
|
|
|
lambdaName <- getUniqueName "lam"
|
|
|
|
let
|
|
|
|
(patternStringMap, patternStrings, numParameters) = processPatterns lambdaName patterns []
|
|
|
|
augmentedContext = patternStrings <> c
|
|
|
|
rhsVal <- evalExp augmentedContext e
|
|
|
|
resultIconName <- getUniqueName "res"
|
|
|
|
rhsDrawingName <- DIA.toName <$> getUniqueName "rhsDraw"
|
|
|
|
let
|
2016-02-21 05:47:56 +03:00
|
|
|
-- TODO remove coerceExpressionResult here
|
2016-02-18 05:51:03 +03:00
|
|
|
rhsCoercedVal@(rhsGraph, _) = coerceExpressionResult rhsVal
|
|
|
|
rhsDrawing = makeRhsDrawing resultIconName rhsCoercedVal
|
|
|
|
icons = toNames [(lambdaName, LambdaRegionIcon numParameters rhsDrawingName)]
|
|
|
|
(internalEdges, unmatchedBoundVars) =
|
|
|
|
makeInternalEdges lambdaName rhsGraph patternStrings patternStringMap
|
2016-02-21 07:15:40 +03:00
|
|
|
drawing = IconGraph icons internalEdges [(rhsDrawingName, rhsDrawing)] unmatchedBoundVars mempty
|
2016-02-18 05:51:03 +03:00
|
|
|
pure (drawing, justName lambdaName)
|
|
|
|
|
2016-02-23 02:45:53 +03:00
|
|
|
makePatternEdges :: String -> GraphAndRef -> NameAndPort -> Either IconGraph (String, Reference)
|
|
|
|
makePatternEdges lambdaName (_, Right patPort) lamPort =
|
|
|
|
Left $ IconGraph mempty [Edge (lamPort, qualifyNameAndPort lambdaName patPort) noEnds] mempty mempty mempty
|
|
|
|
-- TODO case where pattern is a String
|
|
|
|
makePatternEdges _ (_, Left str) lamPort = Right (str, Right lamPort)
|
2016-02-21 08:26:25 +03:00
|
|
|
-- TODO handle inner function definitions.
|
2016-02-21 05:47:56 +03:00
|
|
|
evalMatch :: EvalContext -> Match -> State IDState IconGraph
|
|
|
|
evalMatch c (Match _ name patterns _ rhs _) = do
|
2016-02-18 07:59:43 +03:00
|
|
|
lambdaName <- getUniqueName "lam"
|
|
|
|
let
|
2016-02-08 05:01:57 +03:00
|
|
|
nameString = nameToString name
|
2016-02-18 05:51:03 +03:00
|
|
|
extraVars = [(nameString, justName lambdaName)]
|
|
|
|
(patternStringMap, patternStrings, numParameters) =
|
|
|
|
processPatterns lambdaName patterns extraVars
|
2016-02-21 05:47:56 +03:00
|
|
|
-- TODO remove coerceExpressionResult here
|
|
|
|
rhsVal@(rhsGraph, _) <- coerceExpressionResult <$> evalRhs rhs (patternStrings <> c)
|
2016-02-18 07:59:43 +03:00
|
|
|
resultIconName <- getUniqueName "res"
|
|
|
|
rhsDrawingName <- DIA.toName <$> getUniqueName "rhsDraw"
|
|
|
|
let
|
2016-02-18 05:51:03 +03:00
|
|
|
rhsDrawing = makeRhsDrawing resultIconName rhsVal
|
2016-02-08 05:01:57 +03:00
|
|
|
icons = toNames [
|
2016-02-23 02:45:53 +03:00
|
|
|
(lambdaName, LambdaRegionIcon numParameters rhsDrawingName)
|
|
|
|
--(nameString, TextBoxIcon nameString)
|
2016-02-08 05:01:57 +03:00
|
|
|
]
|
2016-02-23 02:45:53 +03:00
|
|
|
--externalEdges = [Edge (justName nameString, justName lambdaName) noEnds]
|
2016-02-18 05:51:03 +03:00
|
|
|
(internalEdges, unmatchedBoundVars) =
|
|
|
|
makeInternalEdges lambdaName rhsGraph patternStrings patternStringMap
|
2016-02-23 02:45:53 +03:00
|
|
|
drawing = IconGraph icons (internalEdges)
|
|
|
|
[(rhsDrawingName, rhsDrawing)] unmatchedBoundVars [(nameString, Right $ justName lambdaName)]
|
2016-02-18 07:59:43 +03:00
|
|
|
pure drawing
|
2016-02-08 05:01:57 +03:00
|
|
|
|
|
|
|
|
2016-02-23 02:45:53 +03:00
|
|
|
-- -- TODO handle inner function definitions.
|
|
|
|
-- -- TODO: Make sure that any remaining sinks are qualified.
|
|
|
|
-- evalMatch :: EvalContext -> Match -> State IDState IconGraph
|
|
|
|
-- evalMatch c (Match _ name patterns _ rhs _) = do
|
|
|
|
-- lambdaName <- getUniqueName "lam"
|
|
|
|
-- patternVals <- mapM evalPattern patterns
|
|
|
|
-- let
|
|
|
|
-- patternStrings = concatMap namesInPattern patternVals
|
|
|
|
-- rhsContext = nameString : patternStrings <> c
|
|
|
|
-- lambdaPorts = map (nameAndPort lambdaName) [0,1..]
|
|
|
|
-- patternGraph = mconcat $ map fst patternVals
|
|
|
|
-- nameString = nameToString name
|
|
|
|
-- (patternEdgeGraphs, rawNewBinds) = partitionEithers $ zipWith (makePatternEdges lambdaName) patternVals lambdaPorts
|
|
|
|
-- patternEdgeGraph = mconcat patternEdgeGraphs
|
|
|
|
-- newBinds = (nameString, Right $ justName lambdaName): rawNewBinds
|
|
|
|
-- numParameters = length patterns
|
|
|
|
-- -- TODO remove coerceExpressionResult here
|
|
|
|
-- (rhsRawGraph, rhsResult) <- coerceExpressionResult <$> evalRhs rhs rhsContext
|
|
|
|
-- resultIconName <- getUniqueName "res"
|
|
|
|
-- rhsDrawingName <- DIA.toName <$> getUniqueName "rhsDraw"
|
|
|
|
-- let
|
|
|
|
-- rhsAndPatternGraph@(IconGraph _ _ _ sinks _) = makeEdges $ patternGraph <> rhsRawGraph
|
|
|
|
-- qualifiedSinks = fmap (fmap (qualifyNameAndPort lambdaName)) sinks
|
|
|
|
-- (IconGraph _ internalEdges _ newSinks _) = makeEdges (IconGraph mempty mempty mempty qualifiedSinks newBinds)
|
|
|
|
-- rhsDrawing = makeRhsDrawing resultIconName (rhsAndPatternGraph, rhsResult)
|
|
|
|
-- icons = toNames [
|
|
|
|
-- (lambdaName, LambdaRegionIcon numParameters rhsDrawingName),
|
|
|
|
-- (nameString, TextBoxIcon nameString)
|
|
|
|
-- ]
|
|
|
|
-- externalEdges = [Edge (justName nameString, justName lambdaName) noEnds]
|
|
|
|
-- finalGraph = IconGraph icons (internalEdges <> externalEdges) [(rhsDrawingName, rhsDrawing)] newSinks mempty
|
|
|
|
-- pure $ patternEdgeGraph <> finalGraph
|
|
|
|
|
|
|
|
|
2016-02-21 05:47:56 +03:00
|
|
|
evalMatches :: EvalContext -> [Match] -> State IDState IconGraph
|
2016-02-22 02:15:16 +03:00
|
|
|
evalMatches _ [] = pure mempty
|
2016-02-21 05:47:56 +03:00
|
|
|
evalMatches c [match] = evalMatch c match
|
2016-02-08 05:01:57 +03:00
|
|
|
-- TODO turn more than one match into a case expression.
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-21 05:47:56 +03:00
|
|
|
-- TODO: Use the context in evalPatBind and evalMatches
|
|
|
|
evalDecl :: EvalContext -> Decl -> State IDState IconGraph
|
|
|
|
evalDecl c d = evaluatedDecl where
|
2016-02-18 07:59:43 +03:00
|
|
|
evaluatedDecl = case d of
|
2016-02-21 05:47:56 +03:00
|
|
|
pat@PatBind{} -> evalPatBind c pat
|
|
|
|
FunBind matches -> evalMatches c matches
|
2016-02-21 08:26:25 +03:00
|
|
|
|
|
|
|
showTopLevelBinds :: IconGraph -> State IDState IconGraph
|
|
|
|
showTopLevelBinds gr@(IconGraph _ _ _ _ binds) = do
|
|
|
|
let
|
|
|
|
addBind (_, Left _) = pure mempty
|
|
|
|
addBind (patName, Right port) = do
|
|
|
|
uniquePatName <- getUniqueName patName
|
|
|
|
let
|
|
|
|
icons = toNames [(uniquePatName, TextBoxIcon patName)]
|
|
|
|
edges = [Edge (justName uniquePatName, port) noEnds]
|
|
|
|
edgeGraph = iconGraphFromIconsEdges icons edges
|
|
|
|
pure edgeGraph
|
|
|
|
newGraph <- mconcat <$> mapM addBind binds
|
|
|
|
pure $ newGraph <> gr
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-02-21 05:47:56 +03:00
|
|
|
drawingFromDecl :: Decl -> Drawing
|
|
|
|
drawingFromDecl d = iconGraphToDrawing $ evalState evaluatedDecl initialIdState
|
2016-02-21 08:26:25 +03:00
|
|
|
where evaluatedDecl = evalDecl mempty d >>= showTopLevelBinds
|
2016-02-21 05:47:56 +03:00
|
|
|
|
2016-02-19 07:34:08 +03:00
|
|
|
-- Profiling: about 1.5% of time.
|
2016-02-04 11:19:08 +03:00
|
|
|
translateString :: String -> (Drawing, Decl)
|
|
|
|
translateString s = (drawing, decl) where
|
|
|
|
parseResult = parseDecl s -- :: ParseResult Module
|
|
|
|
decl = fromParseResult parseResult
|
2016-02-21 05:47:56 +03:00
|
|
|
drawing = drawingFromDecl decl
|