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

[Crypto] files now in G.Core.Crypto

parent 39b97774
...@@ -5,7 +5,7 @@ import Data.Swagger ...@@ -5,7 +5,7 @@ import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Prelude.Utils as Crypto (hash) import qualified Gargantext.Core.Crypto.Hash as Crypto (hash)
import GHC.Generics (Generic) import GHC.Generics (Generic)
data HashedResponse a = HashedResponse { hash :: Text, value :: a } data HashedResponse a = HashedResponse { hash :: Text, value :: a }
......
...@@ -19,22 +19,19 @@ Main exports of Gargantext: ...@@ -19,22 +19,19 @@ Main exports of Gargantext:
module Gargantext.API.Node.Corpus.Export module Gargantext.API.Node.Corpus.Export
where where
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import qualified Data.List as List
import qualified Data.Map as Map
import Data.Map (Map) import Data.Map (Map)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Set (Set) import Data.Set (Set)
import qualified Data.Set as Set
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo) import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo)
import Gargantext.API.Prelude (GargNoServer) import Gargantext.API.Prelude (GargNoServer)
import Gargantext.Core.Types -- import Gargantext.Core.Crypto.Hash (hash)
import Gargantext.Core.Types
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser) import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser)
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
...@@ -42,13 +39,16 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) ...@@ -42,13 +39,16 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Database.Admin.Types.Node (Node, NodeId, ListId, CorpusId) import Gargantext.Database.Admin.Types.Node (Node, NodeId, ListId, CorpusId)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Database.Query.Table.Node import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.Node.Select (selectNodesWithUsername)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select (selectNodesWithUsername)
import Gargantext.Database.Query.Table.NodeNode (selectDocNodes) import Gargantext.Database.Query.Table.NodeNode (selectDocNodes)
import Gargantext.Database.Schema.Node (_node_id, _node_hyperdata)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Database.Schema.Node (_node_id, _node_hyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils (hash) import Servant
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
-- Corpus Export -- Corpus Export
......
...@@ -30,7 +30,7 @@ import Gargantext.API.Ngrams (TODO) ...@@ -30,7 +30,7 @@ import Gargantext.API.Ngrams (TODO)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude -- (Cmd, CmdM) import Gargantext.Database.Prelude -- (Cmd, CmdM)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils (hash) import Gargantext.Core.Crypto.Hash (hash)
import Servant import Servant
import Servant.Multipart import Servant.Multipart
import Servant.Swagger (HasSwagger(toSwagger)) import Servant.Swagger (HasSwagger(toSwagger))
......
{-|
Module : Gargantext.Core.Crypto.Hash
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
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.Core.Crypto.Hash
where
import Prelude (String)
import Data.Set (Set)
import Data.List (foldl)
import Data.Text (Text)
import Gargantext.Prelude
import qualified Data.ByteString.Lazy.Char8 as Char
import qualified Data.Digest.Pure.SHA as SHA (sha256, showDigest)
import qualified Data.Set as Set
import qualified Data.Text as Text
--------------------------------------------------------------------------
-- | Use this datatype to keep traceability of hashes
-- TODO use newtype
type Hash = Text
-- | Class to make hashes
class IsHashable a where
hash :: a -> Hash
-- | Main API to hash text
-- using sha256 for now
instance IsHashable Char.ByteString where
hash = Text.pack
. SHA.showDigest
. SHA.sha256
instance {-# OVERLAPPING #-} IsHashable String where
hash = hash . Char.pack
instance IsHashable Text where
hash = hash . Text.unpack
instance IsHashable (Set Hash) where
hash = hash . foldl (<>) "" . Set.toList
instance {-# OVERLAPPABLE #-} IsHashable a => IsHashable [a] where
hash = hash . Set.fromList . map hash
{-| {-|
Module : Gargantext.Core.Pass Module : Gargantext.Core.Crypto.Pass
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : Public Domain License : Public Domain
...@@ -16,16 +16,16 @@ https://zuttobenkyou.wordpress.com/2011/12/23/simple-password-generation-with-ha ...@@ -16,16 +16,16 @@ https://zuttobenkyou.wordpress.com/2011/12/23/simple-password-generation-with-ha
-} -}
module Gargantext.Core.Pass module Gargantext.Core.Crypto.Pass
where where
-- import Data.List (nub)
-- import System.Environment (getArgs) -- import System.Environment (getArgs)
-- import System.IO (hSetEcho) -- import System.IO (hSetEcho)
import Control.Monad.State import Control.Monad.State
import Crypto.Random (cprgGenerate) import Crypto.Random (cprgGenerate)
import Crypto.Random.AESCtr import Crypto.Random.AESCtr
import Data.Binary (decode) import Data.Binary (decode)
import Data.List (nub)
import Prelude import Prelude
import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy as B
...@@ -74,14 +74,14 @@ aesRandomInt = do ...@@ -74,14 +74,14 @@ aesRandomInt = do
put aesState' put aesState'
return (decode $ B.fromChunks [bs]) return (decode $ B.fromChunks [bs])
-- gargPass :: Int -> IO String gargPass :: IO (Int, AESRNG)
gargPass len = do gargPass = do
let as = ["alphanumeric","punctuation"] -- let as = ["alphanumeric","punctuation"]
let as' = filter (\c -> elem c keysAll) . nub $ unwords as -- let as' = filter (\c -> elem c keysAll) . nub $ unwords as
aesState <- makeSystem -- gather entropy from the system to use as the initial seed aesState <- makeSystem -- gather entropy from the system to use as the initial seed
--_ <- runStateT (showRandomKey len as') aesState -- enter loop --_ <- runStateT (showRandomKey len as') aesState -- enter loop
-- return () -- return ()
(p,pass) <- runStateT aesRandomInt aesState -- enter loop pass <- runStateT aesRandomInt aesState -- enter loop
pure pass pure pass
{- {-
......
...@@ -28,7 +28,7 @@ import Gargantext.Database.Query.Table.Node ...@@ -28,7 +28,7 @@ import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.Node.Error import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils (hash) import Gargantext.Core.Crypto.Hash (hash)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Control.Lens (view) import Control.Lens (view)
import Gargantext.Config (GargConfig(..)) import Gargantext.Config (GargConfig(..))
......
...@@ -72,7 +72,7 @@ import Gargantext.Database.Admin.Types.Hyperdata ...@@ -72,7 +72,7 @@ import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (Cmd, runPGSQuery) import Gargantext.Database.Prelude (Cmd, runPGSQuery)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils (hash) import Gargantext.Core.Crypto.Hash (hash)
import qualified Data.Text as DT (pack, concat, take) import qualified Data.Text as DT (pack, concat, take)
-- TODO : the import of Document constructor below does not work -- TODO : the import of Document constructor below does not work
......
...@@ -14,9 +14,6 @@ Portability : POSIX ...@@ -14,9 +14,6 @@ Portability : POSIX
module Gargantext.Prelude.Utils module Gargantext.Prelude.Utils
where where
import Prelude (String)
import Data.Set (Set)
import Data.List (foldl)
import Control.Lens (view) import Control.Lens (view)
import Control.Monad.Random.Class (MonadRandom) import Control.Monad.Random.Class (MonadRandom)
import Control.Monad.Reader (MonadReader) import Control.Monad.Reader (MonadReader)
...@@ -26,46 +23,16 @@ import GHC.IO (FilePath) ...@@ -26,46 +23,16 @@ import GHC.IO (FilePath)
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Settings
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType) import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Crypto.Hash
import System.Directory (createDirectoryIfMissing) import System.Directory (createDirectoryIfMissing)
import System.Random (newStdGen) import System.Random (newStdGen)
import qualified Data.ByteString.Lazy.Char8 as Char import qualified Data.Text as Text
import qualified Data.Digest.Pure.SHA as SHA (sha256, showDigest)
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified System.Random.Shuffle as SRS import qualified System.Random.Shuffle as SRS
-------------------------------------------------------------------------- --------------------------------------------------------------------------
shuffle :: MonadRandom m => [a] -> m [a] shuffle :: MonadRandom m => [a] -> m [a]
shuffle ns = SRS.shuffleM ns shuffle ns = SRS.shuffleM ns
--------------------------------------------------------------------------
-- | Use this datatype to keep traceability of hashes
-- TODO use newtype
type Hash = Text
-- | Class to make hashes
class IsHashable a where
hash :: a -> Hash
-- | Main API to hash text
-- using sha256 for now
instance IsHashable Char.ByteString where
hash = Text.pack
. SHA.showDigest
. SHA.sha256
instance {-# OVERLAPPING #-} IsHashable String where
hash = hash . Char.pack
instance IsHashable Text where
hash = hash . Text.unpack
instance IsHashable (Set Hash) where
hash = hash . foldl (<>) "" . Set.toList
instance {-# OVERLAPPABLE #-} IsHashable a => IsHashable [a] where
hash = hash . Set.fromList . map hash
-------------------------------------------------------------------------- --------------------------------------------------------------------------
data NodeToHash = NodeToHash { nodeType :: NodeType data NodeToHash = NodeToHash { nodeType :: NodeType
, nodeId :: NodeId , nodeId :: NodeId
......
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