2 Module : Gargantext.Prelude.Utils
3 Description : Useful Tools near Prelude of the project
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE OverloadedStrings #-}
15 module Gargantext.Prelude.Utils
18 import Control.Lens (view)
19 import Control.Monad.Reader (MonadReader)
20 import Control.Monad.IO.Class (MonadIO, liftIO)
21 import Control.Monad.Random.Class (MonadRandom)
22 import Data.Text (Text)
23 import Control.Monad.Reader (ask)
24 import GHC.IO (FilePath)
25 import Gargantext.Prelude
26 import Gargantext.API.Settings
27 import System.Random (newStdGen)
28 import qualified System.Random.Shuffle as SRS
29 import System.Directory (createDirectoryIfMissing)
30 import qualified Data.ByteString.Lazy.Char8 as Char
31 import qualified Data.Digest.Pure.SHA as SHA (sha256, showDigest)
32 import qualified Data.Text as Text
33 import Gargantext.Database.Types.Node (NodeId, NodeType)
34 import Data.ByteString (ByteString)
35 import Crypto.Argon2 as Crypto
37 import Data.ByteString.Base64.URL as URL
39 --------------------------------------------------------------------------
40 shuffle :: MonadRandom m => [a] -> m [a]
41 shuffle ns = SRS.shuffleM ns
43 --------------------------------------------------------------------------
51 --------------------------------------------------------------------------
52 data NodeToHash = NodeToHash { nodeType :: NodeType
56 secret_key :: ByteString
57 secret_key = "WRV5ymit8s~ge6%08dLR7Q!gBcpb1MY%7e67db2206"
59 type SecretKey = ByteString
61 type FolderPath = FilePath
62 type FileName = FilePath
64 hashNode :: SecretKey -> NodeToHash -> ByteString
65 hashNode sk (NodeToHash nt ni) = case hashResult of
66 Left e -> panic (cs $ show e)
67 Right h -> URL.encode h
69 hashResult = Crypto.hash Crypto.defaultHashOptions
71 (cs $ show nt <> show ni)
74 toPath :: Int -> Text -> (FolderPath,FileName)
75 toPath n x = (Text.unpack $ Text.intercalate "/" [x1,x2], Text.unpack xs)
77 (x1,x') = Text.splitAt n x
78 (x2,xs) = Text.splitAt n x'
80 class SaveFile a where
81 saveFile' :: FilePath -> a -> IO ()
83 class ReadFile a where
84 readFile' :: FilePath -> IO a
87 writeFile :: (MonadReader env m, MonadIO m, HasSettings env, SaveFile a)
90 dataPath <- view (settings . fileFolder) <$> ask
91 (fp,fn) <- liftIO $ (toPath 3) . sha . Text.pack . show <$> newStdGen
93 let foldPath = dataPath <> "/" <> fp
94 filePath = foldPath <> "/" <> fn
96 _ <- liftIO $ createDirectoryIfMissing True foldPath
97 _ <- liftIO $ saveFile' filePath a
102 readFile :: (MonadReader env m, MonadIO m, HasSettings env, ReadFile a)
105 dataPath <- view (settings . fileFolder) <$> ask
106 liftIO $ readFile' $ dataPath <> "/" <> fp