Statistics
| Branch: | Tag: | Revision:

root / src / Node.hs @ dd4c56ed

History | View | Annotate | Download (6.7 kB)

1 e4f08c46 Iustin Pop
{-| Module describing a node.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
    All updates are functional (copy-based) and return a new node with
4 e4f08c46 Iustin Pop
    updated value.
5 e4f08c46 Iustin Pop
-}
6 e4f08c46 Iustin Pop
7 e4f08c46 Iustin Pop
module Node
8 e4f08c46 Iustin Pop
    (
9 e4f08c46 Iustin Pop
      Node(failN1, idx, f_mem, f_disk, slist, plist)
10 e4f08c46 Iustin Pop
    -- * Constructor
11 e4f08c46 Iustin Pop
    , create
12 e4f08c46 Iustin Pop
    -- ** Finalization after data loading
13 e4f08c46 Iustin Pop
    , buildPeers
14 e4f08c46 Iustin Pop
    , setIdx
15 e4f08c46 Iustin Pop
    -- * Instance (re)location
16 e4f08c46 Iustin Pop
    , removePri
17 e4f08c46 Iustin Pop
    , removeSec
18 e4f08c46 Iustin Pop
    , addPri
19 e4f08c46 Iustin Pop
    , addSec
20 01f6a5d2 Iustin Pop
    , setPri
21 01f6a5d2 Iustin Pop
    , setSec
22 e4f08c46 Iustin Pop
    -- * Statistics
23 e4f08c46 Iustin Pop
    , normUsed
24 e4f08c46 Iustin Pop
    -- * Formatting
25 e4f08c46 Iustin Pop
    , list
26 e4f08c46 Iustin Pop
    ) where
27 e4f08c46 Iustin Pop
28 e4f08c46 Iustin Pop
import Data.List
29 e4f08c46 Iustin Pop
import Text.Printf (printf)
30 e4f08c46 Iustin Pop
31 e4f08c46 Iustin Pop
import qualified Container
32 e4f08c46 Iustin Pop
import qualified Instance
33 e4f08c46 Iustin Pop
import qualified PeerMap
34 e4f08c46 Iustin Pop
35 e4f08c46 Iustin Pop
import Utils
36 e4f08c46 Iustin Pop
37 e4f08c46 Iustin Pop
data Node = Node { t_mem :: Int -- ^ total memory (Mib)
38 e4f08c46 Iustin Pop
                 , f_mem :: Int -- ^ free memory (MiB)
39 e4f08c46 Iustin Pop
                 , t_disk :: Int -- ^ total disk space (MiB)
40 e4f08c46 Iustin Pop
                 , f_disk :: Int -- ^ free disk space (MiB)
41 e4f08c46 Iustin Pop
                 , plist :: [Int] -- ^ list of primary instance indices
42 e4f08c46 Iustin Pop
                 , slist :: [Int] -- ^ list of secondary instance indices
43 e4f08c46 Iustin Pop
                 , idx :: Int -- ^ internal index for book-keeping
44 e4f08c46 Iustin Pop
                 , peers:: PeerMap.PeerMap -- ^ primary node to instance
45 e4f08c46 Iustin Pop
                                           -- mapping
46 e4f08c46 Iustin Pop
                 , failN1:: Bool -- ^ whether the node has failed n1
47 e4f08c46 Iustin Pop
                 , maxRes :: Int -- ^ maximum memory needed for
48 e4f08c46 Iustin Pop
                                   -- failover by primaries of this node
49 e4f08c46 Iustin Pop
  } deriving (Show)
50 e4f08c46 Iustin Pop
51 e4f08c46 Iustin Pop
{- | Create a new node.
52 e4f08c46 Iustin Pop
53 e4f08c46 Iustin Pop
The index and the peers maps are empty, and will be need to be update
54 e4f08c46 Iustin Pop
later via the 'setIdx' and 'buildPeers' functions.
55 e4f08c46 Iustin Pop
56 e4f08c46 Iustin Pop
-}
57 01f6a5d2 Iustin Pop
create :: String -> String -> String -> String -> Node
58 e4f08c46 Iustin Pop
create mem_t_init mem_f_init disk_t_init disk_f_init
59 01f6a5d2 Iustin Pop
    = Node
60 e4f08c46 Iustin Pop
    {
61 e4f08c46 Iustin Pop
      t_mem = read mem_t_init,
62 e4f08c46 Iustin Pop
      f_mem = read mem_f_init,
63 e4f08c46 Iustin Pop
      t_disk = read disk_t_init,
64 e4f08c46 Iustin Pop
      f_disk = read disk_f_init,
65 01f6a5d2 Iustin Pop
      plist = [],
66 01f6a5d2 Iustin Pop
      slist = [],
67 e4f08c46 Iustin Pop
      failN1 = True,
68 e4f08c46 Iustin Pop
      idx = -1,
69 e4f08c46 Iustin Pop
      peers = PeerMap.empty,
70 e4f08c46 Iustin Pop
      maxRes = 0
71 e4f08c46 Iustin Pop
    }
