]> gerrit.simantics Code Review - simantics/platform.git/blob - bundles/org.simantics.scl.runtime/scl/Prelude.scl
(refs #7448) Added Exception effect
[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 /// FunctorM ///
1069
1070 class (Functor f) => FunctorM f where
1071     "`mapM f` is equivalent to `sequence . map f`."
1072     mapM :: Monad m => (a -> m b) -> f a -> m (f b)
1073     "Evaluate each action in the sequence from left to right, and collect the results."
1074     sequence :: Monad m => f (m a) -> m (f a) 
1075     mapM f l = sequence (fmap f l)
1076
1077 /// Category ///
1078
1079 "Identity function."
1080 id :: a -> a
1081 id x = x
1082
1083 """
1084 Ignores the given value. This function is used in a situation where a function returns
1085 a value in a context where the value is not expected.
1086 """
1087 @inline
1088 ignore :: a -> ()
1089 ignore _ = ()
1090
1091 @inline
1092 ignoreM :: a -> Maybe b
1093 ignoreM _ = Nothing
1094
1095 """
1096 Composes two functions
1097     (f . g) x = f (g x)
1098 """
1099 (.) :: (b -> <e> c) -> (a -> <e> b) -> (a -> <e> c)
1100 (f . g) x = f (g x)
1101
1102 /// Sequence ///
1103
1104 "A type class for sequences. All sequences must support indexing by integers."
1105 class /*(Additive a) =>*/ Sequence a where
1106     "Length of the sequence"
1107     length :: a -> Integer
1108     "`take n s` returns the first `n` elements of the sequence `s`."
1109     take :: Integer -> a -> a
1110     "`drop n s` removes the first `n` elements of the sequence `s`."
1111     drop :: Integer -> a -> a
1112     """
1113     `sub s begin end` returns a subsequence of `s` starting from
1114     index `begin` and ending just before index `end`.
1115     """ 
1116     sub :: a -> Integer -> Integer -> a
1117     
1118     take n v = sub v 0 (min n (length v))
1119     drop n v = sub v (min n len) len
1120       where
1121         len = length v 
1122
1123 instance Sequence [a] where
1124     length = lengthList
1125     sub = subList
1126     
1127 instance Sequence String where
1128     length = lengthString
1129     sub = subString        
1130
1131 class IndexedSequence f where
1132     "`seq ! i` returns the `i`th element of the sequence `seq`. Indexing starts from zero."
1133     (!) :: f a -> Integer -> a
1134
1135 instance IndexedSequence [] where
1136     (!) = getList
1137
1138 /// Boolean ///
1139
1140 """
1141 Equivalent to the boolean value `True`. The value is meant to be used in
1142 guard patterns:
1143
1144     min a b | a < b     = a
1145             | otherwise = b 
1146 """
1147 @inline
1148 otherwise :: Boolean
1149 otherwise = True
1150
1151 instance Ord Boolean where
1152     compare False False = 0
1153     compare False True  = neg 1
1154     compare True  False = 1
1155     compare True  True  = 0
1156
1157 instance Show Boolean where
1158     show True = "True"
1159     show False = "False"
1160
1161 """
1162 Boolean conjunction (and). The function is a macro that evaluates the second parameter
1163 only if the first parameter is `True`.
1164
1165 <table>
1166 <tr><th>a</th><th>b</th><th>a && b</th></tr>
1167 <tr><td>True</td><td>True</td><td>True</td></tr>
1168 <tr><td>True</td><td>False</td><td>False</td></tr>
1169 <tr><td>False</td><td>not evaluated</td><td>False</td></tr>
1170 </table> 
1171 """
1172 @macro
1173 (&&) :: Boolean -> Boolean ->  Boolean
1174 a && b = if a then b else False
1175
1176 """
1177 Boolean disjunction (or). The function is a macro that evaluates the second parameter
1178 only if the first parameter is `False`.
1179
1180 <table>
1181 <tr><th>a</th><th>b</th><th>a || b</th></tr>
1182 <tr><td>True</td><td>not evaluated</td><td>True</td></tr>
1183 <tr><td>False</td><td>True</td><td>True</td></tr>
1184 <tr><td>False</td><td>False</td><td>False</td></tr>
1185 </table> 
1186 """
1187 @macro
1188 (||) :: Boolean -> Boolean -> Boolean
1189 a || b = if a then True else b
1190
1191 "Boolean negation"
1192 @inline
1193 not a = if a then False else True
1194
1195 /// Maybe ///
1196
1197 //data Maybe a = Nothing | Just a
1198
1199 "Given `Just x` this function returns `x`. If the parameter is `Nothing`, the function raises an exception."
1200 fromJust :: Maybe a -> a
1201 fromJust (Just a) = a
1202
1203 deriving instance (Ord a) => Ord (Maybe a)
1204 deriving instance (Show a) => Show (Maybe a)
1205
1206 instance Functor Maybe where
1207     fmap _ Nothing  = Nothing
1208     fmap f (Just x) = Just (f x)
1209
1210 instance FunctorE Maybe where
1211     map _ Nothing  = Nothing
1212     map f (Just x) = Just (f x)
1213     
1214     iter _ Nothing = ()
1215     iter f (Just x) = ignore (f x)
1216     
1217     iterI _ Nothing = ()
1218     iterI f (Just x) = ignore (f 0 x)
1219     
1220 instance Monad Maybe where    
1221     return x = Just x
1222
1223     @inline
1224     Nothing >>= _ = Nothing
1225     Just x  >>= f = f x
1226
1227     @inline
1228     join Nothing  = Nothing
1229     join (Just x) = x
1230
1231 instance MonadZero Maybe where
1232     mzero = Nothing
1233
1234 instance MonadOr Maybe where
1235     morelse a@(Just _) _ = a
1236     morelse _ b = b
1237
1238 "`execJust v f` executes the function `f` with parameter value `x`, if `v=Just x`. If `v=Nothing`, the function does nothing."
1239 @inline
1240 execJust :: Maybe a -> (a -> <e> b) -> <e> ()
1241 execJust maybeValue procedure = match maybeValue with
1242     Just v -> ignore $ procedure v
1243     _ -> ()
1244
1245 "`fromMaybe def v` returns `def` if `v=Nothing` and `x` if `v=Just x`."
1246 @inline
1247 fromMaybe :: a -> Maybe a -> a
1248 fromMaybe default maybeValue = match maybeValue with
1249     Just v -> v
1250     _ -> default
1251     
1252     
1253 """
1254 Provides a default value if the first parameter is Nothing.
1255 The default value is evaluated only if needed. The function
1256 can be used as an operator and is right associative so that
1257 the following is possible:
1258
1259     tryWithTheFirstMethod
1260         `orElse` tryWithTheSecondMethod
1261         `orElse` fail "Didn't succeed."
1262 """
1263 @inline
1264 orElse :: Maybe a -> (<e> a) -> <e> a
1265 orElse (Just x) _   = x
1266 orElse Nothing  def = def
1267
1268 /// Either ///
1269
1270 """
1271 The Either type represents values with two possibilities: a value of type `Either a b` is either `Left a` or `Right b`.
1272
1273 The `Either` type is sometimes used to represent a value which is either correct or an error; by convention, the `Left` constructor
1274 is used to hold an error value and the `Right` constructor is used to hold a correct value (mnemonic: "right" also means "correct").
1275 """
1276 @JavaType "org.simantics.scl.runtime.either.Either"
1277 data Either a b =
1278     @JavaType "org.simantics.scl.runtime.either.Left"
1279     @FieldNames [value]
1280     Left a
1281   | @JavaType "org.simantics.scl.runtime.either.Right"
1282     @FieldNames [value]
1283     Right b
1284
1285 deriving instance (Ord a, Ord b) => Ord (Either a b)
1286 deriving instance (Show a, Show b) => Show (Either a b)
1287
1288 instance Functor (Either a) where
1289     fmap _ (Left x)  = Left x
1290     fmap f (Right y) = Right (f y)
1291
1292 instance FunctorE (Either a) where
1293     map _ (Left x)  = Left x
1294     map f (Right y) = Right (f y)
1295     
1296     iter _ (Left x) = ()
1297     iter f (Right y) = ignore (f y)
1298     
1299     iterI _ (Left x) = ()
1300     iterI f (Right y) = ignore (f 0 y)
1301         
1302 instance Monad (Either b) where
1303     return y = Right y
1304
1305     Left x  >>= _ = Left x
1306     Right y >>= f = f y
1307
1308     join (Left x)  = Left x
1309     join (Right y) = y
1310     
1311 /// String ///
1312
1313 importJava "java.lang.String" where
1314     @private
1315     @JavaName "concat"
1316     concatString :: String -> String -> String
1317     @private
1318     @JavaName "compareTo"
1319     compareString :: String -> String -> Integer
1320     @private
1321     @JavaName "length"
1322     lengthString :: String -> Integer
1323
1324     """
1325     `replaceString original pattern replacement` replaces all occurrences of `pattern` in the string by `replacement`.
1326     """ 
1327     @JavaName replace
1328     replaceString :: String -> String -> String -> String
1329     
1330     @private
1331     @JavaName split
1332     splitString_ :: String -> String -> Array String
1333     
1334     """
1335     `indexOf string s` finds the first occurrence of `s` from `string` and returns its index.
1336     If the `s` does not occur in the string, return `-1`."
1337     """
1338     @JavaName indexOf
1339     indexOf :: String -> String -> Integer
1340     
1341     "Works like `indexOf` but starts searching from the given index instead of the beginning of the string."
1342     @JavaName indexOf
1343     indexOfStartingFrom :: String -> String -> Integer -> Integer
1344     
1345     "Works like `indexOf` but returns the index of the last occurrence."
1346     @JavaName lastIndexOf
1347     lastIndexOf :: String -> String -> Integer
1348     
1349     "Works like `lastIndexOf` but starts searching from the given index instead of the end of the string."
1350     @JavaName lastIndexOf
1351     lastIndexOfStartingFrom :: String -> String -> Integer -> Integer
1352     
1353     @private
1354     @JavaName substring
1355     subString :: String -> Integer -> Integer -> String
1356
1357     """
1358     `regionMatches str1 offset1 str2 offset2 len` tests whether
1359     `sub str1 offset1 (offset1+len) == sub str2 offset2 (offset2+len)`.
1360     """
1361     regionMatches :: String -> Integer -> String -> Integer -> Integer -> Boolean
1362
1363     "`startsWith string prefix` returns true if the string begins with the given prefix."
1364     startsWith :: String -> String -> Boolean
1365     
1366     "`endsWith string suffix` returns true if the string ends with the given prefix."
1367     endsWith :: String -> String -> Boolean
1368     
1369     "Removes leading and trailing whitespace from the string."
1370     trim :: String -> String
1371     
1372     "`contains string s` returns true if `string` contains `s` as a substring."
1373     contains :: String -> String -> Boolean
1374     
1375     "`charAt string i` returns the `i`th character of the string."
1376     charAt :: String -> Integer -> Character
1377     
1378     "Converts all letters of the string to lower case."
1379     toLowerCase :: String -> String
1380     "Converts all letters of the string to upper case."
1381     toUpperCase :: String -> String
1382     
1383     "Creates a string from a vector of characters."
1384     @JavaName "<init>"
1385     string :: Vector Character -> String
1386
1387 instance Ord String where
1388     compare = compareString
1389     
1390 instance Additive String where
1391     zero = ""
1392     (+) = concatString
1393     sum ss = runProc (StringBuilder.toString $ foldl StringBuilder.appendString StringBuilder.new ss)
1394
1395 @private
1396 importJava "org.simantics.scl.runtime.string.StringEscape" where
1397     appendEscapedString :: StringBuilder.T -> String -> <Proc> StringBuilder.T
1398
1399 instance Show String where
1400     showForPrinting = id
1401     sb <+ v = (appendEscapedString (sb << "\"") v) << "\""
1402
1403 instance Read String where
1404     read str = str
1405     
1406 @deprecated "Instead of 'splitString text pattern', write 'split pattern text' (note change in the parameter order)." 
1407 "`splitString text pattern` splits the string into a list of string where the parts are sepratated in the original list by the given pattern."
1408 splitString :: String -> String -> [String]
1409 splitString source pattern = arrayToList $ splitString_ source pattern
1410
1411 split :: String -> String -> [String]
1412 split pattern text = arrayToList $ splitString_ text pattern
1413
1414 /// Tuple0 ///
1415
1416 instance Ord () where
1417     compare () () = 0
1418
1419 instance Additive () where
1420     zero = ()
1421     () + () = ()
1422
1423 instance Show () where
1424     show () = "()"
1425
1426 /// Tuple2 ///
1427
1428 "Gives the first element of a pair."
1429 @inline
1430 fst :: (a,b) -> a
1431 fst (x,y) = x
1432
1433 "Gives the second element of a pair."
1434 @inline
1435 snd :: (a,b) -> b
1436 snd (x,y) = y
1437
1438 instance (Ord a, Ord b) => Ord (a, b) where
1439     compare (a0, b0) (a1, b1) = compare a0 a1 &<& compare b0 b1
1440
1441 instance (Additive a, Additive b) => Additive (a, b) where
1442     zero = (zero, zero)
1443     (a0, b0) + (a1, b1) = (a0+a1, b0+b1)
1444
1445 instance Functor ((,) a) where
1446     fmap f (a,b) = (a, f b)
1447     
1448 instance (Show a, Show b) => Show (a, b) where
1449     sb <+ (x, y) = sb << "(" <+ x << ", " <+ y << ")"
1450
1451 /// Tuple3 ///
1452
1453 instance (Ord a, Ord b, Ord c) => Ord (a, b, c) where
1454     compare (a0, b0, c0) (a1, b1, c1) = compare a0 a1 &<& compare b0 b1 &<& compare c0 c1
1455
1456 instance (Additive a, Additive b, Additive c) => Additive (a, b, c) where
1457     zero = (zero, zero, zero)
1458     (a0, b0, c0) + (a1, b1, c1) = (a0+a1, b0+b1, c0+c1)
1459
1460 instance Functor ((,,) a b) where
1461     fmap f (a,b,c) = (a, b, f c)
1462
1463 instance (Show a, Show b, Show c) => Show (a, b, c) where
1464     sb <+ (x, y, z) = sb << "(" <+ x << ", " <+ y << ", " <+ z << ")"
1465
1466 /// Tuple4 ///
1467
1468 instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) where
1469     compare (a0, b0, c0, d0) (a1, b1, c1, d1) = 
1470         compare a0 a1 &<& compare b0 b1 &<& compare c0 c1 &<& compare d0 d1
1471
1472 instance (Additive a, Additive b, Additive c, Additive d) => Additive (a, b, c, d) where
1473     zero = (zero, zero, zero, zero)
1474     (a0, b0, c0, d0) + (a1, b1, c1, d1) = (a0+a1, b0+b1, c0+c1, d0+d1)
1475
1476 instance Functor ((,,,) a b c) where
1477     fmap f (a,b,c,d) = (a, b, c, f d)
1478
1479 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
1480     sb <+ (x, y, z, w) = sb << "(" <+ x << ", " <+ y << ", " <+ z << ", " <+ w << ")"
1481     
1482 /// Tuple5 ///
1483
1484 instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) where
1485     compare (a0, b0, c0, d0, e0) (a1, b1, c1, d1, e1) = 
1486         compare a0 a1 &<& compare b0 b1 &<& compare c0 c1 &<& compare d0 d1 &<& compare e0 e1
1487     
1488 instance (Additive a, Additive b, Additive c, Additive d, Additive e) => Additive (a, b, c, d, e) where
1489     zero = (zero, zero, zero, zero, zero)
1490     (a0, b0, c0, d0, e0) + (a1, b1, c1, d1, e1) = (a0+a1, b0+b1, c0+c1, d0+d1, e0+e1)
1491
1492 instance Functor ((,,,,) a b c d) where
1493     fmap f (a,b,c,d,e) = (a, b, c, d, f e)
1494
1495 /// Lists ///
1496
1497 instance (Ord a) => Ord [a] where
1498     compare a b = loop 0 
1499       where
1500         lA = length a
1501         lB = length b
1502         loop i = if i >= lA
1503                  then (if i >= lB then 0 else -1)
1504                  else if i >= lB
1505                  then 1
1506                  else compare (a!i) (b!i) &<& loop (i+1)
1507
1508 instance Functor [] where
1509     fmap = mapList
1510
1511 instance FunctorE [] where
1512     map = mapEList
1513     iter = iterList
1514     iterI = iterIList
1515         
1516 instance Monad [] where
1517     return x = singletonList x
1518     l >>= f  = concatMap f l
1519     join l   = l >>= id
1520
1521 instance MonadZero [] where
1522     mzero = emptyList
1523
1524 instance MonadPlus [] where
1525     mplus = appendList
1526
1527 instance Additive [a] where
1528     zero = emptyList
1529     (+) = appendList
1530
1531 instance FunctorM [] where
1532     sequence = foldl (\m mel -> m >>= \l -> mel >>= \el -> return (addList l el)) (return emptyList)
1533     mapM f l = sequence (map f l)
1534
1535 "Appends the string representations of all elements of the list to the string builder and separates the values with the given separator."
1536 printWithSeparator :: Show a => StringBuilder.T -> String -> [a] -> <Proc> StringBuilder.T
1537 printWithSeparator sb sep l = loop 0
1538   where
1539     len = length l
1540     loop i = if i >= len then sb
1541              else do
1542                  (if i==0 then sb else sb << sep) <+ l!i
1543                  loop (i+1)
1544
1545 "Joins the string representations of the list of values with the given separator."
1546 joinWithSeparator :: Show a => String -> [a] -> String
1547 joinWithSeparator separator values = runProc ( 
1548     StringBuilder.toString $ printWithSeparator StringBuilder.new separator values)
1549
1550
1551 intercalate :: String -> [String] -> String
1552 intercalate separator strings = do
1553     l = length strings
1554     if l == 0
1555     then ""
1556     else if l == 1
1557     then strings!0
1558     else runProc do
1559         sb = StringBuilder.new
1560         sb << strings!0
1561         loop i | i == l = ()
1562                | otherwise = do
1563             sb << separator << strings!i
1564             loop (i+1)
1565         loop 1
1566         StringBuilder.toString sb
1567
1568 instance (Show a) => Show [a] where
1569     sb <+ l = do 
1570         len = length l
1571         loop i = if i < len 
1572                  then do 
1573                      if (i>0) then sb << ", " else sb
1574                      sb <+ l!i
1575                      loop (i+1)
1576                  else sb << "]"
1577         sb << "[" 
1578         loop 0                 
1579
1580 importJava "java.util.List" where
1581     "`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."
1582     @JavaName get
1583     getList :: [a] -> Integer -> a
1584
1585     @private
1586     @JavaName size
1587     lengthList :: [a] -> Integer
1588
1589     @private
1590     subList :: [a] -> Integer -> Integer -> [a]
1591
1592     @private
1593     isEmpty :: [a] -> Boolean
1594     
1595 @private    
1596 importJava "java.util.Collections" where
1597     emptyList :: [a]
1598     //singletonList :: a -> [a]
1599
1600 /*
1601 @inline
1602 emptyList :: [a]
1603 emptyList = build (\empty cons -> empty)
1604 */
1605
1606 "Creates a list with exectly one element."
1607 @inline
1608 singletonList :: a -> [a]
1609 singletonList v = build (\empty cons -> cons empty v)
1610
1611 /*
1612 // foldl f i (a + b) = foldl f (foldl f i a) b 
1613
1614 appendList :: [a] -> [a] -> [a]
1615 appendList a b = build (\empty cons -> foldl cons (foldl cons empty a) b)
1616 */
1617
1618 importJava "org.simantics.scl.runtime.list.ShareableList" where
1619     "Concatenates two lists."
1620     @private
1621     @JavaName "concat"
1622     appendList :: [a] -> [a] -> [a]
1623     
1624     "Adds the given value to the end of the list."
1625     @JavaName "add"   
1626     addList :: [a] -> a -> [a]
1627
1628 @private
1629 importJava "java.util.ArrayList" where
1630     data ArrayList a
1631
1632     @JavaName "<init>"
1633     newArrayList :: <Proc> ArrayList a
1634     
1635     @JavaName add
1636     addArrayList :: ArrayList a -> a -> <Proc> ()
1637
1638 """
1639 A primitive for constructing a list by `empty` and `cons` operations given to the function given as a parameter to this function.
1640 For example:
1641
1642     build (\empty cons -> cons (cons (cons empty 1) 2) 3)
1643     
1644 produces
1645
1646     [1, 2, 3]
1647     
1648 The SCL compiler makes the following optimization when encountering `build` and `foldl` functions after inlining:
1649
1650     foldl f i (build g) = g i f
1651 """
1652 @inline 2
1653 build :: forall b e2. (forall a e1. a -> (a -> b -> <e1> a) -> <e1,e2> a) -> <e2> [b]
1654 build f = runProc do
1655     l = newArrayList
1656     f () (\_ v -> addArrayList l v)
1657     Java.unsafeCoerce l
1658
1659 "A specific implementation of `map` for lists."
1660 @private
1661 @inline
1662 mapEList :: (a -> <e> b) -> [a] -> <e> [b]
1663 mapEList f l = build (\empty cons -> foldl (\cur x -> cons cur (f x)) empty l) 
1664
1665 "A specific implementation of `fmap` for lists."
1666 @inline
1667 mapList :: (a -> b) -> [a] -> [b]
1668 mapList f l = build (\empty cons -> foldl (\cur x -> cons cur (f x)) empty l) 
1669  
1670 "`guardList v` returns a singleton `[()]` if `v=True` and the empty list if `v=False`."
1671 @inline
1672 guardList :: Boolean -> [()]
1673 guardList cond = build (\empty cons -> if cond then cons empty () else empty) 
1674
1675 """
1676 `concatMap` combines `map` and `join` functions.
1677 It maps the elements of a given list to lists with the given function and concatenates the results.
1678
1679     concatMap f lst = join (map f lst) = [y | x <- lst, y <- f x] 
1680 """
1681 @inline
1682 concatMap :: (a -> <e> [b]) -> [a] -> <e> [b]
1683 concatMap f l = build (\empty cons -> foldl (\cur le -> foldl cons cur (f le)) empty l)
1684
1685 """
1686 Applies the given function to the elements of the lists until the function returns something
1687 else than `Nothing`. This return value is also returned as a result of this function.
1688 """
1689 @inline
1690 mapFirst :: (a -> <e> Maybe b) -> [a] -> <e> Maybe b
1691 mapFirst f l = loop 0 
1692   where
1693     len = length l
1694     loop i = if i == len
1695              then Nothing
1696              else match f (l!i) with
1697                  r @ (Just _) -> r
1698                  Nothing -> loop (i+1)
1699
1700 """
1701     foldl op initialValue list
1702     
1703 applies a binary operator `op` to all elements of `list` from left to right
1704 starting with `initialValue`. For example, 
1705
1706     foldl op init [x1, x2, x3, x4] = (((init `op` x1) `op` x2) `op` x3) `op` x4
1707 """
1708 @inline 2
1709 foldl :: forall a b e. (a -> b -> <e> a) -> a -> [b] -> <e> a
1710 foldl f initial l = loop initial 0
1711   where
1712     len = length l
1713     loop cur i = if i==len
1714                  then cur
1715                  else loop (f cur (l!i)) (i+1)
1716
1717 foldlI :: forall a b e. (Integer -> a -> b -> <e> a) -> a -> [b] -> <e> a
1718 foldlI f initial l = loop initial 0
1719   where
1720     len = length l
1721     loop cur i = if i==len
1722                  then cur
1723                  else loop (f i cur (l!i)) (i+1)
1724
1725 scanl :: (b -> a -> <e> b) -> b -> [a] -> <e> [b]
1726 scanl f initial l = build (\empty cons -> let
1727     len = length l
1728     loop cur i accum = let nl = cons accum cur
1729                            in if i==len
1730                            then nl
1731                             else loop (f cur (l!i)) (i+1) nl
1732   in loop initial 0 empty)
1733   
1734 "`foldr` is defined like `foldl` but it process the list from right to left."
1735 @inline
1736 foldr :: (b -> a -> <e> a) -> a -> [b] -> <e> a
1737 foldr f initial l = loop initial (length l - 1)
1738   where
1739     loop cur i = if i < 0
1740                  then cur
1741                  else loop (f (l!i) cur) (i-1)
1742
1743 foldr1 :: (a -> a -> <e> a) -> [a] -> <e> a
1744 foldr1 f l = loop (l!(len-1)) (len-2)
1745   where
1746     len = length l
1747     loop cur i = if i < 0
1748                  then cur
1749                  else loop (f (l!i) cur) (i-1)
1750
1751 """
1752 `filter pred lst` returns those elements of `lst` that the predicate `pred` accepts. For example
1753
1754     filter (> 3) [1, 2, 3, 4, 5, 6] = [4, 5, 6]
1755 """ 
1756 @inline
1757 filter :: (a -> <e> Boolean) -> [a] -> <e> [a]
1758 filter p l = build (\empty cons -> foldl (\cur x -> if p x then cons cur x else cur) empty l)
1759
1760 """
1761 Takes those elements of the input list that match `(Just x)` and adds the contents to the resulting list. For example,
1762
1763     filterJust [Just 1, Nothing, Just 5] = [1, 5] 
1764 """
1765 @inline
1766 filterJust :: [Maybe a] -> [a]
1767 filterJust l = build (\empty cons -> foldl (\cur x -> match x with Just v -> cons cur v ; _ -> cur) empty l)
1768
1769 listToMaybe :: [a] -> Maybe a
1770 listToMaybe l = if isEmpty l then Nothing else Just (l!0)
1771
1772 maybeToList :: Maybe a -> [a]
1773 maybeToList (Just a) = [a]
1774 maybeToList _ = [] 
1775
1776 """
1777 `takeWhile p l`, returns the longest prefix (possibly empty) of list `l` of elements that satisfy `p`
1778 """
1779 takeWhile :: (a -> <e> Boolean) -> [a] -> <e> [a]
1780 takeWhile f l = loop 0 
1781   where
1782     len = length l
1783     loop i | i == len  = l
1784            | f (l!i)   = loop (i+1)
1785            | otherwise = take i l
1786
1787 partition :: (a -> <e> Boolean) -> [a] -> <e> ([a], [a])
1788 partition p l = runProc do
1789     res1 = newArrayList
1790     res2 = newArrayList
1791     for l (\el ->
1792         if p el
1793         then addArrayList res1 el
1794         else addArrayList res2 el
1795     )
1796     (Java.unsafeCoerce res1, Java.unsafeCoerce res2)
1797
1798 """
1799 `range begin end` produces a list of consecutive integers starting from `begin` and ending to `end` (including `end`).
1800 The compiler supports syntactic sugar `[begin..end]` for this function.
1801 """
1802 @inline    
1803 range :: Integer -> Integer -> [Integer]
1804 range first last = build (\empty cons -> do
1805     loop i cur = if i > last then cur else loop (i+1) (cons cur i)
1806     loop first empty)
1807
1808 "A specific implementation of `iter` for lists."
1809 @inline
1810 iterList :: (a -> <e> b) -> [a] -> <e> ()
1811 iterList f l = foldl (\_ x -> ignore (f x)) () l
1812
1813 "A specific implementation of `iterI` for lists."
1814 @inline
1815 iterIList :: (Integer -> a -> <e> b) -> [a] -> <e> ()
1816 iterIList f l = do foldl (\i x -> do f i x ; i+1) 0 l ; () 
1817
1818 """
1819 Generates a list from a given starting state and iteration function.
1820 For example
1821
1822     let nextState 0 = Nothing
1823         nextState i = Just (i, i `div` 2)
1824     in  unfoldr nextState 30
1825         
1826 produces
1827
1828     [30, 15, 7, 3, 1]
1829 """
1830 @inline
1831 unfoldr :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
1832 unfoldr f s = build (\empty cons -> do
1833     loop s cur =
1834         match f s with
1835             Just (el,newS) -> loop newS (cons cur el)
1836             _ -> cur
1837     loop s empty)
1838
1839 importJava "org.simantics.scl.runtime.Lists" where
1840     /*
1841     @private
1842     @JavaName map
1843     mapList :: (a -> b) -> [a] -> [b]    
1844     @private
1845     @JavaName map
1846     mapEList :: (a -> <e> b) -> [a] -> <e> [b]
1847     @private
1848     @JavaName iter
1849     iterList :: (a -> <e> ()) -> [a] -> <e> ()
1850     concatMap :: (a -> <e> [b]) -> [a] -> <e> [b]
1851     */ 
1852     """
1853     Combines two lists into one list of pairs. The length of the resulting list is the length of the smallest input list.
1854     
1855         zip [1, 2, 3, 4, 5] ['a', 'b', 'c'] = [(1, 'a'), (2, 'b'), (3, 'c')]
1856     """
1857     zip :: [a] -> [b] -> [(a,b)]
1858     "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."
1859     zipWith :: (a -> b -> <e> c) -> [a] -> [b] -> <e> [c]
1860     """
1861     Produces two lists from one list of pairs.
1862     
1863         unzip [(1, 'a'), (2, 'b'), (3, 'c')] = ([1, 2, 3], ['a', 'b', 'c'])
1864     """
1865     unzip :: [(a,b)] -> ([a],[b])
1866     
1867     //"@filter p l@ returns those elements of @l@ that the predicate @p@ accepts." 
1868     //filter :: (a -> <e> Boolean) -> [a] -> <e> [a]
1869     //filterJust :: [Maybe a] -> [a]
1870     /*
1871     foldl :: (a -> b -> <e> a) -> a -> [b] -> <e> a
1872     */
1873     "Like `foldl` but assumes that the list is non-empty so the initial is not needed."
1874     foldl1 :: (a -> a -> <e> a) -> [a] -> <e> a
1875     //unfoldr :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
1876     
1877     "Sorts the list using the given comparator."
1878     sortWith :: (a -> a -> <e> Integer) -> [a] -> <e> [a]
1879     "Works like `index` but uses the given functions as hash codes and equality."
1880     indexWith :: (a -> Integer) -> (a -> a -> Boolean) -> [(a,b)] -> a -> Maybe b
1881     groupWith :: (b -> Integer) -> (b -> b -> Boolean) -> (a -> <e> b) -> (a -> <e> c) -> [a] -> <e> [(b, [c])]
1882     "Works like `unique` but uses the given function for equality tests."
1883     uniqueWith :: (a -> a -> Boolean) -> [a] -> [a]
1884     "Works like `\\\\` but uses the given function for equality tests."
1885     deleteAllBy :: (a -> a -> Boolean) -> [a] -> [a] -> [a]
1886     
1887     //range :: Integer -> Integer -> [Integer]
1888     
1889     //build :: (forall a. a -> (a -> b -> <e> a) -> <e> a) -> <e> [b]
1890
1891 "`elem el lst` return true, if `el` occurs in the list `lst`."
1892 elem :: a -> [a] -> Boolean
1893 elem el l = loop 0
1894   where
1895     len = length l
1896     loop i | i < len = if el == l!i
1897                        then True
1898                        else loop (i+1)
1899            | otherwise = False
1900
1901 "`elemMaybe v1 (Just v2)` returns true if `v1 == v2`. `elemMaybe v1 Nothing` is always false."
1902 elemMaybe :: a -> Maybe a -> Boolean
1903 elemMaybe el m = match m with
1904     Just el2 -> el == el2
1905     Nothing -> False
1906
1907 """
1908 Computes a list that contains only elements that belongs to both input lists.
1909 """
1910 intersect :: [a] -> [a] -> [a]
1911 intersect a b = filter f a
1912   where
1913     f e = elem e b
1914
1915 "Reverses a given list. For example, `reverse [1,2,3] = [3,2,1]`"
1916 reverse :: [a] -> [a]
1917 reverse l = [l!(len-i) | i <- [1..len]]
1918   where
1919     len = length l
1920
1921 """
1922 Transposes the rows and columns of its argument. For example,
1923
1924     transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]]
1925     transpose [[1,2],[3,4,5]] == [[1,3],[2,4],[5]]
1926 """
1927 transpose xss = [[xs!i | xs <- xss, i < length xs]
1928                 | i <- [0..maximum [length xs | xs <- xss]-1]]
1929
1930 "Works like `unfoldr` but generates the list from right to left."
1931 unfoldl :: (b -> <e> Maybe (a, b)) -> b -> <e> [a]
1932 unfoldl f seed = reverse $ unfoldr f seed
1933
1934 "Removes the first element of the list, if the list is non-empty."
1935 tail :: [a] -> [a]
1936 tail l = if len < 2 then emptyList else subList l 1 len 
1937   where 
1938     len = length l
1939
1940 "Tries to find the given key from the list of key-value pairs and returns the corresponding value."
1941 lookup ::  a -> [(a, b)] -> Maybe b
1942 lookup el l = do
1943     len = length l
1944     loop i = if i < len 
1945              then match l!i with
1946                (a,b) | a == el   -> Just b
1947                      | otherwise -> loop (i+1)
1948              else Nothing
1949     loop 0
1950
1951 "Conjunction over a list."
1952 @inline
1953 and :: [Boolean] -> Boolean
1954 and = foldl (&&) True
1955
1956 "Disjunction over a list."
1957 @inline
1958 or :: [Boolean] -> Boolean
1959 or  = foldl (||) False
1960
1961 """
1962 `any pred lst` tests whether the predicate `pred` holds some element of `lst`.
1963 It returns immediately when it encounters the first value satisfying the predicate.
1964 """ 
1965 any :: (a -> <e> Boolean) -> [a] -> <e> Boolean
1966 any p =  or . map p
1967
1968 """
1969 `all pred lst` tests whether the predicate `pred` holds for all elements of `lst`.
1970 It returns immediately when it encounters the first value not satisfying the predicate.
1971 """ 
1972 all :: (a -> <e> Boolean) -> [a] -> <e> Boolean
1973 all p =  and . map p
1974
1975 """
1976 Returns the first element of the list satisfying the given condition,
1977 or `Nothing` if there is no such element.
1978 """
1979 findFirst :: (a -> <e> Boolean) -> [a] -> <e> Maybe a
1980 findFirst p l = loop 0
1981   where
1982     len = length l
1983     loop i = if i < len 
1984              then let el = l!i in 
1985                   if p el 
1986                   then Just el 
1987                   else loop (i+1)
1988              else Nothing
1989     loop 0
1990
1991
1992 """
1993 Sorts the given list using its default order.
1994 """
1995 @inline
1996 sort :: Ord a => [a] -> [a]
1997 sort = sortWith compare
1998
1999 """
2000 Sorts the lists by the values computed by the first function.
2001 For example
2002
2003     sortBy snd [(1,5), (2,3), (3,4)] = [(2,3), (3,4), (1,5)] 
2004 """
2005 @inline
2006 sortBy :: Ord b => (a -> <e> b) -> [a] -> <e> [a]
2007 sortBy f l = sortWith (\x y -> compare (f x) (f y)) l
2008 // This is faster if f is slow, but will generate more auxiliary structures
2009 //sortBy f l = map snd (sortWith (\(x,_) (y,_) -> compare x y) [(f x, x) | x <- l])
2010
2011 """
2012 Given a list of key-value pairs, the function produces a function that finds a value
2013 efficiently for the given key.
2014 """
2015 index :: [(a,b)] -> a -> Maybe b
2016 index = indexWith hashCode (==)
2017
2018 """
2019 Given a list of values and a function computing a key for each value, the function produces a function that finds a value
2020 effeciently for the given key.
2021 """
2022 indexBy ::  (a -> b) -> [a] -> b -> Maybe a
2023 indexBy f l = index [(f x, x) | x <- l]
2024
2025 "Groups a list values by a key computed by the given function."
2026 groupBy :: (a -> <e> b) -> [a] -> <e> [(b, [a])]
2027 groupBy f l = groupWith hashCode (==) f id l
2028
2029 "Groups a list of key-value pairs by the keys."
2030 group :: [(a,b)] -> [(a, [b])]
2031 group = groupWith hashCode (==) fst snd
2032
2033 "Removes duplicates (all but the first occurrence) from the list but otherwise preserves the order of the elements."
2034 unique ::  [a] -> [a]
2035 unique = uniqueWith (==)
2036
2037 "Like `unique`, but uses the given function for finding the key values used for uniqueness testing."
2038 uniqueBy :: (a -> b) -> [a] -> [a]
2039 uniqueBy f = uniqueWith (\a b -> f a == f b)
2040
2041 //sortAndUniqueBy :: Ord b => (a -> b) -> [a] -> [a]
2042 //sortAndUniqueBy f = map snd . uniqueWith (\a b -> fst a == fst b) . sortBy fst . map (\x -> (f x, x))
2043
2044 "`a \\\\ b` removes all elements of `b` from the list `a`."
2045 (\\) :: [a] -> [a] -> [a]
2046 (\\) = deleteAllBy (==)
2047
2048 /// Dynamic ///
2049
2050 importJava "java.lang.Object" where
2051     "A data type that can represent any value."
2052     data Dynamic
2053     
2054     @private
2055     @JavaName toString
2056     showDynamic :: Dynamic -> String
2057
2058 instance Show Dynamic where
2059     show = showDynamic
2060
2061 "Converts a value to `Dynamic` type."
2062 toDynamic :: a -> Dynamic
2063 toDynamic = Java.unsafeCoerce
2064
2065 "Converts a `Dynamic` value to a required value, or fails if the conversion is not possible."
2066 importJava "org.simantics.scl.compiler.runtime.ValueConversion" where
2067     fromDynamic :: Typeable a => Dynamic -> a
2068
2069 /// Procedures ///
2070
2071 importJava "org.simantics.scl.runtime.procedure.Ref" where
2072     "A mutable reference to a value of type `a`."
2073     data Ref a
2074     
2075     "Creates a new reference with the given initial value."
2076     @JavaName "<init>"
2077     ref :: a -> <Proc> (Ref a)
2078     
2079     "Returns the current value of the reference."
2080     @JavaName "value"
2081     getRef :: Ref a -> <Proc> a
2082     
2083     "Sets a new value for the reference."
2084     @JavaName "<set>value"
2085     (:=) :: Ref a -> a -> <Proc> ()
2086
2087 instance Show (Ref a) where
2088     show _ = "<reference>"
2089
2090 importJava "org.simantics.scl.runtime.reporting.SCLReporting" where
2091     "Prints the given string to the console."
2092     @JavaName "print"
2093     printString :: String -> <Proc> ()
2094     "Prints an error message to the console."
2095     printError :: String -> <Proc> ()
2096     "Reports that certain amount of work has been done for the current task."
2097     didWork :: Double -> <Proc> ()
2098     """
2099     `printingToFile "fileName" expression` executes the `expression` so that all its console prints
2100     are written to the file given as a first parameter.
2101     """
2102     printingToFile :: String -> (<e> a) -> <e> a
2103     """
2104     `printErrorsAsNormalPrints expression` executes the `expression` so that all its error prints
2105     are printed as normal prints. This is useful mainly in testing scripts for checking that the implementations
2106     give proper error messages with invalid inputs.
2107     """
2108     printErrorsAsNormalPrints :: (<e> a) -> <e> a
2109     """
2110     `disablePrintingForCommand expression` executes the `expression` so that it does not print return values.
2111     Errors are printed normally.
2112     """
2113     disablePrintingForCommand :: (<e> a) -> <e> a
2114     
2115
2116 importJava "org.simantics.scl.runtime.procedure.Procedures" where
2117     "Returns `True` if the current thread has been interrupted."
2118     isInterrupted :: <Proc> Boolean
2119     "Checks whether the current thread has been interrupted and throws an exception if it is."
2120     checkInterrupted :: <Proc> ()
2121     "Generates a random identifier."
2122     generateUID :: <Proc> String
2123     
2124     "Executes the given expression and catches certain class of exceptions (specified by the catch handler that is given as a second parameter.)"
2125     @JavaName catch_
2126     catch :: VecComp ex => (<e,Exception> a) -> (ex -> <e> a) -> <e> a
2127
2128 importJava "java.lang.Throwable" where
2129     data Throwable
2130     @private
2131     @JavaName toString
2132     showThrowable :: Throwable -> String
2133 importJava "java.lang.Exception" where
2134     data Exception
2135     @private
2136     @JavaName toString
2137     showException :: Exception -> String
2138
2139 instance Show Throwable where
2140     show = showThrowable
2141 instance Show Exception where
2142     show = showException
2143
2144 "Prints the given value in the console."
2145 @inline
2146 print :: Show a => a -> <Proc> ()
2147 print v = printString (showForPrinting v)
2148 /*
2149 instance Show TypeRep where
2150     sb <+ (TApply (TCon "Builtin" "[]") b) = 
2151         sb << "[" <+ b << "]"
2152     sb <+ (TApply (TApply (TCon "Builtin" "(,)") c1) c2) = 
2153         sb << "(" <+ c1 << "," <+ c2 << ")"
2154     sb <+ (TApply (TApply (TApply (TCon "Builtin" "(,,)") c1) c2) c3) = 
2155         sb << "(" <+ c1 << "," <+ c2 << "," <+ c3 << ")"
2156     sb <+ (TApply (TApply (TApply (TApply (TCon "Builtin" "(,,,)") c1) c2) c3) c4) =
2157         sb << "(" <+ c1 << "," <+ c2 << "," <+ c3 << "," <+ c4 << ")" 
2158     
2159     sb <+ (TCon _ name) = sb << name
2160     sb <+ (TApply a b) = sb <+ Par 1 a << " " <+ Par 2 b
2161     sb <+ (TFun a b) = sb <+ Par 1 a << " -> " <+ b
2162     
2163     precedence (TCon _ _) = 0
2164     precedence (TFun _ _) = 2
2165     precedence (TApply a _) = if isSpecialType a then 0 else 1
2166       where
2167         isSpecialType (TCon "Builtin" "[]") = True
2168         isSpecialType (TCon "Builtin" "()") = True
2169         isSpecialType (TCon "Builtin" "(,)") = True
2170         isSpecialType (TCon "Builtin" "(,,)") = True
2171         isSpecialType (TCon "Builtin" "(,,,)") = True
2172         isSpecialType (TApply a _) = isSpecialType a
2173 */
2174
2175 // ByteArray
2176
2177 importJava "java.util.Arrays" where
2178     @private
2179     @JavaName toString
2180     byteArrayToString :: ByteArray -> String
2181
2182 instance Show ByteArray where
2183     show = byteArrayToString
2184
2185 // Type
2186
2187 @private
2188 importJava "org.simantics.scl.compiler.types.Type" where
2189     @JavaName toString
2190     showType :: Type -> String
2191
2192 importJava "org.simantics.scl.compiler.types.Types" where
2193     removeForAll :: Type -> Type
2194     
2195 instance Show Type where
2196     show = showType