[phylo] small, mechanical refactorings

parent f54f2036
Pipeline #7649 failed with stages
in 97 minutes and 44 seconds
......@@ -120,8 +120,10 @@ evolvSeaLadder nbFdt lambda freq similarities graph = map snd
where
--------
-- 2) find the local maxima in the quality distribution
-- TODO (seeg, #471) head throws errors when list is too short.
-- I propose this implementation, but I'm not sure of the length of the list
-- TODO (seeg, #471) head throws errors when list is too short
-- (i.e. List.head . List.tail requires at least 2 elements in the
-- list). I propose this implementation, but I'm not sure of the
-- length of the list
-- maxima = if List.length qua' > 1 then
-- [snd (List.head qua') > snd (List.head $ List.tail qua')] ++
-- (findMaxima qua') ++
......@@ -134,9 +136,9 @@ evolvSeaLadder nbFdt lambda freq similarities graph = map snd
-- 1.2)
qua' :: [(Double,Double)]
qua' = foldl (\acc (s,q) ->
if length acc == 0
if null acc
then [(s,q)]
else if (snd (List.last acc)) == q
else if snd (List.last acc) == q
then acc
else acc ++ [(s,q)]
) [] $ zip (Set.toList similarities) qua
......@@ -145,10 +147,10 @@ evolvSeaLadder nbFdt lambda freq similarities graph = map snd
qua :: [Double]
qua = parMap rpar (\thr ->
let edges = filter (\edge -> snd edge >= thr) graph
nodes = nubOrd $ concat $ map (\((n,n'),_) -> [n,n']) edges
nodes = nubOrd $ concatMap (\((n,n'),_) -> [n,n']) edges
branches = toRelatedComponents nodes edges
in toPhyloQuality nbFdt lambda freq branches
) $ (Set.toList similarities)
) $ Set.toList similarities
{-
......@@ -416,9 +418,9 @@ groupDocsByPeriod' f pds docs =
let docs' = groupBy (\d d' -> f d == f d') $ sortOn f docs
periods = parMap rpar (inPeriode f docs') pds
in tracePhylo ("\n" <> "-- | Group "
<> show(length docs)
<> show (length docs)
<> " docs by "
<> show(length pds) <> " periods" <> "\n" :: Text)
<> show (length pds) <> " periods" <> "\n" :: Text)
$ fromList $ zip pds periods
where
--------------------------------------
......@@ -435,8 +437,8 @@ groupDocsByPeriod f pds es =
let periods = parMap rpar (inPeriode f es) pds
in tracePhylo ("\n" <> "-- | Group "
<> show(length es) <> " docs by "
<> show(length pds) <> " periods" <> "\n" :: Text)
<> show (length es) <> " docs by "
<> show (length pds) <> " periods" <> "\n" :: Text)
$ fromList $ zip pds periods
where
--------------------------------------
......@@ -492,9 +494,9 @@ docsToTimeScaleNb docs =
let docs' = fromListWith (+) $ map (\d -> (date d,1)) docs
time = fromList $ map (\t -> (t,0)) $ toTimeScale (keys docs') 1
in tracePhylo ("\n" <> "-- | Group "
<> show(length docs)
<> show (length docs)
<> " docs by "
<> show(length time)
<> show (length time)
<> " unit of time" <> "\n" :: Text)
$ unionWith (+) time docs'
......@@ -548,9 +550,9 @@ initPhylo docs conf =
else defaultPhyloParam { _phyloParam_config = conf }
periods = toPeriods (D.sort $ D.nub $ map date docs) (getTimePeriod timeScale) (getTimeStep timeScale)
in tracePhylo ("\n" <> "-- | Init a phylo out of "
<> show(length docs) <> " docs \n" :: Text)
<> show (length docs) <> " docs \n" :: Text)
$ tracePhylo ("\n" <> "-- | lambda "
<> show(_qua_granularity $ phyloQuality $ _phyloParam_config params) :: Text)
<> show (_qua_granularity $ phyloQuality $ _phyloParam_config params) :: Text)
$ Phylo foundations
docsSources
docsCounts
......
This diff is collapsed.
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