Table.hs 4.47 KB
Newer Older
1
{-# LANGUAGE BangPatterns #-}
2 3 4
--
-- orbit-int hash table (storing vertices on a worker)
--
5 6
module Table( -- Types
              Freq
Aggelos Giantsios's avatar
Aggelos Giantsios committed
7 8
            , VTable
            , Vertex
9
              -- Functions
Aggelos Giantsios's avatar
Aggelos Giantsios committed
10
            , new
11 12 13 14 15 16 17 18 19 20 21 22
            , to_list
            , is_member
            , insert
            , get_freq
            , sum_freqs
            , sum_freqs2
            , freq_to_slots
            , freq_to_nonempty_slots
            , freq_to_vertices
            , max_freq
            , avg_freq
            , avg_nonempty_freq
23 24
            , freq_to_stat
            , freq_from_stat
Yiannis Tsiouris's avatar
Yiannis Tsiouris committed
25 26
            , fill_deg
            ) where
27

28 29 30
import Data.Array (Array, elems, listArray, (!), (//))

import Utils      (Vertex)
31 32 33

type Freq   = [Int]
type VTable = Array Int [Vertex]
34
type TableStats = [(String, String)]
35

36 37 38 39 40
-- Note: Hash tables have a fixed number of slots but each slot can store
-- a list of vertices. The functions is_member/3 and insert/3
-- expect its slot argument to be in range.

-- new(Size) creates a table with Size slots, each containing an empty list.
41
new :: Int -> VTable
42 43 44
new size = listArray (0, size - 1) $ cycle [[]]

-- to_list(T) converts a table T into a list of its entries.
Aggelos Giantsios's avatar
Aggelos Giantsios committed
45
to_list :: VTable -> [Vertex]
46 47 48
to_list = concat . elems

-- is_member(X, I, T) is true iff X is stored in table T at slot I.
Aggelos Giantsios's avatar
Aggelos Giantsios committed
49
is_member :: Vertex -> Int -> VTable -> Bool
50 51 52
is_member x i t = elem x (t ! i)

-- insert(X, I, T) inserts X into table T at slot I.
Aggelos Giantsios's avatar
Aggelos Giantsios committed
53
insert :: Vertex -> Int -> VTable -> VTable
54
insert !x i t = t!i `seq` t // [(i, x : t ! i)]
55 56 57 58 59

-- get_freq computes the fill frequency of table T;
-- the output is a list of integers where the number at position I
-- indicates how many slots of T are filled with I entries;
-- the sum of the output lists equals the number of slots of T.
60
get_freq :: VTable -> Freq
61 62 63 64 65 66
get_freq t = elems $ foldl (flip inc) freqArr freqs
  where freqs = map length $ elems t
        maxFreq = foldl max (head freqs) (tail freqs)
        freqArr = listArray (0, maxFreq) $ cycle [0]

-- freq_to_slots computes the number of slots from a table fill frequency.
67
freq_to_slots :: Freq -> Int
68 69 70 71
freq_to_slots = sum

-- freq_to_nonempty_slots computes the number of non empty slots from a table
-- fill frequency.
72
freq_to_nonempty_slots :: Freq -> Int
73 74 75
freq_to_nonempty_slots = sum . tail

-- freq_to_vertices computes the number of vertices from a table fill frequency.
76
freq_to_vertices :: Freq -> Int
77 78 79
freq_to_vertices f = snd $ foldl (\(i, x) n -> (i + 1, (i * n + x))) (0, 0) f

-- max_freq returns the maximum fill frequency.
80
max_freq :: Freq -> Int
81 82 83
max_freq f = length f - 1

-- avg_freq returns the average fill frequency
84
avg_freq :: Freq -> Float
85 86 87
avg_freq f = (fi $ freq_to_vertices f) / (fi $ freq_to_slots f)

-- avg_nonempty_freq returns the average fill frequency of non empty slots.
88
avg_nonempty_freq :: Freq -> Float
89
avg_nonempty_freq f =
Yiannis Tsiouris's avatar
Yiannis Tsiouris committed
90 91 92
    if verts > 0 then (fi verts) / (fi $ freq_to_nonempty_slots f)
    else 0.0
  where verts = freq_to_vertices f
93 94

-- fill_deg determines the filling degree of the table.
95
fill_deg :: Freq -> Float
96 97 98
fill_deg f = (fi $ freq_to_nonempty_slots f) / (fi $ freq_to_slots f)

-- sum_freqs/2 sums two fill frequencies.
Yiannis Tsiouris's avatar
Yiannis Tsiouris committed
99
sum_freqs2 :: Freq -> Freq -> Freq
100 101 102 103 104
sum_freqs2 [] sumF = sumF
sum_freqs2 f [] = f
sum_freqs2 (n : f) (m : sumF) = n + m : sum_freqs2 f sumF

-- sum_freqs/1 sums a list of fill frequencies.
Yiannis Tsiouris's avatar
Yiannis Tsiouris committed
105
sum_freqs :: [Freq] -> Freq
106 107 108 109
sum_freqs fs = foldl (flip sum_freqs2) [] fs

-- freq_to_stat produces a readable statistics from a table fill frequency;
-- the input frequency F is itself part of the statistics
110 111 112 113 114 115 116 117 118 119
freq_to_stat :: Freq -> TableStats
freq_to_stat frequency =
    [ ("freq", show frequency)
    , ("size", show $ freq_to_vertices frequency)
    , ("slots", show $ freq_to_slots frequency)
    , ("nonempty_slots", show $ freq_to_nonempty_slots frequency)
    , ("fill_deg", show $ fill_deg frequency)
    , ("max_freq", show $ max_freq frequency)
    , ("avg_freq", show $ avg_freq frequency)
    , ("nonempty_avg_freq", show $ avg_nonempty_freq frequency) ]
120 121 122

-- freq_from_stat extracts a table fill frequency from a statistics Stat
-- (assuming Stat was produced by freq_to_stat/1, otherwise returns []);
123
freq_from_stat :: TableStats -> Freq
124
freq_from_stat stat =
125 126 127
    case "freq" `lookup` stat of
        Just val -> read val :: [Int]
        Nothing -> []
128 129 130 131

--------------------------------------------------------------------------------
-- auxiliary functions
inc :: Int -> Array Int Int -> Array Int Int
132
inc i t = t!i `seq` t // [(i, t!i + 1)]
133 134 135

fi :: (Integral a, Num b) => a -> b
fi = fromIntegral