all = searchByType model ANNO.AnnotationType
named = filter (\x -> (getAnnotationNameFromType x) == name) all
if ((length named) == 1)
- then Just (fromResource $ named!0)
+ then Just (named!0)
else Nothing
setAnnotationPropertyValue :: AnnotationPropertyRelation -> Resource -> String -> String -> <WriteGraph> ()
setAnnotationPropertyValue annotation resource property newValue = do
resourceUri = uriOf resource
- annotationName = DB.nameOf (toResource annotation)
+ annotationName = DB.nameOf annotation
completeUri = resourceUri + "#" + annotationName + "#" + property + "#HasDisplayValue"
propertyVariable = variable completeUri
setValue propertyVariable newValue
Browses the given Model for its Charts and then returns them in a list.
"""
chartsOf :: Model -> <ReadGraph> [Chart]
-chartsOf model = recurse (toResource model)
+chartsOf model = recurse model
where
recurse r = do
- cs = resourceChildrenOf r
- charts = map fromResource $ filter isChart cs
+ cs = children r
+ charts = filter isChart cs
chartGrp = filter isChartGroup cs
charts + concatMap recurse chartGrp
isChart r = isInstanceOf r CHART.TimeSeriesChart
exportDocument :: Resource -> String -> <Proc> ()
documentsFolders :: Model -> <ReadGraph> [Resource]
-documentsFolders model = recurse DOCUMENT.DocumentLibrary (toResource model)
+documentsFolders model = recurse DOCUMENT.DocumentLibrary model
where
recurse t r = do
- cs = resourceChildrenOf r
+ cs = children r
libraries = filter isLibrary cs
libraryGrp = filter (not . isLibrary) cs
libraries + concatMap (recurse t) libraryGrp
isLibrary r = isInstanceOf r DOCUMENT.DocumentLibrary
documents :: Model -> <ReadGraph> [Resource]
-documents model = recurse DOCUMENT.Document (toResource model)
+documents model = recurse DOCUMENT.Document model
where
recurse t r = do
- cs = resourceChildrenOf r
+ cs = children r
documents = filter isDocument cs
documentFolder = filter (not . isDocument) cs
documents + concatMap (recurse t) documentFolder
setMonitorPropertyValue :: Monitor -> String -> String -> <WriteGraph> ()
setMonitorPropertyValue monitor property newValue = do
- monitorUri = uriOf (toResource monitor)
+ monitorUri = uriOf monitor
completeUri = monitorUri + "#" + property + "#HasDisplayValue"
propertyVariable = variable completeUri
setValue propertyVariable newValue
setFlagTablePropertyValue :: FlagTable -> String -> String -> <WriteGraph> ()
setFlagTablePropertyValue flagTable property newValue = do
- flagTableUri = uriOf (toResource flagTable)
+ flagTableUri = uriOf flagTable
completeUri = flagTableUri + "#" + property + "#HasDisplayValue"
propertyVariable = variable completeUri
setValue propertyVariable newValue
getLibrary :: Model -> String -> <ReadGraph> Library
librariesOf :: Model -> <ReadGraph> [Library]
-librariesOf model = recurse L0.Library (toResource model)
+librariesOf model = recurse L0.Library model
where
recurse t r = do
- cs = resourceChildrenOf r
- libraries = map fromResource $ filter isLibrary cs
+ cs = children r
+ libraries = filter isLibrary cs
libraryGrp = filter (not . isLibrary) cs
libraries + concatMap (recurse t) libraryGrp
isLibrary r = isInstanceOf r L0.Library
\ No newline at end of file
diagramsOf :: Model -> <ReadGraph> [Diagram]
diagramsOf model = recurse
DIA.Diagram
- (toResource (configurationOf model))
+ (configurationOf model)
where
recurse t r = do
- cs = resourceChildrenOf r
- dias = map fromResource $ filter isDiagramComposite cs
+ cs = children r
+ dias = filter isDiagramComposite cs
folders = filter (not . isDiagramComposite) cs
dias + concatMap (recurse t) folders
isDiagramComposite r = existsStatement r MOD.CompositeToDiagram
"""Returns a model relative path of the given diagram."""
pathOf :: Diagram -> <ReadGraph> [String]
-pathOf diagram = map nameOf $ unfoldl aux $ toResource diagram
+pathOf diagram = map nameOf $ unfoldl aux diagram
where
aux r = if existsStatement r SIMU.IsConfigurationOf
then Nothing
// @Private?
diagramResourceOf :: Diagram -> <ReadGraph> Resource
-diagramResourceOf d = singleObject (toResource d) MOD.CompositeToDiagram
+diagramResourceOf d = singleObject d MOD.CompositeToDiagram
import "Extras/HashMap" as Map
"""Creates or modifies an existing diagram to contain the given diagram elements."""
createDiagramR :: DiagramSpec -> (Dynamic -> <WriteGraph> Resource) -> [DiagramElement Resource] -> <WriteGraph> (Diagram, [Resource])
createDiagramR (ExistingDiagram diagram') joinMap elementSpecs = runProc do
- configuration = toResource diagram'
+ configuration = diagram'
diagram = compositeToDiagram' configuration
hasName = L0.HasName
componentMap = Map.fromList [ (c `relatedValue` hasName :: String, c)
- | c <- resourceChildrenOf configuration
+ | c <- children configuration
]
denyByPredicate diagram L0.ConsistsOf
elements = setElements (DiagramInfo diagram configuration componentMap) joinMap elementSpecs
elements = setElements (DiagramInfo diagram configuration (Map.create ())) joinMap elementSpecs
claimRelatedValue diagram DIA.HasModCount
(fromInteger (length elements) :: Long)
- (fromResource configuration, elements)
+ (configuration, elements)
) where
createConfiguration () = do
lastId = length path - 1
parentFolder = foldl (\p id -> getOrCreateFolder p (path!id))
- (toResource (configurationOf model))
+ (configurationOf model)
[0..lastId-1]
createComposite_ parentFolder (path!lastId) compositeType
getOrCreateFolder parentFolder name =
claimFolder model path folderType = do
lastId = length path
foldl (\p id -> getOrCreateFolder p folderType (path!id))
- (toResource (configurationOf model))
+ (configurationOf model)
[0..lastId-1]
claimModelFolder :: Model -> [String] -> Resource -> <Proc,WriteGraph> Resource
claimModelFolder model path folderType = do
lastId = length path
foldl (\p id -> getOrCreateFolder p folderType (path!id))
- (toResource model)
+ model
[0..lastId-1]
getOrCreateFolder :: Resource -> Resource -> String -> <Proc,WriteGraph> Resource
"""Returns a diagram in the given model with the given model relative path."""
diagram :: Model -> [String] -> <ReadGraph> Diagram
diagram model path =
- fromResource $ foldl
+ foldl
(\r name -> match possibleResourceChild r name with
Just c -> c
Nothing -> fail ("Didn't find " + name + ".")
)
- (toResource (configurationOf model)) path
+ (configurationOf model) path
possibleDiagram :: Model -> [String] -> <ReadGraph> (Maybe Diagram)
possibleDiagram model path =
- map fromResource (foldl
+ foldl
(\r name -> match r with
Just p -> possibleResourceChild p name
Nothing -> Nothing
)
- (Just $ toResource (configurationOf model)) path)
+ (Just (configurationOf model)) path
/*
"""FIXME: doesn't work anymore with the elementsOfR spec
syncActivateDiagram :: Diagram -> <WriteGraph, Proc> Boolean
syncActivateDiagram composite = do
- diagram = compositeToDiagram' $ toResource composite
+ diagram = compositeToDiagram' composite
syncActivateOnce diagram
True
createComposite__ :: Configuration -> String -> Resource -> <WriteGraph> Diagram
compositeToDiagram :: Resource -> <ReadGraph> Diagram
-compositeToDiagram c = fromResource (singleObject c MOD.CompositeToDiagram)
+compositeToDiagram c = singleObject c MOD.CompositeToDiagram
createComposite :: Configuration -> String -> Resource -> <WriteGraph> Diagram
createComposite diagramFolder name compositeType = do
- newName = findFreshName name (toResource diagramFolder)
+ newName = findFreshName name diagramFolder
createComposite__ diagramFolder newName compositeType
elementToComponent :: Element -> <ReadGraph> Component
-elementToComponent element = do
- component = singleObject (toResource element) MOD.ElementToComponent
- fromResource component
+elementToComponent element = singleObject element MOD.ElementToComponent
componentToElement :: Component -> <ReadGraph> Element
-componentToElement component = do
- element = singleObject (toResource component) MOD.ComponentToElement
- fromResource element
+componentToElement component = singleObject component MOD.ComponentToElement
getConnections :: Diagram -> <ReadGraph> [Resource]
-getConnections diagram = [object | object <- (toResource $ compositeToDiagram $ toResource diagram) # L0.ConsistsOf, isInstanceOf object DIA.RouteGraphConnection]
+getConnections diagram = [object | object <- (compositeToDiagram diagram) # L0.ConsistsOf, isInstanceOf object DIA.RouteGraphConnection]
getConnection :: Diagram -> String -> <ReadGraph> [Resource]
getConnection diagram name = do
$ sourceDiagram
for targetDiagrams $ \diagram ->
- syncActivateOnce $ toResource diagram
+ syncActivateOnce diagram
doElementPostProcessing elementMap elementPostProcessing
possibleDrawingTemplate :: Model -> Diagram -> <ReadGraph> Maybe Resource
possibleDrawingTemplate model d = do
d' = diagramResourceOf d
- library = fromJust $ possibleResourceChild (toResource model) "Diagram Templates"
+ library = fromJust $ possibleResourceChild model "Diagram Templates"
match (possibleObject d' TMPL.HasDrawingTemplate) with
Just dt -> match (possibleNameOf dt) with
Just name -> possibleResourceChild library name
()
getTargetComponent (targetDiagram :: Diagram) (sourceComponent :: Resource) =
- (possibleResourceChild (toResource targetDiagram) (fromJust $ possibleNameOf sourceComponent)) :: Maybe Resource
+ (possibleResourceChild targetDiagram (fromJust $ possibleNameOf sourceComponent)) :: Maybe Resource
translateDiagram2 (targetModel :: Model)
(sourceDiagram :: Diagram)
// FLAGS ---------------------------
+@deprecated "Unnecessary function."
toFlag :: Resource -> Flag
-toFlag flag = (fromResource flag)
+toFlag flag = flag
importJava "org.simantics.modeling.flags.MergeFlags" where
@JavaName mergeFlags
hasType STR.ConnectionJoin,
hasStatement
DIA.JoinsFlag
- (toResource flag1),
+ flag1,
hasStatement
DIA.JoinsFlag
- (toResource flag2)
+ flag2
]
()
+@deprecated "Unnecessary function."
flagToElement :: Flag -> Element
-flagToElement flag = do
- flagResource = toResource flag
- fromResource flagResource
+flagToElement flag = flag
getFlags :: Diagram -> <ReadGraph> [Resource]
getFlags dia = do
- children = collectionToList (objects_ (singleObject (toResource dia) MOD.CompositeToDiagram) L0.ConsistsOf)
+ children = collectionToList (objects_ (singleObject dia MOD.CompositeToDiagram) L0.ConsistsOf)
flags = filter (\x -> isInstanceOf x DIA.Flag) children
flags
type Severity = Resource
issuesOf :: Model -> <ReadGraph> [Issue]
-issuesOf model = recurse ISSUE.Issue (toResource model)
+issuesOf model = recurse ISSUE.Issue model
where
recurse t r = do
- cs = resourceChildrenOf r
- issues = map fromResource $ filter isIssue cs
+ cs = children r
+ issues = filter isIssue cs
issueGrp = filter (not . isIssue) cs
issues + concatMap (recurse t) issueGrp
isIssue r = isInstanceOf r ISSUE.Issue
"""
model :: String -> <ReadGraph> Model
model name = match possibleResourceChild (currentProject ()) name with
- Just m -> fromResource m
+ Just m -> m
Nothing -> fail $ "Didn't find a model " + name + "."
"""
and returns the `configuration` resource
"""
configurationOf :: Model -> <ReadGraph> Configuration
-configurationOf m = do
- conf = singleObject (toResource m) SIMU.HasConfiguration
- fromResource conf
+configurationOf m = singleObject m SIMU.HasConfiguration
"""
Returns the list of all models in the current project.
"""
allModels :: () -> <ReadGraph> [Model]
-allModels _ = map fromResource $ objectsWithType (currentProject ()) L0.ConsistsOf SIMU.Model
+allModels _ = objectsWithType (currentProject ()) L0.ConsistsOf SIMU.Model
importJava "org.simantics.modeling.ModelingUtils" where
"""Removes the index associated with the model."""
or error if failed
"""
+@deprecated "This function is equivalent to renameNode."
renameMBNode :: Resource -> String -> <WriteGraph> String
-renameMBNode entity newname = do
- renameNode (toResource entity) newname
+renameMBNode entity newname = renameNode entity newname
importJava "org.simantics.db.common.utils.NameUtils" where
@JavaName findFreshName
getSceneGraphProvider :: Diagram -> <Proc> ICanvasSceneGraphProvider
getSceneGraphProvider diagram = do
- diagramName = syncRead(\() -> getSafeName (toResource diagram))
+ diagramName = syncRead(\() -> getSafeName diagram)
diagramRVI = "/" + diagramName
- model = syncRead(\() -> getPossibleModel (toResource diagram))
- composite = syncRead(\() -> compositeToDiagram' (toResource diagram))
+ model = syncRead(\() -> getPossibleModel diagram)
+ composite = syncRead(\() -> compositeToDiagram' diagram)
getICanvasSceneGraphProvider model composite diagramRVI
getDiagramContext :: ICanvasSceneGraphProvider -> ICanvasContext
getNodeTransform :: Diagram -> String -> <Proc> String
getNodeTransform diagram nodeName = do
- diagramName = syncRead(\() -> getSafeName (toResource diagram))
+ diagramName = syncRead(\() -> getSafeName diagram)
diagramRVI = "/" + diagramName
- model = syncRead(\() -> getPossibleModel (toResource diagram))
- composite = syncRead(\() -> compositeToDiagram' (toResource diagram))
+ model = syncRead(\() -> getPossibleModel diagram)
+ composite = syncRead(\() -> compositeToDiagram' diagram)
provider = getICanvasSceneGraphProvider model composite diagramRVI
context = getCanvasContext provider
getTransform context nodeName
getNodeText :: Diagram -> String -> <Proc> String
getNodeText diagram nodeName = do
- diagramName = syncRead(\() -> getSafeName (toResource diagram))
+ diagramName = syncRead(\() -> getSafeName diagram)
diagramRVI = "/" + diagramName
- model = syncRead(\() -> getPossibleModel (toResource diagram))
- composite = syncRead(\() -> compositeToDiagram' (toResource diagram))
+ model = syncRead(\() -> getPossibleModel diagram)
+ composite = syncRead(\() -> compositeToDiagram' diagram)
provider = getICanvasSceneGraphProvider model composite diagramRVI
context = getCanvasContext provider
getText context nodeName
getNodeCount :: Diagram -> <Proc> String
getNodeCount diagram = do
- diagramName = syncRead(\() -> getSafeName (toResource diagram))
+ diagramName = syncRead(\() -> getSafeName diagram)
diagramRVI = "/" + diagramName
- model = syncRead(\() -> getPossibleModel (toResource diagram))
- composite = syncRead(\() -> compositeToDiagram' (toResource diagram))
+ model = syncRead(\() -> getPossibleModel diagram)
+ composite = syncRead(\() -> compositeToDiagram' diagram)
provider = getICanvasSceneGraphProvider model composite diagramRVI
context = getCanvasContext provider
getCount context
"""
subscriptionFoldersOf :: Model -> <ReadGraph> [SubscriptionFolder]
-subscriptionFoldersOf model = recurse (toResource model)
+subscriptionFoldersOf model = recurse model
where
- recurse r = do
- cs = resourceChildrenOf r
- folders = map fromResource $ filter isSubscriptionFolder cs
- folders
+ recurse r = filter isSubscriptionFolder (children r)
isSubscriptionFolder r = isInstanceOf r MOD.Subscription
configurationOfComponentType :: UserComponent -> <ReadGraph> Resource
configurationOfComponentType component = do
- config = singleObject (toResource component) STR.IsDefinedBy
+ config = singleObject component STR.IsDefinedBy
config
importJava "org.simantics.modeling.flags.LiftFlag" where
flagToTerminal :: Flag -> <WriteGraph> Resource
flagToTerminal flag = do
- result = liftFlag (toResource flag)
+ result = liftFlag flag
if result == Nothing
- then singleObject (toResource flag) DIA.IsLiftedAs
- else do
- show result
- (toResource flag)
-
+ then singleObject flag DIA.IsLiftedAs
+ else flag
+
+@deprecated "Calling this function is unnecessary."
configToDiagram :: Resource -> Diagram
-configToDiagram config = do
- fromResource config
+configToDiagram config = config
populateTerminalToSymbol :: Resource -> (Double, Double) -> <WriteGraph> Element
-populateTerminalToSymbol terminal (x, y) = do
+populateTerminalToSymbol terminal (x, y) = element
+ where
uc = singleObject terminal L0.PartOf
symbol = singleObject uc MOD.ComponentTypeToSymbol
diagram = singleObject symbol STR.IsDefinedBy
(toDoubleArray [1,0,0,1,x,y])
addToGraph diagram terminal element
addCommentMetadata ("Populated terminal " + (show element) + " to user component " + (show uc))
- (fromResource element)
+
importJava "org.simantics.modeling.symbolEditor.PopulateTerminal" where
addToGraph :: Resource -> Resource -> Resource -> <WriteGraph> ()
"""
modelVariableOfVariable :: Variable -> <ReadGraph> Variable
-modelVariableOfVariable var = variable $ uriOf $ toResource $ modelOfVariable var
+modelVariableOfVariable var = variable $ uriOf $ modelOfVariable var
uniqueChild :: Model -> Resource -> String -> <ReadGraph> Variable
uniqueChild model typet childName = do
typeName = DB.nameOf typet
query = "Types: " + typeName + " AND Name: " + childName
- moduleResources = searchByQuery (toResource model) query
+ moduleResources = searchByQuery model query
variable $ uriOf $ moduleResources ! 0
"""
instance Read String where
read str = str
-@deprecated
+@deprecated "Instead of 'splitString text pattern', write 'split pattern text' (note change in the parameter order)."
"`splitString text pattern` splits the string into a list of string where the parts are sepratated in the original list by the given pattern."
splitString :: String -> String -> [String]
splitString source pattern = arrayToList $ splitString_ source pattern