Commit 0a8089a2 authored by Yiannis Tsiouris's avatar Yiannis Tsiouris

Rm Types module and mv now to Utils

parent ce41dc0c
......@@ -3,15 +3,12 @@
--
module Master where
import Control.Distributed.Process (Process, ProcessId, match,
receiveWait)
import Control.Distributed.Process (Process, ProcessId, NodeId,
match, receiveWait)
import Credit (credit, is_one)
import qualified Sequential as Sq (orbit)
import Table (freq_from_stat, freq_to_stat,
sum_freqs)
import Types (Generator, HostInfo (..),
MaybeHosts (..), ParConf, Stats,
Vertex)
import qualified Sequential as Sq (Generator, orbit)
import Table (Stats, Vertex, freq_from_stat,
freq_to_stat, sum_freqs)
import Worker (credit_retd_from_stat,
init_idle_from_stat,
max_idle_from_stat,
......@@ -19,6 +16,19 @@ import Worker (credit_retd_from_stat,
tail_idle_from_stat,
verts_recvd_from_stat)
data MaybeHosts = Seq Int
| Par HostInfo
data HostInfo = JustOne (Int, -- Number of processes
Int, -- Table size
Int, -- Idle timeout
Bool) -- Spawn image comp
| Many [(NodeId, -- Node id
Int, -- Number of processes
Int, -- Table size
Int, -- Idle timeout
Bool)] -- Spawn image comp
type ParConf = ([Sq.Generator], ProcessId, [ProcessId], Int, Int, Bool)
-- DATA
-- Static Machine Configuration:
-- {Gs, %list of generators
......@@ -126,10 +136,10 @@ do_collect_orbit n partOrbits workerStats = do
-- auxiliary functions
-- functions operating on the StaticMachConf
mk_static_mach_conf :: [Generator] -> ProcessId -> [ProcessId] -> Int -> ParConf
mk_static_mach_conf :: [Sq.Generator] -> ProcessId -> [ProcessId] -> Int -> ParConf
mk_static_mach_conf gs master workers globalTableSize = (gs, master, workers, globalTableSize, 0, True)
get_gens :: ParConf -> [Generator]
get_gens :: ParConf -> [Sq.Generator]
get_gens (gs, _, _, _, _, _) = gs
get_master :: ParConf -> ProcessId
......@@ -175,4 +185,3 @@ master_stats elapsedTime workerStats = ("wall_time", show elapsedTime)
maxIdle = foldl max (head idles) (tail idles)
tailIdles = map tail_idle_from_stat workerStats
maxTailIdle = foldl max (head tailIdles) (tail tailIdles)
--
-- orbit-int sequential implementation
--
module Sequential( Generator
module Sequential( -- Types
Generator
-- Functions
, orbit
) where
import Data.Dequeue (BankersDequeue, fromList, popFront, pushBack)
import Data.Hashable (hash)
import Table (freq_to_stat, get_freq, insert, is_member, new,
import Table (Freq, Stats, Vertex, VTable,
freq_to_stat, get_freq, insert, is_member, new,
to_list)
import Types (Freq, Generator, SeqConf, Stats, VTable, Vertex)
import Worker (now)
import Utils (now)
type Generator = Vertex -> Vertex
type SeqConf = ([Generator], Int)
-- DATA
-- Static Machine Configuration:
......@@ -28,8 +34,8 @@ import Worker (now)
-- list of statistics (mainly runtime and fill degree of the table).
orbit :: [Generator] -> [Vertex] -> Int -> ([Vertex], [Stats])
orbit gs xs tableSize = (orbit, [stat])
-- assemble static configuration
where staticMachConf = mk_static_mach_conf gs tableSize
where -- assemble static configuration
staticMachConf = mk_static_mach_conf gs tableSize
-- initialise hash table and work queue
table = new tableSize
queue = fromList xs
......
--
-- orbit-int hash table (storing vertices on a worker)
--
module Table( Freq
module Table( -- Types
Freq
, Stats
, VTable
, Vertex
-- Functions
, new
, to_list
, is_member
......@@ -24,7 +26,11 @@ module Table( Freq
) where
import Data.Array (Array, elems, listArray, (!), (//))
import Types (Freq, Stats, VTable, Vertex)
type Freq = [Int]
type Vertex = Int
type VTable = Array Int [Vertex]
type Stats = [(String, String)]
-- 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
......
--
-- orbit-int types
--
module Types( Ct(..)
, Generator
, Freq
, HostInfo(..)
, MaybeHosts(..)
, ParConf
, SeqConf
, Stats
, Vertex
, VTable) where
import Control.Distributed.Process (NodeId, ProcessId)
import Data.Array (Array)
type Freq = [Int]
type Vertex = Int
type VTable = Array Int [Vertex]
type Stats = [(String, String)]
type Generator = Vertex -> Vertex
data MaybeHosts = Seq Int
| Par HostInfo
data HostInfo = JustOne (Int, Int, Int, Bool) -- Procs, TableSize, IdleTimeout, SpwnImgComp
| Many [(NodeId, Int, Int, Int, Bool)] -- NodeId, Procs, TableSize, IdleTimeout, SpwnImgComp
type SeqConf = ([Generator], Int)
type ParConf = ([Generator], ProcessId, [ProcessId], Int, Int, Bool)
-- counters/timers record
data Ct = Ct {
verts_recvd :: Int -- #vertices received by this server so far
, credit_retd :: Int -- #times server has returned credit to master
, min_atomic_credit :: Int -- minimal atomic credit received so far
, last_event :: Int -- time stamp [ms] of most recent event
, init_idle :: Int -- idle time [ms] between init recv first vertex
, tail_idle :: Int -- idle time [ms] between send last vertex and dump
, max_idle :: Int -- max idle [ms] time between vertices
}
module Utils (now) where
-- current wall clock time (in milliseconds since start of RTS)
-- FIXME: get current wall clock time
now :: Int
now = 42
--
-- orbit-int worker
-- orbit-int worker (computing vertices and holding part of hash table)
--
module Worker( defaultCt
, now
, worker_stats
, verts_recvd_from_stat
module Worker( --init
--, distribute_vertices
--, send_image
verts_recvd_from_stat
, credit_retd_from_stat
, min_atomic_credit_from_stat
, init_idle_from_stat
......@@ -13,8 +13,20 @@ module Worker( defaultCt
) where
import Control.Distributed.Process (NodeId)
import Table (freq_to_stat)
import Types (Ct (..), Freq, Stats)
import Table (Freq, Stats, freq_to_stat)
import Utils (now)
-- counters/timers record
data Ct = Ct {
verts_recvd :: Int -- #vertices received by this server so far
, credit_retd :: Int -- #times server has returned credit to master
, min_atomic_credit :: Int -- minimal atomic credit received so far
, last_event :: Int -- time stamp [ms] of most recent event
, init_idle :: Int -- idle time [ms] between init recv first vertex
, tail_idle :: Int -- idle time [ms] between send last vertex and dump
, max_idle :: Int -- max idle [ms] time between vertices
}
defaultCt :: Ct
defaultCt = Ct { verts_recvd = 0
......@@ -26,11 +38,6 @@ defaultCt = Ct { verts_recvd = 0
, max_idle = -1
}
-- current wall clock time (in milliseconds since start of RTS)
-- FIXME get current wall clock time
now :: Int
now = 42
-- produce readable statistics
worker_stats :: NodeId -> Freq -> Ct -> Stats
worker_stats node frequency statData = ("node", show node)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment