glance/app/Translate.hs

681 lines
24 KiB
Haskell
Raw Normal View History

{-# LANGUAGE NoMonomorphismRestriction, TupleSections #-}
module Translate(
translateStringToSyntaxGraph,
translateStringToCollapsedGraphAndDecl,
2018-11-29 11:26:47 +03:00
translateModuleToCollapsedGraphs,
2018-12-10 07:02:35 +03:00
customParseDecl
) where
import Diagrams.Prelude((<>))
2016-11-28 04:25:30 +03:00
import Control.Monad(replicateM)
2016-02-06 08:07:06 +03:00
import Control.Monad.State(State, evalState)
import Data.Either(partitionEithers)
2016-12-26 12:25:14 +03:00
import qualified Data.Graph.Inductive.PatriciaTree as FGR
2016-12-26 08:45:58 +03:00
import Data.List(unzip5, partition, intercalate)
2019-07-31 22:01:37 +03:00
import qualified Data.Map as Map
import Data.Maybe(fromMaybe, mapMaybe)
import qualified Data.Set as Set
2017-01-02 11:37:27 +03:00
2016-11-28 04:25:30 +03:00
import qualified Language.Haskell.Exts as Exts
import qualified Language.Haskell.Exts.Pretty as PExts
2016-12-26 12:25:14 +03:00
2019-02-19 14:21:13 +03:00
import GraphAlgorithms(annotateGraph, collapseAnnotatedGraph)
import Icons(inputPort, resultPort, argumentPorts, caseRhsPorts,
casePatternPorts)
import SimplifySyntax(SimpAlt(..), stringToSimpDecl, SimpExp(..), SimpPat(..)
, qNameToString, nameToString, customParseDecl
, SimpDecl(..), hsDeclToSimpDecl, SelectorAndVal(..))
import TranslateCore(Reference, SyntaxGraph(..), EvalContext, GraphAndRef(..)
, SgSink(..), syntaxGraphFromNodes
, syntaxGraphFromNodesEdges, getUniqueName
2019-01-12 11:55:13 +03:00
, edgesForRefPortList, makeApplyGraph, makeMultiIfGraph
, combineExpressions, namesInPattern, lookupReference
, deleteBindings, makeEdges, makeBox, syntaxGraphToFglGraph
, getUniqueString, bindsToSyntaxGraph, SgBind(..)
, graphAndRefToGraph, initialIdState)
2019-02-19 14:21:13 +03:00
import Types(AnnotatedGraph, Labeled(..), NameAndPort(..), IDState,
Edge, SyntaxNode(..), NodeName, SgNamedNode,
LikeApplyFlavor(..), CaseOrMultiIfTag(..), Named(..)
, mkEmbedder)
2016-12-18 04:13:36 +03:00
import Util(makeSimpleEdge, nameAndPort, justName)
{-# ANN module "HLint: ignore Use record patterns" #-}
-- OVERVIEW --
-- The core functions and data types used in this module are in TranslateCore.
-- The TranslateCore also contains most/all of the translation functions that
-- do not use Language.Haskell.Exts.
2016-02-18 10:14:14 +03:00
2016-12-26 12:25:14 +03:00
-- BEGIN Helper Functions --
2016-12-12 12:06:21 +03:00
2018-11-12 10:13:19 +03:00
-- | Make a syntax graph that has the bindings for a list of "as pattern" (@)
-- names.
2016-12-26 08:45:58 +03:00
makeAsBindGraph :: Reference -> [Maybe String] -> SyntaxGraph
2018-11-12 10:13:19 +03:00
makeAsBindGraph ref asNames
= bindsToSyntaxGraph $ mapMaybe makeBind asNames
2018-11-12 10:13:19 +03:00
where
makeBind mName = case mName of
Nothing -> Nothing
Just asName -> Just $ SgBind asName ref
2016-12-26 08:45:58 +03:00
2016-12-27 11:37:59 +03:00
grNamePortToGrRef :: (SyntaxGraph, NameAndPort) -> GraphAndRef
grNamePortToGrRef (graph, np) = GraphAndRef graph (Right np)
-- TODO Find a better name for bindOrAltHelper
2018-11-12 10:13:19 +03:00
bindOrAltHelper :: Show l =>
EvalContext
-> SimpPat l
-> SimpExp l
2018-11-12 10:13:19 +03:00
-> State IDState ((GraphAndRef, Maybe String), GraphAndRef)
bindOrAltHelper c pat e = do
patGraphAndRef <- evalPattern pat
let
rhsContext = namesInPattern patGraphAndRef <> c
rhsGraphAndRef <- evalExp rhsContext e
pure (patGraphAndRef, rhsGraphAndRef)
2017-01-02 11:37:27 +03:00
patternName :: (GraphAndRef, Maybe String) -> String
patternName (GraphAndRef _ ref, mStr) = fromMaybe
(case ref of
Left str -> str
Right _ -> ""
)
mStr
2016-12-26 12:25:14 +03:00
-- END Helper Functions --
-- BEGIN evalLit
2018-11-12 10:13:19 +03:00
-- This is in Translate and not Translate core since currently it is only used
-- by evalLit.
2016-12-26 12:25:14 +03:00
makeLiteral :: (Show x) => x -> State IDState (SyntaxGraph, NameAndPort)
makeLiteral = makeBox . show
evalLit :: Exts.Literal l -> State IDState (SyntaxGraph, NameAndPort)
evalLit (Exts.Int _ x _) = makeLiteral x
evalLit (Exts.Char _ x _) = makeLiteral x
evalLit (Exts.String _ x _) = makeLiteral x
2016-12-26 12:25:14 +03:00
-- TODO: Print the Rational as a floating point.
evalLit (Exts.Frac _ x _) = makeLiteral x
2016-12-26 12:25:14 +03:00
-- 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-12-26 12:25:14 +03:00
-- END evalLit
-- BEGIN evalPattern
-- BEGIN evalPApp
asNameBind :: (GraphAndRef, Maybe String) -> Maybe SgBind
2016-12-27 12:32:51 +03:00
asNameBind (GraphAndRef _ ref, mAsName) = case mAsName of
2016-12-26 12:25:14 +03:00
Nothing -> Nothing
Just asName -> Just $ SgBind asName ref
2016-12-26 12:25:14 +03:00
2018-11-12 10:13:19 +03:00
patternArgumentMapper ::
((GraphAndRef, Maybe String), t)
-> (String, Either (GraphAndRef, t) (SgNamedNode, SyntaxGraph))
patternArgumentMapper (asGraphAndRef@(graphAndRef, _), port)
= (patName, eitherVal)
2017-01-02 11:37:27 +03:00
where
graph = graphAndRefToGraph graphAndRef
patName = patternName asGraphAndRef
eitherVal = case graph of
(SyntaxGraph [namedNode] [] _ _ _) -> Right (namedNode, graph)
_ -> Left (graphAndRef, port)
2016-12-28 07:40:50 +03:00
2018-11-12 10:13:19 +03:00
graphToTuple ::
SyntaxGraph
2019-07-31 22:01:37 +03:00
-> ([SgNamedNode], [Edge], [SgSink], [SgBind], Map.Map NodeName NodeName)
2016-12-28 07:40:50 +03:00
graphToTuple (SyntaxGraph a b c d e) = (a, b, c, d, e)
2018-11-12 10:13:19 +03:00
graphsToComponents ::
[SyntaxGraph]
2019-07-31 22:01:37 +03:00
-> ([SgNamedNode], [Edge], [SgSink], [SgBind], Map.Map NodeName NodeName)
graphsToComponents graphs
= (mconcat a, mconcat b, mconcat c, mconcat d, mconcat e)
2018-11-12 10:13:19 +03:00
where
(a, b, c, d, e) = unzip5 $ fmap graphToTuple graphs
2016-12-28 07:40:50 +03:00
2018-11-12 10:13:19 +03:00
makeNestedPatternGraph ::
NodeName
-> String
-> [(GraphAndRef, Maybe String)]
-> (SyntaxGraph, NameAndPort)
2016-12-28 07:40:50 +03:00
makeNestedPatternGraph applyIconName funStr argVals = nestedApplyResult
2016-12-26 12:25:14 +03:00
where
2019-02-25 12:48:17 +03:00
dummyNode = PatternApplyNode "" []
2017-01-02 11:37:27 +03:00
2018-11-12 10:13:19 +03:00
argsAndPorts
= zip argVals $ map (nameAndPort applyIconName) $ argumentPorts dummyNode
2016-12-28 07:40:50 +03:00
mappedArgs = fmap patternArgumentMapper argsAndPorts
2018-11-12 10:13:19 +03:00
(unnestedArgsAndPort, nestedNamedNodesAndGraphs)
= partitionEithers (fmap snd mappedArgs)
2016-12-28 07:40:50 +03:00
2018-11-12 10:13:19 +03:00
(nestedArgs, _, nestedSinks, nestedBinds, nestedEMaps)
= graphsToComponents $ fmap snd nestedNamedNodesAndGraphs
2016-12-28 07:40:50 +03:00
2017-01-02 11:37:27 +03:00
argListMapper (str, arg) = case arg of
Left _ -> Labeled Nothing str
Right (namedNode, _) -> Labeled (Just namedNode) str
2016-12-28 07:40:50 +03:00
argList = fmap argListMapper mappedArgs
combinedGraph = combineExpressions True unnestedArgsAndPort
2019-02-25 12:48:17 +03:00
pAppNode = PatternApplyNode funStr argList
icons = [Named applyIconName (mkEmbedder pAppNode)]
2016-12-26 12:25:14 +03:00
asNameBinds = mapMaybe asNameBind argVals
2016-12-28 07:40:50 +03:00
allBinds = nestedBinds <> asNameBinds
2016-12-26 12:25:14 +03:00
2019-07-31 22:01:37 +03:00
newEMap = Map.fromList
((\(Named n _) -> (n, applyIconName)) <$> nestedArgs)
2018-11-12 10:13:19 +03:00
<> nestedEMaps
2016-12-26 12:25:14 +03:00
newGraph = SyntaxGraph
icons
[]
nestedSinks
allBinds
newEMap
2018-11-12 10:13:19 +03:00
nestedApplyResult = (newGraph <> combinedGraph
, nameAndPort applyIconName (resultPort pAppNode))
evalPApp :: Show l =>
Exts.QName l
-> [SimpPat l]
2018-11-12 10:13:19 +03:00
-> State IDState (SyntaxGraph, NameAndPort)
evalPApp name patterns = case patterns of
[] -> makeBox constructorName
_ -> do
2016-12-28 01:58:09 +03:00
patName <- getUniqueName
evaledPatterns <- mapM evalPattern patterns
2016-12-28 07:40:50 +03:00
pure $ makeNestedPatternGraph patName constructorName evaledPatterns
where
2016-03-22 03:36:02 +03:00
constructorName = qNameToString name
2016-12-26 12:25:14 +03:00
-- END evalPApp
-- BEGIN evalPLit
showLiteral :: Exts.Literal l -> String
showLiteral (Exts.Int _ x _) = show x
showLiteral (Exts.Char _ x _) = show x
showLiteral (Exts.String _ x _) = show x
2016-12-26 12:25:14 +03:00
-- TODO: Print the Rational as a floating point.
showLiteral (Exts.Frac _ x _) = show x
2016-12-26 12:25:14 +03:00
-- TODO: Test the unboxed literals
showLiteral (Exts.PrimInt _ x _) = show x
showLiteral (Exts.PrimWord _ x _) = show x
showLiteral (Exts.PrimFloat _ x _) = show x
showLiteral (Exts.PrimDouble _ x _) = show x
showLiteral (Exts.PrimChar _ x _) = show x
showLiteral (Exts.PrimString _ x _) = show x
2018-11-12 10:13:19 +03:00
evalPLit ::
Exts.Sign l -> Exts.Literal l -> State IDState (SyntaxGraph, NameAndPort)
2016-12-26 12:25:14 +03:00
evalPLit sign l = case sign of
Exts.Signless _ -> evalLit l
Exts.Negative _ -> makeBox ('-' : showLiteral l)
2016-12-26 12:25:14 +03:00
-- END evalPLit
2018-11-12 10:13:19 +03:00
evalPAsPat :: Show l =>
Exts.Name l -> SimpPat l -> State IDState (GraphAndRef, Maybe String)
2016-03-05 00:24:09 +03:00
evalPAsPat n p = do
2016-12-27 11:37:59 +03:00
(GraphAndRef evaledPatGraph evaledPatRef, mInnerName) <- evalPattern p
2016-03-05 00:24:09 +03:00
let
2016-12-26 08:45:58 +03:00
outerName = nameToString n
asBindGraph = makeAsBindGraph (Left outerName) [mInnerName]
2018-11-12 10:13:19 +03:00
pure (GraphAndRef (asBindGraph <> evaledPatGraph) evaledPatRef
, Just outerName)
2016-12-26 08:45:58 +03:00
2018-11-12 10:13:19 +03:00
makePatternResult :: Functor f =>
f (SyntaxGraph, NameAndPort) -> f (GraphAndRef, Maybe String)
makePatternResult
= fmap (\(graph, namePort) -> (GraphAndRef graph (Right namePort), Nothing))
2016-03-05 00:24:09 +03:00
evalPattern :: Show l => SimpPat l -> State IDState (GraphAndRef, Maybe String)
evalPattern p = case p of
SpVar _ n -> pure (GraphAndRef mempty (Left $ nameToString n), Nothing)
SpLit _ sign lit -> makePatternResult $ evalPLit sign lit
SpApp _ name patterns -> makePatternResult $ evalPApp name patterns
SpAsPat _ name pat -> evalPAsPat name pat
SpWildCard _ -> makePatternResult $ makeBox "_"
-- _ -> error ("evalPattern todo: " <> show p)
2016-12-26 12:25:14 +03:00
-- END evalPattern
-- BEGIN evalQName
2016-03-05 05:49:02 +03:00
-- strToGraphRef is not in TranslateCore, since it is only used by evalQName.
2016-12-27 11:37:59 +03:00
strToGraphRef :: EvalContext -> String -> State IDState GraphAndRef
2016-03-05 05:49:02 +03:00
strToGraphRef c str = fmap mapper (makeBox str) where
mapper gr = if str `elem` c
2016-12-27 11:37:59 +03:00
then GraphAndRef mempty (Left str)
else grNamePortToGrRef gr
2016-03-05 05:49:02 +03:00
2016-12-26 12:25:14 +03:00
-- END evalQName
-- BEGIN apply and compose helper functions
2016-12-26 08:45:58 +03:00
2018-11-12 10:13:19 +03:00
evalFunExpAndArgs :: Show l =>
EvalContext
-> LikeApplyFlavor
-> (SimpExp l, [SimpExp l])
2018-11-12 10:13:19 +03:00
-> State IDState (SyntaxGraph, NameAndPort)
evalFunExpAndArgs c flavor (funExp, argExps) = do
2016-02-10 05:58:28 +03:00
funVal <- evalExp c funExp
argVals <- mapM (evalExp c) argExps
2016-12-28 01:58:09 +03:00
applyIconName <- getUniqueName
2018-11-12 10:13:19 +03:00
pure
$ makeApplyGraph (length argExps) flavor False applyIconName funVal argVals
2016-02-19 09:07:38 +03:00
2016-12-26 12:25:14 +03:00
-- END apply and compose helper functions
2016-03-05 08:35:23 +03:00
2018-11-12 10:13:19 +03:00
evalFunctionComposition :: Show l =>
EvalContext -> [SimpExp l] -> State IDState (SyntaxGraph, NameAndPort)
evalFunctionComposition c functions = do
let reversedFunctios = reverse functions
evaluatedFunctions <- mapM (evalExp c) reversedFunctios
neverUsedPort <- Left <$> getUniqueString "unusedArgument"
2016-12-28 01:58:09 +03:00
applyIconName <- getUniqueName
2018-11-12 10:13:19 +03:00
pure $ makeApplyGraph
(length evaluatedFunctions)
ComposeNodeFlavor
False
applyIconName
(GraphAndRef mempty neverUsedPort)
evaluatedFunctions
-- | Turn (a . b . c) into [a, b, c]
compositionToList :: SimpExp l -> [SimpExp l]
compositionToList e = case e of
(SeApp _ (SeApp _ (SeName _ ".") f1) f2)
-> f1 : compositionToList f2
x -> [x]
2016-12-26 12:25:14 +03:00
-- BEGIN evaluateAppExpression
-- | Given two expressions f and x, where f is applied to x,
-- return the nesting depth if (f x) is rendered with
-- the (normal apply icon, compose apply icon)
applyComposeScoreHelper :: SimpExp l -> SimpExp l -> (Int, Int)
applyComposeScoreHelper exp1 exp2 = (appScore, compScore) where
2016-12-09 06:19:47 +03:00
(e1App, e1Comp) = applyComposeScore exp1
(e2App, e2Comp) = applyComposeScore exp2
leftApp = min e1App (1 + e1Comp)
rightApp = 1 + min e2App e2Comp
appScore = max leftApp rightApp
leftComp = 1 + min e1App e1Comp
rightComp = min (1 + e2App) e2Comp
2018-11-11 14:17:06 +03:00
2016-12-09 06:19:47 +03:00
compScore = max leftComp rightComp
2016-12-09 06:19:47 +03:00
-- TODO Consider putting this logic in a separate "simplifyExpression" function.
2018-11-12 10:13:19 +03:00
-- | Returns the amount of nesting if the App is converted to
-- (applyNode, composeNode)
applyComposeScore :: SimpExp l -> (Int, Int)
applyComposeScore e = case e of
SeApp _ exp1 exp2 -> applyComposeScoreHelper exp1 exp2
_ -> (0, 0)
2016-12-09 06:19:47 +03:00
-- Todo add test for this function
-- | Given an App expression, return
-- (function, list of arguments)
appExpToFuncArgs :: SimpExp l -> (SimpExp l, [SimpExp l])
appExpToFuncArgs e = case e of
SeApp _ exp1 exp2 -> (funExp, args <> [exp2])
where
(funExp, args) = appExpToFuncArgs exp1
x -> (x, [])
2016-02-06 08:07:06 +03:00
-- | Given and App expression, return
-- (argument, list composed functions)
appExpToArgFuncs :: SimpExp l -> (SimpExp l, [SimpExp l])
appExpToArgFuncs e = case e of
SeApp _ exp1 exp2 -> (argExp, funcs <> [exp1])
2016-12-09 06:19:47 +03:00
where
(argExp, funcs) = appExpToArgFuncs exp2
2016-12-09 06:19:47 +03:00
simpleExp -> (simpleExp, [])
2016-12-26 12:25:14 +03:00
-- TODO Refactor this and all sub-expressions
2018-11-12 10:13:19 +03:00
evalApp :: Show l =>
EvalContext -> SimpExp l
-> State IDState (SyntaxGraph, NameAndPort)
evalApp c expr = case expr of
-- TODO This pattern for "." appears at least twice in this file. Refactor?
(SeApp _ (SeApp _ (SeName _ ".") _) _)
-> evalFunctionComposition c (compositionToList expr)
_ -> if appScore <= compScore
then evalFunExpAndArgs c ApplyNodeFlavor (appExpToFuncArgs expr)
else evalFunExpAndArgs c ComposeNodeFlavor (appExpToArgFuncs expr)
where
(appScore, compScore) = applyComposeScore expr
2016-12-26 12:25:14 +03:00
-- END evaluateAppExpression
-- BEGIN evalGeneralLet
getBoundVarName :: Show l => SimpDecl l -> [String]
getBoundVarName d = case d of
SdPatBind _ pat _ -> namesInPattern
-- TODO Should evalState be used here?
$ evalState (evalPattern pat) initialIdState
SdTypeSig _ _ _ -> []
SdCatchAll _ -> []
evalDecls :: Show l =>
EvalContext -> [SimpDecl l] -> State IDState (SyntaxGraph, EvalContext)
evalDecls c decls =
2016-02-21 05:47:56 +03:00
let
boundNames = concatMap getBoundVarName decls
2016-02-21 05:47:56 +03:00
augmentedContext = boundNames <> c
2017-01-01 06:11:51 +03:00
in
2018-11-30 12:39:14 +03:00
(,augmentedContext) . mconcat <$> mapM (evalDecl augmentedContext) decls
2016-02-21 05:47:56 +03:00
evalLet :: Show l =>
EvalContext
-> [SimpDecl l]
-> SimpExp l
2018-11-12 10:13:19 +03:00
-> State IDState GraphAndRef
evalLet c decls expr = do
(bindGraph, bindContext) <- evalDecls c decls
expVal <- evalExp bindContext expr
2016-02-21 05:47:56 +03:00
let
2016-12-27 11:37:59 +03:00
GraphAndRef expGraph expResult = expVal
2016-02-22 02:15:16 +03:00
newGraph = deleteBindings . makeEdges $ expGraph <> bindGraph
bindings = sgBinds bindGraph
2016-12-27 11:37:59 +03:00
pure $ GraphAndRef newGraph (lookupReference bindings expResult)
2016-02-20 00:46:14 +03:00
2016-12-26 12:25:14 +03:00
-- END evalGeneralLet
evalSelectorAndVal :: Show l =>
EvalContext -> SelectorAndVal l -> State IDState (GraphAndRef, GraphAndRef)
evalSelectorAndVal c SelectorAndVal{svSelector=sel, svVal=val}
= (,) <$> evalExp c sel <*> evalExp c val
2016-12-26 12:25:14 +03:00
2019-01-12 11:55:13 +03:00
evalMultiIf :: Show l =>
EvalContext -> [SelectorAndVal l] -> State IDState (SyntaxGraph, NameAndPort)
2019-01-12 11:55:13 +03:00
evalMultiIf c selectorsAndVals = let
evaledRhss = unzip <$> mapM (evalSelectorAndVal c) selectorsAndVals
in
2019-01-12 11:55:13 +03:00
makeMultiIfGraph (length selectorsAndVals)
<$>
getUniqueName
<*>
fmap fst evaledRhss
<*>
fmap snd evaledRhss
2016-12-26 12:25:14 +03:00
-- BEGIN evalCase
2018-11-12 10:13:19 +03:00
-- TODO patRhsAreConnected is sometimes incorrectly true if the pat is just a
-- name
-- returns (combined graph, pattern reference, rhs reference)
evalAlt :: Show l =>
2018-11-12 10:13:19 +03:00
EvalContext
-> SimpAlt l
2018-11-12 10:13:19 +03:00
-> State IDState (Bool, SyntaxGraph, Reference, Reference, Maybe String)
evalAlt c (SimpAlt pat rhs) = do
((GraphAndRef patGraph patRef, mPatAsName), GraphAndRef rhsGraph rhsRef) <-
bindOrAltHelper c pat rhs
2016-02-24 07:47:08 +03:00
let
grWithEdges = makeEdges (rhsGraph <> patGraph)
lookedUpRhsRef = lookupReference (sgBinds grWithEdges) rhsRef
2018-11-12 10:13:19 +03:00
-- The pattern and rhs are conneted if makeEdges added extra edges, or if
-- the rhsRef refers to a source in the pattern.
patRhsAreConnected
= (rhsRef /= lookedUpRhsRef)
|| ( length (sgEdges grWithEdges)
>
(length (sgEdges rhsGraph) + length (sgEdges patGraph)))
pure (patRhsAreConnected
, deleteBindings grWithEdges
, patRef
, lookedUpRhsRef
, mPatAsName)
2016-02-24 07:47:08 +03:00
evalCaseHelper ::
Int
-> NodeName
-> [NodeName]
-> GraphAndRef
-> [(Bool, SyntaxGraph, Reference, Reference, Maybe String)]
-> (SyntaxGraph, NameAndPort)
2018-11-12 10:13:19 +03:00
evalCaseHelper numAlts caseIconName resultIconNames
(GraphAndRef expGraph expRef) evaledAlts
= result
where
(patRhsConnected, altGraphs, patRefs, rhsRefs, asNames) = unzip5 evaledAlts
combindedAltGraph = mconcat altGraphs
2019-07-19 10:35:31 +03:00
caseNode = CaseOrMultiIfNode CaseTag numAlts
icons = [Named caseIconName (mkEmbedder caseNode)]
2018-11-12 10:13:19 +03:00
caseGraph = syntaxGraphFromNodes icons
expEdge = (expRef, nameAndPort caseIconName (inputPort caseNode))
patEdges = zip patRefs $ map (nameAndPort caseIconName) casePatternPorts
rhsEdges = zip patRhsConnected $ zip rhsRefs
$ map (nameAndPort caseIconName) caseRhsPorts
(connectedRhss, unConnectedRhss) = partition fst rhsEdges
makeCaseResult :: NodeName -> Reference -> SyntaxGraph
makeCaseResult resultIconName rhsRef = case rhsRef of
Left _ -> mempty
Right rhsPort -> syntaxGraphFromNodesEdges rhsNewIcons rhsNewEdges
where
rhsNewIcons = [Named resultIconName (mkEmbedder CaseResultNode)]
2018-11-12 10:13:19 +03:00
rhsNewEdges = [makeSimpleEdge (rhsPort, justName resultIconName)]
caseResultGraphs =
mconcat
$ zipWith makeCaseResult resultIconNames (fmap (fst . snd) connectedRhss)
filteredRhsEdges = fmap snd unConnectedRhss
patternEdgesGraph = edgesForRefPortList True patEdges
caseEdgeGraph = edgesForRefPortList False (expEdge : filteredRhsEdges)
bindGraph = makeAsBindGraph expRef asNames
finalGraph = deleteBindings $ makeEdges $ mconcat [bindGraph
, patternEdgesGraph
, caseResultGraphs
, expGraph
, caseEdgeGraph
, caseGraph
, combindedAltGraph]
result = (finalGraph, nameAndPort caseIconName (resultPort caseNode))
evalCase :: Show l =>
EvalContext -> SimpExp l -> [SimpAlt l]
-> State IDState (SyntaxGraph, NameAndPort)
evalCase c e alts =
2016-02-24 07:47:08 +03:00
let
numAlts = length alts
in
evalCaseHelper (length alts)
<$>
getUniqueName
<*>
replicateM numAlts getUniqueName
<*>
evalExp c e
<*>
mapM (evalAlt c) alts
2016-02-24 07:47:08 +03:00
2016-12-26 12:25:14 +03:00
-- END evalCase
-- BEGIN generalEvalLambda
2016-02-22 06:34:33 +03:00
2016-12-26 08:45:58 +03:00
-- TODO Returning a SyntaxGraph is probably not very efficient
asBindGraphZipper :: Maybe String -> NameAndPort -> SyntaxGraph
asBindGraphZipper asName nameNPort = makeAsBindGraph (Right nameNPort) [asName]
-- TODO Refactor evalLambda
evalLambda :: Show l
=> l
-> EvalContext
-> [SimpPat l]
-> SimpExp l
2018-11-05 09:54:17 +03:00
-> State IDState (SyntaxGraph, NameAndPort)
evalLambda _ context patterns expr = do
2016-12-28 01:58:09 +03:00
lambdaName <- getUniqueName
2016-12-26 08:45:58 +03:00
patternValsWithAsNames <- mapM evalPattern patterns
let
2016-12-26 08:45:58 +03:00
patternVals = fmap fst patternValsWithAsNames
patternStrings = concatMap namesInPattern patternValsWithAsNames
rhsContext = patternStrings <> context
GraphAndRef rhsRawGraph rhsRef <- evalExp rhsContext expr
2018-11-11 14:17:06 +03:00
let
2017-01-02 11:37:27 +03:00
paramNames = fmap patternName patternValsWithAsNames
enclosedNodeNames = Set.fromList $ naName <$> sgNodes combinedGraph
lambdaNode = FunctionDefNode paramNames enclosedNodeNames
lambdaPorts = map (nameAndPort lambdaName) $ argumentPorts lambdaNode
2016-12-27 11:37:59 +03:00
patternGraph = mconcat $ fmap graphAndRefToGraph patternVals
(patternEdges, newBinds) =
2016-03-28 02:49:58 +03:00
partitionEithers $ zipWith makePatternEdges patternVals lambdaPorts
2016-12-18 04:13:36 +03:00
icons = [Named lambdaName (mkEmbedder lambdaNode)]
returnPort = nameAndPort lambdaName (inputPort lambdaNode)
2016-12-18 04:13:36 +03:00
(newEdges, newSinks) = case rhsRef of
Left s -> (patternEdges, [SgSink s returnPort])
2018-11-11 14:17:06 +03:00
Right rhsPort ->
(makeSimpleEdge (rhsPort, returnPort) : patternEdges, mempty)
2016-12-18 04:13:36 +03:00
finalGraph = SyntaxGraph icons newEdges newSinks newBinds mempty
2016-12-26 08:45:58 +03:00
2018-11-11 14:17:06 +03:00
asBindGraph = mconcat $ zipWith
asBindGraphZipper
(fmap snd patternValsWithAsNames)
lambdaPorts
combinedGraph = deleteBindings . makeEdges
$ (asBindGraph <> rhsRawGraph <> patternGraph <> finalGraph)
pure (combinedGraph, nameAndPort lambdaName (resultPort lambdaNode))
where
2018-11-12 10:13:19 +03:00
-- TODO Like evalPatBind, this edge should have an indicator that it is the
-- input to a pattern.
-- makePatternEdges creates the edges between the patterns and the parameter
-- ports.
makePatternEdges :: GraphAndRef -> NameAndPort -> Either Edge SgBind
2016-12-27 11:37:59 +03:00
makePatternEdges (GraphAndRef _ ref) lamPort = case ref of
Right patPort -> Left $ makeSimpleEdge (lamPort, patPort)
Left str -> Right $ SgBind str (Right lamPort)
2016-12-26 12:25:14 +03:00
-- END generalEvalLambda
evalExp :: Show l => EvalContext -> SimpExp l -> State IDState GraphAndRef
2016-12-26 12:25:14 +03:00
evalExp c x = case x of
SeName _ s -> strToGraphRef c s
SeLit _ lit -> grNamePortToGrRef <$> evalLit lit
SeApp _ _ _ -> grNamePortToGrRef <$> evalApp c x
SeLambda l patterns e -> grNamePortToGrRef <$> evalLambda l c patterns e
SeLet _ decls expr -> evalLet c decls expr
SeCase _ expr alts -> grNamePortToGrRef <$> evalCase c expr alts
2019-01-12 11:55:13 +03:00
SeMultiIf _ selectorsAndVals
-> grNamePortToGrRef <$> evalMultiIf c selectorsAndVals
2016-12-26 12:25:14 +03:00
-- BEGIN evalDecl
evalPatBind :: Show l =>
l -> EvalContext -> SimpPat l -> SimpExp l -> State IDState SyntaxGraph
evalPatBind _ c pat e = do
((GraphAndRef patGraph patRef, mPatAsName), GraphAndRef rhsGraph rhsRef) <-
bindOrAltHelper c pat e
2016-12-26 12:25:14 +03:00
let
(newEdges, newSinks, bindings) = case patRef of
(Left s) -> (mempty, mempty, [SgBind s rhsRef])
2016-12-26 12:25:14 +03:00
(Right patPort) -> case rhsRef of
(Left rhsStr) -> (mempty, [SgSink rhsStr patPort], mempty)
2016-12-26 12:25:14 +03:00
(Right rhsPort) -> ([makeSimpleEdge (rhsPort, patPort)], mempty, mempty)
asBindGraph = makeAsBindGraph rhsRef [mPatAsName]
2016-12-26 12:25:14 +03:00
gr = asBindGraph <> SyntaxGraph mempty newEdges newSinks bindings mempty
pure . makeEdges $ (gr <> rhsGraph <> patGraph)
2016-12-16 11:47:48 +03:00
-- Pretty printing the entire type sig results in extra whitespace in the middle
-- TODO May want to trim whitespace from (prettyPrint typeForNames)
evalTypeSig :: Show l =>
[Exts.Name l] -> Exts.Type l
-> State IDState (SyntaxGraph, NameAndPort)
evalTypeSig names typeForNames = makeBox
(intercalate "," (fmap prettyPrintWithoutNewlines names)
2016-12-16 11:47:48 +03:00
++ " :: "
++ prettyPrintWithoutNewlines typeForNames)
where
-- TODO Make custom version of prettyPrint for type signitures.
2018-11-12 10:13:19 +03:00
-- Use (unwords . words) to convert consecutive whitspace characters to one
-- space.
prettyPrintWithoutNewlines = unwords . words . Exts.prettyPrint
2016-12-16 11:47:48 +03:00
evalDecl :: Show l => EvalContext -> SimpDecl l -> State IDState SyntaxGraph
evalDecl c d = case d of
SdPatBind l pat e -> evalPatBind l c pat e
SdTypeSig _ names typeForNames -> fst <$> evalTypeSig names typeForNames
SdCatchAll decl -> fst <$> makeBox (PExts.prettyPrint decl)
2016-12-26 12:25:14 +03:00
-- END evalDecl
-- BEGIN Exported functions
showTopLevelBinds :: SyntaxGraph -> State IDState SyntaxGraph
2016-12-07 05:39:38 +03:00
showTopLevelBinds gr = do
let
binds = sgBinds gr
addBind (SgBind _ (Left _)) = pure mempty
addBind (SgBind patName (Right port)) = do
2016-12-28 01:58:09 +03:00
uniquePatName <- getUniqueName
let
icons = [Named uniquePatName $ mkEmbedder (BindNameNode patName)]
2016-12-08 13:41:47 +03:00
edges = [makeSimpleEdge (port, justName uniquePatName)]
edgeGraph = syntaxGraphFromNodesEdges icons edges
pure edgeGraph
newGraph <- mconcat <$> mapM addBind binds
pure $ newGraph <> gr
translateDeclToSyntaxGraph :: Show l => SimpDecl l -> SyntaxGraph
translateDeclToSyntaxGraph d = graph where
evaluatedDecl = evalDecl mempty d >>= showTopLevelBinds
graph = evalState evaluatedDecl initialIdState
-- | Convert a single function declaration into a SyntaxGraph
translateStringToSyntaxGraph :: String -> SyntaxGraph
translateStringToSyntaxGraph = translateDeclToSyntaxGraph . stringToSimpDecl
2019-02-19 14:21:13 +03:00
syntaxGraphToCollapsedGraph :: SyntaxGraph -> AnnotatedGraph FGR.Gr
syntaxGraphToCollapsedGraph
= collapseAnnotatedGraph . annotateGraph . syntaxGraphToFglGraph
2019-02-25 12:48:17 +03:00
-- = annotateGraph . syntaxGraphToFglGraph
2016-12-16 11:47:48 +03:00
2019-02-19 14:21:13 +03:00
translateDeclToCollapsedGraph :: Show l => Exts.Decl l -> AnnotatedGraph FGR.Gr
2018-11-12 10:13:19 +03:00
translateDeclToCollapsedGraph
= syntaxGraphToCollapsedGraph . translateDeclToSyntaxGraph . hsDeclToSimpDecl
-- Profiling: At one point, this was about 1.5% of total time.
2018-11-12 10:13:19 +03:00
translateStringToCollapsedGraphAndDecl ::
2019-02-19 14:21:13 +03:00
String -> (AnnotatedGraph FGR.Gr, Exts.Decl Exts.SrcSpanInfo)
translateStringToCollapsedGraphAndDecl s = (drawing, decl) where
2017-01-01 06:11:51 +03:00
decl = customParseDecl s -- :: ParseResult Module
drawing = translateDeclToCollapsedGraph decl
2018-11-12 10:13:19 +03:00
translateModuleToCollapsedGraphs :: Show l =>
2019-02-19 14:21:13 +03:00
Exts.Module l -> [AnnotatedGraph FGR.Gr]
translateModuleToCollapsedGraphs (Exts.Module _ _ _ _ decls)
2018-11-12 10:13:19 +03:00
= fmap translateDeclToCollapsedGraph decls
2018-11-05 09:54:17 +03:00
translateModuleToCollapsedGraphs moduleSyntax
= error $ "Unsupported syntax in translateModuleToCollapsedGraphs: "
<> show moduleSyntax
2016-12-26 12:25:14 +03:00
-- END Exported functions