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