summaryrefslogtreecommitdiff
path: root/doc
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-05-03 10:42:13 -0300
committerGravatar Joey Hess <joey@kitenet.net>2014-05-03 10:42:13 -0300
commit825310a68967fd75b5c51242648f3406b9738e9b (patch)
tree0b95c9d3381fe166cc2139f95f0430500224e3c1 /doc
parented4a8c68b1dbda381d08b31fd591649ca6683cd6 (diff)
add mocambos network data
Diffstat (limited to 'doc')
-rw-r--r--doc/design/assistant/syncing/simroutes.hs143
1 files changed, 117 insertions, 26 deletions
diff --git a/doc/design/assistant/syncing/simroutes.hs b/doc/design/assistant/syncing/simroutes.hs
index 87e8781ba..b5e446b0b 100644
--- a/doc/design/assistant/syncing/simroutes.hs
+++ b/doc/design/assistant/syncing/simroutes.hs
@@ -17,7 +17,7 @@ import qualified Data.Map.Strict as M
-}
totalFiles :: Int
-totalFiles = 10
+totalFiles = 100
-- How likely is a given file to be wanted by any particular node?
probabilityFilesWanted :: Probability
@@ -26,7 +26,7 @@ probabilityFilesWanted = 0.10
-- How many different locations can each transfer node move between?
-- (Min, Max)
transferDestinationsRange :: (Int, Int)
-transferDestinationsRange = (2, 5)
+transferDestinationsRange = (2, 3)
-- Controls how likely transfer nodes are to move around in a given step
-- of the simulation.
@@ -54,7 +54,8 @@ numSteps :: Int
numSteps = 100
-- IO code
-main = putStrLn . summarize =<< evalRandIO (simulate numSteps =<< genNetwork)
+--main = putStrLn . summarize =<< evalRandIO (simulate numSteps =<< genNetwork)
+main = putStrLn . summarize =<< evalRandIO (simulate numSteps =<< mocambos)
-- Only pure code below :)
data Network = Network (M.Map NodeName ImmobileNode) [TransferNode]
@@ -65,6 +66,8 @@ data ImmobileNode = ImmobileNode NodeRepo
type NodeName = String
+type Route = [NodeName]
+
data TransferNode = TransferNode
{ currentlocation :: NodeName
, possiblelocations :: [NodeName]
@@ -193,41 +196,44 @@ genNetwork :: (RandomGen g) => Rand g Network
genNetwork = do
l <- sequence (replicate numImmobileNodes mkImmobile)
let immobiles = M.fromList (zip (map show [1..]) l)
- transfers <- sequence (replicate numTransferNodes (mkTransfer immobiles))
+ transfers <- sequence (replicate numTransferNodes (mkTransfer $ M.keys immobiles))
return $ Network immobiles transfers
mkImmobile :: (RandomGen g) => Rand g ImmobileNode
-mkImmobile = ImmobileNode <$> genrepo
- where
- genrepo = NodeRepo
- -- The files this node wants.
- -- Currently assumes each file is equally popular.
- <$> sequence (replicate (truncate (fromIntegral totalFiles * probabilityFilesWanted)) randomRequest)
- -- The files this node already has.
- --
- -- We'll assume equal production, so split the total
- -- number of files amoung the immobile nodes.
- -- (This will produce some duplication of files
- -- (consider birthday paradox), and some missing files.)
- --
- -- TODO: Some immobile nodes are internet connected,
- -- and these should all share their files automatically)
- -- (Also when running the sim.)
- <*> (S.fromList <$> sequence (replicate (totalFiles `div` numImmobileNodes) randomFile))
-
-mkTransfer :: (RandomGen g) => M.Map NodeName ImmobileNode -> Rand g TransferNode
+mkImmobile = ImmobileNode <$> mkImmobileRepo
+
+mkImmobileRepo :: (RandomGen g) => Rand g NodeRepo
+mkImmobileRepo = NodeRepo
+ -- The files this node wants.
+ -- Currently assumes each file is equally popular.
+ <$> sequence (replicate (truncate (fromIntegral totalFiles * probabilityFilesWanted)) randomRequest)
+ -- The files this node already has.
+ --
+ -- We'll assume equal production, so split the total
+ -- number of files amoung the immobile nodes.
+ -- (This will produce some duplication of files
+ -- (consider birthday paradox), and some missing files.)
+ --
+ -- TODO: Some immobile nodes are internet connected,
+ -- and these should all share their files automatically)
+ -- (Also when running the sim.)
+ <*> (S.fromList <$> sequence (replicate (totalFiles `div` numImmobileNodes) randomFile))
+
+mkTransfer :: (RandomGen g) => [NodeName] -> Rand g TransferNode
mkTransfer immobiles = do
-- Transfer nodes are given random routes. May be simplistic.
-- Also, some immobile nodes will not be serviced by any transfer nodes.
numpossiblelocs <- getRandomR transferDestinationsRange
- possiblelocs <- sequence (replicate numpossiblelocs (randomfrom indexes))
+ possiblelocs <- sequence (replicate numpossiblelocs (randomfrom immobiles))
+ mkTransferBetween possiblelocs
+
+mkTransferBetween :: (RandomGen g) => [NodeName] -> Rand g TransferNode
+mkTransferBetween possiblelocs = do
currentloc <- randomfrom possiblelocs
movefreq <- getRandomR transferMoveFrequencyRange
-- transfer nodes start out with no files or requests in their repo
let repo = (NodeRepo [] S.empty)
return $ TransferNode currentloc possiblelocs movefreq repo
- where
- indexes = M.keys immobiles
randomfrom :: (RandomGen g) => [a] -> Rand g a
randomfrom l = do
@@ -250,3 +256,88 @@ summarize (Network is _ts) = unlines $ map (\(d, s) -> d ++ ": " ++ s)
in S.difference wantedfs (haveFiles r)
repo (ImmobileNode r) = r
overis f = map f $ M.elems is
+
+mocambos :: (RandomGen g) => Rand g Network
+mocambos = do
+ major <- mapM (immobilenamed . fst) communities
+ minor <- mapM immobilenamed (concatMap snd communities)
+ majortransfer <- mapM mkTransferBetween majorroutes
+ minortransfer <- mapM mkTransferBetween (concatMap minorroutes communities)
+ return $ Network
+ (M.fromList (major++minor))
+ (majortransfer ++ minortransfer)
+ where
+ immobilenamed name = do
+ node <- mkImmobile
+ return (name, node)
+
+ -- As a simplification, this only makes 2 hop routes, between minor
+ -- and major communities; no 3-legged routes.
+ minorroutes :: (NodeName, [NodeName]) -> [Route]
+ minorroutes (major, minors) = map (\n -> [major, n]) minors
+
+communities :: [(NodeName, [NodeName])]
+communities =
+ [ ("Tainá/SP",
+ [ "badtas"
+ , "vauedo ribera"
+ , "cofundo"
+ , "jao"
+ , "fazenda"
+ ]
+ )
+ , ("Odomode/RS",
+ [ "moradadapaz"
+ , "pelotas"
+ ]
+ )
+ , ("MercadoSul/DF",
+ [ "mesquito"
+ , "kalungos"
+ ]
+ )
+ , ("Coco/PE",
+ [ "xambá"
+ , "alafin"
+ , "terreiaos"
+ ]
+ )
+ , ("Linharinho/ES",
+ [ "monte alegne"
+ ]
+ )
+ , ("Boneco/BA",
+ [ "barroso"
+ , "lagoa santa"
+ , "terravista"
+ ]
+ )
+ , ("Zumbidospalmanes/NA",
+ [ "allantana"
+ ]
+ )
+ , ("Casa Pneta/PA",
+ [ "marajó"
+ ]
+ )
+ , ("Purarue/PA",
+ [ "oriaminá"
+ ]
+ )
+ , ("Madiba/NET", [])
+ ]
+
+majorroutes :: [Route]
+majorroutes =
+ -- person's routes
+ [ ["Tainá/SP", "Odomode/RS"]
+ , ["Tainá/SP", "MercadoSul/DF"]
+ , ["MercadoSul/DF", "Boneco/BA"]
+ , ["MercadoSul/DF", "Zumbidospalmanes/NA"]
+ , ["Zumbidospalmanes/NA", "Casa Pneta/PA"]
+ , ["Casa Pneta/PA", "Purarue/PA"]
+ , ["Casa Pneta/PA", "Linharinho/ES"]
+ , ["Boneco/BA", "Coco/PE"]
+ -- internet connections
+ , ["Tainá/SP", "MercadoSul/DF", "Coco/PE", "Purarue/PA", "Odomode/RS", "Madiba/NET"]
+ ]