Skip to content

Commit

Permalink
minor refactorings
Browse files Browse the repository at this point in the history
  • Loading branch information
jsbezerra committed May 18, 2017
1 parent c06f1f7 commit 1b1e55e
Show file tree
Hide file tree
Showing 6 changed files with 50 additions and 27 deletions.
4 changes: 2 additions & 2 deletions src/CLI/CriticalPairAnalysis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,13 +12,13 @@ import Analysis.EssentialCriticalPairs
import Analysis.Interlevel.EvolutionarySpans
import Analysis.Interlevel.InterLevelCP
import Control.Monad (when)
import Data.List.Utils
import Data.Matrix hiding ((<|>))
import Data.Monoid ((<>))
import qualified Data.Set as Set
import GlobalOptions
import Options.Applicative
import SndOrder.Rule
import Util.List
import qualified XML.GGXReader as XML
import qualified XML.GGXWriter as GW

Expand Down Expand Up @@ -152,7 +152,7 @@ printEvoConflicts = map printOneEvo
show (printConf (True,False) (thd e)) ++ ", " ++
show (printConf (False,True) (thd e)) ++ ", " ++
show (printConf (True,True) (thd e)) ++ ")"
printConf str evos = countElem str (map cpe evos)
printConf str evos = countElement str (map cpe evos)

