Commit 8d3ac246 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[CLEAN] split Prelude.Utils

parent e55c38aa
......@@ -118,7 +118,7 @@ import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Schema.Node (node_id, node_parentId, node_userId)
import Gargantext.Prelude hiding (log)
import Gargantext.Prelude.Job
import Gargantext.Prelude.Utils (hasTime, getTime)
import Gargantext.Prelude.Clock (hasTime, getTime)
import Prelude (error)
import Servant hiding (Patch)
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
......
{-|
Module : Gargantext.Prelude.Clock
Description : Useful Tools near Prelude of the project
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Prelude.Clock
where
import Data.Aeson (ToJSON, toJSON)
import Formatting.Clock (timeSpecs)
import Formatting.Internal (Format(..))
import Gargantext.Prelude
import qualified System.Clock as Clock (getTime, TimeSpec, Clock(..))
---------------------------------------------------------------------------------
getTime :: MonadBase IO m => m Clock.TimeSpec
getTime = liftBase $ Clock.getTime Clock.ProcessCPUTime
hasTime :: Formatting.Internal.Format r (Clock.TimeSpec -> Clock.TimeSpec -> r)
hasTime = timeSpecs
......@@ -23,8 +23,6 @@ import Control.Monad.Reader (MonadReader)
import Data.Aeson (ToJSON, toJSON)
import Data.Text (Text)
import Data.Tuple.Extra (both)
import Formatting.Clock (timeSpecs)
import Formatting.Internal (Format(..))
import GHC.IO (FilePath)
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Gargantext.Database.Prelude (HasConfig(..))
......@@ -35,16 +33,9 @@ import System.Directory (createDirectoryIfMissing)
import System.IO.Error
import System.Random (newStdGen)
import qualified Data.Text as Text
import qualified System.Clock as Clock (getTime, TimeSpec, Clock(..))
import qualified System.Directory as SD
import qualified System.Random.Shuffle as SRS
-------------------------------------------------------------------
hasTime :: Formatting.Internal.Format r (Clock.TimeSpec -> Clock.TimeSpec -> r)
hasTime = timeSpecs
getTime :: MonadBase IO m => m Clock.TimeSpec
getTime = liftBase $ Clock.getTime Clock.ProcessCPUTime
-------------------------------------------------------------------
-- | Main Class to use (just declare needed functions)
class GargDB a where
......
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