File: IntSet.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 (100 lines) | stat: -rw-r--r-- 2,711 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
98
99
100
module Data.IntSet where

import Prelude hiding (map,empty,elems,filter)
import Data.Functor
import qualified Data.List as L
import Foreign.Vector
import Data.Foldable (foldr)
import Data.Array (vectorToArray)
import Control.DeepSeq

data IntSet

type Key = Int

foreign import bpcall "IntSet:empty" _empty :: () -> IntSet
empty = _empty ()

foreign import bpcall "IntSet:" singleton :: Key -> IntSet

-- Should this be more efficient? With immer it might be OK, but maybe we should
-- convert to an EVector Int, and then convert that to an IntSet
fromList []     = empty
fromList (k:ks) = insert k $ fromList ks

foreign import bpcall "IntSet:" insert :: Key -> IntSet -> IntSet

foreign import bpcall "IntSet:" delete :: Key -> IntSet -> IntSet

foreign import bpcall "IntSet:" member :: Int -> IntSet -> Bool

notMember k = not . member k

-- lookupLT
-- lookupGT
-- lookupLE
-- lookup GE

null m = size m == 0

foreign import bpcall "IntSet:" size :: IntSet -> Int

foreign import bpcall "IntSet:" union :: IntSet -> IntSet -> IntSet

unions :: Foldable f => f (IntSet) -> IntSet
unions sets = foldr union empty sets

foreign import bpcall "IntSet:" difference :: IntSet -> IntSet -> IntSet

(\\) = difference

foreign import bpcall "IntSet:" isSubsetOf :: IntSet -> IntSet -> Bool

isProperSubsetOf :: IntSet -> IntSet -> Bool
isProperSubsetOf s1 s2 = (s1 `isSubsetOf` s2) && (size s1 < size s2)

foreign import bpcall "IntSet:" intersection :: IntSet -> IntSet -> IntSet

foreign import bpcall "IntSet:" disjoint :: IntSet -> IntSet -> Int

-- Note!  These are supposed be to in ascending order of keys, but are not.

foreign import bpcall "IntSet:keys" _keys :: IntSet -> EVector Key
elems m = vector_to_list $ _keys m

toList m = elems m

toArray s = vectorToArray $ _keys s

toAscList m = toList m

toDescList m = toList m

filter :: (Key -> Bool) -> IntSet -> IntSet
filter p set = fromList $ L.filter p $ toList set

-- partition :: (Key -> Bool) -> IntSet -> (IntSet, IntSet)
-- split :: Key -> IntSet -> (IntSet, IntSet)
-- splitMember :: Key -> IntSet -> (IntSet, Bool, IntSet)
-- splitRoot :: IntSet -> [IntSet]

map :: (Key -> Key) -> IntSet -> IntSet
map f set = fromList $ L.map f $ toList set
-- mapMonotonic :: (Key -> Key) -> IntSet -> IntSet

-- findMin :: IntSet -> Key
-- findMax :: IntSet -> Key
-- deleteMin :: IntSet -> IntSet
-- deleteMax :: IntSet -> IntSet
-- deleteFindMin :: IntSet -> (Key, IntSet)
-- deleteFindMax :: IntSet -> (Key, IntSet)
-- maxView :: IntSet -> Maybe (Key, IntSet)
-- minView :: IntSet -> Maybe (Key, IntSet) 

instance Show (IntSet) where
    show m = show $ toList m

foreign import bpcall "IntSet:" mapNegate :: IntSet -> IntSet

instance NFData IntSet