printAnalysis :: (EpiPairs m, DPO m) =>
Bool -> AnalysisType -> MorphismsConfig -> [Production m] -> IO ()
Expand Down
30 changes: 15 additions & 15 deletions src/library/Graph/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ module Graph.Graph (
import Abstract.Cardinality
import Abstract.Valid
import Data.List
import Data.List.Utils
import Util.List
import Data.Maybe (fromJust, fromMaybe)


Expand Down Expand Up @@ -353,53 +353,53 @@ fromNodesAndEdges nodes edges =
-- identifier aready exists, its payload is removed. /O(v)/.
insertNode :: NodeId -> Graph (Maybe n) e -> Graph (Maybe n) e
insertNode n (Graph ns es) =
Graph (addToAL ns n (Node n Nothing)) es
Graph (insertByKey ns n (Node n Nothing)) es

-- | Insert a node with given identifier and payload into a graph. If a node with the given
-- identifier already exists, its payload is updated. /O(v)/.
insertNodeWithPayload :: NodeId -> n -> Graph n e -> Graph n e
insertNodeWithPayload n p (Graph ns es) =
Graph (addToAL ns n (Node n p)) es
Graph (insertByKey ns n (Node n p)) es

-- | (@insertEdge e src tgt g@) will insert an edge with identifier @e@ from @src@ to @tgt@ in graph
-- @g@, without payload. If @src@ or @tgt@ are not nodes of @g@, the graph is not modified. If an
-- edge with identifier @e@ already exists, it is updated. /O(v + e)/.
insertEdge :: EdgeId -> NodeId -> NodeId -> Graph n (Maybe e) -> Graph n (Maybe e)
insertEdge e src tgt g@(Graph ns es)
| src `elem` keysAL ns && tgt `elem` keysAL ns =
Graph ns (addToAL es e (Edge e src tgt Nothing))
| src `elem` listKeys ns && tgt `elem` listKeys ns =
Graph ns (insertByKey es e (Edge e src tgt Nothing))
| otherwise = g

-- | (@insertEdgeWithPayload e src tgt p g@) will insert an edge with identifier @e@ from @src@ to
-- @tgt@ in graph @g@ with payload @p@. If @src@ or @tgt@ are not nodes of @g@, the graph is not
-- modified. If an edge with identifier @e@ already exists, it is updated. /O(v + e)/.
insertEdgeWithPayload :: EdgeId -> NodeId -> NodeId -> e -> Graph n e -> Graph n e
insertEdgeWithPayload e src tgt p g@(Graph ns es)
| src `elem` keysAL ns && tgt `elem` keysAL ns =
Graph ns (addToAL es e (Edge e src tgt p))
| src `elem` listKeys ns && tgt `elem` listKeys ns =
Graph ns (insertByKey es e (Edge e src tgt p))
| otherwise = g

-- | Removes the given node from the graph, unless it has any incident edges. /O(v + e²)/.
removeNode :: NodeId -> Graph n e -> Graph n e
removeNode n g@(Graph ns es)
| Prelude.null $ getIncidentEdges g n = Graph (delFromAL ns n) es
| Prelude.null $ getIncidentEdges g n = Graph (deleteByKey ns n) es
| otherwise = g

-- | Removes the given node from the graph, even if it has any incident edges.
-- It does not verify if the node has incident edges, thus it may generate invalid graphs.
removeNodeForced :: NodeId -> Graph n e -> Graph n e
removeNodeForced n (Graph ns es) = Graph (delFromAL ns n) es
removeNodeForced n (Graph ns es) = Graph (deleteByKey ns n) es

-- | Removes the given node and all incident edges from the graph. /O(v + e)/
removeNodeAndIncidentEdges :: NodeId -> Graph n e -> Graph n e
removeNodeAndIncidentEdges nodeId (Graph nodes edges) =
Graph
(delFromAL nodes nodeId)
(deleteByKey nodes nodeId)
(filter (\(_, e) -> sourceId e /= nodeId && targetId e /= nodeId) edges)

-- | Remove the given edge from the graph. /O(e)/.
removeEdge :: EdgeId -> Graph n e -> Graph n e
removeEdge e (Graph ns es) = Graph ns (delFromAL es e)
removeEdge e (Graph ns es) = Graph ns (deleteByKey es e)

-- | Update the node's payload, applying the given function on it. /O(v)/.
updateNodePayload :: NodeId -> Graph n e -> (n -> n) -> Graph n e
Expand All @@ -413,7 +413,7 @@ updateNodePayload nodeId graph@(Graph nodes _) f =
updatedNode =
node { nodeInfo = f (nodeInfo node) }
in
graph { nodeMap = addToAL nodes nodeId updatedNode }
graph { nodeMap = insertByKey nodes nodeId updatedNode }


-- | Update the edge's payload, applying the function on it. /O(e)/.
Expand All @@ -429,17 +429,17 @@ updateEdgePayload edgeId graph@(Graph _ edges) f =
edge { edgeInfo = f (edgeInfo edge) }

in
graph { edgeMap = addToAL edges edgeId updatedEdge }
graph { edgeMap = insertByKey edges edgeId updatedEdge }


-- | List of all node id's from from the graph. /O(v)/.
nodeIds :: Graph n e -> [NodeId]
nodeIds (Graph nodes _) = keysAL nodes
nodeIds (Graph nodes _) = listKeys nodes


-- | List of all edge id's from from the graph. /O(e)/.
edgeIds :: Graph n e -> [EdgeId]
edgeIds (Graph _ edges) = keysAL edges
edgeIds (Graph _ edges) = listKeys edges


-- | List of all nodes from the graph. /O(v)/.
Expand Down
25 changes: 24 additions & 1 deletion src/library/Util/List.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
module Util.List
( replace
( countElement
, deleteByKey
, insertByKey
, listKeys
, replace
, repeated
)

Expand All @@ -14,3 +18,22 @@ replace idx new list = take idx list ++ [new] ++ drop (idx+1) list
repeated :: (Eq a) => [a] -> Bool
repeated [] = False
repeated (x:xs) = x `elem` xs || repeated xs


-- | Given a list of pairs of the form (key, value), it returns a list containg onlying the listKeys
listKeys :: [(key, a)] -> [key]
listKeys = map fst

{- | Given a list of pairs of the form (key, value), a key @k@ and a value @v@, it will
add the pair (k,v) to the list and remove all previous pairs that match the key @k@. -}
insertByKey :: Eq k => [(k, a)] -> k -> a -> [(k, a)]
insertByKey l k value = (k, value) : deleteByKey l k

{- | Given a list of pairs of the form (key, value) and a key, it removes
all pairs that match the given key.-}
deleteByKey :: Eq k => [(k, a)] -> k -> [(k, a)]
deleteByKey l k = filter (\a -> fst a /= k) l

{- | Given an element @e@ and a list @l@, it returns the number of times that @e@ appears in @l@ -}
countElement :: Eq a => a -> [a] -> Int
countElement i = length . filter (i==)
8 changes: 4 additions & 4 deletions src/library/XML/GGXWriter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ module XML.GGXWriter
writeSndOderDependenciesFile
) where

import Data.List.Utils (startswith)
import Data.Maybe
import Text.XML.HXT.Core

Expand All @@ -19,6 +18,7 @@ import Abstract.Morphism (codomain)
import qualified Analysis.CriticalPairs as CP
import qualified Analysis.CriticalSequence as CS
import qualified Analysis.EssentialCriticalPairs as ECP
import Data.List
import qualified Graph.Graph as G
import SndOrder.Morphism
import qualified SndOrder.Rule as SO
Expand Down Expand Up @@ -160,7 +160,7 @@ writeCriticalPairAnalysis names productions cpOL csOL = writeCpaOptions : confli
dependenceContainer = if null csOL then [] else
[writeConflictContainer "trigger_switch_dependency" nacNames productions csOL,
writeConflictFreeContainer productions csOL]
nacNames = filter (\(x,_) -> startswith "NAC" x) names
nacNames = filter (\(x,_) -> isPrefixOf "NAC" x) names

writeConflictContainer :: ArrowXml a => String -> [(String,String)] -> [(String,GR.GraphRule b c)] -> [Overlappings] -> a XmlTree XmlTree
writeConflictContainer kind nacNames productions overlappings =
Expand Down Expand Up @@ -220,7 +220,7 @@ writeGrammar (gg1,gg2) names = writeAggProperties ++
writeRules gg1 nacNames ++
writeSndOrderRules gg2
where
nacNames = filter (\(x,_) -> startswith "NAC" x) names
nacNames = filter (\(x,_) -> isPrefixOf "NAC" x) names

writeInitialGraph :: ArrowXml a => TypedGraph b c -> a XmlTree XmlTree
writeInitialGraph initial = writeHostGraph ("Init", initial)
Expand Down Expand Up @@ -537,7 +537,7 @@ writeConditions nacNames ruleName rule =
mkelem "ApplCondition" [] $ map (writeNac ruleName) (zip (getNacs ruleName rule) (map snd nacsRule++nacsNoName))
where
-- filter the name of the nacs of this rule
nacsRule = filter (\(x,_) -> startswith ("NAC_"++ruleName) x) nacNames
nacsRule = filter (\(x,_) -> isPrefixOf ("NAC_"++ruleName) x) nacNames
-- in the case of do not find, writes Nac_0,Nac_1,...
nacsNoName = [a++b | a <- ["Nac_"], b <- map show [0::Int ..]]

Expand Down
6 changes: 3 additions & 3 deletions tests/SecondOrderTest.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
import Abstract.DPO
import Abstract.Morphism
import Analysis.Interlevel.InterLevelCP
import Data.List.Utils (countElem)
import Data.Maybe (fromMaybe)
import SndOrder.Morphism
import SndOrder.Morphism.NACmanipulation
import Test.HUnit
import TypedGraph.Graph
import TypedGraph.Morphism
import Utils
import Util.List
import qualified XML.GGXReader as XML

-- | Checks if the number of minimalSafetyNACs was correctly generated.
Expand All @@ -32,8 +32,8 @@ checkDanglingExtension gg1 =

[(_,typeOfMsg),(_,typeOfData)] = typedNodes (codomain left)

msgsInDang = countElem typeOfMsg (map snd nods)
dataInDang = countElem typeOfData (map snd nods)
msgsInDang = countElement typeOfMsg (map snd nods)
dataInDang = countElement typeOfData (map snd nods)
nods = typedNodes dangGraph
edgs = typedEdges dangGraph

Expand Down
4 changes: 2 additions & 2 deletions verigraph.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,8 @@ library
TypedGraph.DPO.OccurenceRelation
TypedGraph.Graph
TypedGraph.Morphism
Util.Closures
Util.List
XML.GGXReader
XML.GGXWriter
other-modules:
Expand Down Expand Up @@ -89,8 +91,6 @@ library
SndOrder.Morphism.FindMorphism
SndOrder.Rule.Core
SndOrder.Rule.DPO
Util.Closures
Util.List
XML.Formulas
XML.GGXParseIn
XML.GGXParseOut
Expand Down

0 comments on commit 1b1e55e

Please sign in to comment.