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

[Tests] crypto tests added

parent 0d2607c3
Pipeline #957 failed with stage
......@@ -56,6 +56,7 @@ library:
- Gargantext.Database.Admin.Types.Hyperdata
- Gargantext.Database.Admin.Types.Node
- Gargantext.Prelude
- Gargantext.Prelude.Utils
- Gargantext.Text
- Gargantext.Text.Context
- Gargantext.Text.Corpus.Parsers
......
{-|
Module : Graph.Distance
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
module Graph.Distance where
import Test.Hspec
import Gargantext.Viz.Graph.Distances.Matrice
import Gargantext.Prelude
test :: IO ()
test = hspec $ do
describe "Cross" $ do
let result = cross' $ matrix 3 ([1,1..] :: [Double])
it "compare" $ do
shouldBe result (matrix 3 ([2,2..] :: [Double]))
......@@ -17,6 +17,7 @@ import qualified Ngrams.Lang.Occurrences as Occ
import qualified Ngrams.Metrics as Metrics
import qualified Parsers.Date as PD
import qualified Graph.Distance as GD
import qualified Utils.Crypto as Crypto
main :: IO ()
main = do
......@@ -25,4 +26,5 @@ main = do
-- Lang.ngramsExtractionTest EN
-- Metrics.main
PD.testFromRFC3339
GD.test
-- GD.test
Crypto.test
{-|
Module : Utils.Crypto
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Utils.Crypto where
import Data.Text (Text)
import Test.Hspec
import Gargantext.Prelude
import Gargantext.Prelude.Utils
-- | Crypto Hash tests
test :: IO ()
test = hspec $ do
describe "Hash String with frontend works" $ do
let text = "To hash with backend" :: Text
let hashed = "8a69a94d164279af2b7d1443ce08da6184b3d7e815406076e148159c284b53c3" :: Hash
-- ^ hash from fronted with text above
it "compare" $ do
hash text `shouldBe` hashed
describe "Hash List with backend works" $ do
let list = ["a","b"] :: [Text]
let hashed = "ab19ec537f09499b26f0f62eed7aefad46ab9f498e06a7328ce8e8ef90da6d86" :: Hash
-- ^ hash from frontend with text above
it "compare" $ do
hash list `shouldBe` hashed
------------------------------------------------------------------------
-- | TODO property based tests
describe "Hash works with any order of list" $ do
let hash1 = hash (["a","b"] :: [Text])
let hash2 = hash (["b","a"] :: [Text])
it "compare" $ do
hash1 `shouldBe` hash2
......@@ -54,7 +54,7 @@ instance IsHashable Char.ByteString where
. SHA.showDigest
. SHA.sha256
instance IsHashable String where
instance {-# OVERLAPPING #-} IsHashable String where
hash = hash . Char.pack
instance IsHashable Text where
......@@ -63,8 +63,8 @@ instance IsHashable Text where
instance IsHashable (Set Hash) where
hash = hash . foldl (<>) "" . Set.toList
instance IsHashable [Hash] where
hash = hash . Set.fromList
instance {-# OVERLAPPABLE #-} IsHashable a => IsHashable [a] where
hash = hash . Set.fromList . map hash
--------------------------------------------------------------------------
data NodeToHash = NodeToHash { nodeType :: NodeType
......
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