]> gerrit.simantics Code Review - simantics/platform.git/blob - bundles/org.simantics.scl.runtime/scl/Prelude.scl
cce9064090ca123545e387b711e7cab902e95680
[simantics/platform.git] / bundles / org.simantics.scl.runtime / scl / Prelude.scl
1 import "JavaBuiltin" as Java
2 import "StringBuilder" as StringBuilder
3
4 /** The following types and names are builtin *************
5 data Boolean = True | False
6 data Byte
7 data Character
8 data Short
9 data Integer
10 data Long
11 data Float
12 data Double
13 data BooleanArray
14 data ByteArray
15 data CharacterArray
16 data ShortArray
17 data IntegerArray
18 data LongArray
19 data FloatArray
20 data DoubleArray
21 data Array a
22 data String
23 data a -> b
24 data [a] = [] | [a] | [a,a] | [a,a,a] | ...
25 data () = ()
26 data (a,b) = (a,b)
27 data (a,b,c) = (a,b,c)
28 data Maybe a = Nothing | Just a
29
30 fail :: String -> a
31
32 data TypeRep = TCon String | TApply TypeRep TypeRep
33 class Typeable a
34 typeOf :: Typeable a => a -> Type
35
36 data Binding a
37 class Serializable a
38 binding :: Serializable a => Binding a
39 ***********************************************************/
40
41 type BooleanArray = Vector Boolean
42 type ByteArray = Vector Byte
43 type CharacterArray = Vector Character
44 type ShortArray = Vector Short
45 type IntegerArray = Vector Integer
46 type LongArray = Vector Long
47 type FloatArray = Vector Float
48 type DoubleArray = Vector Double
49
50 importJava "java.util.Arrays" where
51     @private
52     @JavaName toString
53     showDoubleArray :: DoubleArray -> String
54     
55     "Converts an array to a list."
56     @JavaName asList    
57     arrayToList :: Array a -> [a]
58
59 importJava "java.util.List" where
60     "Converts a list to an array."
61     @JavaName toArray
62     listToArray :: [a] -> Array a
63
64 instance Show DoubleArray where
65     show = showDoubleArray
66
67 importJava "org.simantics.scl.runtime.Coercion" where
68     "Converts a list of doubles to a double array."
69     toDoubleArray :: [Double] -> DoubleArray
70     "Converts a double array to a list of doubles."
71     fromDoubleArray :: DoubleArray -> [Double]
72
73 /*
74  * Precedences and associativity of all operators defined in Prelude
75  */
76
77 infixr 10 (!)
78 infixr 9  (.)
79 infixr 8  (^)
80 infixl 7  (*), (/), div, mod
81 infixl 6  (+), (-)
82 infixl 5  (\\), (<<), (<+)
83 infix  4  (!=), (<), (<=), (>=), (>)
84 infixr 3  (&&), (&<&)
85 infixr 2  (||), orElse, morelse
86 infixr 1  (>>=), (>>), (:=), (>=>)
87 infixr 1  ($)
88 infixl 1  catch
89
90 "Creates a constant function. `const x` defines a function that always returns `x`."
91 @inline
92 const :: a -> b -> a
93 const c x = c
94
95 """
96 Function application. `f $ x` is equivalent with `f x`. The function has two uses.
97 First is to remove parentheses from deeply nested expressions:
98
99     f (g (h x))  ==  f $ g $ h x
100     
101 The second use is with higher order functions:
102
103     map ($ parameter) functions
104 """
105 @macro
106 @inline
107 ($) :: (a -> <e> b) -> a -> <e> b
108 f $ x = f x
109
110 "Transforms a function taking a pair as a parameter to a function taking two values as a parameter."
111 @inline
112 curry :: ((a, b) -> <e> c) -> a -> b -> <e> c
113 curry f x y =  f (x, y)
114
115 "Transforms a function two values as a parameter to a function taking a pair as a parameter."
116 @inline
117 uncurry :: (a -> b -> <e> c) -> ((a, b) -> <e> c)
118 uncurry f (x, y) = f x y
119
120 "Transforms a function taking a triple as a parameter to a function taking three values as a parameter."
121 @inline
122 curry3 :: ((a, b, c) -> <e> d) -> a -> b -> c -> <e> d
123 curry3 f x y z =  f (x, y, z)
124
125 "Transforms a function three values as a parameter to a function taking a priple as a parameter."
126 @inline
127 uncurry3 :: (a -> b -> c -> <e> d) -> ((a, b, c) -> <e> d)
128 uncurry3 f (x, y, z) = f x y z
129
130 "Flips the parameters of a binary function."
131 @inline
132 flip :: (a -> b -> <e> c) -> b -> a -> <e> c
133 flip f x y =  f y x
134
135 "Swaps the order of elements of a pair (2-tuple)."
136 swap :: (a,b) -> (b,a)
137 swap (x,y) = (y,x)
138
139 /// Comparison ///
140
141 @inline
142 (!=) :: a -> a -> Boolean
143 a != b = not (a == b)
144
145 """
146 The class of linearly ordered types.
147 Method `compare` must be implemented in instances. 
148 """
149 class Ord a where
150     """
151     `compare x y` returns a negative number, if `x` is smaller than `y`,
152     a positive number, if `x` is bigger than `y` and zero if they are equal. 
153     """
154     compare :: a -> a -> Integer
155     compare a b = if a < b then -1 else if a > b then 1 else 0
156     
157     "Less"
158     (<) :: a -> a -> Boolean
159     a < b = compare a b < 0
160     "Less or equal"
161     (<=) :: a -> a -> Boolean
162     a <= b = compare a b <= 0
163     "Greater"
164     (>) :: a -> a -> Boolean
165     a > b = compare a b > 0
166     "Greater or equal"
167     (>=) :: a -> a -> Boolean
168     a >= b = compare a b >= 0
169     
170     "Minimum of the parameters"
171     min :: a -> a -> a
172     min a b = if a < b then a else b
173     "Maximum of the parameters"
174     max :: a -> a -> a
175     max a b = if a > b then a else b
176
177 """
178 Combines two integers such that if the first one is non-zero, it is returned, otherwise
179 the second-one. The second parameter is not implemented, if it is not needed.
180
181 The function is useful for implementing efficient recursive comparison of structures,
182 for example:
183
184     compare (x1,y1,z1) (x2,y2,z2) = compare x1 x2 &<& compare y1 y2 &<& compare z1 z2
185 """
186 @inline
187 (&<&) :: Integer -> (<e> Integer) -> <e> Integer
188 a &<& b = if a == 0 then b else a
189
190 "Maximum over a list"
191 @inline
192 maximum :: Ord a => [a] -> a
193 maximum = foldl1 max
194
195 "Minimum over a list"
196 @inline
197 minimum :: Ord a => [a] -> a
198 minimum = foldl1 min
199
200 "As `maximum` but compares the elements by the given projection."
201 maximumBy :: Ord b => (a -> <e> b) -> [a] -> <e> a
202 maximumBy f l = snd $ foldl1 maxF $ map (\x -> (f x, x)) l
203   where
204     maxF a b = if fst a >= fst b then a else b
205
206 """
207 As `minimum` but compares the elements by the given projection.
208 For example
209
210     minimumBy snd l
211     
212 returns a pair with the smallest second component.
213 """    
214 minimumBy :: Ord b => (a -> <e> b) -> [a] -> <e> a
215 minimumBy f l = snd $ foldl1 minF $ map (\x -> (f x, x)) l
216   where
217     minF a b = if fst a <= fst b then a else b  
218
219 /// Functions ///
220 /*
221 instance Functor ((->) a) where
222     map f g x = f (g x)
223
224 instance Monad ((->) a) where
225     return v x = v
226     (m >>= f) x = f (m x) x
227     join f x = f x x
228
229 instance Category (->) where
230     id x = x
231     @inline
232     (f . g) x = f (g x)
233 */
234 instance (Additive b) => Additive (a -> <e> b) where
235     zero x = zero
236     (f + g) x = f x + g x
237
238 instance (Ring b) => Ring (a -> <e> b) where
239     one x = one
240     (neg f) x = neg (f x)
241     (f - g) x = f x - g x
242     (f * g) x = f x * g x
243     (fromInteger c) x = fromInteger c
244
245 //instance Show (a -> <e> b) where
246 //    show f = "<function>"
247
248 "Appends a string to the string builder."
249 (<<) :: StringBuilder.T -> String -> <Proc> StringBuilder.T
250 (<<) =  StringBuilder.appendString
251
252 """
253 The class of types whose elements can be converted to a string representation.
254 Method `show` or `(<+)` must be implemented.
255 """
256 class Show a where
257     "Converts a value to string."
258     show :: a -> String
259     "Appends the string representation of the value to the string builder."
260     (<+) :: StringBuilder.T -> a -> <Proc> StringBuilder.T
261     """
262     Returns the precedence of the value. It is used to determine if parenteheses
263     are needed around the string representation of the value. The default value is 0
264     and means that parentheses are never added.
265     """ 
266     precedence :: a -> Integer
267     
268     "Converts a value to a string like `show` but does not put string literals in double quotes."
269     showForPrinting :: a -> String
270     
271     show v = runProc (StringBuilder.toString (StringBuilder.new <+ v))
272     showForPrinting v = show v
273     sb <+ v = StringBuilder.appendString sb (show v)
274     precedence v = 0
275
276 """
277 `Par` data type is used to control the placement of parentheses when converting values to string.
278 Value `Par prec val` is converted to string like `val` but parentheses are put around, if the 
279 precedence of the value is greater than `prec`.
280 """
281 data Par a = Par Integer a
282
283 instance (Show a) => Show (Par a) where
284     sb <+ (Par outerPrec v) = if prec > outerPrec
285                                  then sb << "(" <+ v << ")"
286                                  else sb <+ v
287                               where prec = precedence v
288
289 "Type class for parsing strings to values."
290 class Read a where
291     "Converts a string to a required type of value."
292     read :: String -> a
293 """
294 The `Additive` class is used for types that are additive monoids. The operations
295 must satisfy the following laws (at least approximately, when implemented for
296 floating point numbers):
297     (a + b) + c   = a + (b + c)
298     a + 0 = 0 + a = a
299 """
300 class Additive a where
301     """
302     Neutral element of (+), i.e,
303     
304         x + zero == x
305         zero + x == x       
306     """
307     zero :: a
308     "Adds two objects (numbers, vectors, strings, etc.) together."
309     (+)  :: a -> a -> a
310     """
311     Sum of the elements:
312     
313         sum [e1,e2,...,eN] = e1 + e2 + ... + eN
314     
315     Implemented usually more efficiently than with repetitive 
316     application of `(+)`.
317     """
318     sum  :: [a] -> a
319     sum = foldl (+) zero    
320 /*
321 class (Additive a) => AdditiveGroup a where
322     neg :: a -> a    
323     (-) :: a -> a -> a
324     x - y = x + (neg y)
325 */
326 """
327 The `Ring` class is used for types that are algebraic rings. The operations
328 must satisfy the following laws (at least approximately)
329 in addition to the laws of Additive:
330
331     a + b         = b + a
332     a - b         = a + (neg b)
333     a - a         = 0
334     (a * b) * c   = a * (b * c)
335     a * 1 = 1 * a = a
336     a * (b + c)   = a * b + a * c
337     (a + b) * c   = a * c + b * c 
338 """
339 class (Additive a) => Ring a where
340     """
341     Negation. Synonym for unary `-`.
342     """
343     neg :: a -> a
344     "Subtraction"    
345     (-) :: a -> a -> a
346     "Neutral element of multiplication"
347     one :: a
348     "Multiplication"
349     (*) :: a -> a -> a
350     "Converts an integer to a desired numeric type."
351     fromInteger :: Integer -> a
352     x - y = x + (neg y)
353     
354
355 """
356 The `OrderedRing` class combines the Ring and Ord classes. It additionally 
357 supports absolute value function.
358 """    
359 class (Ring a, Ord a) => OrderedRing a where
360     "Absolute value."
361     abs :: a -> a
362     abs x = if x < zero then neg x else x
363     "Converts the given number to `Integer`"
364     toInteger :: a -> Integer   
365
366 """
367 The `Integer` class is used for types that represent either all integers or some
368 range of them. 
369 """
370 class (OrderedRing a) => Integral a where
371     "Integer division truncated toward zero."
372     div :: a -> a -> a
373     "Integer remainder, satisfying ``(x `div` y)*y + (x `mod` y) = x``"    
374     mod :: a -> a -> a
375
376 """
377 The `Real` class is used for types that represent some approximation of real numbers. 
378 """
379 class (OrderedRing a) => Real a where
380     "Division"
381     (/) :: a -> a -> a
382     "Exponentation"
383     (^) :: a -> a -> a
384     "Pi (3.141592654...)"
385     pi  :: a
386     "Square root"
387     sqrt :: a -> a
388     "Exponent function"
389     exp :: a -> a
390     "Natural logarithm"
391     log :: a -> a 
392     "Sine"
393     sin :: a -> a
394     "Cosine"
395     cos :: a -> a
396     "Tangent"
397     tan :: a -> a
398     "Inverse sine"
399     asin :: a -> a
400     "Inverse cosine"
401     acos :: a -> a
402     "Inverse tangent."
403     atan :: a -> a
404     "Hyperbolic sine"
405     sinh :: a -> a
406     "Hyperbolic cosine"
407     cosh :: a -> a
408     "Hyperbolic tangent"
409     tanh :: a -> a
410     "Inverse hyberbolic sine"
411     asinh :: a -> a
412     "Inverse hyberbolic cosine"
413     acosh :: a -> a
414     "Inverse hyberbolic tangent"
415     atanh :: a -> a    
416     "The largest integer not greater than the given number"
417     floor :: a -> a
418     "The smallest integer not smaller than the given number"
419     ceil :: a -> a
420     round :: a -> Long
421     """
422     Two parameter version of `atan`. Its value is determined by the following
423     equations when (x,y) is a unit vector:
424     
425         x = cos (atan2 y x)
426         y = sin (atan2 y x)
427         
428     When x > 0,
429     
430         atan2 y x = atan (y/x)
431     """    
432     atan2 :: a -> a -> a
433     "Converts a `Double` value to a desired numeric type."
434     fromDouble :: Double -> a
435     "Converts the given number to `Double`"
436     toDouble :: a -> Double
437     
438     a ^ b = exp (b * log a)
439     
440     sinh x = 0.5 * (exp x - exp (neg x))
441     cosh x = 0.5 * (exp x + exp (neg x))
442     tanh x = (e2x - 1) / (e2x + 1) 
443       where
444         e2x = exp (2*x)
445        
446     asinh x = log (x + sqrt (x*x + one))
447     acosh x = log (x + sqrt (x*x - one))
448     atanh x = 0.5 * log ((one+x)/(one-x))
449     
450 /// Import mathematical functions ///
451
452 @private
453 importJava "java.lang.Math" where
454     @JavaName PI
455     piDouble :: Double
456     
457     @JavaName sin
458     sinDouble :: Double -> Double
459
460     @JavaName cos
461     cosDouble :: Double -> Double
462
463     @JavaName tan
464     tanDouble :: Double -> Double
465
466     @JavaName asin
467     asinDouble :: Double -> Double
468
469     @JavaName acos
470     acosDouble :: Double -> Double
471
472     @JavaName atan
473     atanDouble :: Double -> Double
474
475     @JavaName atan2    
476     atan2Double :: Double -> Double -> Double
477     
478     @JavaName sinh
479     sinhDouble :: Double -> Double
480
481     @JavaName cosh
482     coshDouble :: Double -> Double
483
484     @JavaName tanh
485     tanhDouble :: Double -> Double
486     
487     @JavaName exp
488     expDouble :: Double -> Double
489
490     @JavaName log
491     logDouble :: Double -> Double
492
493     @JavaName pow
494     powDouble :: Double -> Double -> Double
495
496     @JavaName sqrt
497     sqrtDouble :: Double -> Double
498     
499     @JavaName ceil
500     ceilDouble :: Double -> Double
501
502     @JavaName floor
503     floorDouble :: Double -> Double
504
505     @JavaName round
506     roundDouble :: Double -> Long
507     
508     @JavaName abs
509     absInteger :: Integer -> Integer
510
511     @JavaName abs
512     absLong :: Long -> Long
513
514     @JavaName abs
515     absFloat :: Float -> Float
516
517     @JavaName abs
518     absDouble :: Double -> Double
519         
520     @JavaName min
521     minInteger :: Integer -> Integer -> Integer
522
523     @JavaName min
524     minLong :: Long -> Long -> Long
525
526     @JavaName min
527     minFloat :: Float -> Float -> Float
528
529     @JavaName min
530     minDouble :: Double -> Double -> Double
531     
532     @JavaName max
533     maxInteger :: Integer -> Integer -> Integer
534
535     @JavaName max
536     maxLong :: Long -> Long -> Long
537
538     @JavaName max
539     maxFloat :: Float -> Float -> Float
540
541     @JavaName max
542     maxDouble :: Double -> Double -> Double
543
544 /// Integer ///
545
546 @private
547 importJava "java.lang.Byte" where
548     @JavaName toString
549     showByte :: Byte -> String
550     
551     @JavaName parseByte
552     readByte :: String -> Byte
553
554 instance Ord Byte where
555     (<) = Java.bcmplt
556     (<=) = Java.bcmple
557     (>) = Java.bcmpgt
558     (>=) = Java.bcmpge
559     
560 instance Additive Byte where
561     zero = Java.i2b Java.iconst_0
562     (+) = Java.badd
563     
564 instance Ring Byte where
565     neg = Java.bneg
566     (-) = Java.bsub
567     one = Java.i2b Java.iconst_1
568     (*) = Java.bmul
569     fromInteger = Java.i2b
570
571 instance Show Byte where
572     show = showByte
573     precedence v = if v >= 0 then 0 else 100
574
575 instance Read Byte where
576     read = readByte
577
578
579 @private
580 importJava "java.lang.Short" where
581     @JavaName toString
582     showShort :: Short -> String
583     
584     @JavaName parseShort
585     readShort :: String -> Short
586
587 instance Ord Short where
588     (<) = Java.scmplt
589     (<=) = Java.scmple
590     (>) = Java.scmpgt
591     (>=) = Java.scmpge
592     
593 instance Additive Short where
594     zero = Java.sconst_0
595     (+) = Java.sadd
596     
597 instance Ring Short where
598     neg = Java.sneg
599     (-) = Java.ssub
600     one = Java.sconst_1
601     (*) = Java.smul
602     fromInteger = Java.i2s
603
604 instance Show Short where
605     show = showShort
606     precedence v = if v >= 0 then 0 else 100
607
608 instance Read Short where
609     read = readShort
610     
611 /// Integer ///
612
613 @private
614 importJava "java.lang.Integer" where
615     @JavaName toString
616     showInteger :: Integer -> String
617     
618     @JavaName parseInt
619     readInteger :: String -> Integer
620
621 instance Ord Integer where
622     (<) = Java.icmplt
623     (<=) = Java.icmple
624     (>) = Java.icmpgt
625     (>=) = Java.icmpge
626
627 instance Additive Integer where
628     zero = Java.iconst_0
629     (+) = Java.iadd
630     
631 instance Ring Integer where
632     neg = Java.ineg
633     (-) = Java.isub
634     one = Java.iconst_1
635     (*) = Java.imul
636     fromInteger x = x
637     
638 instance OrderedRing Integer where
639     abs = absInteger
640     toInteger x = x
641
642 instance Integral Integer where
643     div = Java.idiv
644     mod = Java.irem
645
646 instance Show Integer where
647     show = showInteger
648     precedence v = if v >= 0 then 0 else 100
649
650 instance Read Integer where
651     read = readInteger
652
653 /// Long ///
654
655 @private
656 importJava "java.lang.Long" where
657     @JavaName toString
658     showLong :: Long -> String
659     
660     @JavaName parseLong
661     readLong :: String -> Long
662
663 instance Ord Long where
664     (<) = Java.lcmplt
665     (<=) = Java.lcmple
666     (>) = Java.lcmpgt
667     (>=) = Java.lcmpge
668
669 instance Additive Long where
670     zero = Java.lconst_0
671     (+) = Java.ladd
672     
673 instance Ring Long where
674     neg = Java.lneg
675     (-) = Java.lsub
676     one = Java.lconst_1
677     (*) = Java.lmul
678     fromInteger = Java.i2l
679     
680 instance OrderedRing Long where
681     abs = absLong
682     toInteger = Java.l2i
683
684 instance Integral Long where
685     div = Java.ldiv
686     mod = Java.lrem
687     
688 instance Show Long where
689     show = showLong
690     precedence v = if v >= 0 then 0 else 100
691
692 instance Read Long where
693     read = readLong
694     
695 /// Float ///
696
697 importJava "java.lang.Float" where
698     @private
699     @JavaName compare
700     compareFloat :: Float -> Float -> Integer
701
702     @private
703     @JavaName toString
704     showFloat :: Float -> String
705
706     @private
707     @JavaName parseFloat
708     readFloat :: String -> Float
709     
710     "Converts 32-bit floating point number to a 32-bit integer with the same byte level representation."
711     floatToIntBits :: Float -> Integer  
712
713 instance Ord Float where
714     compare = compareFloat
715     (<) = Java.fcmplt
716     (<=) = Java.fcmple
717     (>) = Java.fcmpgt
718     (>=) = Java.fcmpge
719
720 instance Additive Float where
721     zero = Java.fconst_0
722     (+) = Java.fadd
723     
724 instance Ring Float where
725     neg = Java.fneg
726     (-) = Java.fsub
727     one = Java.fconst_1
728     (*) = Java.fmul
729     fromInteger = Java.i2f
730
731 instance OrderedRing Float where
732     abs = absFloat
733     toInteger = Java.f2i
734     
735 instance Real Float where
736     (/) = Java.fdiv
737     x ^ y = Java.d2f (powDouble (Java.f2d x) (Java.f2d y))
738     pi = fromDouble piDouble
739     sqrt = Java.d2f . sqrtDouble . Java.f2d
740     exp = Java.d2f . expDouble . Java.f2d
741     log = Java.d2f . logDouble . Java.f2d
742     sin = Java.d2f . sinDouble . Java.f2d
743     cos = Java.d2f . cosDouble . Java.f2d
744     tan = Java.d2f . tanDouble . Java.f2d
745     asin = Java.d2f . asinDouble . Java.f2d
746     acos = Java.d2f . acosDouble . Java.f2d
747     atan = Java.d2f . atanDouble . Java.f2d
748     sinh = Java.d2f . sinhDouble . Java.f2d
749     cosh = Java.d2f . coshDouble . Java.f2d
750     tanh = Java.d2f . tanhDouble . Java.f2d
751     floor = Java.d2f . floorDouble . Java.f2d
752     ceil = Java.d2f . ceilDouble . Java.f2d
753     atan2 y x = Java.d2f (atan2Double (Java.f2d y) (Java.f2d x))
754     round = roundDouble . Java.f2d
755     fromDouble = Java.d2f
756     toDouble = Java.f2d
757
758 instance Show Float where
759     show = showFloat
760     precedence v = if v >= 0 then 0 else 100
761
762 instance Read Float where
763     read = readFloat
764     
765 /// Double ///
766
767 importJava "java.lang.Double" where
768     @private
769     @JavaName compare
770     compareDouble :: Double -> Double -> Integer
771     
772     @private
773     @JavaName toString
774     showDouble :: Double -> String
775     
776     @private
777     @JavaName parseDouble
778     readDouble :: String -> Double
779     
780     "Converts 64-bit floating point number to a 64-bit integer with the same byte level representation."
781     doubleToLongBits :: Double -> Long
782     
783     isFinite :: Double -> Boolean
784     isNaN :: Double -> Boolean
785     isInfinite :: Double -> Boolean
786
787 instance Ord Double where
788     compare = compareDouble
789     (<) = Java.dcmplt
790     (<=) = Java.dcmple
791     (>) = Java.dcmpgt
792     (>=) = Java.dcmpge 
793
794 instance Additive Double where
795     zero = Java.dconst_0
796     (+) = Java.dadd
797     
798 instance Ring Double where
799     neg = Java.dneg
800     (-) = Java.dsub
801     one = Java.dconst_1
802     (*) = Java.dmul
803     fromInteger = Java.i2d
804
805 instance OrderedRing Double where
806     abs = absDouble
807     toInteger = Java.d2i
808     
809 instance Real Double where
810     (/) = Java.ddiv
811     (^) = powDouble
812     pi = piDouble
813     sqrt = sqrtDouble
814     exp = expDouble
815     log = logDouble
816     sin = sinDouble
817     cos = cosDouble
818     tan = tanDouble
819     asin = asinDouble
820     acos = acosDouble
821     atan = atanDouble
822     sinh = sinhDouble
823     cosh = coshDouble
824     tanh = tanhDouble
825     floor = floorDouble
826     ceil = ceilDouble
827     atan2 = atan2Double
828     round = roundDouble
829     fromDouble x = x
830     toDouble x = x
831
832 instance Show Double where
833     show = showDouble
834     precedence v = if v >= 0 then 0 else 100
835
836 instance Read Double where
837     read = readDouble
838
839 /// Character ///
840
841 importJava "java.lang.Character" where
842     @JavaName toString
843     showCharacter :: Character -> String
844     
845     "Returns true, if the given character is a letter."
846     isLetter :: Character -> Boolean
847     
848     "Returns true, if the given character is a digit."
849     isDigit :: Character -> Boolean
850
851 instance Ord Character where
852     (<) = Java.ccmplt
853     (<=) = Java.ccmple
854     (>) = Java.ccmpgt
855     (>=) = Java.ccmpge
856     
857 instance Show Character where
858     sb <+ c = sb << "'" << showCharacter c << "'"
859     
860 "Adds a given integer to the character code."
861 addChar :: Character -> Integer -> Character
862 addChar = Java.cadd
863
864 "Subtracts a given integer from the character code."
865 subChar :: Character -> Character -> Integer
866 subChar = Java.csub
867
868 /// Functor ///
869
870 """
871 The `Functor` class is used for types that can be mapped over. Instances of `Functor` should satisfy the following laws:
872
873     fmap id  ==  id
874     fmap (f . g)  ==  fmap f . fmap g
875 """
876 class Functor f where
877     "Lifts a pure function to the given functor."
878     fmap :: (a -> b) -> f a -> f b
879 /*
880 class CoFunctor f where
881     comap :: (a -> b) -> f b -> f a
882 */
883 /// Applicative ///
884 /*
885 class (Functor f) => Applicative f where
886     return :: a -> f a
887     (<*>) :: f (a -> b) -> f a -> f b
888     (*>) :: f a -> f b -> f b
889     (<*) :: f a -> f b -> f a
890     
891     u *> v = pure (const id) <*> u <*> v
892     u <* v = pure const <*> u <*> v
893     fmap f x = pure f <*> x
894 */
895 /// Monad ///
896
897 """
898 The `Monad` class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory.
899 From the perspective of a SCL programmer, however, it is best to think of a monad as an abstract datatype of actions.
900 SCL's `mdo expressions provide a convenient syntax for writing monadic expressions.
901
902 Instances of `Monad` should satisfy the following laws:
903
904     return a >>= k  ==  k a
905     m >>= return  ==  m
906     m >>= (\x -> k x >>= h)  ==  (m >>= k) >>= h
907     fmap f xs  ==  xs >>= return . f
908 """
909 class (Functor m) => Monad m where
910     "Inject a value into the monadic type."
911     return :: a -> m a
912     "Sequentially compose two actions, passing any value produced by the first as an argument to the second."
913     (>>=) :: m a -> (a -> m b) -> m b
914     """
915     The join function is the conventional monad join operator. It removes one level of monadic
916     structure.
917     
918     For lists, `join` concatenates a list of lists:
919     
920         join [[1,2], [3,4]] = [1, 2, 3, 4]
921     """
922     join :: m (m a) -> m a
923     join m = m >>= id
924
925 """
926 Sequentially compose two actions, discarding any value produced by the first, like sequencing operators
927 (such as the semicolon) in imperative languages."
928 """
929 @macro
930 (>>) :: Monad m => m a -> m b -> m b
931 a >> b = a >>= (\_ -> b)
932
933 "Left-to-right Kleisli composition of monads."
934 (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
935 (f >=> g) x = (f x) >>= g 
936
937 "While loop. `while cond body` executes the `body` while the `cond` is true." 
938 @inline
939 while :: (<e> Boolean) -> (<e> a) -> <e> ()
940 while cond body = loop ()
941   where loop _ = if cond 
942                  then do body ; loop ()
943                  else ()
944
945 """
946 Sequences the given monadic value infinitely:
947
948     repeatForever m = m >> m >> m >> ...
949 """
950 repeatForever m = m >> repeatForever m
951
952 replicateM :: Monad m => Integer -> m a -> m [a]
953 replicateM count m = loop count emptyList
954   where
955     loop count l | count <= 0 = return l
956                  | otherwise  = mdo
957                      v <- m
958                      loop (count-1) (addList l v)
959
960 replicateM_ :: Monad m => Integer -> m a -> m ()
961 replicateM_ count m | count <= 0 = return ()
962                     | otherwise  = m >> replicateM_ (count-1) m
963
964 /// MonadZero ///
965
966 """
967 A class of monads with zero element satisfying
968
969     mzero >>= f = mzero
970 """ 
971 class (Monad m) => MonadZero m where
972     mzero :: m a
973
974 "Injects a boolean test to a type beloning to `MonadZero`."
975 guard :: MonadZero m => Boolean -> m ()
976 guard True = return ()
977 guard False = mzero
978
979 /// MonadPlus ///
980
981 """
982 A class of monads with associative binary operator `mplus` satisfying the following laws:  
983
984     mplus mzero b = b
985     mplus a mzero = a
986     mplus (mplus a b) c = mplus a (mplus b c)
987     mplus a b >>= k = mplus (a >>= k) (b >>= k)
988 """
989 class (MonadZero m) => MonadPlus m where
990     mplus :: m a -> m a -> m a
991
992 /// MonadOr ///
993
994 """
995 A class of monads with associative binary operator `morelse` satisfying the following laws:  
996
997     morelse mzero b = b
998     morelse a mzero = a
999     morelse (morelse a b) c = morelse a (morelse b c)
1000     morelse (return a) b = return a
1001 """
1002 class (MonadZero m) => MonadOr m where
1003     morelse :: m a -> m a -> m a
1004
1005 /// FunctorE ///
1006
1007 """
1008 A class of types that can be mapped over with effectful mapping functions.
1009 """
1010 class (Functor f) => FunctorE f where
1011     """
1012     Applies the function to all elements of the container and
1013     returns the similarly shaped container with the results:
1014     
1015     For lists,
1016     
1017         map f [e1, e2, ..., eN] = [f e1, f e2, ..., f eN]
1018         
1019     for example
1020     
1021         map (*2) [1..5] = [2, 4, 6, 8, 10]
1022     """
1023     map :: (a -> <e> b) -> f a -> <e> (f b)
1024     "Calls the given function with all elements of the given container."
1025     iter :: (a -> <e> b) -> f a -> <e> ()
1026     "Calls the given function with all elements of the given container giving also the index of the element as a parameter."
1027     iterI :: (Integer -> a -> <e> b) -> f a -> <e> ()
1028
1029 "Iterates the elements of the given collection. Same as `iter` but parameters flipped." 
1030 for :: FunctorE f => f a -> (a -> <e> b) -> <e> ()
1031 @macro
1032 for l f = iter f l
1033
1034 "Iterates the elements of the given collection providing also the indices of the elements. Same as `iterI` but parameters flipped." 
1035 forI :: FunctorE f => f a -> (Integer -> a -> <e> b) -> <e> ()
1036 @macro
1037 forI l f = iterI f l
1038
1039 "`forN n f` calls `f` for all integers `0`, ..., `n-1`"
1040 @inline
1041 forN :: Integer -> (Integer -> <e> b) -> <e> ()
1042 forN n f = loop 0
1043   where
1044     loop i = if i < n
1045              then do f i ; loop (i+1)
1046              else ()
1047
1048 @inline
1049 mapI :: (Integer -> a -> <e> b) -> [a] -> <e> [b]
1050 mapI f l = build (\empty cons -> let
1051     len = length l
1052     loop i accum = if i < len
1053                    then loop (i+1) (cons accum (f i (l!i)))
1054                    else accum
1055   in loop 0 empty)
1056
1057 """
1058 `mapMaybe` combines `map` and `filter` functions. 
1059 It applies the given function to every element of the input list. If the result
1060 is `Just x`, then `x` is added to the resulting list.
1061
1062     mapMaybe f lst = [y | x <- lst, Just y = f x]
1063 """
1064 @inline
1065 mapMaybe :: (a -> <e> Maybe b) -> [a] -> <e> [b]
1066 mapMaybe f l = build (\empty cons -> foldl (\cur x -> match f x with Just v -> cons cur v ; _ -> cur) empty l)
1067
1068 """
1069 Applies the given function to all elements of the list. Produces two lists: the first contains all elements `x`
1070 for which the function returned `Left x` and the second list contains all elements `y` for which the function
1071 returned `Right y`.
1072 """
1073 mapEither :: (a -> <e> Either b c) -> [a] -> <e> ([b], [c])
1074 mapEither f list = runProc do
1075     l = newArrayList
1076     r = newArrayList
1077     for list (\x -> match f x with
1078         Left v -> addArrayList l v
1079         Right v -> addArrayList r v)
1080     (Java.unsafeCoerce l, Java.unsafeCoerce r)
1081
1082 "`replicate n v` returns a list of length `n` such that each element is a copy of `v`."
1083 @inline
1084 replicate :: Integer -> a -> [a]
1085 replicate n v = build (\empty cons ->
1086     let aux 0 l = l
1087         aux i l = aux (i-1) (cons l v)
1088     in aux n empty 
1089     )
1090
1091 /// FunctorM ///
1092
1093 class (FunctorE f) => FunctorM f where
1094     "`mapM f` is equivalent to `sequence . map f`."
1095     mapM :: Monad m => (a -> <e> m b) -> f a -> <e> m (f b)
1096     "Evaluate each action in the sequence from left to right, and collect the results."
1097     sequence :: Monad m => f (m a) -> m (f a) 
1098     mapM f l = sequence (map f l)
1099
1100 /// MonadE ///
1101
1102 class (FunctorE m, Monad m) => MonadE m where
1103     bindE :: m a -> (a -> <e> m b) -> <e> m b
1104
1105 instance MonadE Maybe where
1106     bindE Nothing  _ = Nothing
1107     bindE (Just v) f = f v
1108     
1109 instance MonadE (Either a) where
1110     bindE (Left v)  _ = Left v
1111     bindE (Right v) f = f v
1112
1113 instance MonadE [] where
1114     bindE l f = concatMap f l
1115     
1116 /// Category ///
1117
1118 "Identity function."
1119 id :: a -> a
1120 id x = x
1121
1122 """
1123 Ignores the given value. This function is used in a situation where a function returns
1124 a value in a context where the value is not expected.
1125 """
1126 @inline
1127 ignore :: a -> ()
1128 ignore _ = ()
1129
1130 @inline
1131 ignoreM :: a -> Maybe b
1132 ignoreM _ = Nothing
1133
1134 """
1135 Composes two functions
1136     (f . g) x = f (g x)
1137 """
1138 (.) :: (b -> <e> c) -> (a -> <e> b) -> (a -> <e> c)
1139 (f . g) x = f (g x)
1140
1141 /// Sequence ///
1142
1143 "A type class for sequences. All sequences must support indexing by integers."
1144 class /*(Additive a) =>*/ Sequence a where
1145     "Length of the sequence"
1146     length :: a -> Integer
1147     "`take n s` returns the first `n` elements of the sequence `s`."
1148     take :: Integer -> a -> a
1149     "`drop n s` removes the first `n` elements of the sequence `s`."
1150     drop :: Integer -> a -> a
1151     """
1152     `sub s begin end` returns a subsequence of `s` starting from
1153     index `begin` and ending just before index `end`.
1154     """ 
1155     sub :: a -> Integer -> Integer -> a
1156     
1157     take n v = sub v 0 (min n (length v))
1158     drop n v = sub v (min n len) len
1159       where
1160         len = length v 
1161
1162 instance Sequence [a] where
1163     length = lengthList
1164     sub = subList
1165     
1166 instance Sequence String where
1167     length = lengthString
1168     sub = subString        
1169
1170 class IndexedSequence f where
1171     "`seq ! i` returns the `i`th element of the sequence `seq`. Indexing starts from zero."
1172     (!) :: f a -> Integer -> a
1173
1174 "Returns the first element of a sequence"
1175 @inline
1176 first l = l!0
1177
1178 "Returns the last element of a sequence"
1179 @inline
1180 last l = l!(length l-1)
1181
1182 instance IndexedSequence [] where
1183     (!) = getList
1184
1185 /// Boolean ///
1186
1187 """
1188 Equivalent to the boolean value `True`. The value is meant to be used in
1189 guard patterns:
1190
1191     min a b | a < b     = a
1192             | otherwise = b 
1193 """
1194 @inline
1195 otherwise :: Boolean
1196 otherwise = True
1197
1198 instance Ord Boolean where
1199     compare False False = 0
1200     compare False True  = neg 1
1201     compare True  False = 1
1202     compare True  True  = 0
1203
1204 instance Show Boolean where
1205     show True = "True"
1206     show False = "False"
1207
1208 """
1209 Boolean conjunction (and). The function is a macro that evaluates the second parameter
1210 only if the first parameter is `True`.
1211
1212 <table>
1213 <tr><th>a</th><th>b</th><th>a && b</th></tr>
1214 <tr><td>True</td><td>True</td><td>True</td></tr>
1215 <tr><td>True</td><td>False</td><td>False</td></tr>
1216 <tr><td>False</td><td>not evaluated</td><td>False</td></tr>
1217 </table> 
1218 """
1219 @macro
1220 (&&) :: Boolean -> Boolean ->  Boolean
1221 a && b = if a then b else False
1222
1223 """
1224 Boolean disjunction (or). The function is a macro that evaluates the second parameter
1225 only if the first parameter is `False`.
1226
1227 <table>
1228 <tr><th>a</th><th>b</th><th>a || b</th></tr>
1229 <tr><td>True</td><td>not evaluated</td><td>True</td></tr>
1230 <tr><td>False</td><td>True</td><td>True</td></tr>
1231 <tr><td>False</td><td>False</td><td>False</td></tr>
1232 </table> 
1233 """
1234 @macro
1235 (||) :: Boolean -> Boolean -> Boolean
1236 a || b = if a then True else b
1237
1238 "Boolean negation"
1239 @inline
1240 not a = if a then False else True
1241
1242 /// Maybe ///
1243
1244 //data Maybe a = Nothing | Just a
1245
1246 "Given `Just x` this function returns `x`. If the parameter is `Nothing`, the function raises an exception."
1247 fromJust :: Maybe a -> a
1248 fromJust (Just a) = a
1249
1250 deriving instance (Ord a) => Ord (Maybe a)
1251 deriving instance (Show a) => Show (Maybe a)
1252
1253 instance Functor Maybe where
1254     fmap _ Nothing  = Nothing
1255     fmap f (Just x) = Just (f x)
1256
1257 instance FunctorE Maybe where
1258     map _ Nothing  = Nothing
1259     map f (Just x) = Just (f x)
1260     
1261     iter _ Nothing = ()
1262     iter f (Just x) = ignore (f x)
1263     
1264     iterI _ Nothing = ()
1265     iterI f (Just x) = ignore (f 0 x)
1266     
1267 instance Monad Maybe where    
1268     return x = Just x
1269
1270     @inline
1271     Nothing >>= _ = Nothing
1272     Just x  >>= f = f x
1273
1274     @inline
1275     join Nothing  = Nothing
1276     join (Just x) = x
1277
1278 instance MonadZero Maybe where
1279     mzero = Nothing
1280
1281 instance MonadOr Maybe where
1282     morelse a@(Just _) _ = a
1283     morelse _ b = b
1284
1285 "`execJust v f` executes the function `f` with parameter value `x`, if `v=Just x`. If `v=Nothing`, the function does nothing."
1286 @inline
1287 execJust :: Maybe a -> (a -> <e> b) -> <e> ()
1288 execJust maybeValue procedure = match maybeValue with
1289     Just v -> ignore $ procedure v
1290     _ -> ()
1291
1292 "`fromMaybe def v` returns `def` if `v=Nothing` and `x` if `v=Just x`."
1293 @inline
1294 fromMaybe :: a -> Maybe a -> a
1295 fromMaybe default maybeValue = match maybeValue with
1296     Just v -> v
1297     _ -> default
1298     
1299     
1300 """
1301 Provides a default value if the first parameter is Nothing.
1302 The default value is evaluated only if needed. The function
1303 can be used as an operator and is right associative so that
1304 the following is possible:
1305
1306     tryWithTheFirstMethod
1307         `orElse` tryWithTheSecondMethod
1308         `orElse` fail "Didn't succeed."
1309 """
1310 @inline
1311 orElse :: Maybe a -> (<e> a) -> <e> a
1312 orElse (Just x) _   = x
1313 orElse Nothing  def = def
1314
1315 /// Either ///
1316
1317 """
1318 The Either type represents values with two possibilities: a value of type `Either a b` is either `Left a` or `Right b`.
1319
1320 The `Either` type is sometimes used to represent a value which is either correct or an error; by convention, the `Left` constructor
1321 is used to hold an error value and the `Right` constructor is used to hold a correct value (mnemonic: "right" also means "correct").
1322 """
1323 @JavaType "org.simantics.scl.runtime.either.Either"
1324 data Either a b =
1325     @JavaType "org.simantics.scl.runtime.either.Left"
1326     @FieldNames [value]
1327     Left a
1328   | @JavaType "org.simantics.scl.runtime.either.Right"
1329     @FieldNames [value]
1330     Right b
1331
1332 deriving instance (Ord a, Ord b) => Ord (Either a b)
1333 deriving instance (Show a, Show b) => Show (Either a b)
1334
1335 instance Functor (Either a) where
1336     fmap _ (Left x)  = Left x
1337     fmap f (Right y) = Right (f y)
1338
1339 instance FunctorE (Either a) where
1340     map _ (Left x)  = Left x
1341     map f (Right y) = Right (f y)
1342     
1343     iter _ (Left x) = ()
1344     iter f (Right y) = ignore (f y)
1345     
1346     iterI _ (Left x) = ()
1347     iterI f (Right y) = ignore (f 0 y)
1348         
1349 instance Monad (Either b) where
1350     return y = Right y
1351
1352     Left x  >>= _ = Left x
1353     Right y >>= f = f y
1354
1355     join (Left x)  = Left x
1356     join (Right y) = y
1357     
1358 /// String ///
1359
1360 importJava "java.lang.String" where
1361     @private
1362     @JavaName "concat"
1363     concatString :: String -> String -> String
1364     @private
1365     @JavaName "compareTo"
1366     compareString :: String -> String -> Integer
1367     @private
1368     @JavaName "length"
1369     lengthString :: String -> Integer
1370
1371     """
1372     `replaceString original pattern replacement` replaces all occurrences of `pattern` in the string by `replacement`.
1373     """ 
1374     @JavaName replace
1375     replaceString :: String -> String -> String -> String
1376     
1377     @private
1378     @JavaName split
1379     splitString_ :: String -> String -> Array String
1380     
1381     """
1382     `indexOf string s` finds the first occurrence of `s` from `string` and returns its index.
1383     If the `s` does not occur in the string, return `-1`."
1384     """
1385     @JavaName indexOf
1386     indexOf :: String -> String -> Integer
1387     
1388     "Works like `indexOf` but starts searching from the given index instead of the beginning of the string."
1389     @JavaName indexOf
1390     indexOfStartingFrom :: String -> String -> Integer -> Integer
1391     
1392     "Works like `indexOf` but returns the index of the last occurrence."
1393     @JavaName lastIndexOf
1394     lastIndexOf :: String -> String -> Integer
1395     
1396     "Works like `lastIndexOf` but starts searching from the given index instead of the end of the string."
1397     @JavaName lastIndexOf
1398     lastIndexOfStartingFrom :: String -> String -> Integer -> Integer
1399     
1400     @private
1401     @JavaName substring
1402     subString :: String -> Integer -> Integer -> String
1403
1404     """
1405     `regionMatches str1 offset1 str2 offset2 len` tests whether
1406     `sub str1 offset1 (offset1+len) == sub str2 offset2 (offset2+len)`.
1407     """
1408     regionMatches :: String -> Integer -> String -> Integer -> Integer -> Boolean
1409
1410     "`startsWith string prefix` returns true if the string begins with the given prefix."
1411     startsWith :: String -> String -> Boolean
1412     
1413     "`endsWith string suffix` returns true if the string ends with the given prefix."
1414     endsWith :: String -> String -> Boolean
1415     
1416     "Removes leading and trailing whitespace from the string."
1417     trim :: String -> String
1418     
1419     "`contains string s` returns true if `string` contains `s` as a substring."
1420     contains :: String -> String -> Boolean
1421     
1422     "`charAt string i` returns the `i`th character of the string."
1423     charAt :: String -> Integer -> Character
1424     
1425     "Converts all letters of the string to lower case."
1426     toLowerCase :: String -> String
1427     "Converts all letters of the string to upper case."
1428     toUpperCase :: String -> String
1429     
1430     "Creates a string from a vector of characters."
1431     @JavaName "<init>"
1432     string :: Vector Character -> String
1433     
1434     getBytes :: String -> String -> ByteArray
1435
1436 getBytesUTF8 :: String -> ByteArray
1437 getBytesUTF8 str = getBytes str "UTF-8"
1438
1439 instance Ord String where
1440     compare = compareString
1441     
1442 instance Additive String where
1443     zero = ""
1444     (+) = concatString
1445     sum ss = runProc (StringBuilder.toString $ foldl StringBuilder.appendString StringBuilder.new ss)
1446
1447 @private
1448 importJava "org.simantics.scl.runtime.string.StringEscape" where
1449     appendEscapedString :: StringBuilder.T -> String -> <Proc> StringBuilder.T
1450
1451 instance Show String where
1452     showForPrinting = id
1453     sb <+ v = (appendEscapedString (sb << "\"") v) << "\""
1454
1455 instance Read String where
1456     read str = str
1457     
1458 @deprecated "Instead of 'splitString text pattern', write 'split pattern text' (note change in the parameter order)." 
1459 "`splitString text pattern` splits the string into a list of string where the parts are sepratated in the original list by the given pattern."
1460 splitString :: String -> String -> [String]
1461 splitString source pattern = arrayToList $ splitString_ source pattern
1462
1463 """
1464 `split pattern text` splits `text` around matches of the given regular expression `pattern`.
1465
1466 This function works as if by invoking the two-argument split method with the given expression and a limit argument of zero. Trailing empty strings are therefore not included in the resulting array.
1467
1468 The string "boo:and:foo", for example, yields the following results with these expressions:
1469
1470     Regex   Result
1471     :       { "boo", "and", "foo" }
1472     o       { "b", "", ":and:f" }
1473 """
1474 split :: String -> String -> [String]
1475 split pattern text = arrayToList $ splitString_ text pattern
1476
1477 /// Tuple0 ///
1478
1479 instance Ord () where
1480     compare () () = 0
1481
1482 instance Additive () where
1483     zero = ()
1484     () + () = ()
1485
1486 instance Show () where
1487     show () = "()"
1488
1489 /// Tuple2 ///
1490
1491 "Gives the first element of a pair."
1492 @inline
1493 fst :: (a,b) -> a
1494 fst (x,y) = x
1495
1496 "Gives the second element of a pair."
1497 @inline
1498 snd :: (a,b) -> b
1499 snd (x,y) = y
1500
1501 @inline
1502 mapFst :: (a -> b) -> (a,c) -> (b,c)
1503 mapFst f (x,y) = (f x, y)
1504
1505 @inline
1506 mapSnd :: (a -> b) -> (c,a) -> (c,b)
1507 mapSnd f (x,y) = (x, f y)
1508
1509 instance (Ord a, Ord b) => Ord (a, b) where
1510     compare (a0, b0) (a1, b1) = compare a0 a1 &<& compare b0 b1
1511
1512 instance (Additive a, Additive b) => Additive (a, b) where
1513     zero = (zero, zero)
1514     (a0, b0) + (a1, b1) = (a0+a1, b0+b1)
1515
1516 instance Functor ((,) a) where
1517     fmap f (a,b) = (a, f b)
1518     
1519 instance (Show a, Show b) => Show (a, b) where
1520     sb <+ (x, y) = sb << "(" <+ x << ", " <+ y << ")"
1521
1522 /// Tuple3 ///
1523
1524 instance (Ord a, Ord b, Ord c) => Ord (a, b, c) where
1525     compare (a0, b0, c0) (a1, b1, c1) = compare a0 a1 &<& compare b0 b1 &<& compare c0 c1
1526
1527 instance (Additive a, Additive b, Additive c) => Additive (a, b, c) where
1528     zero = (zero, zero, zero)
1529     (a0, b0, c0) + (a1, b1, c1) = (a0+a1, b0+b1, c0+c1)
1530
1531 instance Functor ((,,) a b) where
1532     fmap f (a,b,c) = (a, b, f c)
1533
1534 instance (Show a, Show b, Show c) => Show (a, b, c) where
1535     sb <+ (x, y, z) = sb << "(" <+ x << ", " <+ y << ", " <+ z << ")"
1536
1537 /// Tuple4 ///
1538
1539 instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) where
1540     compare (a0, b0, c0, d0) (a1, b1, c1, d1) = 
1541         compare a0 a1 &<& compare b0 b1 &<& compare c0 c1 &<& compare d0 d1
1542
1543 instance (Additive a, Additive b, Additive c, Additive d) => Additive (a, b, c, d) where
1544     zero = (zero, zero, zero, zero)
1545     (a0, b0, c0, d0) + (a1, b1, c1, d1) = (a0+a1, b0+b1, c0+c1, d0+d1)
1546
1547 instance Functor ((,,,) a b c) where
1548     fmap f (a,b,c,d) = (a, b, c, f d)
1549
1550 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
1551     sb <+ (x, y, z, w) = sb << "(" <+ x << ", " <+ y << ", " <+ z << ", " <+ w << ")"
1552     
1553 /// Tuple5 ///
1554
1555 instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) where
1556     compare (a0, b0, c0, d0, e0) (a1, b1, c1, d1, e1) = 
1557         compare a0 a1 &<& compare b0 b1 &<& compare c0 c1 &<& compare d0 d1 &<& compare e0 e1
1558     
1559 instance (Additive a, Additive b, Additive c, Additive d, Additive e) => Additive (a, b, c, d, e) where
1560     zero = (zero, zero, zero, zero, zero)
1561     (a0, b0, c0, d0, e0) + (a1, b1, c1, d1, e1) = (a0+a1, b0+b1, c0+c1, d0+d1, e0+e1)
1562
1563 instance Functor ((,,,,) a b c d) where
1564     fmap f (a,b,c,d,e) = (a, b, c, d, f e)
1565
1566 /// Lists ///
1567
1568 instance (Ord a) => Ord [a] where
1569     compare a b = loop 0 
1570       where
1571         lA = length a
1572         lB = length b
1573         loop i = if i >= lA
1574                  then (if i >= lB then 0 else -1)
1575                  else if i >= lB
1576                  then 1
1577                  else compare (a!i) (b!i) &<& loop (i+1)
1578
1579 instance Functor [] where
1580     fmap = mapList
1581
1582 instance FunctorE [] where
1583     map = mapEList
1584     iter = iterList
1585     iterI = iterIList
1586         
1587 instance Monad [] where
1588     return x = singletonList x
1589     l >>= f  = concatMap f l
1590     join l   = l >>= id
1591
1592 instance MonadZero [] where
1593     mzero = emptyList
1594
1595 instance MonadPlus [] where
1596     mplus = appendList
1597
1598 instance Additive [a] where
1599     zero = emptyList
1600     (+) = appendList
1601
1602 instance FunctorM [] where
1603     sequence = foldl (\m mel -> m >>= \l -> mel >>= \el -> return (addList l el)) (return emptyList)
1604     mapM f l = sequence (map f l)
1605
1606 "Appends the string representations of all elements of the list to the string builder and separates the values with the given separator."
1607 printWithSeparator :: Show a => StringBuilder.T -> String -> [a] -> <Proc> StringBuilder.T
1608 printWithSeparator sb sep l = loop 0
1609   where
1610     len = length l
1611     loop i = if i >= len then sb
1612              else do
1613                  (if i==0 then sb else sb << sep) <+ l!i
1614                  loop (i+1)
1615
1616 """
1617 Joins the string representations of the list of values with the given separator.
1618
1619 See [intercalate](#intercalate) for an alternative that works with Strings
1620 and doesn't escape its arguments.
1621 """
1622 joinWithSeparator :: Show a => String -> [a] -> String
1623 joinWithSeparator separator values = runProc ( 
1624     StringBuilder.toString $ printWithSeparator StringBuilder.new separator values)
1625
1626
1627 """
1628 The intercalate function takes a String and a list of Strings
1629 and concatenates the list after interspersing the first argument
1630 between each element of the list.
1631
1632 See also more generic [joinWithSeparator](#joinWithSeparator)
1633 which escapes its arguments using `show`.
1634 """
1635 intercalate :: String -> [String] -> String
1636 intercalate separator strings = do
1637     l = length strings
1638     if l == 0
1639     then ""
1640     else if l == 1
1641     then strings!0
1642     else runProc do
1643         sb = StringBuilder.new
1644         sb << strings!0
1645         loop i | i == l = ()
1646                | otherwise = do
1647             sb << separator << strings!i
1648             loop (i+1)
1649         loop 1
1650         StringBuilder.toString sb
1651
1652 instance (Show a) => Show [a] where
1653     sb <+ l = do 
1654         len = length l
1655         loop i = if i < len 
1656                  then do 
1657                      if (i>0) then sb << ", " else sb
1658                      sb <+ l!i
1659                      loop (i+1)
1660                  else sb << "]"
1661         sb << "[" 
1662         loop 0                 
1663
1664 importJava "java.util.List" where
1665     "`getList l i` returns the `i`th element of the list `l`. Indexing starts from zero. You can also use the `!` infix function for this purpose."
1666     @JavaName get
1667     getList :: [a] -> Integer -> a
1668
1669     @private
1670     @JavaName size
1671     lengthList :: [a] -> Integer
1672
1673     @private
1674     subList :: [a] -> Integer -> Integer -> [a]
1675
1676     @private
1677     isEmpty :: [a] -> Boolean
1678     
1679 @private    
1680 importJava "java.util.Collections" where
1681     emptyList :: [a]
1682     //singletonList :: a -> [a]
1683
1684 /*
1685 @inline
1686 emptyList :: [a]
1687 emptyList = build (\empty cons -> empty)
1688 */
1689
1690 "Creates a list with exectly one element."
1691 @inline
1692 singletonList :: a -> [a]
1693 singletonList v = build (\empty cons -> cons empty v)
1694
1695 /*
1696 // foldl f i (a + b) = foldl f (foldl f i a) b 
1697
1698 appendList :: [a] -> [a] -> [a]
1699 appendList a b = build (\empty cons -> foldl cons (foldl cons empty a) b)
1700 */
1701
1702 importJava "org.simantics.scl.runtime.list.ShareableList" where
1703     "Concatenates two lists."
1704     @private
1705     @JavaName "concat"
1706     appendList :: [a] -> [a] -> [a]
1707     
1708     "Adds the given value to the end of the list."
1709     @JavaName "add"   
1710     addList :: [a] -> a -> [a]
1711
1712 @private
1713 importJava "java.util.ArrayList" where
1714     data ArrayList a
1715
1716     @JavaName "<init>"
1717     newArrayList :: <Proc> ArrayList a
1718     
1719     @JavaName add
1720     addArrayList :: ArrayList a -> a -> <Proc> ()
1721
1722 """
1723 A primitive for constructing a list by `empty` and `cons` operations given to the function given as a parameter to this function.
1724 For example:
1725
1726     build (\empty cons -> cons (cons (cons empty 1) 2) 3)
1727     
1728 produces
1729
1730     [1, 2, 3]
1731     
1732 The SCL compiler makes the following optimization when encountering `build` and `foldl` functions after inlining:
1733
1734     foldl f i (build g) = g i f
1735 """
1736 @inline 2
1737 build :: forall b e2. (forall a e1. a -> (a -> b -> <e1> a) -> <e1,e2> a) -> <e2> [b]
1738 build f = runProc do
1739     l = newArrayList
1740     f () (\_ v -> addArrayList l v)
1741     Java.unsafeCoerce l
1742
1743 "A specific implementation of `map` for lists."
1744 @private
1745 @inline
1746 mapEList :: (a -> <e> b) -> [a] -> <e> [b]
1747 mapEList f l = build (\empty cons -> foldl (\cur x -> cons cur (f x)) empty l) 
1748
1749 "A specific implementation of `fmap` for lists."
1750 @inline
1751 mapList :: (a -> b) -> [a] -> [b]
1752 mapList f l = build (\empty cons -> foldl (\cur x -> cons cur (f x)) empty l) 
1753  
1754 "`guardList v` returns a singleton `[()]` if `v=True` and the empty list if `v=False`."
1755 @inline
1756 guardList :: Boolean -> [()]
1757 guardList cond = build (\empty cons -> if cond then cons empty () else empty) 
1758
1759 """
1760 `concatMap` combines `map` and `join` functions.
1761 It maps the elements of a given list to lists with the given function and concatenates the results.
1762
1763     concatMap f lst = join (map f lst) = [y | x <- lst, y <- f x] 
1764 """
1765 @inline
1766 concatMap :: (a -> <e> [b]) -> [a] -> <e> [b]
1767 concatMap f l = build (\empty cons -> foldl (\cur le -> foldl cons cur (f le)) empty l)
1768
1769 """
1770 Applies the given function to the elements of the lists until the function returns something
1771 else than `Nothing`. This return value is also returned as a result of this function.
1772 """
1773 @inline
1774 mapFirst :: (a -> <e> Maybe b) -> [a] -> <e> Maybe b
1775 mapFirst f l = loop 0 
1776   where
1777     len = length l
1778     loop i = if i == len
1779              then Nothing
1780              else match f (l!i) with
1781                  r @ (Just _) -> r
1782                  Nothing -> loop (i+1)
1783
1784 """
1785     foldl op initialValue list
1786     
1787 applies a binary operator `op` to all elements of `list` from left to right
1788 starting with `initialValue`. For example, 
1789
1790     foldl op init [x1, x2, x3, x4] = (((init `op` x1) `op` x2) `op` x3) `op` x4
1791 """
1792 @inline 2
1793 foldl :: forall a b e. (a -> b -> <e> a) -> a -> [b] -> <e> a
1794 foldl f initial l = loop initial 0
1795   where
1796     len = length l
1797     loop cur i = if i==len
1798                  then cur
1799                  else loop (f cur (l!i)) (i+1)
1800
1801 foldlI :: forall a b e. (Integer -> a -> b -> <e> a) -> a -> [b] -> <e> a
1802 foldlI f initial l = loop initial 0
1803   where
1804     len = length l
1805     loop cur i = if i==len
1806                  then cur
1807                  else loop (f i cur (l!i)) (i+1)
1808
1809 scanl :: (b -> a -> <e> b) -> b -> [a] -> <e> [b]
1810 scanl f initial l = build (\empty cons -> let
1811     len = length l
1812     loop cur i accum = let nl = cons accum cur
1813                            in if i==len
1814                            then nl
1815                             else loop (f cur (l!i)) (i+1) nl
1816   in loop initial 0 empty)
1817   
1818 "`foldr` is defined like `foldl` but it process the list from right to left."
1819 @inline
1820 foldr :: (b -> a -> <e> a) -> a -> [b] -> <e> a
1821 foldr f initial l = loop initial (length l - 1)
1822   where
1823     loop cur i = if i < 0
1824                  then cur
1825                  else loop (f (l!i) cur) (i-1)
1826
1827 foldr1 :: (a -> a -> <e> a) -> [a] -> <e> a
1828 foldr1 f l = loop (l!(len-1)) (len-2)
1829   where
1830     len = length l
1831     loop cur i = if i < 0
1832                  then cur
1833                  else loop (f (l!i) cur) (i-1)
1834
1835 """
1836 `filter pred lst` returns those elements of `lst` that the predicate `pred` accepts. For example
1837
1838     filter (> 3) [1, 2, 3, 4, 5, 6] = [4, 5, 6]
1839 """ 
1840 @inline
1841 filter :: (a -> <e> Boolean) -> [a] -> <e> [a]
1842 filter p l = build (\empty cons -> foldl (\cur x -> if p x then cons cur x else cur) empty l)
1843
1844 """
1845 Takes those elements of the input list that match `(Just x)` and adds the contents to the resulting list. For example,
1846
1847     filterJust [Just 1, Nothing, Just 5] = [1, 5] 
1848 """
1849 @inline
1850 filterJust :: [Maybe a] -> [a]
1851 filterJust l = build (\empty cons -> foldl (\cur x -> match x with Just v -> cons cur v ; _ -> cur) empty l)
1852
1853 listToMaybe :: [a] -> Maybe a
1854 listToMaybe l = if isEmpty l then Nothing else Just (l!0)
1855
1856 maybeToList :: Maybe a -> [a]
1857 maybeToList (Just a) = [a]
1858 maybeToList _ = [] 
1859
1860 """
1861 `takeWhile p l`, returns the longest prefix (possibly empty) of list `l` of elements that satisfy `p`
1862 """
1863 takeWhile :: (a -> <e> Boolean) -> [a] -> <e> [a]
1864 takeWhile f l = loop 0 
1865   where
1866     len = length l
1867     loop i | i == len  = l
1868            | f (l!i)   = loop (i+1)
1869            | otherwise = take i l
1870
1871 partition :: (a -> <e> Boolean) -> [a] -> <e> ([a], [a])
1872 partition p l = runProc do
1873     res1 = newArrayList
1874     res2 = newArrayList
1875     for l (\el ->
1876         if p el
1877         then addArrayList res1 el
1878         else addArrayList res2 el
1879     )
1880     (Java.unsafeCoerce res1, Java.unsafeCoerce res2)
1881
1882 """
1883 `range begin end` produces a list of consecutive integers starting from `begin` and ending to `end` (including `end`).
1884 The compiler supports syntactic sugar `[begin..end]` for this function.
1885 """
1886 @inline    
1887 range :: Integer -> Integer -> [Integer]
1888 range first last = build (\empty cons -> do
1889     loop i cur = if i > last then cur else loop (i+1) (cons cur i)
1890     loop first empty)
1891
1892 "A specific implementation of `iter` for lists."
1893 @inline
1894 iterList :: (a -> <e> b) -> [a] -> <e> ()
1895 iterList f l = foldl (\_ x -> ignore (f x)) () l
1896
1897 "A specific implementation of `iterI` for lists."
1898 @inline
1899 iterIList :: (Integer -> a -> <e> b) -> [a] -> <e> ()
1900 iterIList f l = do foldl (\i x -> do f i x ; i+1) 0 l ; () 
1901
1902 """
1903 Generates a list from a given starting state and iteration function.
1904 For example
1905
1906     let nextState 0 = Nothing
1907         nextState i = Just (i, i `div` 2)
1908     in  unfoldr nextState 30
1909         
1910 produces
1911
1912     [30, 15, 7, 3, 1]
1913 """
1914 @inline
1915 unfoldr :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
1916 unfoldr f s = build (\empty cons -> do
1917     loop s cur =
1918         match f s with
1919             Just (el,newS) -> loop newS (cons cur el)
1920             _ -> cur
1921     loop s empty)
1922
1923 importJava "org.simantics.scl.runtime.Lists" where
1924     /*
1925     @private
1926     @JavaName map
1927     mapList :: (a -> b) -> [a] -> [b]    
1928     @private
1929     @JavaName map
1930     mapEList :: (a -> <e> b) -> [a] -> <e> [b]
1931     @private
1932     @JavaName iter
1933     iterList :: (a -> <e> ()) -> [a] -> <e> ()
1934     concatMap :: (a -> <e> [b]) -> [a] -> <e> [b]
1935     */ 
1936     """
1937     Combines two lists into one list of pairs. The length of the resulting list is the length of the smallest input list.
1938     
1939         zip [1, 2, 3, 4, 5] ['a', 'b', 'c'] = [(1, 'a'), (2, 'b'), (3, 'c')]
1940     """
1941     zip :: [a] -> [b] -> [(a,b)]
1942     "Combines two lists by using the given function for combining the elements. The length of the resulting list is the length of the smallest input list."
1943     zipWith :: (a -> b -> <e> c) -> [a] -> [b] -> <e> [c]
1944     """
1945     Produces two lists from one list of pairs.
1946     
1947         unzip [(1, 'a'), (2, 'b'), (3, 'c')] = ([1, 2, 3], ['a', 'b', 'c'])
1948     """
1949     unzip :: [(a,b)] -> ([a],[b])
1950     
1951     //"@filter p l@ returns those elements of @l@ that the predicate @p@ accepts." 
1952     //filter :: (a -> <e> Boolean) -> [a] -> <e> [a]
1953     //filterJust :: [Maybe a] -> [a]
1954     /*
1955     foldl :: (a -> b -> <e> a) -> a -> [b] -> <e> a
1956     */
1957     "Like `foldl` but assumes that the list is non-empty so the initial is not needed."
1958     foldl1 :: (a -> a -> <e> a) -> [a] -> <e> a
1959     //unfoldr :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
1960     
1961     "Sorts the list using the given comparator."
1962     sortWith :: (a -> a -> <e> Integer) -> [a] -> <e> [a]
1963     
1964     """
1965     Given a list of key-value pairs, the function produces a function that finds a value
1966     efficiently for the given key.
1967     """
1968     index :: [(a,b)] -> a -> Maybe b
1969     
1970     """
1971     Given a list of values and a function computing a key for each value, the function produces a function that finds a value
1972     effeciently for the given key.
1973     """
1974     indexBy ::  (a -> <e> b) -> [a] -> <e> (b -> Maybe a)
1975     
1976     "Works like `index` but uses the given functions as hash codes and equality."
1977     indexWith :: (a -> Integer) -> (a -> a -> Boolean) -> [(a,b)] -> a -> Maybe b
1978     
1979     "Groups a list values by a key computed by the given function."
1980     groupBy :: (a -> <e> b) -> [a] -> <e> [(b, [a])]
1981     
1982     "Groups a list of key-value pairs by the keys."
1983     group :: [(a,b)] -> [(a, [b])]
1984
1985     "Composition of index and groupBy."
1986     indexGroupBy :: (a -> <e> b) -> [a] -> <e> (b -> [a])
1987     
1988     "Composition of index and group."
1989     indexGroup :: [(a,b)] -> a -> [b]
1990     
1991     groupWith :: (b -> Integer) -> (b -> b -> Boolean) -> (a -> <e> b) -> (a -> <e> c) -> [a] -> <e> [(b, [c])]
1992     
1993     "Removes duplicates (all but the first occurrence) from the list but otherwise preserves the order of the elements."
1994     unique :: [a] -> [a]
1995     
1996     "Like `unique`, but uses the given function for finding the key values used for uniqueness testing."
1997     uniqueBy :: (a -> b) -> [a] -> [a]
1998
1999     "Works like `unique` but uses the given function for equality tests."
2000     uniqueWith :: (a -> a -> Boolean) -> [a] -> [a]
2001     
2002     "Works like `\\\\` but uses the given function for equality tests."
2003     deleteAllBy :: (a -> a -> Boolean) -> [a] -> [a] -> [a]
2004     
2005     @private
2006     listDifference :: [a] -> [a] -> [a]
2007     
2008     //range :: Integer -> Integer -> [Integer]
2009     
2010     //build :: (forall a. a -> (a -> b -> <e> a) -> <e> a) -> <e> [b]
2011
2012 "`elem el lst` return true, if `el` occurs in the list `lst`."
2013 elem :: a -> [a] -> Boolean
2014 elem el l = loop 0
2015   where
2016     len = length l
2017     loop i | i < len = if el == l!i
2018                        then True
2019                        else loop (i+1)
2020            | otherwise = False
2021
2022 "`elemMaybe v1 (Just v2)` returns true if `v1 == v2`. `elemMaybe v1 Nothing` is always false."
2023 elemMaybe :: a -> Maybe a -> Boolean
2024 elemMaybe el m = match m with
2025     Just el2 -> el == el2
2026     Nothing -> False
2027
2028 "`elemIndex el lst` returns the index of the first element in the given list `lst` which is equal (by ==) to the query element, or Nothing if there is no such element."
2029 elemIndex :: a -> [a] -> Maybe Integer
2030 elemIndex el l = loop 0
2031   where
2032     len = length l
2033     loop i | i < len = if el == l!i
2034                        then Just i
2035                        else loop (i+1)
2036            | otherwise = Nothing
2037
2038 """
2039 Computes a list that contains only elements that belongs to both input lists.
2040 """
2041 intersect :: [a] -> [a] -> [a]
2042 intersect a b = filter f a
2043   where
2044     f e = elem e b
2045
2046 "Reverses a given list. For example, `reverse [1,2,3] = [3,2,1]`"
2047 reverse :: [a] -> [a]
2048 reverse l = [l!(len-i) | i <- [1..len]]
2049   where
2050     len = length l
2051
2052 """
2053 Transposes the rows and columns of its argument. For example,
2054
2055     transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]]
2056     transpose [[1,2],[3,4,5]] == [[1,3],[2,4],[5]]
2057 """
2058 transpose xss = [[xs!i | xs <- xss, i < length xs]
2059                 | i <- [0..maximum [length xs | xs <- xss]-1]]
2060
2061 "Works like `unfoldr` but generates the list from right to left."
2062 unfoldl :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
2063 unfoldl f seed = reverse $ unfoldr f seed
2064
2065 "Removes the first element of the list, if the list is non-empty."
2066 tail :: [a] -> [a]
2067 tail l = if len < 2 then emptyList else subList l 1 len 
2068   where 
2069     len = length l
2070
2071 "Tries to find the given key from the list of key-value pairs and returns the corresponding value."
2072 lookup ::  a -> [(a, b)] -> Maybe b
2073 lookup el l = do
2074     len = length l
2075     loop i = if i < len 
2076              then match l!i with
2077                (a,b) | a == el   -> Just b
2078                      | otherwise -> loop (i+1)
2079              else Nothing
2080     loop 0
2081
2082 "Conjunction over a list."
2083 @inline
2084 and :: [Boolean] -> Boolean
2085 and = foldl (&&) True
2086
2087 "Disjunction over a list."
2088 @inline
2089 or :: [Boolean] -> Boolean
2090 or  = foldl (||) False
2091
2092 """
2093 `any pred lst` tests whether the predicate `pred` holds some element of `lst`.
2094 It returns immediately when it encounters the first value satisfying the predicate.
2095 """ 
2096 any :: (a -> <e> Boolean) -> [a] -> <e> Boolean
2097 any p =  or . map p
2098
2099 """
2100 `all pred lst` tests whether the predicate `pred` holds for all elements of `lst`.
2101 It returns immediately when it encounters the first value not satisfying the predicate.
2102 """ 
2103 all :: (a -> <e> Boolean) -> [a] -> <e> Boolean
2104 all p =  and . map p
2105
2106 """
2107 Returns the first element of the list satisfying the given condition,
2108 or `Nothing` if there is no such element.
2109 """
2110 findFirst :: (a -> <e> Boolean) -> [a] -> <e> Maybe a
2111 findFirst p l = loop 0
2112   where
2113     len = length l
2114     loop i = if i < len 
2115              then let el = l!i in 
2116                   if p el 
2117                   then Just el 
2118                   else loop (i+1)
2119              else Nothing
2120     loop 0
2121
2122
2123 """
2124 Sorts the given list using its default order.
2125 """
2126 @inline
2127 sort :: Ord a => [a] -> [a]
2128 sort = sortWith compare
2129
2130 """
2131 Sorts the lists by the values computed by the first function.
2132 For example
2133
2134     sortBy snd [(1,5), (2,3), (3,4)] = [(2,3), (3,4), (1,5)] 
2135 """
2136 @inline
2137 sortBy :: Ord b => (a -> <e> b) -> [a] -> <e> [a]
2138 sortBy f l = sortWith (\x y -> compare (f x) (f y)) l
2139 // This is faster if f is slow, but will generate more auxiliary structures
2140 //sortBy f l = map snd (sortWith (\(x,_) (y,_) -> compare x y) [(f x, x) | x <- l])
2141
2142 "`a \\\\ b` removes all elements of `b` from the list `a`."
2143 (\\) :: [a] -> [a] -> [a]
2144 (\\) = listDifference
2145
2146 /// Dynamic ///
2147
2148 importJava "java.lang.Object" where
2149     "A data type that can represent any value."
2150     data Dynamic
2151     
2152     @private
2153     @JavaName toString
2154     showDynamic :: Dynamic -> String
2155
2156 instance Show Dynamic where
2157     show = showDynamic
2158
2159 "Converts a value to `Dynamic` type."
2160 toDynamic :: a -> Dynamic
2161 toDynamic = Java.unsafeCoerce
2162
2163 "Converts a `Dynamic` value to a required value, or fails if the conversion is not possible."
2164 importJava "org.simantics.scl.compiler.runtime.ValueConversion" where
2165     fromDynamic :: Typeable a => Dynamic -> a
2166
2167 /// Procedures ///
2168
2169 importJava "org.simantics.scl.runtime.procedure.Ref" where
2170     "A mutable reference to a value of type `a`."
2171     data Ref a
2172     
2173     "Creates a new reference with the given initial value."
2174     @JavaName "<init>"
2175     ref :: a -> <Proc> (Ref a)
2176     
2177     "Returns the current value of the reference."
2178     @JavaName "value"
2179     getRef :: Ref a -> <Proc> a
2180     
2181     "Sets a new value for the reference."
2182     @JavaName "<set>value"
2183     (:=) :: Ref a -> a -> <Proc> ()
2184
2185 instance Show (Ref a) where
2186     show _ = "<reference>"
2187
2188 importJava "org.simantics.scl.runtime.reporting.SCLReporting" where
2189     "Prints the given string to the console."
2190     @JavaName "print"
2191     printString :: String -> <Proc> ()
2192     "Prints an error message to the console."
2193     printError :: String -> <Proc> ()
2194     "Reports that certain amount of work has been done for the current task."
2195     didWork :: Double -> <Proc> ()
2196     """
2197     `printingToFile "fileName" expression` executes the `expression` so that all its console prints
2198     are written to the file given as a first parameter.
2199     """
2200     printingToFile :: String -> (<e> a) -> <e> a
2201     """
2202     `printErrorsAsNormalPrints expression` executes the `expression` so that all its error prints
2203     are printed as normal prints. This is useful mainly in testing scripts for checking that the implementations
2204     give proper error messages with invalid inputs.
2205     """
2206     printErrorsAsNormalPrints :: (<e> a) -> <e> a
2207     """
2208     `disablePrintingForCommand expression` executes the `expression` so that it does not print return values.
2209     Errors are printed normally.
2210     """
2211     disablePrintingForCommand :: (<e> a) -> <e> a
2212     
2213
2214 importJava "org.simantics.scl.runtime.procedure.Procedures" where
2215     "Returns `True` if the current thread has been interrupted."
2216     isInterrupted :: <Proc> Boolean
2217     "Checks whether the current thread has been interrupted and throws an exception if it is."
2218     checkInterrupted :: <Proc> ()
2219     "Generates a random identifier."
2220     generateUID :: <Proc> String
2221     
2222     "Executes the given expression and catches certain class of exceptions (specified by the catch handler that is given as a second parameter.)"
2223     @JavaName catch_
2224     catch :: VecComp ex => (<e,Exception> a) -> (ex -> <e> a) -> <e> a
2225
2226 importJava "java.lang.Throwable" where
2227     data Throwable
2228     @private
2229     @JavaName toString
2230     showThrowable :: Throwable -> String
2231     @private
2232     @JavaName getMessage 
2233     getMessageThrowable :: Throwable -> String
2234     @private
2235     @JavaName getCause 
2236     getCauseThrowable :: Throwable -> Maybe Throwable
2237 importJava "java.lang.Exception" where
2238     data Exception
2239     @private
2240     @JavaName toString
2241     showException :: Exception -> String
2242
2243 instance Show Throwable where
2244     show = showThrowable
2245 instance Show Exception where
2246     show = showException
2247
2248 class Throwable e where
2249     toThrowable :: e -> Throwable
2250
2251 messageOfException :: Throwable e => e -> String
2252 messageOfException = getMessageThrowable . toThrowable
2253
2254 causeOfException :: Throwable e => e -> Maybe Throwable
2255 causeOfException = getCauseThrowable . toThrowable
2256
2257 instance Throwable Throwable where
2258     toThrowable = id
2259 instance Throwable Exception where
2260     toThrowable = Java.unsafeCoerce
2261
2262 "Prints the given value in the console."
2263 @inline
2264 print :: Show a => a -> <Proc> ()
2265 print v = printString (showForPrinting v)
2266 /*
2267 instance Show TypeRep where
2268     sb <+ (TApply (TCon "Builtin" "[]") b) = 
2269         sb << "[" <+ b << "]"
2270     sb <+ (TApply (TApply (TCon "Builtin" "(,)") c1) c2) = 
2271         sb << "(" <+ c1 << "," <+ c2 << ")"
2272     sb <+ (TApply (TApply (TApply (TCon "Builtin" "(,,)") c1) c2) c3) = 
2273         sb << "(" <+ c1 << "," <+ c2 << "," <+ c3 << ")"
2274     sb <+ (TApply (TApply (TApply (TApply (TCon "Builtin" "(,,,)") c1) c2) c3) c4) =
2275         sb << "(" <+ c1 << "," <+ c2 << "," <+ c3 << "," <+ c4 << ")" 
2276     
2277     sb <+ (TCon _ name) = sb << name
2278     sb <+ (TApply a b) = sb <+ Par 1 a << " " <+ Par 2 b
2279     sb <+ (TFun a b) = sb <+ Par 1 a << " -> " <+ b
2280     
2281     precedence (TCon _ _) = 0
2282     precedence (TFun _ _) = 2
2283     precedence (TApply a _) = if isSpecialType a then 0 else 1
2284       where
2285         isSpecialType (TCon "Builtin" "[]") = True
2286         isSpecialType (TCon "Builtin" "()") = True
2287         isSpecialType (TCon "Builtin" "(,)") = True
2288         isSpecialType (TCon "Builtin" "(,,)") = True
2289         isSpecialType (TCon "Builtin" "(,,,)") = True
2290         isSpecialType (TApply a _) = isSpecialType a
2291 */
2292
2293 // ByteArray
2294
2295 importJava "java.util.Arrays" where
2296     @private
2297     @JavaName toString
2298     byteArrayToString :: ByteArray -> String
2299
2300 instance Show ByteArray where
2301     show = byteArrayToString
2302
2303 // Type
2304
2305 @private
2306 importJava "org.simantics.scl.compiler.types.Type" where
2307     @JavaName toString
2308     showType :: Type -> String
2309
2310 importJava "org.simantics.scl.compiler.types.Types" where
2311     removeForAll :: Type -> Type
2312     
2313 instance Show Type where
2314     show = showType