]> gerrit.simantics Code Review - simantics/platform.git/blob - bundles/org.simantics.scl.db/scl/Simantics/DB.scl
ec9cc2671e3294f5f5335bf1c252f6653d0ffebc
[simantics/platform.git] / bundles / org.simantics.scl.db / scl / Simantics / DB.scl
1 import "JavaBuiltin" as Java
2 include "http://www.simantics.org/Layer0-1.1" as L0
3 import "Map" as Map
4
5 infixl 5 (#)
6  
7 effect ReadGraph
8     "graph"
9     "org.simantics.db.ReadGraph"
10
11 effect WriteGraph
12     "graph"
13     "org.simantics.db.WriteGraph"
14     
15 importJava "org.simantics.db.Resource" where
16     "A resource is a node in a semantic graph."
17     data Resource
18     
19     "Returns the 64-bit unique identifier of the resource."
20     @JavaName getResourceId
21     resourceId :: Resource -> Long
22     
23     isPersistent :: Resource -> Boolean
24     
25 importJava "org.simantics.db.ReadGraph" where
26     data ReadGraphX
27     
28 instance Ord Resource where
29     compare a b = compare (resourceId a) (resourceId b)
30   
31 instance Show Resource where
32     show r = "#" + show (resourceId r)
33
34 instance Show Statement where
35     show s = "#" + show (resourceId ( subjectOf s)) + "#" + show (resourceId ( predicateOf s)) + "#" + show (resourceId ( objectOf s))
36
37 importJava "org.simantics.db.Statement" where
38     "A statement is an edge in a semantic graph."
39     data Statement
40     
41     @JavaName getSubject
42     subjectOf :: Statement -> Resource
43     @JavaName getPredicate
44     predicateOf :: Statement -> Resource
45     @JavaName getObject
46     objectOf :: Statement -> Resource
47     
48     isAsserted :: Statement -> Resource -> <ReadGraph> Boolean
49     
50 importJava "org.simantics.db.ReadGraph" where
51     "Converts an absolute URI to a resource or returns `Nothing` if there is no such resource."
52     @JavaName getPossibleResource
53     possibleResource :: String -> <ReadGraph> (Maybe Resource)
54     
55     getDataType :: Resource -> <ReadGraph> Datatype
56
57     @JavaName getSupertypes
58     superTypesOf :: Resource -> <ReadGraph> Set.T Resource
59     
60     @private
61     @JavaName getURI
62     uriOfResource :: Resource -> <ReadGraph> String
63
64     @private
65     @JavaName getPossibleURI
66     possibleUriOfResource :: Resource -> <ReadGraph> Maybe String
67     
68     @JavaName getObjects
69     objects_ :: Resource -> Resource -> <ReadGraph> Collection Resource
70     
71     @JavaName getStatements
72     statements_ :: Resource -> Resource -> <ReadGraph> Collection Statement
73     
74     @JavaName hasStatement
75     existsStatement :: Resource -> Resource -> <ReadGraph> Boolean
76     
77     @JavaName hasStatement
78     existsStatement3 :: Resource -> Resource -> Resource -> <ReadGraph> Boolean
79
80     "Assumes that there is exactly one object with the given subject and predicate and returns it."
81     @JavaName getSingleObject
82     singleObject :: Resource -> Resource -> <ReadGraph> Resource
83
84     """
85     If there is exactly one object with the given `subject` and `predicate`,
86     `possibleObject subject predicate` returns it. Otherwise, it returns
87     `Nothing`.
88     """
89     @JavaName getPossibleObject
90     possibleObject :: Resource -> Resource -> <ReadGraph> Maybe Resource
91
92     "Assumes that there is exactly one statement with the given subject and predicate and returns it."
93     @JavaName getSingleStatement
94     singleStatement :: Resource -> Resource -> <ReadGraph> Statement
95
96     @JavaName getPossibleStatement
97     possibleStatement :: Resource -> Resource -> <ReadGraph> Maybe Statement
98
99     @JavaName getRelatedVariantValue
100     relatedVariantValue :: Resource -> Resource -> <ReadGraph> Variant
101
102     @JavaName getRelatedValue
103     relatedValue_ :: Resource -> Resource -> Binding a -> <ReadGraph> a
104     
105     @JavaName getRelatedValue
106     untypedRelatedValue :: Resource -> Resource -> <ReadGraph> a
107
108     @JavaName getRelatedValue2
109     relatedValue2 :: Resource -> Resource -> <ReadGraph> a
110
111     @JavaName getRelatedVariantValue2
112     relatedVariantValue2 :: Resource -> Resource -> <ReadGraph> Variant
113     
114     @JavaName getPossibleRelatedValue
115     possibleRelatedValue_ :: Resource -> Resource -> Binding a -> <ReadGraph> Maybe a
116     
117     @JavaName getPossibleRelatedValue
118     untypedPossibleRelatedValue :: Resource -> Resource -> <ReadGraph> Maybe a
119     
120     @private
121     @JavaName getValue
122     valueOf_ :: Resource -> Binding a -> <ReadGraph> a
123     
124     @private
125     @JavaName getVariantValue
126     variantValueOf_ :: Resource -> <ReadGraph> Variant
127     
128     @JavaName getValue
129     untypedValueOf :: Resource -> <ReadGraph> Dynamic
130     
131     @JavaName getPossibleValue
132     untypedPossibleValueOf :: Resource -> <ReadGraph> Maybe Dynamic
133     
134     @JavaName getInverse
135     inverseOf :: Resource -> <ReadGraph> Resource
136     
137     @JavaName getSingleType
138     singleTypeOf :: Resource -> Resource -> <ReadGraph> Resource
139     
140     @JavaName getPossibleType
141     possibleTypeOf :: Resource -> Resource -> <ReadGraph> Maybe Resource
142     
143     "`isInstanceOf r t` returns true, if `r` is an instance of `t`"
144     isInstanceOf :: Resource -> Resource -> <ReadGraph> Boolean
145     isSubrelationOf :: Resource -> Resource -> <ReadGraph> Boolean
146     isInheritedFrom :: Resource -> Resource -> <ReadGraph> Boolean
147     
148     getRootLibrary :: () -> <ReadGraph> Resource
149     
150     @JavaName getPredicates
151     predicatesOf :: Resource -> <ReadGraph> [Resource]
152
153 importJava "org.simantics.db.layer0.util.ExtendedUris" where
154     "Converts an absolute URI to a resource"
155     @JavaName resolveAbsoluteUri    
156     resource :: String -> <ReadGraph> Resource
157     
158     "Converts a relative URI to a resource starting from the given resource"
159     @JavaName resolveRelativeUri
160     relativeResource :: Resource -> String -> <ReadGraph> Resource
161
162 "Reads the value of a literal that is an object with the given subject and predicate"
163 @inline
164 relatedValue :: Serializable a => Resource -> Resource -> <ReadGraph> a
165 relatedValue s p = relatedValue_ s p binding
166
167 @inline
168 possibleRelatedValue :: Serializable a => Resource -> Resource -> <ReadGraph> Maybe a
169 possibleRelatedValue s p = possibleRelatedValue_ s p binding
170
171 class Browsable a where
172     fromUri :: String -> <ReadGraph> a
173
174     "Returns the URI of the given value."
175     uriOf :: a -> <ReadGraph> String
176     
177     "Returns the URI of the given value if it exists or Nothing."
178     possibleUriOf :: a -> <ReadGraph> Maybe String
179     
180     "Reads the name of the value."
181     nameOf :: a -> <ReadGraph> String
182     possibleNameOf :: a -> <ReadGraph> Maybe String
183     
184     valueOf :: Serializable v => a -> <ReadGraph> v
185     
186     variantValueOf :: a -> <ReadGraph> Variant 
187     
188     children :: a -> <ReadGraph> [a]
189     parent :: a -> <ReadGraph> a
190     possibleParent :: a -> <ReadGraph> Maybe a
191     
192     child :: a -> String -> <ReadGraph> a
193     possibleChild :: a -> String -> <ReadGraph> Maybe a
194     
195 instance Browsable Resource where
196     fromUri = resource
197     uriOf = uriOfResource
198     possibleUriOf = possibleUriOfResource
199     nameOf r = relatedValue r L0.HasName
200     possibleNameOf r = possibleRelatedValue r L0.HasName
201     @inline
202     valueOf r = valueOf_ r binding
203     variantValueOf = variantValueOf_
204     
205     children r = r # L0.ConsistsOf
206     parent r = singleObject r L0.PartOf
207     possibleParent r = possibleObject r L0.PartOf
208     
209     possibleChild = possibleResourceChild
210     child r n = fromJust (possibleResourceChild r n)
211
212 importJava "org.simantics.db.WriteOnlyGraph" where
213     markUndoPoint :: () -> <WriteGraph> ()
214
215 importJava "org.simantics.db.WriteGraph" where
216     "Creates a new resource."
217     newResource :: () -> <WriteGraph> Resource
218     "Adds a statement to the semantic graph."
219     claim :: Resource -> Resource -> Resource -> <WriteGraph> ()
220     @JavaName claimLiteral
221     claimRelatedValue_ :: Resource -> Resource -> a -> Binding a -> <WriteGraph> ()
222     @JavaName claimLiteral
223     untypedClaimRelatedValue :: Resource -> Resource -> a -> <WriteGraph> ()
224     @JavaName claimValue
225     untypedClaimValue :: Resource -> a -> <WriteGraph> ()
226     @JavaName claimLiteral
227     claimRelatedValueWithType_ :: Resource -> Resource -> Resource -> a -> Binding a -> <WriteGraph> ()
228     "Removes a statement with the given subject, predicate and object"
229     deny :: Resource -> Resource -> Resource -> <WriteGraph> ()
230     @JavaName deny
231     denyByPredicate :: Resource -> Resource -> <WriteGraph> ()
232     @JavaName deny
233     denyAllStatements :: Resource -> <WriteGraph> ()
234     newClusterSet :: Resource -> <WriteGraph> ()
235     @JavaName denyValue
236     denyValue :: Resource -> <WriteGraph> ()
237
238 claimAssertion :: Resource -> Resource -> Resource -> <WriteGraph> ()
239 claimAssertion type_ predicate object = do
240     ass = newResource ()
241     claim ass L0.HasPredicate predicate
242     claim ass L0.HasObject object
243     claim type_ L0.Asserts ass
244
245 "Sets the value of the literal that is an object with the given subject and predicate."
246 @inline
247 claimRelatedValue :: Serializable a => Resource -> Resource -> a -> <WriteGraph> ()
248 claimRelatedValue s p v = claimRelatedValue_ s p v binding
249
250 @inline
251 claimRelatedValueWithType :: Serializable a => Resource -> Resource -> Resource -> a -> <WriteGraph> ()
252 claimRelatedValueWithType s p t v = claimRelatedValueWithType_ s p t v binding
253
254 importJava "org.simantics.layer0.utils.direct.GraphUtils" where
255     @JavaName getPossibleChild
256     possibleResourceChild :: Resource -> String -> <ReadGraph> (Maybe Resource)
257
258 @deprecated "Use function children instead."
259 resourceChildrenOf :: Resource -> <ReadGraph> [Resource]
260 resourceChildrenOf r = r # L0.ConsistsOf
261
262 importJava "org.simantics.db.common.utils.OrderedSetUtils" where
263     @JavaName add
264     addToOrderedSet :: Resource -> Resource -> <WriteGraph> Boolean
265     
266     @JavaName set
267     setOrderedSet :: Resource -> [Resource] -> <WriteGraph> Boolean
268     
269     @JavaName getSingleOwnerList
270     parentOrderedSet :: Resource -> <ReadGraph> Resource
271     
272     @JavaName toList
273     elementsOfOrderedSet :: Resource -> <ReadGraph> [Resource]
274     
275 importJava "org.simantics.db.common.utils.ListUtils" where
276     @JavaName toList
277     elementsOfList :: Resource -> <ReadGraph> [Resource]
278     
279     @JavaName create
280     createList :: [Resource] -> <WriteGraph> Resource
281
282     @JavaName create
283     createListWithType :: Resource -> [Resource] -> <WriteGraph> Resource
284     
285     @javaName insertBack
286     insertBack :: Resource -> [Resource] -> <WriteGraph> ()
287     
288     @javaName removeElement
289     removeElement :: Resource -> Resource -> <WriteGraph> Boolean
290     
291     @javaName swapWithPrevious
292     swapWithPrevious :: Resource -> Resource -> <WriteGraph> Boolean
293
294     @javaName swapWithNext
295     swapWithNext :: Resource -> Resource -> <WriteGraph> Boolean
296
297
298 importJava "org.simantics.db.common.utils.CommonDBUtils" where
299     isParent :: Resource -> Resource -> <ReadGraph> Boolean
300     possibleRelatedString :: Resource -> Resource -> <ReadGraph> Maybe String
301     possibleRelatedInteger :: Resource -> Resource -> <ReadGraph> Maybe Integer
302     objectsWithType :: Resource -> Resource -> Resource -> <ReadGraph> [Resource]
303     possibleObjectWithType :: Resource -> Resource -> Resource -> <ReadGraph> Maybe Resource
304
305 importJava "org.simantics.db.common.utils.NameUtils" where
306     findFreshName :: String -> Resource -> <ReadGraph> String
307     findFreshEscapedName :: String -> Resource -> <ReadGraph> String
308
309 "`subject # predicate` returns all objects with the given `subject` and `predicate`."
310 (#) :: Resource -> Resource -> <ReadGraph> [Resource]
311 subject # predicate = collectionToList $ objects_ subject predicate
312
313 "statements subject predicate` returns all statements with the given subject and predicate."
314 statements :: Resource -> Resource -> <ReadGraph> [Statement]
315 statements subject predicate = collectionToList $ statements_ subject predicate
316
317 importJava "org.simantics.scl.db.SCLFunctions" where
318     "Executes a read transaction and waits that it completes."
319     syncRead :: (() -> <Proc,ReadGraph> a) -> <Proc> a
320     "Executes a write transaction and waits that it completes."
321     syncWrite :: (() -> <Proc,ReadGraph,WriteGraph> a) -> <Proc> a
322     "Executes a delayed write transaction and waits that it completes."
323     delayedSyncWrite :: (() -> <Proc,WriteGraph> a) -> <Proc> a
324     
325     "Begins a read transaction and immediately returns."
326     asyncRead :: (() -> <Proc,ReadGraph> a) -> <Proc> ()
327     "Begins a write transaction and immediately returns."
328     asyncWrite :: (() -> <Proc,ReadGraph,WriteGraph> a) -> <Proc> ()
329     
330     virtualSyncWriteMem :: String -> (() -> <ReadGraph,WriteGraph> a) -> <WriteGraph> a
331     virtualSyncWriteWS :: String -> (() -> <ReadGraph,WriteGraph> a) -> <WriteGraph> a
332     
333     safeExec :: (() -> <Proc> a) -> <Proc> a
334     activateOnce :: Resource -> <Proc> ()
335     syncActivateOnce :: Resource -> <WriteGraph, Proc> ()
336     resourceFromId :: Long -> <ReadGraph> Resource
337     enableDependencies :: () -> <WriteGraph> ()
338     disableDependencies :: () -> <WriteGraph> ()
339     
340     unaryQuery :: (a -> <ReadGraph,e> b) -> a -> <ReadGraph> b
341     unaryQueryCached :: (a -> <ReadGraph,e> b) -> a -> <ReadGraph> b
342
343     "Makes a new read request with given procedure for calculating the result. The request is cached only if the current request is listened."
344     subquery :: (<ReadGraph,Proc> a) -> <ReadGraph,Proc> a
345     "Makes a new read request with given procedure for calculating the result. The request is always cached."
346     subqueryC :: (<ReadGraph,Proc> a) -> <ReadGraph,Proc> a
347     "Makes a new read asynchronous request with function to handle the request result. The last `isDisposed` function parameter is used to determine if the listener is still alive or not."
348     subqueryL :: (<ReadGraph,Proc> a) -> (a -> <ReadGraph, e> ()) -> (Throwable -> <ReadGraph, e> ()) -> (<e> Boolean) -> <ReadGraph, Proc, e> ()
349     "Tries to convert the given Dynamic value to a value with the inferred type"
350     possibleFromDynamic :: Typeable a => String -> Dynamic -> Maybe a
351
352 importJava "org.simantics.db.layer0.util.Layer0Utils" where
353     undo :: () -> <Proc> String
354     undoOperations :: Integer -> <Proc> String
355     redo :: () -> <Proc> String
356     queryDebugSupport :: String -> <Proc> String
357     queryListSupport :: String -> <Proc> String
358     addCommentMetadata :: String -> <WriteGraph> ()
359     sortByCluster :: [a] -> (a->Resource) -> <ReadGraph> [a]
360     makeSynchronous :: Boolean -> <ReadGraph> ()
361     listOntologies :: () -> <ReadGraph> [Resource]
362     emptyTrashBin :: () -> <Proc> ()
363     purgeDatabase :: () -> <Proc> ()
364     prettyPrintResource :: Resource -> Boolean -> <ReadGraph> String
365
366     @private
367     @JavaName copyTo
368     copyTo_ :: Resource -> Resource -> <WriteGraph> Collection Resource
369     @JavaName getPossiblePredicateByName
370     possiblePredicateByName :: Resource -> String -> <ReadGraph> Maybe Resource
371     @JavaName getPossiblePredicateByNameFromType
372     possiblePredicateByNameFromType :: Resource -> String -> <ReadGraph> Maybe Resource
373     
374     addMetadataListener :: ChangeListener -> <Proc> ()
375     removeMetadataListener :: ChangeListener -> <Proc> ()
376
377 copyTo :: Resource -> Resource -> <WriteGraph> Resource
378 copyTo targetContainer source = do
379     (collectionToList $ copyTo_ targetContainer source)!0
380
381 importJava "org.simantics.db.common.utils.CommonDBUtils" where
382     selectClusterSet :: Resource -> <WriteGraph> () 
383
384 importJava "org.simantics.Simantics" where
385     @JavaName getProjectResource
386     currentProject :: () -> /*<Proc>*/ Resource
387
388 // Move to somewhere more generic module
389 importJava "java.util.Collection" where
390     data Collection a
391
392 importJava "java.util.ArrayList" where
393     @JavaName "<init>"
394     collectionToList :: Collection a -> [a]
395 /*@macro
396 collectionToList :: Collection a -> [a]
397 collectionToList x = Java.unsafeCoerce x
398 */ 
399
400 resourceToCollection :: a -> Collection a
401 resourceToCollection x = Java.unsafeCoerce x
402
403 newEntity :: [Resource -> <ReadGraph,WriteGraph> ()] -> <ReadGraph,WriteGraph> Resource
404 newEntity entitySpecs = do
405     entity = newResource ()
406     for entitySpecs (\spec -> spec entity)
407     entity
408
409 updateEntity :: Resource -> [Resource -> <ReadGraph,WriteGraph> ()] -> <ReadGraph,WriteGraph> Resource
410 updateEntity entity entitySpecs = do
411     for entitySpecs (\spec -> spec entity)
412     entity
413
414 hasStatement predicate object entity = 
415     claim entity predicate object
416 hasProperty relation value entity = 
417     claimRelatedValue entity relation value
418 hasPossibleProperty relation value entity =
419     match value with
420       Just v -> claimRelatedValue entity relation v
421       Nothing -> ()
422 hasTypedProperty relation value t entity = 
423     claimRelatedValueWithType entity relation t value        
424 hasName (n :: String) = hasProperty L0.HasName n
425 hasLabel (l :: String) = hasProperty L0.HasLabel l
426 hasType t = hasStatement L0.InstanceOf t
427 hasParent p = hasStatement L0.PartOf p
428
429 importJava "org.simantics.databoard.util.URIStringUtils" where
430     @JavaName splitURISCL
431     splitURI :: String -> [String]
432     @JavaName escape
433     escapeURI :: String -> String
434     @JavaName unescape
435     unescapeURI :: String -> String
436
437 @private
438 importJava "org.simantics.db.layer0.request.ActiveModels" where
439     @JavaName getPossibleActiveModel
440     activeModel :: Resource -> <ReadGraph> Maybe Resource
441
442 "Gives the current active model."
443 currentModel :: <ReadGraph> Resource
444 currentModel = match activeModel (currentProject ()) with
445     Just model -> model
446     Nothing -> fail "No active model."
447
448 "Gives the current active model if it exists or Nothing otherwise."
449 possibleCurrentModel :: <ReadGraph> Maybe Resource
450 possibleCurrentModel = activeModel (currentProject ())
451     
452 startUndoPoint :: String -> <WriteGraph> ()
453 startUndoPoint string = do
454     markUndoPoint ()
455     addCommentMetadata (string)
456     ()
457
458 @inline
459 lift1Read :: (a -> <ReadGraph,Proc> b) -> (a -> <Proc> b)
460 lift1Read f x = syncRead (\_ -> f x)
461
462 @inline
463 lift2Read :: (a -> b -> <ReadGraph,Proc> c) -> (a -> b -> <Proc> c)
464 lift2Read f x y = syncRead (\_ -> f x y)
465
466 @inline
467 lift3Read :: (a -> b -> c -> <ReadGraph,Proc> d) -> (a -> b -> c -> <Proc> d)
468 lift3Read f x y z = syncRead (\_ -> f x y z)
469
470 @inline
471 lift1Write :: (a -> <WriteGraph,Proc> b) -> (a -> <Proc> b)
472 lift1Write f x = syncWrite (\_ -> f x)
473
474 @inline
475 lift2Write :: (a -> b -> <WriteGraph,Proc> c) -> (a -> b -> <Proc> c)
476 lift2Write f x y = syncWrite (\_ -> f x y)
477
478 @inline
479 lift3Write :: (a -> b -> c -> <WriteGraph,Proc> d) -> (a -> b -> c -> <Proc> d)
480 lift3Write f x y z = syncWrite (\_ -> f x y z)
481
482 """
483 Returns a child Browsable of the specified parent that has that is the child
484 of the specified parent with the specified name path.
485 """
486 childWithPath :: Browsable a => a -> [String] -> <ReadGraph> a
487 childWithPath parent path = 
488     foldl (\r name -> match possibleChild r name with
489               Just c -> c
490               Nothing -> fail ("Didn't find " + name + ".") 
491           ) 
492           parent path
493
494 """
495 Like `childWithPath` but returns Maybe a which will be `Nothing` if no child
496 was found.
497 """
498 possibleChildWithPath :: Browsable a => a -> [String] -> <ReadGraph> Maybe a
499 possibleChildWithPath parent path = 
500     foldl (\r name -> match r with
501               Just c -> possibleChild c name
502               Nothing -> Nothing 
503           ) 
504           (Just parent) path
505
506 importJava "org.simantics.db.MetadataI" where
507     data MetadataI
508
509 importJava "org.simantics.db.event.ChangeListener" where
510     data ChangeListener
511
512 importJava "org.simantics.db.layer0.genericrelation.DependencyChanges" where
513     data DependencyChanges