72 e4f08c46 Iustin Pop
73 e4f08c46 Iustin Pop
-- | Changes the index.
74 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
75 e4f08c46 Iustin Pop
setIdx :: Node -> Int -> Node
76 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
77 e4f08c46 Iustin Pop
78 e4f08c46 Iustin Pop
-- | Given the rmem, free memory and disk, computes the failn1 status.
79 e4f08c46 Iustin Pop
computeFailN1 :: Int -> Int -> Int -> Bool
80 e4f08c46 Iustin Pop
computeFailN1 new_rmem new_mem new_disk =
81 e4f08c46 Iustin Pop
    new_mem <= new_rmem || new_disk <= 0
82 e4f08c46 Iustin Pop
83 e4f08c46 Iustin Pop
84 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
85 e4f08c46 Iustin Pop
computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
86 e4f08c46 Iustin Pop
computeMaxRes new_peers = PeerMap.maxElem new_peers
87 e4f08c46 Iustin Pop
88 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
89 e4f08c46 Iustin Pop
buildPeers :: Node -> Container.Container Instance.Instance -> Int -> Node
90 e4f08c46 Iustin Pop
buildPeers t il num_nodes =
91 e4f08c46 Iustin Pop
    let mdata = map
92 e4f08c46 Iustin Pop
                (\i_idx -> let inst = Container.find i_idx il
93 e4f08c46 Iustin Pop
                           in (Instance.pnode inst, Instance.mem inst))
94 e4f08c46 Iustin Pop
                (slist t)
95 e4f08c46 Iustin Pop
        pmap = PeerMap.accumArray (+) 0 (0, num_nodes - 1) mdata
96 e4f08c46 Iustin Pop
        new_rmem = computeMaxRes pmap
97 e4f08c46 Iustin Pop
        new_failN1 = computeFailN1 new_rmem (f_mem t) (f_disk t)
98 e4f08c46 Iustin Pop
    in t {peers=pmap, failN1 = new_failN1, maxRes = new_rmem}
99 e4f08c46 Iustin Pop
100 e4f08c46 Iustin Pop
-- | Removes a primary instance.
101 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
102 e4f08c46 Iustin Pop
removePri t inst =
103 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
104 e4f08c46 Iustin Pop
        new_plist = delete iname (plist t)
105 e4f08c46 Iustin Pop
        new_mem = f_mem t + Instance.mem inst
106 e4f08c46 Iustin Pop
        new_disk = f_disk t + Instance.disk inst
107 e4f08c46 Iustin Pop
        new_failn1 = computeFailN1 (maxRes t) new_mem new_disk
108 e4f08c46 Iustin Pop
    in t {plist = new_plist, f_mem = new_mem, f_disk = new_disk,
109 e4f08c46 Iustin Pop
          failN1 = new_failn1}
110 e4f08c46 Iustin Pop
111 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
112 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
113 e4f08c46 Iustin Pop
removeSec t inst =
114 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
115 e4f08c46 Iustin Pop
        pnode = Instance.pnode inst
116 e4f08c46 Iustin Pop
        new_slist = delete iname (slist t)
117 e4f08c46 Iustin Pop
        new_disk = f_disk t + Instance.disk inst
118 e4f08c46 Iustin Pop
        old_peers = peers t
119 e4f08c46 Iustin Pop
        old_peem = PeerMap.find pnode old_peers
120 e4f08c46 Iustin Pop
        new_peem =  old_peem - (Instance.mem inst)
121 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pnode new_peem old_peers
122 e4f08c46 Iustin Pop
        old_rmem = maxRes t
123 e4f08c46 Iustin Pop
        new_rmem = if old_peem < old_rmem then
124 e4f08c46 Iustin Pop
                       old_rmem
125 e4f08c46 Iustin Pop
                   else
126 e4f08c46 Iustin Pop
                       computeMaxRes new_peers
127 e4f08c46 Iustin Pop
        new_failn1 = computeFailN1 new_rmem (f_mem t) new_disk
128 e4f08c46 Iustin Pop
    in t {slist = new_slist, f_disk = new_disk, peers = new_peers,
129 e4f08c46 Iustin Pop
          failN1 = new_failn1, maxRes = new_rmem}
130 e4f08c46 Iustin Pop
131 e4f08c46 Iustin Pop
-- | Adds a primary instance.
132 e4f08c46 Iustin Pop
addPri :: Node -> Instance.Instance -> Maybe Node
133 e4f08c46 Iustin Pop
addPri t inst =
134 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
135 e4f08c46 Iustin Pop
        new_mem = f_mem t - Instance.mem inst
136 e4f08c46 Iustin Pop
        new_disk = f_disk t - Instance.disk inst
137 e4f08c46 Iustin Pop
        new_failn1 = computeFailN1 (maxRes t) new_mem new_disk in
138 e4f08c46 Iustin Pop
      if new_failn1 then
139 e4f08c46 Iustin Pop
        Nothing
