Commit 48e5a16c authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Small cosmetic changes

parent 6cc5cf44
Pipeline #7827 failed with stages
in 56 minutes and 29 seconds
...@@ -40,11 +40,10 @@ TODO: ...@@ -40,11 +40,10 @@ TODO:
- charger les listes - charger les listes
-} -}
{-# LANGUAGE Arrows #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-} {-# LANGUAGE TupleSections #-}
module Gargantext.Core.NodeStory module Gargantext.Core.NodeStory
( module Gargantext.Core.NodeStory.Types ( module Gargantext.Core.NodeStory.Types
...@@ -131,11 +130,13 @@ buildForest mp = unfoldForestM unfoldNode $ Map.toList mp ...@@ -131,11 +130,13 @@ buildForest mp = unfoldForestM unfoldNode $ Map.toList mp
let initialChildren = getChildren (mSetToList $ el ^. ngramsElementChildren) let initialChildren = getChildren (mSetToList $ el ^. ngramsElementChildren)
go initialChildren *> pure (mkTreeNode (n, el)) go initialChildren *> pure (mkTreeNode (n, el))
where where
go :: [ TreeNode e ] -- This function is quite simple: the internal 'State' keeps track of the current
-> ExceptT BuildForestError (State (Int, Set VisitedNode)) () -- position of the visit, and if we discover a term we already seen before, we throw
-- an error, otherwise we store it in the state at the current position and carry on.
go :: [ TreeNode e ] -> ExceptT BuildForestError (State (Int, Set VisitedNode)) ()
go [] = pure () go [] = pure ()
go (x:xs) = do go (x:xs) = do
(pos, visited) <- get (!pos, !visited) <- get
let nt = fst x let nt = fst x
case Set.member (VN pos nt) visited of case Set.member (VN pos nt) visited of
True -> throwError $ BFE_loop_detected visited True -> throwError $ BFE_loop_detected visited
......
...@@ -8,11 +8,9 @@ Stability : experimental ...@@ -8,11 +8,9 @@ Stability : experimental
Portability : POSIX Portability : POSIX
-} -}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
module Gargantext.Core.NodeStory.Types module Gargantext.Core.NodeStory.Types
( HasNodeStory ( HasNodeStory
......
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