3a_asm: playing around
[calu.git] / 3a_asm / DT.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Module      :  Text.Assembler.PPC64
4 -- Copyright   : (c) Jeff Douglas
5 -- License     :  BSD3
6 --
7 -- Maintainer  : Jeff Douglas
8 -- Stability   : experimental
9 -- Portability : portable
10 --
11 -- |
12 --
13 -----------------------------------------------------------------------------
14
15 module DT where
16
17 import Prelude hiding (and,or)
18
19 import Data.Bits hiding (xor)
20 import qualified Data.Map as Map
21 import Data.Word
22 import Text.Printf
23 import Text.Parsec
24 import Text.Parsec.String
25 import Text.Parsec.Combinator
26 import Control.Monad
27 import Control.Applicative hiding ((<|>))
28
29 parseInstructions = many1 instruction
30
31 testins :: String -> IO ()
32 testins input =
33         case (parse instruction "" (input++"\n")) of
34                 Left err -> do { putStr "fail :/"; print err}
35                 Right x -> do { printf "0x%08X\n" x }
36
37 -- parsing --
38 instruction :: Parser Word32
39 instruction = foldl1 (<|>) (fmap try instructions) <* char '\n'
40
41 instructions = [
42         add, addi]
43
44 comma = char ','
45 mnem m = string m >> space
46
47 iLit :: Parser Word32
48 iLit = liftM read (many1 digit)
49
50 imm5 :: Parser String
51 imm5 = do {a <- digit; b <- digit; return [a,b]}
52
53 reg :: Parser Word32
54 reg = do {string "r"; liftM read (imm5)}
55
56 (<.>) p n = p<*comma<*>n
57 (<@>) p n = p<*char '('<*>n<*char ')'
58 infixl 1 <.>
59 infixl 1 <@>
60
61 -- branch instructions
62 b = ins "b" v1 $ iform 18 0 0
63 ba = ins "ba" v1 $ iform 18 1 0
64 bl = ins "bl" v1 $ iform 18 0 1
65 bla = ins "bla" v1 $ iform 18 1 1
66
67 bc = ins "bc" csv3 $ bform 16 0 0
68 bca = ins "bca" csv3 $ bform 16 1 0
69 bcl = ins "bcl" csv3 $ bform 16 0 1
70 bcla = ins "bcla" csv3 $ bform 16 1 1
71
72 bclr = ins "bclr" csv3 $ xlform'b 19 16 0
73 bclrl = ins "bclrl" csv3 $ xlform'b 19 16 1
74
75 bcctr = ins "bcctr" csv3 $ xlform'b 19 528 0
76 bcctrl = ins "bcctrl" csv3 $ xlform'b 19 528 1
77
78 -- system call instruction
79 sc = ins "sc" v1 $ scform 17
80
81 -- condition register logical instructions
82 crand = ins "crand" csv3 $ xlform'a 19 257
83 cror = ins "cror" csv3 $ xlform'a 19 449
84 crxor = ins "cxor" csv3 $ xlform'a 19 193
85 crnand = ins "crnand" csv3 $ xlform'a 19 225
86 crnor = ins "crnor" csv3 $ xlform'a 19 33
87 creqv = ins "creqv" csv3 $ xlform'a 19 289
88 crandc = ins "crandc" csv3 $ xlform'a 19 129
89 crorc = ins "crorc" csv3 $ xlform'a 19 417
90
91 -- condition register field instruction
92 mcrf = ins "mcrf" csv2 $ xlform'c 19 0
93
94 -- fixed point load instructions
95 lbz = ins "lbz" csv3 $ dform'a 34
96 lbzx = ins "lbzx" csv3 $ xform'a 31 87
97 lbzu = ins "lbzu" csv3 $ dform'a 35
98 lbzux = ins "lbzux" csv3 $ xform'a 31 119
99 lhz = ins "lhz" csv3 $ dform'a 40
100 lhzx = ins "lhz" csv3 $ xform'a 31 279
101 lhzu = ins "lhzu" csv3 $ dform'a 41
102 lhzux = ins "lhzux" csv3 $ xform'a 31 311
103 lha = ins "lha" csv3 $ dform'a 42
104 lhax = ins "lhax" csv3 $ xform'a 31 343
105 lhau = ins "lhau" csv3 $ dform'a 43
106 lhaux = ins "lhaux" csv3 $ xform'a 31 375
107 lwz = ins "lwz" csv3 $ dform'a 32
108 lwzx = ins "lwzx" csv3 $ xform'a 31 23
109 lwzu = ins "lwzu" csv3 $ dform'a 33
110 lwzux = ins "lwzux" csv3 $ xform'a 31 55
111 lwa = ins "lwa" csv3 $ dsform 58 2
112 lwax = ins "lwax" csv3 $ xform'a  31 341
113 lwaux = ins "lwaux" csv3 $ xform'a 31 373
114 ld = ins "ld" csv3 $ dsform 58 151
115 ldx = ins "ldx" csv3 $ xform'a 31 21
116 ldu = ins "ldu" csv3 $ dsform 58 1
117 ldux = ins "ldux" csv3 $ xform'a 31 53
118
119 -- fixed point store instructions
120 stb = ins "stb" csv3 $ dform'a 38
121 stbx = ins "stbx" csv3 $ xform'a 31 215
122 stbu = ins "stbu" csv3 $ dform'a 39
123 stbux = ins "stbux" csv3 $ xform'a 31 247
124 sth = ins "sth" csv3 $ dform'a 44
125 sthx = ins "sthx" csv3 $ xform'a 31 407
126 sthu = ins "sthu" csv3 $ dform'a 45
127 sthux = ins "sthux" csv3 $ xform'a 31 439
128 stw = ins "stw" csv3 $ dform'a 36
129 stwx = ins "stwx" csv3 $ xform'a 31 151
130 stwu = ins "stwu" csv3 $ dform'a 37
131 stwux = ins "stwux" csv3 $ xform'a 31 183
132 std = ins "std" csv3 $ dsform 62 0
133 stdx = ins "stdx" csv3 $ xform'a 31 149
134 stdu = ins "stdu" csv3 $ dsform 37 1
135 stdux = ins "stdux" csv3 $ xform'a 31 181
136
137 -- fixed-point load and store with byte reversal instructions
138 lhbrx = ins "lhbrx" csv3 $ xform'a 31 790
139 lwbrx = ins "lwbrx" csv3 $ xform'a 31 534
140 sthbrx = ins "sthbrx" csv3 $ xform'a 31 918
141 stwbrx = ins "stwbrx" csv3 $ xform'a 31 662
142
143 -- fixed point load and store multiple instructions
144 lmw = ins "lmw" csv3 $ dform'a 46
145 stmw = ins "stmw" csv3 $ dform'a 47
146
147 -- fixed point move assist instructions
148 lswi = ins "lswi" csv3 $ xform'a 31 597
149 lswx = ins "lswx" csv3 $ xform'a 31 533
150 stswi = ins "stswi" csv3 $ xform'a 31 725
151 stswx = ins "stswx" csv3 $ xform'a 31 661
152
153 --fixed point arithmetic instructions
154 addi = ins "addi" csv3 $ dform'a 14
155 addis = ins "addis" csv3 $ dform'a 15
156
157 add = ins "add" csv3 $ xoform 31 266 0 0
158 add_ = ins "add." csv3 $ xoform 31 266 0 1
159 addo = ins "addo" csv3 $ xoform 31 266 1 0
160 addo_ = ins "addo." csv3 $ xoform 31 266 1 1
161 subf = ins "subf" csv3 $ xoform 31 40 0 0
162 subf_ = ins "subf." csv3 $ xoform 31 40 0 1
163 subfo = ins "subfo" csv3 $ xoform 31 40 1 0
164 subfo_ = ins "subfo." csv3 $ xoform 31 40 1 1
165
166 addic = ins "addic" csv3 $ dform'a 12
167 addic_ = ins "addic." csv3 $ dform'a 13
168 subfic = ins "subfic" csv3 $ dform'a 8
169
170 addc = ins "addc" csv3 $ xoform 31 10 0 0
171 addc_ = ins "addc." csv3 $ xoform 31 10 0 1
172 addco = ins "addco" csv3 $ xoform 31 10 1 0
173 addco_ = ins "addco." csv3 $ xoform 31 10 1 1
174
175 subfc = ins "subfc" csv3 $ xoform 31 8 0 0
176 subfc_ = ins "subfc." csv3 $ xoform 31 8 0 1
177 subfco = ins "subfco" csv3 $ xoform 31 8 1 1
178 subfco_ = ins "subfco." csv3 $ xoform 31 8 1 1
179
180 adde = ins "adde" csv3 $ xoform 31 138 0 0
181 adde_ = ins "adde." csv3 $ xoform 31 138 0 1
182 addeo = ins "addeo" csv3 $ xoform 31 138 1 0
183 addeo_ = ins "addeo." csv3 $ xoform 31 138 1 1
184
185 subfe = ins "subfe" csv3 $ xoform 31 136 0 0
186 subfe_ = ins "subfe." csv3 $ xoform 31 136 0 1
187 subfeo = ins "subfeo" csv3 $ xoform 31 136 1 0
188 subfeo_ = ins "subfeo." csv3 $ xoform 31 136 1 1
189
190 addme = ins "addme" csv2 $ xoform' 31 234 0 0
191 addme_ = ins "addme." csv2 $ xoform' 31 234 0 1
192 addmeo = ins "addmeo" csv2 $ xoform' 31 234 1 0
193 addmeo_ = ins "addmeo." csv2 $ xoform' 31 234 1 1
194
195 subfme = ins "subfme" csv2 $ xoform' 31 232 0 0
196 subfme_ = ins "subfme." csv2 $ xoform' 31 232 0 1
197 subfmeo = ins "subfmeo" csv2 $ xoform' 31 232 1 0
198 subfmeo_ = ins "subfmeo." csv2 $ xoform' 31 232 1 1
199
200 addze = ins "addze" csv2 $ xoform' 31 202 0 0
201 addze_ = ins "addze." csv2 $ xoform' 31 202 0 1
202 addzeo = ins "addzeo" csv2 $ xoform' 31 202 1 0
203 addzeo_ = ins "addzeo." csv2 $ xoform' 31 202 1 1
204
205 subfze = ins "subfze" csv2 $ xoform' 31 202 0 0
206 subfze_ = ins "subfze." csv2 $ xoform' 31 202 0 1
207 subfzeo = ins "subfzeo" csv2 $ xoform' 31 202 1 0
208 subfzeo_ = ins "subfzeo." csv2 $ xoform' 31 202 1 1
209
210 neg = ins "neg" csv2 $ xoform' 31 104 0 0
211 neg_ = ins "neg." csv2 $ xoform' 31 104 0 1
212 nego = ins "nego" csv2 $ xoform' 31 104 1 0
213 nego_ = ins "nego." csv2 $ xoform' 31 104 1 1
214
215 mulli = ins "mulli" csv3 $ dform'a 7
216
217 mulld = ins "mulld" csv3 $ xoform 31 233 0 0
218 mulld_ = ins "mulld." csv3 $ xoform 31 233 0 1
219 mulldo = ins "mulldo" csv3 $ xoform 31 233 1 0
220 mulldo_ = ins "mulldo." csv3 $ xoform 31 233 1 1
221
222 mullw = ins "mullw" csv3 $ xoform 31 235 0 0
223 mullw_ = ins "mullw." csv3 $ xoform 31 235 0 1
224 mullwo = ins "mullwo" csv3 $ xoform 31 235 1 0
225 mullwo_ = ins "mullwo." csv3 $ xoform 31 235 1 1
226
227 mulhd = ins "mulhd" csv3 $ xoform 31 73 0 0
228 mulhd_ = ins "mulhd." csv3 $ xoform 31 73 0 1
229
230 mulhw = ins "mulhw" csv3 $ xoform 31 75 0 0
231 mulhw_ = ins "mulhw." csv3 $ xoform 31 75 0 1
232
233 mulhdu = ins "mulhdu" csv3 $ xoform 31 9 0 0
234 mulhdu_ = ins "mulhdu." csv3 $ xoform 31 9 0 1
235
236 mulhwu = ins "mulhwu" csv3 $ xoform 31 11 0 0
237 mulhwu_ = ins "mulhwu." csv3 $ xoform 31 11 0 1
238
239 divd = ins "divd" csv3 $ xoform 31 489 0 0
240 divd_ = ins "divd." csv3 $ xoform 31 489 0 1
241 divdo = ins "divdo" csv3 $ xoform 31 489 1 0
242 divdo_ = ins "divdo." csv3 $ xoform 31 489 1 1
243
244 divw = ins "divw" csv3 $ xoform 31 491 0 0
245 divw_ = ins "divw." csv3 $ xoform 31 491 0 1
246 divwo = ins "divwo" csv3 $ xoform 31 491 1 0
247 divwo_ = ins "divwo." csv3 $ xoform 31 491 1 1
248
249 divdu = ins "divdu" csv3 $ xoform 31 457 0 0
250 divdu_ = ins "divdu." csv3 $ xoform 31 457 0 1
251 divduo = ins "divduo" csv3 $ xoform 31 457 1 0
252 divduo_ = ins "divduo." csv3 $ xoform 31 457 1 1
253
254 divwu = ins "divwu" csv3 $ xoform 31 459 0 0
255 divwu_ = ins "divwu." csv3 $ xoform 31 459 0 1
256 divwuo = ins "divdwo" csv3 $ xoform 31 459 1 0
257 divwuo_ = ins "divdwo." csv3 $ xoform 31 459 1 1
258
259 -- fixed-point compare instructions
260 -- check out bit 9 in cmp
261 cmpi = ins "cmpi" csv3 $ dform'b 11 0
262 -- check out bit 9 in cmp
263 cmp = ins "cmp" csv3 $ xform'b 31 0 0
264 -- check out bit 9 in cmpli
265 cmpli = ins "cmpli" csv3 $ dform'b 10 0
266 -- check out bit 9 in cmpl
267 cmpl = ins "cmpl" csv3 $ xform'b 32 0 0
268
269 -- fixed-point trap instructions
270 tdi = ins "tdi" csv3 $ dform'a 2
271 twi = ins "twi" csv3 $ dform'a 3
272 td = ins "td" csv3 $ xform'a 31 68
273 tw = ins "tw" csv3 $ xform'a 31 4
274
275 -- fixed-point logical instructions
276 andi_ = ins "andi." csv3 $ dform'a 28
277 andis_ = ins "andis" csv3 $ dform'a 29
278 ori = ins "ori" csv3 $ dform'a 24
279 oris = ins "oris" csv3 $ dform'a 25
280 xori = ins "ori" csv3 $ dform'a 26
281 xors = ins "oris" csv3 $ dform'a 27
282 and = ins "and" csv3 $ xform'c 31 28 0
283 and_ = ins "and." csv3 $ xform'c 31 28 1
284 or = ins "or" csv3 $ xform'c 31 444 0
285 or_ = ins "or." csv3 $ xform'c 31 444 1
286 xor = ins "xor" csv3 $ xform'c 31 316 0
287 xor_ = ins "xor." csv3 $ xform'c 31 316 1
288 nand = ins "nand" csv3 $ xform'c 31 476 0
289 nand_ = ins "nand." csv3 $ xform'c 31 476 1
290 nor = ins "nor" csv3 $ xform'c 31 124 0
291 nor_ = ins "nor." csv3 $ xform'c 31 124 1
292 eqv = ins "eqv" csv3 $ xform'c 31 284 0
293 eqv_ = ins "eqv." csv3 $ xform'c 31 284 1
294 andc = ins "andc" csv3 $ xform'c 31 60 0
295 andc_ = ins "andc." csv3 $ xform'c 31 60 1
296 orc = ins "orc" csv3 $ xform'c 31 412 0
297 orc_ = ins "orc." csv3 $ xform'c 31 412 1
298 extsb = ins "extsb" csv2 $ xform'd 31 954 0
299 extsb_ = ins "extsb." csv2 $ xform'd 31 954 1
300 extsh = ins "extsh" csv2 $ xform'd 31 922 0
301 extsh_ = ins "extsh." csv2 $ xform'd 31 922 1
302 extsw = ins "extsw" csv2 $ xform'd 31 986 0
303 extsw_ = ins "extsw." csv2 $ xform'd 31 986 1
304 cntlzd = ins "cntlzd" csv2 $ xform'd 31 58 0
305 cntlzd_ = ins "cntlzd." csv2 $ xform'd 31 58 1
306 popcntb = ins "popcntb" csv2 $ xform'd 31 122 0
307 cntlzw = ins "cntlzw" csv2 $ xform'd 31 26 0
308 cntlzw_ = ins "cntlzw." csv2 $ xform'd 31 26 1
309
310 -- fixed-point rotate and shift instructions
311 rldicl  = ins "rldicl"  csv4 $ mdform 30 0 0
312 rldicl_ = ins "rldicl." csv4 $ mdform 30 0 1
313 rldicr  = ins "rldicr"  csv4 $ mdform 30 1 0
314 rldicr_ = ins "rldicr." csv4 $ mdform 30 1 1
315 rldic  = ins "rldic"  csv4 $ mdform 30 2 0
316 rldic_ = ins "rldic." csv4 $ mdform 30 2 1
317 rlwinm  = ins "rlwinm"  csv5 $ mform 21 0
318 rlwinm_ = ins "rlwinm." csv5 $ mform 21 1
319 rldcl  = ins "rldcl"  csv4 $ mdsform 30 8 0
320 rldcl_ = ins "rldcl." csv4 $ mdsform 30 8 1
321 rldcr  = ins "rldcr"  csv4 $ mdsform 30 9 0
322 rldcr_ = ins "rldcr." csv4 $ mdsform 30 9 1
323 rlwnm  = ins "rlwnm"  csv5 $ mform 23 0
324 rlwnm_ = ins "rlwnm." csv5 $ mform 23 1
325 rldimi  = ins "rldimi"  csv4 $ mdform 30 3 0
326 rldimi_ = ins "rldimi." csv4 $ mdform 30 3 1
327 rlwimi  = ins "rlwimi"  csv5 $ mform 20 0
328 rlwimi_ = ins "rlwimi." csv5 $ mform 20 1
329
330 -- fixed-point shift instructions
331 sld  = ins "sld"  csv3 $ xform'c 31 27 0
332 sld_ = ins "sld." csv3 $ xform'c 31 27 1
333 slw  = ins "slw"  csv3 $ xform'c 31 24 0
334 slw_ = ins "slw." csv3 $ xform'c 31 24 1
335 srd  = ins "srd"  csv3 $ xform'c 31 539 0
336 srd_ = ins "srd." csv3 $ xform'c 31 539 1
337 srw  = ins "srw"  csv3 $ xform'c 31 536 0
338 srw_ = ins "srw." csv3 $ xform'c 31 536 1
339 sradi  = ins "sradi"  csv3 $ xsform 31 413 0
340 sradi_ = ins "sradi." csv3 $ xsform 31 413 1
341 srawi  = ins "srawi"  csv3 $ xform'c 31 824 0
342 srawi_ = ins "srawi." csv3 $ xform'c 31 824 1
343 srad = ins "srad" csv3 $ xform'c 31 794 0
344 srad_ = ins "srad." csv3 $ xform'c 31 794 1
345 sraw = ins "sraw" csv3 $ xform'c 31 792 0
346 sraw_ = ins "sraw." csv3 $ xform'c 31 792 1
347
348 -- move to/from system register instructions
349 mtspr = ins "mtspr" csv2 $ xfxform 31 467
350 mfspr = ins "mfspr" csv2 $ xfxform 31 339
351 mtcrf = ins "mtcrf" csv2 $ xfxform'b 31 0 144
352
353 -- floating-point processor instructions --
354 -- floating-point load instructions
355 lfs = ins "lfs" csv3 $ dform'a 48
356
357
358 ---
359 ins m form e  = mnem m>>form e
360 v1 f = f<$>iLit
361 csv2 f =f<$>iLit<.>iLit
362 csv3 f = f<$>reg<.>reg<.>iLit
363 csv4 f = f<$>iLit<.>iLit<.>iLit<.>iLit
364 csv5 f = f<$>iLit<.>iLit<.>iLit<.>iLit<.>iLit
365
366 -- instruction fomats
367 iform opcd aa lk li = pack [(opcd,6),(li,30),(aa,31),(lk,0)]
368 bform opcd aa lk bo bi bd = pack [(opcd,6),(bo,11),(bi,16),(bd,30),(aa,31),(lk,0)]
369 scform opcd lev = pack [(opcd,6),(lev,27),(1,31)]
370 dform'a opcd rt ra d = pack [(opcd,6),(rt,11),(ra,16),(d,0)]
371 dform'b opcd bf l ra si = pack [(opcd,6),(bf,9),(0,10),(l,11),(ra,16),(si,0)]
372 dsform opcd rt ra ds xo = pack [(opcd,6),(rt,11),(ra,16),(ds,30),(xo,0)]
373 xform'a opcd rt ra rb xo = pack [(opcd,6),(rt,11),(ra,16),(rb,21),(xo,31)]
374 xform'b opcd xo bf l ra rb = pack [(opcd,6),(bf,9),(0,10),(l,11),(ra,16),(rb,21),(xo,31),(0,0)]
375 xform'c opcd xo rs ra rb rc = pack [(opcd,6),(rs,11),(ra,16),(rb,21),(xo,31),(rc,0)]
376 xform'd opcd xo rc rs ra = pack [(opcd,6),(rs,11),(ra,16),(0,21),(xo,31),(rc,0)]
377 xlform'a opcd xo bt ba bb = pack [(opcd,6),(bt,11),(ba,16),(bb,21),(xo,31)]
378 xlform'b opcd xo lk bo bi bh = pack [(opcd,6),(bo,11),(bi,16),(bh,21),(xo,31),(lk,0)]
379 xlform'c opcd xo bf bfa = pack [(opcd,6),(bf,9),(bfa,14),(xo,31)]
380 xfxform opcd xo rs spr = pack [(opcd,6),(rs,11),(spr,21),(xo,31)]
381 xfxform'b opcd h xo fxm rs = pack [(opcd,6),(rs,11),(h,12),(fxm,20),(xo,31)]
382 --xflform
383 -- fix xsform
384 xsform opcd xo rc ra rs sh = pack [(opcd,6),(rs,11),(ra,16),(sh,21),(xo,30),(sh,31),(rc,0)]
385 xoform opcd xo oe rc rt ra rb = pack [(opcd,6),(rt,11),(ra,16),(rb,21),(oe,22),(xo,31),(rc,0)]
386 xoform' opcd xo oe rc rt ra = pack [(opcd,6),(rt,11),(ra,16),(0,21),(oe,22),(xo,31),(rc,0)]
387 --aform
388 mform opcd rc ra rs sh mb me = pack [(opcd,6),(rs,11),(ra,16),(sh,21),(mb,26),(me,31),(rc,0)]
389 -- mdform needs to be fixed to handle sh correctly
390 mdform opcd h rc ra rs sh mb = pack [(opcd,6),(rs,11),(ra,16),(sh,21),(mb,27),(h,30),(sh,31),(rc,0)]
391 mdsform opcd h rc ra rs rb mb = pack [(opcd,6),(rs,11),(ra,16),(rb,21),(mb,27),(h,31),(rc,0)]
392
393 -- bit-packing --
394 pack bf = foldr1 (.|.) $ map (uncurry rotateR) bf
395