140 e4f08c46 Iustin Pop
      else
141 e4f08c46 Iustin Pop
        let new_plist = iname:(plist t) in
142 e4f08c46 Iustin Pop
        Just t {plist = new_plist, f_mem = new_mem, f_disk = new_disk,
143 e4f08c46 Iustin Pop
                failN1 = new_failn1}
144 e4f08c46 Iustin Pop
145 e4f08c46 Iustin Pop
-- | Adds a secondary instance.
146 e4f08c46 Iustin Pop
addSec :: Node -> Instance.Instance -> Int -> Maybe Node
147 e4f08c46 Iustin Pop
addSec t inst pdx =
148 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
149 e4f08c46 Iustin Pop
        old_peers = peers t
150 e4f08c46 Iustin Pop
        new_disk = f_disk t - Instance.disk inst
151 e4f08c46 Iustin Pop
        new_peem = PeerMap.find pdx old_peers + Instance.mem inst
152 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pdx new_peem old_peers
153 e4f08c46 Iustin Pop
        new_rmem = max (maxRes t) new_peem
154 e4f08c46 Iustin Pop
        new_failn1 = computeFailN1 new_rmem (f_mem t) new_disk in
155 e4f08c46 Iustin Pop
    if new_failn1 then
156 e4f08c46 Iustin Pop
        Nothing
157 e4f08c46 Iustin Pop
    else
158 e4f08c46 Iustin Pop
        let new_slist = iname:(slist t) in
159 e4f08c46 Iustin Pop
        Just t {slist = new_slist, f_disk = new_disk,
160 e4f08c46 Iustin Pop
                peers = new_peers, failN1 = new_failn1,
161 e4f08c46 Iustin Pop
                maxRes = new_rmem}
162 e4f08c46 Iustin Pop
163 01f6a5d2 Iustin Pop
-- | Add a primary instance to a node without other updates
164 01f6a5d2 Iustin Pop
setPri :: Node -> Int -> Node
165 01f6a5d2 Iustin Pop
setPri t idx = t { plist = idx:(plist t) }
166 01f6a5d2 Iustin Pop
167 01f6a5d2 Iustin Pop
-- | Add a secondary instance to a node without other updates
168 01f6a5d2 Iustin Pop
setSec :: Node -> Int -> Node
169 01f6a5d2 Iustin Pop
setSec t idx = t { slist = idx:(slist t) }
170 01f6a5d2 Iustin Pop
171 e4f08c46 Iustin Pop
-- | Simple converter to string.
172 e4f08c46 Iustin Pop
str :: Node -> String
173 e4f08c46 Iustin Pop
str t =
174 e4f08c46 Iustin Pop
    printf ("Node %d (mem=%5d MiB, disk=%5.2f GiB)\n  Primaries:" ++
175 e4f08c46 Iustin Pop
            " %s\nSecondaries: %s")
176 e4f08c46 Iustin Pop
      (idx t) (f_mem t) ((f_disk t) `div` 1024)
177 e4f08c46 Iustin Pop
      (commaJoin (map show (plist t)))
178 e4f08c46 Iustin Pop
      (commaJoin (map show (slist t)))
179 e4f08c46 Iustin Pop
180 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
181 e4f08c46 Iustin Pop
list :: String -> Node -> String
182 e4f08c46 Iustin Pop
list n t =
183 e4f08c46 Iustin Pop
    let pl = plist t
184 e4f08c46 Iustin Pop
        sl = slist t
185 e4f08c46 Iustin Pop
        (mp, dp) = normUsed t
186 e4f08c46 Iustin Pop
    in
187 e4f08c46 Iustin Pop
      printf "  %s(%d)\t%5d\t%5d\t%3d\t%3d\t%s\t%s\t%.5f\t%.5f"
188 e4f08c46 Iustin Pop
                 n (idx t) (f_mem t) ((f_disk t) `div` 1024)
189 e4f08c46 Iustin Pop
                 (length pl) (length sl)
190 e4f08c46 Iustin Pop
                 (commaJoin (map show pl))
191 e4f08c46 Iustin Pop
                 (commaJoin (map show sl))
192 e4f08c46 Iustin Pop
                 mp dp
193 e4f08c46 Iustin Pop
194 e4f08c46 Iustin Pop
-- | Normalize the usage status
195 e4f08c46 Iustin Pop
-- This converts the used memory and disk values into a normalized integer
196 e4f08c46 Iustin Pop
-- value, currently expresed as per mille of totals
197 e4f08c46 Iustin Pop
198 e4f08c46 Iustin Pop
normUsed :: Node -> (Double, Double)
199 e4f08c46 Iustin Pop
normUsed n =
200 e4f08c46 Iustin Pop
    let mp = (fromIntegral $ f_mem n) / (fromIntegral $ t_mem n)
201 e4f08c46 Iustin Pop
        dp = (fromIntegral $ f_disk n) / (fromIntegral $ t_disk n)
202 e4f08c46 Iustin Pop
    in (mp, dp)