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:
- charger les listes
-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TupleSections #-}
module Gargantext.Core.NodeStory
( module Gargantext.Core.NodeStory.Types
......@@ -131,11 +130,13 @@ buildForest mp = unfoldForestM unfoldNode $ Map.toList mp
let initialChildren = getChildren (mSetToList $ el ^. ngramsElementChildren)
go initialChildren *> pure (mkTreeNode (n, el))
where
go :: [ TreeNode e ]
-> ExceptT BuildForestError (State (Int, Set VisitedNode)) ()
-- This function is quite simple: the internal 'State' keeps track of the current
-- 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 (x:xs) = do
(pos, visited) <- get
(!pos, !visited) <- get
let nt = fst x
case Set.member (VN pos nt) visited of
True -> throwError $ BFE_loop_detected visited
......
......@@ -8,11 +8,9 @@ Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Core.NodeStory.Types
( 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