File: Array.hs

package info (click to toggle)
bali-phy 4.0~beta16%2Bdfsg-1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 15,192 kB
  • sloc: cpp: 119,288; xml: 13,482; haskell: 9,722; python: 2,930; yacc: 1,329; perl: 1,169; lex: 904; sh: 343; makefile: 26
file content (97 lines) | stat: -rw-r--r-- 2,788 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
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
{-# LANGUAGE NoImplicitPrelude #-}
module Data.Array (module Data.Array,
                   module Data.Ix)
    where

-- See GHC/Arr.hs for some implementation details
-- In Data.Array         - Basic non-strict arrays (interface, I think)
-- See Data.Array.MArray - Mutable arrays   (interface)
-- See Data.Array.IArray - Immutable arrays (interfaced)
-- See Data.Array.ST     - Mutable boxed and unboxed array in the ST monad.
-- See Data.Array.IO     - Mutable boxed and unboxed array in the IO monad.
-- See Data.Array.Unboxed

import Compiler.Base -- for `seq`
import Data.Bool
import Data.Maybe
import Data.Ix
import Data.List
import Data.Ord
import Data.Function
import Compiler.Num
import Foreign.Vector
import Data.Functor
import Data.Foldable
import Text.Show

data Array a b

infixl 9 !
foreign import bpcall "Array:getIndex" (!) :: Array a b -> a -> b

foreign import bpcall "Array:arraySize" numElements :: Array a b -> Int
foreign import bpcall "Array:mkArray" mkArray :: a -> (a -> b) -> Array a b

foreign import bpcall "Array:" removeElement :: Int -> Array Int e -> Array Int e

listArray n l = mkArray n (\i -> l !! i)

listArray' l = listArray (length l) l

-- array (0,ix2) list = mkArray ix2 (\i -> find_in_assoc_list list i)

bounds arr = (0,numElements arr-1)

indices = range . bounds

elems   arr = [ arr!ix | ix <- indices arr ]

assocs  arr = [ (ix, arr!ix) | ix <- indices arr ]

to_vector = list_to_vector . toList
array_to_vector x = list_to_vector (elems x)
vectorToArray v = mkArray (vector_size v) (get_vector_index v)

instance Functor (Array Int) where
    fmap f arr = mkArray (numElements arr) (\i -> f (arr!i))

instance Foldable (Array Int) where
    toList  = elems
    length = numElements

    foldl f z arr = go 0 z where
        go i x | i < n      = go (i+1) (f x (arr!i))
               | otherwise  = x
        n = length arr

    foldl' f z arr = go 0 z where
        go i x | i < n      = let z' = (f x (arr!i)) in z' `seq` go (i+1) z'
               | otherwise  = x
        n = length arr

    foldl1 f arr = go 1 (arr!0) where
        go i x | i < n      = let z' = (f x (arr!i)) in z' `seq` go (i+1) z'
               | otherwise  = x
        n = length arr

    foldr f z arr = go 0 where
        go i | i < n     = f (arr!i) $ go (i+1)
             | otherwise = z
        n = length arr

    foldr1 f arr = go 0 where
        go i | i < n' = f (arr!i) $ go (i+1)
             | otherwise =  (arr!n')
        n' = length arr - 1

elemIndexArray val array = go 0 where
    go i | i >= n            = Nothing
         | (array!i) == val  = Just i
         | otherwise         = go (i+1)
    n = numElements array

mapnA n f arr = mkArray n (\i -> f $ arr!i)


instance Show i => Show (Array Int i) where
    show a = show (toList a)