Commit bf1098d5 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DOC] fix haddock errors

parent c88689c3
Pipeline #1074 failed with stage
...@@ -854,8 +854,8 @@ ngramsStatePatchConflictResolution ...@@ -854,8 +854,8 @@ ngramsStatePatchConflictResolution
-> ConflictResolutionNgramsPatch -> ConflictResolutionNgramsPatch
ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm
= (ours, (const ours, ours), (False, False)) = (ours, (const ours, ours), (False, False))
-- ^------^------- they mean that Mod has always priority. -- (False, False) mean here that Mod has always priority.
--(True, False) <- would mean priority to the left (same as ours). -- (True, False) <- would mean priority to the left (same as ours).
-- undefined {- TODO think this through -}, listTypeConflictResolution) -- undefined {- TODO think this through -}, listTypeConflictResolution)
......
...@@ -50,7 +50,7 @@ selectPublic :: HasNodeError err ...@@ -50,7 +50,7 @@ selectPublic :: HasNodeError err
=> Cmd err [( Node HyperdataFolder, Maybe Int)] => Cmd err [( Node HyperdataFolder, Maybe Int)]
selectPublic = selectPublicNodes selectPublic = selectPublicNodes
-- | For tests only -- For tests only
-- pure $ replicate 6 defaultPublicData -- pure $ replicate 6 defaultPublicData
filterPublicDatas :: [( Node HyperdataFolder, Maybe Int)] -> [(Node HyperdataFolder, [NodeId])] filterPublicDatas :: [( Node HyperdataFolder, Maybe Int)] -> [(Node HyperdataFolder, [NodeId])]
......
...@@ -97,7 +97,7 @@ grid s e tr te = do ...@@ -97,7 +97,7 @@ grid s e tr te = do
-> m (Score, Model) -> m (Score, Model)
grid' x y tr' te' = do grid' x y tr' te' = do
model'' <- liftBase $ trainList x y tr' model'' <- liftBase $ trainList x y tr'
let let
model' = ModelSVM model'' (Just x) (Just y) model' = ModelSVM model'' (Just x) (Just y)
...@@ -114,10 +114,10 @@ grid s e tr te = do ...@@ -114,10 +114,10 @@ grid s e tr te = do
$ List.concat $ List.concat
$ map (\(k,vs) -> zip (repeat k) vs) $ map (\(k,vs) -> zip (repeat k) vs)
$ Map.toList t $ Map.toList t
res' <- liftBase $ predictList m toGuess res' <- liftBase $ predictList m toGuess
pure $ score'' $ score' $ List.zip res res' pure $ score'' $ score' $ List.zip res res'
score <- mapM (getScore model') te' score <- mapM (getScore model') te'
pure (mean score, model') pure (mean score, model')
...@@ -131,6 +131,3 @@ grid s e tr te = do ...@@ -131,6 +131,3 @@ grid s e tr te = do
--fp <- saveFile (ModelSVM model') --fp <- saveFile (ModelSVM model')
--save best result --save best result
pure $ snd <$> r pure $ snd <$> r
...@@ -35,7 +35,7 @@ import qualified Data.Map as Map ...@@ -35,7 +35,7 @@ import qualified Data.Map as Map
import qualified Data.Vector.Storable as Vec import qualified Data.Vector.Storable as Vec
type GraphListSize = Int type MapListSize = Int
type InclusionSize = Int type InclusionSize = Int
{- {-
...@@ -64,8 +64,8 @@ data Scored ts = Scored ...@@ -64,8 +64,8 @@ data Scored ts = Scored
localMetrics' :: Ord t => Map (t,t) Int -> Map t (Vec.Vector Double) localMetrics' :: Ord t => Map (t,t) Int -> Map t (Vec.Vector Double)
localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [inc,spe])) localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [inc,spe]))
(Map.toList fi) (Map.toList fi)
scores scores
where where
(ti, fi) = createIndices m (ti, fi) = createIndices m
(is, ss) = incExcSpeGen $ cooc2mat ti m (is, ss) = incExcSpeGen $ cooc2mat ti m
...@@ -73,8 +73,7 @@ localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [ ...@@ -73,8 +73,7 @@ localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [
$ DAA.run $ DAA.run
$ DAA.zip (DAA.use is) (DAA.use ss) $ DAA.zip (DAA.use is) (DAA.use ss)
-- TODO Code to be removed below
-- TODO Code to be remove below
-- TODO in the textflow we end up needing these indices , it might be -- TODO in the textflow we end up needing these indices , it might be
-- better to compute them earlier and pass them around. -- better to compute them earlier and pass them around.
scored' :: Ord t => Map (t,t) Int -> [Scored t] scored' :: Ord t => Map (t,t) Int -> [Scored t]
...@@ -87,20 +86,20 @@ scored' m = zipWith (\(_,t) (inc,spe) -> Scored t (inc) (spe)) (Map.toList fi) s ...@@ -87,20 +86,20 @@ scored' m = zipWith (\(_,t) (inc,spe) -> Scored t (inc) (spe)) (Map.toList fi) s
$ DAA.zip (DAA.use is) (DAA.use ss) $ DAA.zip (DAA.use is) (DAA.use ss)
takeScored :: Ord t => GraphListSize -> InclusionSize -> Map (t,t) Int -> ([t],[t]) takeScored :: Ord t => MapListSize -> InclusionSize -> Map (t,t) Int -> ([t],[t])
takeScored listSize incSize = both (map _scored_terms) takeScored listSize incSize = both (map _scored_terms)
. linearTakes listSize incSize _scored_speGen . takeLinear listSize incSize _scored_speGen
_scored_incExc _scored_incExc
. scored . scored
-- | Filter Scored data -- | Filter Scored data
-- >>> linearTakes 2 3 fst snd $ Prelude.zip ([1..10] :: [Int]) (reverse $ [1..10] :: [Int]) -- >>> takeLinear 2 3 fst snd $ Prelude.zip ([1..10] :: [Int]) (reverse $ [1..10] :: [Int])
-- [(3,8),(6,5)] -- [(3,8),(6,5)]
linearTakes :: (Ord b1, Ord b2) takeLinear :: (Ord b1, Ord b2)
=> GraphListSize -> InclusionSize => MapListSize -> InclusionSize
-> (a -> b2) -> (a -> b1) -> [a] -> ([a],[a]) -> (a -> b2) -> (a -> b1) -> [a] -> ([a],[a])
linearTakes mls incSize speGen incExc = (List.splitAt mls) takeLinear mls incSize speGen incExc = (List.splitAt mls)
. List.concat . List.concat
. map (take $ round . map (take $ round
$ (fromIntegral mls :: Double) $ (fromIntegral mls :: Double)
......
...@@ -245,8 +245,8 @@ conditional' m = ( run $ ie $ map fromIntegral $ use m ...@@ -245,8 +245,8 @@ conditional' m = ( run $ ie $ map fromIntegral $ use m
-- \[N_{m} = \sum_{i,i \neq i}^{m} \sum_{j, j \neq j}^{m} S_{ij}\] -- \[N_{m} = \sum_{i,i \neq i}^{m} \sum_{j, j \neq j}^{m} S_{ij}\]
-- --
distributional :: Matrix Int -> Matrix Double distributional :: Matrix Int -> Matrix Double
distributional m = run -- $ matMiniMax distributional m = -- run {- $ matMiniMax -}
$ diagNull n run $ diagNull n
$ rIJ n $ rIJ n
$ filterWith 0 100 $ filterWith 0 100
$ filter' 0 $ filter' 0
......
...@@ -247,7 +247,7 @@ exportToDot phylo export = ...@@ -247,7 +247,7 @@ exportToDot phylo export =
toDotEdge (groupIdToDotId k) (groupIdToDotId k') "" GroupToAncestor toDotEdge (groupIdToDotId k) (groupIdToDotId k') "" GroupToAncestor
) $ mergeAncestors $ export ^. export_groups ) $ mergeAncestors $ export ^. export_groups
-- | 10) create the edges between the periods -- 10) create the edges between the periods
_ <- mapM (\(prd,prd') -> _ <- mapM (\(prd,prd') ->
toDotEdge (periodIdToDotId prd) (periodIdToDotId prd') "" PeriodToPeriod toDotEdge (periodIdToDotId prd) (periodIdToDotId prd') "" PeriodToPeriod
) $ nubBy (\combi combi' -> fst combi == fst combi') $ listToCombi' $ getPeriodIds phylo ) $ nubBy (\combi combi' -> fst combi == fst combi') $ listToCombi' $ getPeriodIds phylo
......
...@@ -417,13 +417,13 @@ mergeMeta bId groups = ...@@ -417,13 +417,13 @@ mergeMeta bId groups =
groupsToBranches :: Map PhyloGroupId PhyloGroup -> [[PhyloGroup]] groupsToBranches :: Map PhyloGroupId PhyloGroup -> [[PhyloGroup]]
groupsToBranches groups = groupsToBranches groups =
-- | run the related component algorithm {- run the related component algorithm -}
let egos = map (\g -> [getGroupId g] let egos = map (\g -> [getGroupId g]
++ (map fst $ g ^. phylo_groupPeriodParents) ++ (map fst $ g ^. phylo_groupPeriodParents)
++ (map fst $ g ^. phylo_groupPeriodChilds) ++ (map fst $ g ^. phylo_groupPeriodChilds)
++ (map fst $ g ^. phylo_groupAncestors)) $ elems groups ++ (map fst $ g ^. phylo_groupAncestors)) $ elems groups
graph = relatedComponents egos graph = relatedComponents egos
-- | update each group's branch id {- update each group's branch id -}
in map (\ids -> in map (\ids ->
let groups' = elems $ restrictKeys groups (Set.fromList ids) let groups' = elems $ restrictKeys groups (Set.fromList ids)
bId = mergeBranchIds $ map (\g -> snd $ g ^. phylo_groupBranchId) groups' bId = mergeBranchIds $ map (\g -> snd $ g ^. phylo_groupBranchId) groups'
......
...@@ -343,7 +343,7 @@ toPhyloQuality beta freq branches = ...@@ -343,7 +343,7 @@ toPhyloQuality beta freq branches =
groupsToBranches' :: Map PhyloGroupId PhyloGroup -> [[PhyloGroup]] groupsToBranches' :: Map PhyloGroupId PhyloGroup -> [[PhyloGroup]]
groupsToBranches' groups = groupsToBranches' groups =
-- | run the related component algorithm {- run the related component algorithm -}
let egos = groupBy (\gs gs' -> (fst $ fst $ head' "egos" gs) == (fst $ fst $ head' "egos" gs')) let egos = groupBy (\gs gs' -> (fst $ fst $ head' "egos" gs) == (fst $ fst $ head' "egos" gs'))
$ sortOn (\gs -> fst $ fst $ head' "egos" gs) $ sortOn (\gs -> fst $ fst $ head' "egos" gs)
$ map (\group -> [getGroupId group] $ map (\group -> [getGroupId group]
......
...@@ -48,7 +48,7 @@ getNgramsCooc cId maybeListId tabType maybeLimit = do ...@@ -48,7 +48,7 @@ getNgramsCooc cId maybeListId tabType maybeLimit = do
(ngs', ngs) <- getNgrams cId maybeListId tabType (ngs', ngs) <- getNgrams cId maybeListId tabType
let let
take' Nothing xs = xs take' Nothing xs = xs
take' (Just n) xs = take n xs take' (Just n) xs = take n xs
lId <- defaultList cId lId <- defaultList cId
......
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