mirror of
https://github.com/rgleichman/glance.git
synced 2024-11-26 09:07:01 +03:00
Simplify and rename SyntaxNodes.
This commit is contained in:
parent
21e0091743
commit
96be8aa835
@ -43,20 +43,20 @@ syntaxNodeIsEmbeddable :: ParentType
|
||||
-> Bool
|
||||
syntaxNodeIsEmbeddable parentType n mParentPort _mChildPort
|
||||
= case (parentType, n) of
|
||||
(ApplyParent, LikeApplyNode _ _) -> parentPortNotResult
|
||||
(ApplyParent, ApplyNode _ _ _) -> parentPortNotResult
|
||||
(ApplyParent, LiteralNode _) -> parentPortNotResult
|
||||
-- TODO Embedded FunctionDefNodes are missing their enclosures.
|
||||
-- (ApplyParent, FunctionDefNode _ _)
|
||||
-- -> isInput mParentPort && isResult mChildPort
|
||||
|
||||
(CaseParent, LiteralNode _) -> parentPortNotResult
|
||||
(CaseParent, LikeApplyNode _ _)
|
||||
(CaseParent, ApplyNode _ _ _)
|
||||
-> parentPortNotResult && parentPortNotInput
|
||||
(CaseParent, NestedPatternApplyNode _ _)
|
||||
(CaseParent, PatternApplyNode _ _)
|
||||
-> parentPortNotResult && parentPortNotInput
|
||||
|
||||
(MultiIfParent, LiteralNode _) -> parentPortNotResult
|
||||
(MultiIfParent, LikeApplyNode _ _)
|
||||
(MultiIfParent, ApplyNode _ _ _)
|
||||
-> parentPortNotResult && parentPortNotInput
|
||||
|
||||
_ -> False
|
||||
@ -75,12 +75,9 @@ syntaxNodeIsEmbeddable parentType n mParentPort _mChildPort
|
||||
|
||||
parentTypeForNode :: SyntaxNode -> ParentType
|
||||
parentTypeForNode n = case n of
|
||||
LikeApplyNode _ _ -> ApplyParent
|
||||
NestedApplyNode _ _ _ -> ApplyParent
|
||||
CaseNode _ -> CaseParent
|
||||
MultiIfNode _ -> MultiIfParent
|
||||
NestedCaseOrMultiIfNode CaseTag _ _ -> CaseParent
|
||||
NestedCaseOrMultiIfNode MultiIfTag _ _ -> MultiIfParent
|
||||
ApplyNode _ _ _ -> ApplyParent
|
||||
CaseOrMultiIfNode CaseTag _ _ -> CaseParent
|
||||
CaseOrMultiIfNode MultiIfTag _ _ -> MultiIfParent
|
||||
_ -> NotAParent
|
||||
|
||||
lookupSyntaxNode :: ING.Graph gr =>
|
||||
@ -181,18 +178,12 @@ embedChildSyntaxNode parentNode childNode oldGraph = newGraph
|
||||
SgNamedNode nodeName oldSyntaxNode = oldNodeLabel
|
||||
newNodeLabel = SgNamedNode nodeName newSyntaxNode
|
||||
newSyntaxNode = case oldSyntaxNode of
|
||||
LikeApplyNode flavor x
|
||||
-> NestedApplyNode flavor x childrenAndEdgesToParent
|
||||
NestedApplyNode flavor x existingNodes
|
||||
-> NestedApplyNode flavor x
|
||||
ApplyNode flavor x existingNodes
|
||||
-> ApplyNode flavor x
|
||||
(childrenAndEdgesToParent <> existingNodes)
|
||||
CaseNode x
|
||||
-> NestedCaseOrMultiIfNode CaseTag x childrenAndEdgesToParent
|
||||
NestedCaseOrMultiIfNode tag x existingNodes
|
||||
-> NestedCaseOrMultiIfNode tag x
|
||||
CaseOrMultiIfNode tag x existingNodes
|
||||
-> CaseOrMultiIfNode tag x
|
||||
(childrenAndEdgesToParent <> existingNodes)
|
||||
MultiIfNode x
|
||||
-> NestedCaseOrMultiIfNode MultiIfTag x childrenAndEdgesToParent
|
||||
_ -> oldSyntaxNode
|
||||
|
||||
changeEdgeToParent :: ING.Node -> ING.Node -> ING.LEdge b -> ING.LEdge b
|
||||
|
@ -211,13 +211,10 @@ multiIfBoolPorts = caseRhsPorts
|
||||
|
||||
argumentPorts :: SyntaxNode -> [Port]
|
||||
argumentPorts n = case n of
|
||||
LikeApplyNode _ _-> defaultPorts
|
||||
NestedApplyNode _ _ _ -> defaultPorts
|
||||
NestedPatternApplyNode _ _-> defaultPorts
|
||||
ApplyNode _ _ _ -> defaultPorts
|
||||
PatternApplyNode _ _-> defaultPorts
|
||||
FunctionDefNode _ _ -> defaultPorts
|
||||
NestedCaseOrMultiIfNode _ _ _-> defaultPorts
|
||||
MultiIfNode _ -> defaultPorts
|
||||
CaseNode _ -> defaultPorts
|
||||
CaseOrMultiIfNode _ _ _-> defaultPorts
|
||||
NameNode _ -> []
|
||||
BindNameNode _ -> []
|
||||
LiteralNode _ -> []
|
||||
|
@ -33,8 +33,8 @@ import TranslateCore(Reference, SyntaxGraph(..), EvalContext, GraphAndRef(..)
|
||||
, getUniqueString, bindsToSyntaxGraph, SgBind(..)
|
||||
, graphAndRefToGraph, initialIdState)
|
||||
import Types(AnnotatedGraph, Labeled(..), NameAndPort(..), IDState,
|
||||
Edge, SyntaxNode(..), NodeName, SgNamedNode(..),
|
||||
LikeApplyFlavor(..))
|
||||
Edge, SyntaxNode(..), NodeName, SgNamedNode(..),
|
||||
LikeApplyFlavor(..), CaseOrMultiIfTag(..))
|
||||
import Util(makeSimpleEdge, nameAndPort, justName)
|
||||
|
||||
{-# ANN module "HLint: ignore Use record patterns" #-}
|
||||
@ -147,7 +147,7 @@ makeNestedPatternGraph ::
|
||||
-> (SyntaxGraph, NameAndPort)
|
||||
makeNestedPatternGraph applyIconName funStr argVals = nestedApplyResult
|
||||
where
|
||||
dummyNode = NestedPatternApplyNode "" []
|
||||
dummyNode = PatternApplyNode "" []
|
||||
|
||||
argsAndPorts
|
||||
= zip argVals $ map (nameAndPort applyIconName) $ argumentPorts dummyNode
|
||||
@ -167,7 +167,7 @@ makeNestedPatternGraph applyIconName funStr argVals = nestedApplyResult
|
||||
|
||||
combinedGraph = combineExpressions True unnestedArgsAndPort
|
||||
|
||||
pAppNode = NestedPatternApplyNode funStr argList
|
||||
pAppNode = PatternApplyNode funStr argList
|
||||
icons = [SgNamedNode applyIconName pAppNode]
|
||||
|
||||
asNameBinds = catMaybes $ fmap asNameBind argVals
|
||||
@ -452,7 +452,7 @@ evalCaseHelper numAlts caseIconName resultIconNames
|
||||
where
|
||||
(patRhsConnected, altGraphs, patRefs, rhsRefs, asNames) = unzip5 evaledAlts
|
||||
combindedAltGraph = mconcat altGraphs
|
||||
caseNode = CaseNode numAlts
|
||||
caseNode = CaseOrMultiIfNode CaseTag numAlts []
|
||||
icons = [SgNamedNode caseIconName caseNode]
|
||||
caseGraph = syntaxGraphFromNodes icons
|
||||
expEdge = (expRef, nameAndPort caseIconName (inputPort caseNode))
|
||||
@ -646,7 +646,7 @@ translateStringToSyntaxGraph = translateDeclToSyntaxGraph . stringToSimpDecl
|
||||
syntaxGraphToCollapsedGraph :: SyntaxGraph -> AnnotatedGraph FGR.Gr
|
||||
syntaxGraphToCollapsedGraph
|
||||
= collapseAnnotatedGraph . annotateGraph . syntaxGraphToFglGraph
|
||||
-- = annotateGraph . syntaxGraphToFglGraph
|
||||
-- = annotateGraph . syntaxGraphToFglGraph
|
||||
|
||||
translateDeclToCollapsedGraph :: Show l => Exts.Decl l -> AnnotatedGraph FGR.Gr
|
||||
translateDeclToCollapsedGraph
|
||||
|
@ -182,7 +182,7 @@ makeApplyGraph numArgs applyFlavor inPattern applyIconName funVal argVals
|
||||
, nameAndPort applyIconName (resultPort applyNode)
|
||||
)
|
||||
where
|
||||
applyNode = LikeApplyNode applyFlavor numArgs
|
||||
applyNode = ApplyNode applyFlavor numArgs []
|
||||
argumentNamePorts
|
||||
= map (nameAndPort applyIconName) (argumentPorts applyNode)
|
||||
functionPort = nameAndPort applyIconName (inputPort applyNode)
|
||||
@ -200,7 +200,7 @@ makeMultiIfGraph ::
|
||||
makeMultiIfGraph numPairs multiIfName bools exps
|
||||
= (newGraph, nameAndPort multiIfName (resultPort multiIfNode))
|
||||
where
|
||||
multiIfNode = MultiIfNode numPairs
|
||||
multiIfNode = CaseOrMultiIfNode MultiIfTag numPairs []
|
||||
expsWithPorts = zip exps $ map (nameAndPort multiIfName) multiIfRhsPorts
|
||||
boolsWithPorts = zip bools $ map (nameAndPort multiIfName) multiIfBoolPorts
|
||||
combindedGraph = combineExpressions False $ expsWithPorts <> boolsWithPorts
|
||||
@ -278,20 +278,16 @@ nListString 1 = "[_]"
|
||||
nListString n = '[' : replicate (n -1) ',' ++ "]"
|
||||
|
||||
nodeToIcon :: SyntaxNode -> Icon
|
||||
nodeToIcon (LikeApplyNode flavor n)
|
||||
= NestedApply flavor Nothing (replicate n Nothing)
|
||||
nodeToIcon (NestedApplyNode flavor x edges)
|
||||
nodeToIcon (ApplyNode flavor x edges)
|
||||
= nestedApplySyntaxNodeToIcon flavor x edges
|
||||
nodeToIcon (NestedPatternApplyNode s children)
|
||||
nodeToIcon (PatternApplyNode s children)
|
||||
= nestedPatternNodeToIcon s children
|
||||
nodeToIcon (NameNode s) = TextBoxIcon s
|
||||
nodeToIcon (BindNameNode s) = BindTextBoxIcon s
|
||||
nodeToIcon (LiteralNode s) = TextBoxIcon s
|
||||
nodeToIcon (FunctionDefNode x names) = FlatLambdaIcon x names
|
||||
nodeToIcon (MultiIfNode n) = MultiIfIcon n
|
||||
nodeToIcon (CaseNode n) = CaseIcon n
|
||||
nodeToIcon CaseResultNode = CaseResultIcon
|
||||
nodeToIcon (NestedCaseOrMultiIfNode tag x edges)
|
||||
nodeToIcon (CaseOrMultiIfNode tag x edges)
|
||||
= nestedCaseOrMultiIfNodeToIcon tag x edges
|
||||
|
||||
makeArg :: [(SgNamedNode, Edge)] -> Port -> Maybe NamedIcon
|
||||
@ -307,7 +303,7 @@ nestedApplySyntaxNodeToIcon :: LikeApplyFlavor
|
||||
nestedApplySyntaxNodeToIcon flavor numArgs args =
|
||||
NestedApply flavor headIcon argList
|
||||
where
|
||||
dummyNode = LikeApplyNode flavor numArgs
|
||||
dummyNode = ApplyNode flavor numArgs []
|
||||
argPorts = take numArgs (argumentPorts dummyNode)
|
||||
headIcon = makeArg args (inputPort dummyNode)
|
||||
argList = fmap (makeArg args) argPorts
|
||||
@ -321,7 +317,7 @@ nestedCaseOrMultiIfNodeToIcon tag numArgs args = case tag of
|
||||
CaseTag -> NestedCaseIcon argList
|
||||
MultiIfTag -> NestedMultiIfIcon argList
|
||||
where
|
||||
dummyNode = CaseNode numArgs
|
||||
dummyNode = CaseOrMultiIfNode CaseTag numArgs []
|
||||
argPorts = take (2 * numArgs) $ argumentPorts dummyNode
|
||||
argList = fmap (makeArg args) (inputPort dummyNode : argPorts)
|
||||
|
||||
|
13
app/Types.hs
13
app/Types.hs
@ -84,23 +84,18 @@ data SgNamedNode = SgNamedNode {
|
||||
|
||||
-- TODO remove Ints from SyntaxNode data constructors.
|
||||
data SyntaxNode =
|
||||
-- Function application, composition, and applying to a composition
|
||||
LikeApplyNode LikeApplyFlavor Int
|
||||
-- NestedApplyNode is only created in GraphAlgorithms, not during translation.
|
||||
-- Function application, composition, and applying to a composition
|
||||
-- The list of nodes is unordered (replace with a map?)
|
||||
| NestedApplyNode LikeApplyFlavor Int [(SgNamedNode, Edge)]
|
||||
| NestedPatternApplyNode String [Labeled (Maybe SgNamedNode)]
|
||||
ApplyNode LikeApplyFlavor Int [(SgNamedNode, Edge)]
|
||||
| PatternApplyNode String [Labeled (Maybe SgNamedNode)]
|
||||
| NameNode String -- Identifiers or symbols
|
||||
| BindNameNode String
|
||||
| LiteralNode String -- Literal values like the string "Hello World"
|
||||
| FunctionDefNode -- Function definition (ie. lambda expression)
|
||||
[String] -- Parameter labels
|
||||
[NodeName] -- Nodes inside the lambda
|
||||
| MultiIfNode
|
||||
Int -- Number of alternatives
|
||||
| CaseNode Int
|
||||
| CaseResultNode -- TODO remove caseResultNode
|
||||
| NestedCaseOrMultiIfNode CaseOrMultiIfTag Int [(SgNamedNode, Edge)]
|
||||
| CaseOrMultiIfNode CaseOrMultiIfTag Int [(SgNamedNode, Edge)]
|
||||
deriving (Show, Eq, Ord)
|
||||
|
||||
newtype Port = Port Int deriving (Typeable, Eq, Ord, Show)
|
||||
|
@ -47,8 +47,8 @@ maybeRenameNodeFolder (renamedNodes, nameMap, counter) mNode = case mNode of
|
||||
renameSyntaxNode :: NameMap -> SyntaxNode -> Int -> (SyntaxNode, NameMap, Int)
|
||||
renameSyntaxNode nameMap node counter = case node of
|
||||
-- TODO Keep the Nothing subNodes
|
||||
NestedPatternApplyNode s subNodes
|
||||
-> (NestedPatternApplyNode s (reverse renamedSubNodes)
|
||||
PatternApplyNode s subNodes
|
||||
-> (PatternApplyNode s (reverse renamedSubNodes)
|
||||
, newNameMap
|
||||
, counter2)
|
||||
where
|
||||
|
@ -23,7 +23,7 @@ import Icons(coloredTextBox)
|
||||
{-# ANN module "HLint: ignore Unnecessary hiding" #-}
|
||||
|
||||
prettyPrintSyntaxNode :: SyntaxNode -> String
|
||||
prettyPrintSyntaxNode (NestedApplyNode _ _ namedNodesAndEdges)
|
||||
prettyPrintSyntaxNode (ApplyNode _ _ namedNodesAndEdges)
|
||||
= concatMap printNameAndEdge namedNodesAndEdges
|
||||
where
|
||||
printNameAndEdge (namedNode, edge)
|
||||
|
Loading…
Reference in New Issue
Block a user