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

[CLEAN] fix imports / explicit instances / warnings

parent 54a4da56
...@@ -28,7 +28,8 @@ import Gargantext.API.Node () -- instances ...@@ -28,7 +28,8 @@ import Gargantext.API.Node () -- instances
import Gargantext.API.Prelude (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..)) import Gargantext.Database.Action.Flow (flowCorpusFile, flowAnnuaire, TermType(..))
import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument) import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument)
import Gargantext.Database.Admin.Types.Node (CorpusId) import Gargantext.Database.Admin.Types.Node (CorpusId)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
......
...@@ -55,6 +55,7 @@ library: ...@@ -55,6 +55,7 @@ library:
- Gargantext.Core.Types.Main - Gargantext.Core.Types.Main
- Gargantext.Core.Utils.Prefix - Gargantext.Core.Utils.Prefix
- Gargantext.Database.Action.Flow - Gargantext.Database.Action.Flow
- Gargantext.Database.Action.Flow.Types
- Gargantext.Database.Action.User.New - Gargantext.Database.Action.User.New
- Gargantext.Database.Query.Table.User - Gargantext.Database.Query.Table.User
- Gargantext.Database.Query.Table.Node - Gargantext.Database.Query.Table.Node
......
...@@ -41,26 +41,21 @@ instance HasConfig Env where ...@@ -41,26 +41,21 @@ instance HasConfig Env where
instance HasConnectionPool Env where instance HasConnectionPool Env where
connPool = env_pool connPool = env_pool
{- To be removed instance HasNodeStoryEnv Env where
instance HasRepoVar Env where hasNodeStory = env_nodeStory
repoVar = repoEnv . repoVar
instance HasRepoSaver Env where instance HasNodeStoryVar Env where
repoSaver = repoEnv . repoSaver hasNodeStoryVar = hasNodeStory . nse_getter
instance HasRepo Env where
repoEnv = env_repo
-}
-- TODONS
instance HasNodeStorySaver Env
instance HasNodeStoryEnv Env
instance HasNodeStoryVar Env
instance HasNodeStorySaver Env where
hasNodeStorySaver = hasNodeStory . nse_saver
instance HasSettings Env where instance HasSettings Env where
settings = env_settings settings = env_settings
instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where
_env = env_scrapers . Servant.Job.Core._env _env = env_scrapers . Servant.Job.Core._env
...@@ -75,11 +70,13 @@ data MockEnv = MockEnv ...@@ -75,11 +70,13 @@ data MockEnv = MockEnv
makeLenses ''MockEnv makeLenses ''MockEnv
data DevEnv = DevEnv data DevEnv = DevEnv
{ _dev_env_pool :: !(Pool Connection) { _dev_env_settings :: !Settings
, _dev_env_config :: !GargConfig
, _dev_env_pool :: !(Pool Connection)
, _dev_env_nodeStory :: !NodeStoryEnv , _dev_env_nodeStory :: !NodeStoryEnv
, _dev_env_settings :: !Settings
, _dev_env_config :: !GargConfig
} }
makeLenses ''DevEnv makeLenses ''DevEnv
...@@ -90,19 +87,17 @@ instance HasConfig DevEnv where ...@@ -90,19 +87,17 @@ instance HasConfig DevEnv where
instance HasConnectionPool DevEnv where instance HasConnectionPool DevEnv where
connPool = dev_env_pool connPool = dev_env_pool
-- TODONS instance HasSettings DevEnv where
instance HasNodeStorySaver DevEnv settings = dev_env_settings
{-
instance HasRepoVar DevEnv where
repoVar = repoEnv . repoVar
instance HasRepoSaver DevEnv where
repoSaver = repoEnv . repoSaver
instance HasRepo DevEnv where instance HasNodeStoryEnv DevEnv where
repoEnv = dev_env_repo hasNodeStory = dev_env_nodeStory
-}
instance HasNodeStoryVar DevEnv where
hasNodeStoryVar = hasNodeStory . nse_getter
instance HasNodeStorySaver DevEnv where
hasNodeStorySaver = hasNodeStory . nse_saver
instance HasSettings DevEnv where
settings = dev_env_settings
...@@ -18,9 +18,9 @@ TODO-SECURITY: Critical ...@@ -18,9 +18,9 @@ TODO-SECURITY: Critical
module Gargantext.API.Admin.Settings module Gargantext.API.Admin.Settings
where where
import Codec.Serialise (Serialise(), serialise, deserialise) import Codec.Serialise (Serialise(), serialise{-, deserialise-})
import Control.Concurrent -- import Control.Concurrent
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction) -- import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction)
import Control.Lens import Control.Lens
import Control.Monad.Logger import Control.Monad.Logger
import Control.Monad.Reader import Control.Monad.Reader
...@@ -30,15 +30,15 @@ import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo) ...@@ -30,15 +30,15 @@ import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (databaseParameters, HasConfig(..)) import Gargantext.Database.Prelude (databaseParameters)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..), gc_repofilepath, readConfig) import Gargantext.Prelude.Config (GargConfig(..), {-gc_repofilepath,-} readConfig)
import Network.HTTP.Client.TLS (newTlsManager) import Network.HTTP.Client.TLS (newTlsManager)
import Servant.Auth.Server (defaultJWTSettings, CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings, readKey, writeKey) import Servant.Auth.Server (defaultJWTSettings, CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings, readKey, writeKey)
import Servant.Client (parseBaseUrl) import Servant.Client (parseBaseUrl)
import Servant.Job.Async (newJobEnv, defaultSettings) import Servant.Job.Async (newJobEnv, defaultSettings)
import System.Directory import System.Directory
import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive)) -- import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive))
import System.IO (FilePath, hClose) import System.IO (FilePath, hClose)
import System.IO.Temp (withTempFile) import System.IO.Temp (withTempFile)
import System.Log.FastLogger import System.Log.FastLogger
......
...@@ -49,7 +49,7 @@ withDevEnv iniPath k = do ...@@ -49,7 +49,7 @@ withDevEnv iniPath k = do
} }
-- | Run Cmd Sugar for the Repl (GHCI) -- | Run Cmd Sugar for the Repl (GHCI)
runCmdRepl :: (Show err, HasNodeStorySaver DevEnv) => Cmd'' DevEnv err a -> IO a runCmdRepl :: Show err => Cmd'' DevEnv err a -> IO a
runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
runCmdReplServantErr :: Cmd'' DevEnv ServerError a -> IO a runCmdReplServantErr :: Cmd'' DevEnv ServerError a -> IO a
...@@ -59,17 +59,17 @@ runCmdReplServantErr = runCmdRepl ...@@ -59,17 +59,17 @@ runCmdReplServantErr = runCmdRepl
-- the command. -- the command.
-- This function is constrained to the DevEnv rather than -- This function is constrained to the DevEnv rather than
-- using HasConnectionPool and HasRepoVar. -- using HasConnectionPool and HasRepoVar.
runCmdDev :: (Show err, HasNodeStorySaver DevEnv) => DevEnv -> Cmd'' DevEnv err a -> IO a runCmdDev :: (Show err) => DevEnv -> Cmd'' DevEnv err a -> IO a
runCmdDev env f = runCmdDev env f =
(either (fail . show) pure =<< runCmd env f) (either (fail . show) pure =<< runCmd env f)
`finally` `finally`
runReaderT saveRepo env runReaderT saveRepo env
runCmdDevNoErr :: (HasNodeStorySaver DevEnv) => DevEnv -> Cmd' DevEnv () a -> IO a runCmdDevNoErr :: DevEnv -> Cmd' DevEnv () a -> IO a
runCmdDevNoErr = runCmdDev runCmdDevNoErr = runCmdDev
runCmdDevServantErr :: (HasNodeStorySaver DevEnv) => DevEnv -> Cmd' DevEnv ServerError a -> IO a runCmdDevServantErr :: DevEnv -> Cmd' DevEnv ServerError a -> IO a
runCmdDevServantErr = runCmdDev runCmdDevServantErr = runCmdDev
runCmdReplEasy :: (HasNodeStorySaver DevEnv) => Cmd'' DevEnv GargError a -> IO a runCmdReplEasy :: Cmd'' DevEnv GargError a -> IO a
runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
...@@ -104,7 +104,6 @@ import Gargantext.API.Prelude ...@@ -104,7 +104,6 @@ import Gargantext.API.Prelude
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid, HasInvalidError) import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid, HasInvalidError)
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.Core.Utils (something)
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast') import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
......
...@@ -12,7 +12,7 @@ module Gargantext.API.Ngrams.Types where ...@@ -12,7 +12,7 @@ module Gargantext.API.Ngrams.Types where
import Codec.Serialise (Serialise()) import Codec.Serialise (Serialise())
import Control.Category ((>>>)) import Control.Category ((>>>))
import Control.Concurrent import Control.Concurrent
import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^?), (%~), (.~), (%=), at, _Just, Each(..), itraverse_, both, forOf_, (?~)) import Control.Lens (makeLenses, makePrisms, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^?), (%~), (.~), (%=), at, _Just, Each(..), itraverse_, both, forOf_, (?~))
import Control.Monad.State import Control.Monad.State
import Data.Aeson hiding ((.=)) import Data.Aeson hiding ((.=))
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
...@@ -33,7 +33,7 @@ import GHC.Generics (Generic) ...@@ -33,7 +33,7 @@ import GHC.Generics (Generic)
import Gargantext.Core.Text (size) import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..), ListId, NodeId, TODO) import Gargantext.Core.Types (ListType(..), ListId, NodeId, TODO)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
import Gargantext.Database.Prelude (fromField', CmdM', HasConnectionPool, HasConfig) import Gargantext.Database.Prelude (fromField')
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Crypto.Hash (IsHashable(..)) import Gargantext.Prelude.Crypto.Hash (IsHashable(..))
import Protolude (maybeToEither) import Protolude (maybeToEither)
......
...@@ -33,9 +33,8 @@ import Data.Typeable ...@@ -33,9 +33,8 @@ import Data.Typeable
import Data.Validity import Data.Validity
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Core.Types
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
import Gargantext.Database.Query.Tree import Gargantext.Database.Query.Tree
......
...@@ -22,7 +22,6 @@ import Gargantext.Database.Schema.Ngrams (NgramsType(..)) ...@@ -22,7 +22,6 @@ import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.HashMap.Strict as HasMap
-- TODO put this in Prelude -- TODO put this in Prelude
cons :: a -> [a] cons :: a -> [a]
...@@ -71,4 +70,3 @@ history' types lists = (Map.map (Map.unionsWith (<>))) ...@@ -71,4 +70,3 @@ history' types lists = (Map.map (Map.unionsWith (<>)))
$ unPatchMapToMap m $ unPatchMapToMap m
...@@ -16,7 +16,7 @@ Portability : POSIX ...@@ -16,7 +16,7 @@ Portability : POSIX
module Gargantext.Core.Viz.Graph.API module Gargantext.Core.Viz.Graph.API
where where
import Control.Lens (set, (^.), _Just, (^?), at, view) import Control.Lens (set, (^.), _Just, (^?), at)
import Data.Aeson import Data.Aeson
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Swagger import Data.Swagger
...@@ -25,7 +25,6 @@ import Debug.Trace (trace) ...@@ -25,7 +25,6 @@ import Debug.Trace (trace)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.API.Ngrams.Types (NgramsRepo, r_version)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..), withMetric) import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..), withMetric)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
...@@ -43,15 +42,13 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError) ...@@ -43,15 +42,13 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Table.Node.User (getNodeUser) import Gargantext.Database.Query.Table.Node.User (getNodeUser)
import Gargantext.Database.Schema.Node
import Gargantext.Database.Schema.Ngrams import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node (node_parent_id, node_hyperdata, node_name, node_user_id)
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Job.Async import Servant.Job.Async
import Servant.XML import Servant.XML
import qualified Gargantext.Database.Schema.Node as Node
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | There is no Delete specific API for Graph since it can be deleted -- | There is no Delete specific API for Graph since it can be deleted
......
...@@ -28,14 +28,13 @@ import Gargantext.Core.Text.Context (TermList) ...@@ -28,14 +28,13 @@ import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Terms.WithList import Gargantext.Core.Text.Terms.WithList
import Gargantext.Database.Query.Table.Node(defaultList) import Gargantext.Database.Query.Table.Node(defaultList)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Action.Flow
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Core.Viz.LegacyPhylo hiding (Svg, Dot) import Gargantext.Core.Viz.LegacyPhylo hiding (Svg, Dot)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Database.Query.Table.NodeNode (selectDocs) import Gargantext.Database.Query.Table.NodeNode (selectDocs)
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core (HasDBid)
-- import Gargantext.Core.Viz.Phylo.LevelMaker (toPhylo) -- import Gargantext.Core.Viz.Phylo.LevelMaker (toPhylo)
-- import Gargantext.Core.Viz.Phylo.Tools -- import Gargantext.Core.Viz.Phylo.Tools
...@@ -47,7 +46,7 @@ import qualified Data.Text as Text ...@@ -47,7 +46,7 @@ import qualified Data.Text as Text
type MinSizeBranch = Int type MinSizeBranch = Int
flowPhylo :: FlowCmdM env err m flowPhylo :: (FlowCmdM env err m, HasDBid NodeType)
=> CorpusId => CorpusId
-> m Phylo -> m Phylo
flowPhylo cId = do flowPhylo cId = do
......
...@@ -18,7 +18,7 @@ module Gargantext.Database.Action.Flow.List ...@@ -18,7 +18,7 @@ module Gargantext.Database.Action.Flow.List
where where
import Control.Concurrent import Control.Concurrent
import Control.Lens (view, (^.), (+~), (%~), at, (.~), _Just) import Control.Lens ((^.), (+~), (%~), at, (.~), _Just)
import Control.Monad.Reader import Control.Monad.Reader
import Data.Map (Map, toList) import Data.Map (Map, toList)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
...@@ -28,7 +28,6 @@ import Gargantext.API.Ngrams.Tools (getRepoVar) ...@@ -28,7 +28,6 @@ import Gargantext.API.Ngrams.Tools (getRepoVar)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (HasInvalidError(..), assertValid) import Gargantext.Core.Types (HasInvalidError(..), assertValid)
import Gargantext.Core.Types.Main (ListType(CandidateTerm)) import Gargantext.Core.Types.Main (ListType(CandidateTerm))
import Gargantext.Core.Utils (something)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
......
...@@ -16,7 +16,7 @@ module Gargantext.Database.Action.Flow.Pairing ...@@ -16,7 +16,7 @@ module Gargantext.Database.Action.Flow.Pairing
-- (pairing) -- (pairing)
where where
import Control.Lens (_Just, (^.), view) import Control.Lens (_Just, (^.))
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.Maybe (catMaybes, fromMaybe) import Data.Maybe (catMaybes, fromMaybe)
......
...@@ -21,7 +21,6 @@ module Gargantext.Database.Action.Flow.Types ...@@ -21,7 +21,6 @@ module Gargantext.Database.Action.Flow.Types
import Data.Aeson (ToJSON) import Data.Aeson (ToJSON)
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (HasInvalidError) import Gargantext.Core.Types (HasInvalidError)
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Core.Text import Gargantext.Core.Text
......
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