File: Static.hs

package info (click to toggle)
haskell-encoding 0.10.2-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 3,392 kB
  • sloc: haskell: 4,372; ansic: 11; makefile: 4
file content (81 lines) | stat: -rw-r--r-- 3,182 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
{-# LANGUAGE MagicHash,FlexibleInstances,BangPatterns,CPP #-}
module Data.Static where

import GHC.Exts
import GHC.Prim
import GHC.Word
import Data.Word
import Data.Bits
import Data.Char

class StaticElement e where
    extract :: Addr# -> Int# -> e
    gen :: e -> [Word8]

instance StaticElement Word8 where
    extract addr i = W8# (indexWord8OffAddr# addr i)
    gen w = [w]

instance StaticElement Word16 where
    extract addr i = W16# (indexWord16OffAddr# addr i)
    gen w = let r1 = fromIntegral w
                r2 = fromIntegral $ w `shiftR` 8
            in [r1,r2]

instance StaticElement Word32 where
    extract addr i = W32# (indexWord32OffAddr# addr i)
    gen w = let r1 = fromIntegral w
                r2 = fromIntegral $ w `shiftR`  8
                r3 = fromIntegral $ w `shiftR` 16
                r4 = fromIntegral $ w `shiftR` 24
            in [r1,r2,r3,r4]

instance StaticElement Char where
    extract addr i = C# (indexWideCharOffAddr# addr i)
    gen c = gen (fromIntegral (ord c)::Word32)

instance StaticElement (Maybe Char) where
    extract addr i = let !v = indexWord32OffAddr# addr i
#if __GLASGOW_HASKELL__ < 708
                     in if eqWord# v (int2Word# 4294967295#) -- -1 in Word32
#elif __GLASGOW_HASKELL__ < 902
                     in if isTrue# (eqWord# v (int2Word# 4294967295#)) -- -1 in Word32
#else
                     in if isTrue# (eqWord32# v (wordToWord32# (int2Word# 4294967295#))) -- -1 in Word32
#endif
                        then Nothing
#if __GLASGOW_HASKELL__ < 902
                        else (if (I# (word2Int# v)) > 0x10FFFF
                              then error (show (I# (word2Int# v))++" is not a valid char ("++show (I# i)++")")
                              else Just (chr (I# (word2Int# v)))
                             )
#else
                        else (if (I# (int32ToInt# (word32ToInt32# v))) > 0x10FFFF
                              then error (show (I# (int32ToInt# (word32ToInt32# v)))++" is not a valid char ("++show (I# i)++")")
                              else Just (chr (I#  (int32ToInt# (word32ToInt32# v))))
                             )
#endif

    gen Nothing = gen (complement (0 :: Word32))
    gen (Just c) = gen (fromIntegral (ord c)::Word32)

instance StaticElement a => StaticElement (a,a) where
    extract addr i = let x1 = extract addr (i *# 2#)
                         x2 = extract addr (i *# 2# +# 1#)
                     in (x1,x2)
    gen (x1,x2) = gen x1 ++ gen x2

instance StaticElement a => StaticElement (a,a,a) where
    extract addr i = let x1 = extract addr (i *# 3#)
                         x2 = extract addr (i *# 3# +# 1#)
                         x3 = extract addr (i *# 3# +# 2#)
                     in (x1,x2,x3)
    gen (x1,x2,x3) = gen x1 ++ gen x2 ++ gen x3

instance StaticElement a => StaticElement (a,a,a,a) where
    extract addr i = let x1 = extract addr (i *# 4#)
                         x2 = extract addr (i *# 4# +# 1#)
                         x3 = extract addr (i *# 4# +# 2#)
                         x4 = extract addr (i *# 4# +# 3#)
                     in (x1,x2,x3,x4)
    gen (x1,x2,x3,x4) = gen x1 ++ gen x2 ++ gen x3 ++ gen x4