Compilerbau: Codeerzeugung |
|
1module PPL.Instructions where
2
3type Code = [Instr]
4
5data Instr
6 = LoadI Int -- load int const
7 | LoadF Double -- load float const
8 | LoadS String -- load string const
9 | LoadU -- load undefined value
10 | LoadEL -- load empty list
11 | Load Address -- read data memory
12 | Store Address -- write data memory
13 | Pop -- remove arg from stack
14 | Dup -- duplicate top of stack
15 | Compute Opcode -- evaluate something
16 | SysCall Subroutine -- system call (svc)
17 | PushJ Dest -- subroutine call
18 | PopJ -- computed jump (subroutine return)
19 | Entry Int -- allocate stack frame
20 | Exit -- delete stack frame
21 | Branch Bool Dest -- gotos and branches
22 | Jump Dest
23 | Label Label -- symbolic jump target
24 | IllegalInstr String -- not yet implemented
25 deriving (Eq, Show)
26
27data Address
28 = LocA Int -- local address
29 | AbsA Int -- global address
30 deriving (Eq, Show)
31
32data Dest
33 = Symb Label
34 | Disp Int
35 deriving (Eq, Show)
36
37data Opcode
38 = OPabort
39 | OPabove
40 | OPaddf
41 | OPaddi
42 | OPappendl
43 | OPbitmap
44 | OPblack
45 | OPblackAndWhite
46 | OPconcatHorizontal
47 | OPconcatVertical
48 | OPconcl
49 | OPconcs
50 | OPcut
51 | OPdecri
52 | OPdiff
53 | OPdivf
54 | OPdivi
55 | OPeqf
56 | OPeqi
57 | OPf2s
58 | OPflipDiagonal
59 | OPflipHorizontal
60 | OPflipVertical
61 | OPgamma
62 | OPgef
63 | OPgei
64 | OPgrey
65 | OPgtf
66 | OPgti
67 | OPheight
68 | OPi2f
69 | OPi2s
70 | OPincri
71 | OPindexl
72 | OPinverseDiff
73 | OPinverseMean
74 | OPinvert
75 | OPisemptyl
76 | OPlengthl
77 | OPmaxf
78 | OPmaxi
79 | OPmaxp
80 | OPmean
81 | OPmergeHorizontal
82 | OPmergeVertical
83 | OPminf
84 | OPmini
85 | OPminp
86 | OPmodi
87 | OPmulf
88 | OPmuli
89 | OPmulp
90 | OPpartitionHorizontal
91 | OPpartitionVertical
92 | OPpaste
93 | OPconsl
94 | OPreduceColor
95 | OPreplicate
96 | OPresize
97 | OProtate
98 | OPround
99 | OPscale
100 | OPshift
101 | OPshrink
102 | OPsideBySide
103 | OPsplitHorizontal
104 | OPsplitVertical
105 | OPsubf
106 | OPsubi
107 | OPtaill
108 | OPterminate
109 | OPtrunc
110 | OPwhite
111 | OPwidth
112 deriving (Eq, Show)
113
114type Arg = String
115type Comment = String
116type Label = String
117type Subroutine = String
118
119type DataSeg = Int
120
121type Executable = (Code, DataSeg)
|
1begin
2 var
3 i, j, k : int
4 := 1, 2, 3;
5
6 -- simple integer arithmetic example
7
8 i := -i + j -1 + j * k div (i mod 3)
9end
10
|
1---"sequence" (VoidType)
2 |
3 +---"begin" (VoidType)
4 |
5 +---"sequence" (VoidType)
6 |
7 +---"decl" (VoidType)
8 | |
9 | +---"id" i (IntType)
10 |
11 +---"decl" (VoidType)
12 | |
13 | +---"id" j (IntType)
14 |
15 +---"decl" (VoidType)
16 | |
17 | +---"id" k (IntType)
18 |
19 +---":=" (VoidType)
20 | |
21 | +---"id" i (IntType)
22 | |
23 | +---"id" j (IntType)
24 | |
25 | +---"id" k (IntType)
26 | |
27 | +---1 (IntType)
28 | |
29 | +---2 (IntType)
30 | |
31 | +---3 (IntType)
32 |
33 +---":=" (VoidType)
34 | |
35 | +---"id" i (IntType)
36 | |
37 | +---"addi" (IntType)
38 | |
39 | +---"subi" (IntType)
40 | | |
41 | | +---"addi" (IntType)
42 | | | |
43 | | | +---"negi" (IntType)
44 | | | | |
45 | | | | +---"id" i (IntType)
46 | | | |
47 | | | +---"id" j (IntType)
48 | | |
49 | | +---1 (IntType)
50 | |
51 | +---"divi" (IntType)
52 | |
53 | +---"muli" (IntType)
54 | | |
55 | | +---"id" j (IntType)
56 | | |
57 | | +---"id" k (IntType)
58 | |
59 | +---"modi" (IntType)
60 | |
61 | +---"id" i (IntType)
62 | |
63 | +---3 (IntType)
64 |
65 +---":=" (VoidType)
66 | |
67 | +---"id" i (IntType)
68 | |
69 | +---UndefVal (IntType)
70 |
71 +---":=" (VoidType)
72 | |
73 | +---"id" j (IntType)
74 | |
75 | +---UndefVal (IntType)
76 |
77 +---":=" (VoidType)
78 |
79 +---"id" k (IntType)
80 |
81 +---UndefVal (IntType)
|
1.text
2 loadi 1
3 loadi 2
4 loadi 3
5 store m[2]
6 store m[1]
7 store m[0]
8 loadi 0
9 load m[0]
10 subi
11 load m[1]
12 addi
13 loadi 1
14 subi
15 load m[1]
16 load m[2]
17 muli
18 load m[0]
19 loadi 3
20 modi
21 divi
22 addi
23 store m[0]
24 undef
25 store m[0]
26 undef
27 store m[1]
28 undef
29 store m[2]
30 terminate
31
32.data 3
|
|
1{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
2
3module PPL.CodeGeneration where
4
5import PPL.AbstractSyntax
6import PPL.Instructions
7import PPL.GlobalState
8
9import Data.Maybe
10
11-- -------------------------------------------------------------------
12-- label generation
13
14initLabel :: GS ()
15initLabel = updateState "newlabel" (LabCnt 0)
16
17newLabel :: GS Label
18newLabel
19 = do
20 LabCnt l <- lookupState "newlabel"
21 updateState "newlabel" (LabCnt (l+1))
22 return ("l" ++ show l)
23
24-- -------------------------------------------------------------------
25-- variable allocation
26
27setAllocator :: Alloc -> GS ()
28setAllocator a
29 = updateState "alloc" (Allocator a)
30
31getAllocator :: GS Alloc
32getAllocator
33 = do
34 Allocator a <- lookupState "alloc"
35 return a
36
37initAddr :: GS ()
38initAddr
39 = do
40 updateState "maxaddr" (AddrCnt 0)
41 setAddrCnt 0
42
43newAddr :: GS Int
44newAddr
45 = do
46 a <- getAddrCnt
47 setAddrCnt (a + 1)
48 return a
49
50setAddrCnt :: Int -> GS ()
51setAddrCnt a
52 = do
53 updateState "newaddr" (AddrCnt a)
54 m <- getDataSegLen
55 updateState "maxaddr" (AddrCnt (a `max` m))
56
57getDataSegLen :: GS Int
58getDataSegLen
59 = do
60 AddrCnt a <- lookupState "maxaddr"
61 return a
62
63getAddrCnt :: GS Int
64getAddrCnt
65 = do
66 AddrCnt a <- lookupState "newaddr"
67 return a
68
69initAddrList :: GS ()
70initAddrList
71 = do
72 setAddrList []
73
74getAddrList :: GS AddrList
75getAddrList
76 = do
77 AddrList al <- lookupState "addrlist"
78 return al
79
80setAddrList :: AddrList -> GS ()
81setAddrList al
82 = updateState "addrlist" (AddrList al)
83
84getAddr :: String -> GS Address
85getAddr var
86 = do
87 al <- getAddrList
88 return (maybe (AbsA 0) id (lookup var al))
89
90allocVar :: String -> GS ()
91allocVar id'
92 = do
93 al <- getAddrList
94 addr <- allocCell
95 setAddrList ((id', addr):al)
96
97allocCell :: GS Address
98allocCell
99 = do
100 a <- newAddr
101 alloc <- getAllocator
102 return (alloc a)
103
104-- -------------------------------------------------------------------
105
106codegeneration :: AttrTree -> Executable
107codegeneration = snd . compProg
108
109compProg :: AttrTree -> (State, Executable)
110compProg p
111 = let
112 GS compile = compProg' p
113 in
114 compile initialState
115
116compProg' :: AttrTree -> GS Executable
117compProg' p
118 = do
119 initLabel
120 initAddr
121 initAddrList
122 is <- compProg'' p
123 ds <- getDataSegLen
124 return (is, ds)
125
126compProg'' :: AttrTree -> GS Code
127compProg'' (Opr "sequence" (body : decll), _)
128 = do
129 -- allocate global variables
130 initAddr
131 setAllocator AbsA
132 sequence_ (map compGlobDecl (filter isGlobDecl decll))
133
134 -- code for global variable init
135 initCode <- sequence (map compExpr (filter isGlobInit decll))
136 -- code for main program
137 bodyCode <- compExpr body
138 len <- getDataSegLen
139
140 -- code for functions
141 fctCode <- sequence (map compExpr (filter isGlobFct decll))
142
143 -- restore global data segement length
144 initAddr
145 setAddrCnt len
146 setAllocator AbsA
147
148 return ( concat initCode
149 ++
150 bodyCode
151 ++
152 [ Compute OPterminate ]
153 ++
154 concat fctCode
155 )
156
157
158compGlobDecl :: AttrTree -> GS ()
159compGlobDecl (Opr _ [(Ident id', _t)], _)
160 = do
161 allocVar id'
162 return ()
163
164isGlobDecl :: AttrTree -> Bool
165isGlobInit :: AttrTree -> Bool
166isGlobFct :: AttrTree -> Bool
167
168isGlobDecl (Opr "decl" _, _) = True
169isGlobDecl _ = False
170
171isGlobInit (Opr ":=" _, _) = True
172isGlobInit _ = False
173
174isGlobFct (Opr "fctdecl" _, _) = True
175isGlobFct _ = False
176
177-- -------------------------------------------------------------------
178-- compile statements
179
180compExpr :: AttrTree -> GS Code
181
182compExpr (Opr "fctdecl" ((Ident id', _) : body : fpl), rt)
183 = do
184 -- initialize counter for local data segment
185 initAddr
186 setAllocator LocA
187 -- allocate cell for return address
188 retAddr <- allocCell
189 -- allocate parameter and gen code
190 -- to initialize them
191 paramCode <- sequence (map compStoreParam (reverse fpl))
192
193 -- compile function body
194 bodyCode <- compExpr body
195 -- get size of local data segment
196 len <- getDataSegLen
197 -- combine entry code
198 -- parameter saving code
199 -- function body code
200 -- and exit code
201 return ( [ Label ("_" ++ id')
202
203 , Entry len -- allocate local data segment
204 -- save return address
205 , Store retAddr
206 -- mark start of fct body
207 , Label ("s_" ++ id')
208 ]
209 ++
210 concat paramCode
211 ++
212 bodyCode
213 ++
214 ( if rt == VoidType
215 then [ LoadU ]
216 else []
217 )
218 ++
219 -- mark end of body
220 [ Label ("e_" ++ id')
221 -- load return address
222 , Load retAddr
223 -- deallocate local data segement
224 , Exit
225 -- jump back to calling point
226 , PopJ
227 ]
228 )
229
230
231compExpr (Opr "begin" [e], _)
232 = do
233 addrCnt <- getAddrCnt
234 addrList <- getAddrList
235 code <- compExpr e
236 setAddrList addrList
237 setAddrCnt addrCnt
238 return code
239
240compExpr (Opr "decl" [(Ident id', _t)], _)
241 = do
242 allocVar id'
243 return []
244
245compExpr (Opr "sequence" sl, _)
246 = do
247 sl1 <- sequence (map compExpr sl)
248 return (concat sl1)
249
250compExpr (Opr "while" [cond, body], _)
251 = do
252 l1 <- newLabel
253 l2 <- newLabel
254 codeBody <- compExpr body
255 codeCond <- compBranch l2 True cond
256 return ( [ Jump (Symb l1) ]
257 ++
258 [ Label l2 ]
259 ++
260 codeBody
261 ++
262 [ Label l1 ]
263 ++
264 codeCond
265 )
266
267compExpr (Opr "repeat" [body, cond], _)
268 = do
269 l1 <- newLabel
270 codeBody <- compExpr body
271 codeCond <- compBranch l1 False cond
272 return ( [ Label l1 ]
273 ++
274 codeBody
275 ++
276 codeCond
277 )
278
279compExpr (Opr "if" [cond, thenp, elsep], _)
280 = do
281 l1 <- newLabel
282 l2 <- newLabel
283 codeCond <- compBranch l1 False cond
284 codeThenp <- compExpr thenp
285 codeElsep <- compExpr elsep
286 if length codeElsep == 0
287 then
288 return ( codeCond
289 ++ codeThenp
290 ++ [ Label l1 ]
291 )
292 else
293 return ( codeCond
294 ++ codeThenp
295 ++ [ Jump (Symb l2) ]
296 ++ [ Label l1 ]
297 ++ codeElsep
298 ++ [ Label l2 ]
299 )
300
301compExpr (Opr ":=" asl, _)
302 = do
303 let l = length asl `div` 2
304 let vl = take l asl
305 let el = drop l asl
306 codeRHS <- sequence (map compExpr el)
307 codeLHS <- sequence (map compStore (reverse vl))
308 return (concat codeRHS ++ concat codeLHS)
309
310compExpr (Opr "do" [e], _)
311 = do
312 c <- compExpr e
313 return (c ++ [Pop])
314
315-- -------------------------------------------------------------------
316-- transform non strict boolean operators
317
318 -- a and b -> if a then b else false
319
320compExpr (Opr "and" [e1,e2], t)
321 = compExpr (Opr "if" [e1, e2, boolConstFalse], t)
322
323 -- a or b -> if a then true else b
324
325compExpr (Opr "or" [e1,e2], t)
326 = compExpr (Opr "if" [e1, boolConstTrue, e2], t)
327
328 -- a => b -> if a then b else true
329
330compExpr (Opr "impl" [e1,e2], t)
331 = compExpr (Opr "if" [e1, e2, boolConstTrue], t)
332
333 -- eliminate xor ops
334
335compExpr (Opr "xor" el, t)
336 = compExpr (Opr "not" el', t)
337 where
338 el' = [(Opr "equiv" el, t)]
339
340 -- map equivalence to integer =
341compExpr (Opr "equiv" el, _t)
342 = compExpr (Opr "eqi" el, IntType)
343
344 -- not a -> 1 - a
345
346compExpr (Opr "not" [e], _t)
347 = compExpr (Opr "subi" [intConst1, e], IntType)
348
349
350compExpr (Opr "b2s" [e], BoolType)
351 = compExpr (Opr "if" [ e
352 , stringConstTrue
353 , stringConstFalse
354 ]
355 , StringType
356 )
357
358-- -------------------------------------------------------------------
359 -- unary + elimination
360compExpr (Opr "ident" [e], _)
361 = compExpr e
362
363 -- unary - partial evaluation
364
365compExpr (Opr "negi" [(IntVal i, _)], t)
366 = compExpr (IntVal (0 - i), t)
367
368compExpr (Opr "negf" [(FloatVal f, _)], t)
369 = compExpr (FloatVal (0.0 - f), t)
370
371 -- -a -> 0 - a
372
373compExpr (Opr "negi" [e], t)
374 = compExpr (Opr "subi" [intConst0, e], t)
375
376compExpr (Opr "negf" [e], t)
377 = compExpr (Opr "subf" [floatConst0, e], t)
378
379 -- eliminate /= ops
380
381compExpr (Opr op el, t)
382 | isNeOp op
383 = compExpr (Opr "not" el', t)
384 where
385 el' = [(Opr (getComplOp op) el, t)]
386
387 -- use arg types for rel ops translation
388
389compExpr (Opr op el, BoolType)
390 | isRelOp op
391 = compExpr (Opr op el, t1)
392 where
393 (_,t1):_ = el
394
395
396 -- "a < b" -> "b > a", "a <= b" -> "b >= a"
397
398compExpr (Opr op [e1,e2], t)
399 | isSymOp op
400 = compExpr (Opr (symOp op) [e2,e1], t)
401
402
403-- -------------------------------------------------------------------
404-- transform list ops
405
406compExpr (Opr "headl" [e], t)
407 = compExpr (Opr "indexl" [e, (IntVal 0, IntType)], t)
408
409-- -------------------------------------------------------------------
410-- compile constants and variables
411
412compExpr (BoolVal b, _)
413 = return [ LoadI (fromEnum b)]
414
415compExpr (IntVal i, _)
416 = return [ LoadI i]
417
418compExpr (FloatVal f, _)
419 = return [ LoadF f]
420
421compExpr (StringVal s, _)
422 = return [ LoadS s]
423
424compExpr (EmptyList , _)
425 = return [ LoadEL ]
426
427compExpr (UndefVal , _)
428 = return [ LoadU ]
429
430compExpr (Ident id', _)
431 = do
432 a <- getAddr id'
433 return [ Load a ]
434
435-- -------------------------------------------------------------------
436
437-- compile build in operations
438
439compExpr (Opr op al, _t)
440 | op `elem` svcFcts
441 = do
442 codeArgl <- sequence (map compExpr al)
443 return ( concat codeArgl
444 ++
445 [SysCall op]
446 )
447
448compExpr (Opr "definedfct" ((StringVal fn, _):al), _t)
449 = do
450 codeArgl <- sequence (map compExpr al)
451 return ( concat codeArgl
452 ++
453 [PushJ (Symb ("_" ++ fn))]
454 )
455
456compExpr (Opr op al, _t)
457 = do
458 codeArgl <- sequence (map compExpr al)
459 return ( concat codeArgl
460 ++
461 [ Compute (fromJust (lookup op opr2Opcode)) ]
462 )
463
464-- -------------------------------------------------------------------
465
466-- default: error or not yet implemented
467
468compExpr e
469 = return [IllegalInstr (show e)]
470
471-- -------------------------------------------------------------------
472
473undefValue :: AttrTree
474intConst0 :: AttrTree
475intConst1 :: AttrTree
476floatConst0 :: AttrTree
477boolConstTrue :: AttrTree
478boolConstFalse :: AttrTree
479stringConstTrue :: AttrTree
480stringConstFalse:: AttrTree
481whiteValue :: AttrTree
482blackValue :: AttrTree
483
484undefValue = (UndefVal, UnknownType)
485intConst0 = (IntVal 0, IntType)
486intConst1 = (IntVal 1, IntType)
487floatConst0 = (FloatVal 0.0, FloatType)
488boolConstTrue = (BoolVal True, BoolType)
489boolConstFalse = (BoolVal False, BoolType)
490stringConstTrue = (StringVal "true", StringType)
491stringConstFalse= (StringVal "false", StringType)
492whiteValue = (FloatVal 1.0, FloatType)
493blackValue = (FloatVal 0.0, FloatType)
494
495appendNl :: AttrTree -> AttrTree
496appendNl e
497 = (Opr "+" [e, (StringVal "\n", StringType)], StringType)
498
499-- -------------------------------------------------------------------
500
501-- opcode tables
502
503complOps :: [(String, String)]
504complOps
505 = [ ("nei", "eqi")
506 , ("nef", "eqf")
507 , ("nes", "eqs")
508 ]
509
510symOps :: [(String, String)]
511symOps
512 = [ ("lti", "gti")
513 , ("ltf", "gtf")
514 , ("lei", "gei")
515 , ("lef", "gef")
516 ]
517
518isOp :: [(String, String)] -> String -> Bool
519isOp ops op
520 = op `elem` (map fst ops)
521
522getOp :: [(String, String)] -> String -> String
523getOp table op
524 = let
525 Just opcode = lookup op table
526 in opcode
527
528isNeOp :: String -> Bool
529isSymOp :: String -> Bool
530
531isNeOp = isOp complOps
532isSymOp = isOp symOps
533
534getComplOp :: String -> String
535symOp :: String -> String
536
537getComplOp = getOp complOps
538symOp = getOp symOps
539
540isRelOp :: String -> Bool
541isRelOp op
542 = op `elem` ["eqi", "eqf", "eqs"
543 ,"gei", "gef", "ges"
544 ,"gti", "gtf", "gts"
545 ]
546
547svcFcts :: [String]
548svcFcts
549 = [ "write"
550 , "writeln"
551 , "getArgs"
552 , "dump"
553 , "load"
554 , "store"
555 ]
556
557-- -------------------------------------------------------------------
558-- compile store
559
560compStore :: AttrTree -> GS Code
561compStore (Ident id', _)
562 = do
563 a <- getAddr id'
564 return [ Store a ]
565
566compStoreParam :: AttrTree -> GS Code
567compStoreParam (Opr "decl" [var@(Ident id', _t)], _)
568 = do
569 allocVar id'
570 compStore var
571
572-- -------------------------------------------------------------------
573-- compile branches
574
575compBranch :: Label -> Bool -> AttrTree -> GS Code
576
577compBranch lab cond (BoolVal b, _)
578 | cond == b
579 = return [Jump (Symb lab)]
580 | otherwise
581 = return []
582
583compBranch lab cond (Opr "not" [e1], _)
584 = compBranch lab (not cond) e1
585
586compBranch lab cond (Opr "and" [e1,e2], _)
587 = if cond
588 then
589 do
590 lab1 <- newLabel
591 cond1 <- compBranch lab1 (not cond) e1
592 cond2 <- compBranch lab cond e2
593 return ( cond1
594 ++
595 cond2
596 ++
597 [ Label lab1 ]
598 )
599 else
600 do
601 cond1 <- compBranch lab cond e1
602 cond2 <- compBranch lab cond e2
603 return ( cond1
604 ++
605 cond2
606 )
607
608 -- apply de Morgan
609
610compBranch lab cond (Opr "or" [e1,e2], _)
611 = compBranch lab (not cond) (Opr "and" el, BoolType)
612 where
613 el = [ (Opr "not" [e1], BoolType)
614 , (Opr "not" [e2], BoolType)
615 ]
616
617 -- apply de Morgan
618
619compBranch lab cond (Opr "impl" [e1,e2], _)
620 = compBranch lab (not cond) (Opr "and" el, BoolType)
621 where
622 el = [ e1
623 , (Opr "not" [e2], BoolType)
624 ]
625
626 -- eliminate xor ops
627
628compBranch lab cond (Opr "xor" el, _)
629 = compBranch lab (not cond) (Opr "equiv" el, BoolType)
630
631 -- eliminate /= ops
632
633compBranch lab cond (Opr op el, _)
634 | isNeOp op
635 = compBranch lab (not cond) (Opr (getComplOp op) el, BoolType)
636
637compBranch lab cond expr
638 = do
639 is <- compExpr expr
640 return ( is
641 ++
642 [Branch cond (Symb lab)]
643 )
644
645-- --------------------
646--
647-- mapping of node labels to ppl opcodes
648
649opr2Opcode :: [(String, Opcode)]
650opr2Opcode
651 = [ ("abort", OPabort)
652 , ("above", OPabove)
653 , ("addf", OPaddf)
654 , ("addi", OPaddi)
655 , ("appendl", OPappendl)
656 , ("bitmap", OPbitmap)
657 , ("black", OPblack)
658 , ("blackAndWhite", OPblackAndWhite)
659 , ("concatHorizontal", OPconcatHorizontal)
660 , ("concatVertical", OPconcatVertical)
661 , ("concl", OPconcl)
662 , ("concs", OPconcs)
663 , ("cut", OPcut)
664 , ("diff", OPdiff)
665 , ("divf", OPdivf)
666 , ("divi", OPdivi)
667 , ("eqf", OPeqf)
668 , ("eqi", OPeqi)
669 , ("exit", OPterminate)
670 , ("f2s", OPf2s)
671 , ("flipDiagonal", OPflipDiagonal)
672 , ("flipHorizontal", OPflipHorizontal)
673 , ("flipVertical", OPflipVertical)
674 , ("gamma", OPgamma)
675 , ("gef", OPgef)
676 , ("gei", OPgei)
677 , ("grey", OPgrey)
678 , ("gtf", OPgtf)
679 , ("gti", OPgti)
680 , ("height", OPheight)
681 , ("i2f", OPi2f)
682 , ("i2s", OPi2s)
683 , ("indexl", OPindexl)
684 , ("inverseDiff", OPinverseDiff)
685 , ("inverseMean", OPinverseMean)
686 , ("invert", OPinvert)
687 , ("isemptyl", OPisemptyl)
688 , ("lengthl", OPlengthl)
689 , ("maxf", OPmaxf)
690 , ("maxi", OPmaxi)
691 , ("maxp", OPmaxp)
692 , ("mean", OPmean)
693 , ("mergeHorizontal", OPmergeHorizontal)
694 , ("mergeVertical", OPmergeVertical)
695 , ("minf", OPminf)
696 , ("mini", OPmini)
697 , ("minp", OPminp)
698 , ("modi", OPmodi)
699 , ("mulf", OPmulf)
700 , ("muli", OPmuli)
701 , ("mulp", OPmulp)
702 , ("partitionHorizontal", OPpartitionHorizontal)
703 , ("partitionVertical", OPpartitionVertical)
704 , ("paste", OPpaste)
705 , ("consl", OPconsl)
706 , ("reduceColor", OPreduceColor)
707 , ("replicate", OPreplicate)
708 , ("resize", OPresize)
709 , ("rotate", OProtate)
710 , ("round", OPround)
711 , ("scale", OPscale)
712 , ("shift", OPshift)
713 , ("shrink", OPshrink)
714 , ("sideBySide", OPsideBySide)
715 , ("splitHorizontal", OPsplitHorizontal)
716 , ("splitVertical", OPsplitVertical)
717 , ("subf", OPsubf)
718 , ("subi", OPsubi)
719 , ("taill", OPtaill)
720 , ("trunc", OPtrunc)
721 , ("white", OPwhite)
722 , ("width", OPwidth)
723 ]
|
Letzte Änderung: 14.02.2012 | © Prof. Dr. Uwe Schmidt |