Commit 2c43e4a1 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[CryptoRandom] wip

parent 0f519d6e
...@@ -22,7 +22,7 @@ module Gargantext.Core.Types ( module Gargantext.Core.Types.Main ...@@ -22,7 +22,7 @@ module Gargantext.Core.Types ( module Gargantext.Core.Types.Main
, HasInvalidError(..), assertValid , HasInvalidError(..), assertValid
, Name , Name
, TableResult(..), NodeTableResult , TableResult(..), NodeTableResult
, Ordering(..) , Ordering(..), randomOrdering, randomBool, genWith
, TODO(..) , TODO(..)
) where ) where
...@@ -30,6 +30,7 @@ import Control.Lens (Prism', (#)) ...@@ -30,6 +30,7 @@ import Control.Lens (Prism', (#))
import Control.Monad.Except (MonadError(throwError)) import Control.Monad.Except (MonadError(throwError))
import Data.Aeson import Data.Aeson
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Maybe
import Data.Monoid import Data.Monoid
import Data.Semigroup import Data.Semigroup
import Data.Set (Set, empty) import Data.Set (Set, empty)
...@@ -39,7 +40,8 @@ import Data.Text (Text, unpack) ...@@ -39,7 +40,8 @@ import Data.Text (Text, unpack)
import Data.Validity import Data.Validity
import GHC.Generics import GHC.Generics
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import System.Random
import Prelude (fromEnum, toEnum)
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Core.Utils.Prefix (unPrefix, wellNamedSchema) import Gargantext.Core.Utils.Prefix (unPrefix, wellNamedSchema)
...@@ -47,6 +49,54 @@ import Gargantext.Prelude ...@@ -47,6 +49,54 @@ import Gargantext.Prelude
------------------------------------------------------------------------ ------------------------------------------------------------------------
data Ordering = Down | Up data Ordering = Down | Up
deriving (Enum, Show, Eq, Bounded)
------------------------------------------------------------------------
-- Random work (WIP)
-- TODO mv in Prelude.Random
instance Random Ordering where
randomR (a, b) g =
case randomR (fromEnum a, fromEnum b) g of
(x, g') -> (toEnum x, g')
random g = randomR (minBound, maxBound) g
type Seed = Int
{- | Crypto work
TODO XOR to share secret
-}
randomOrdering :: Maybe Seed -> Int -> IO [Ordering]
randomOrdering = randomWith
randomBool :: Maybe Seed -> Int -> IO [Bool]
randomBool= randomWith
randomWith :: Random a => Maybe Seed -> Int -> IO [a]
randomWith seed n = do
g <- case seed of
Nothing -> newStdGen
Just s -> pure $ mkStdGen s
pure $ take n $ (randoms g)
newtype PrivateSeed = PrivateSeed Int
newtype PublicSeed = PublicSeed Int
genWith :: PrivateSeed -> PublicSeed -> Int -> IO [Bool]
genWith (PrivateSeed x) (PublicSeed o) n = do
xs <- randomBool (Just x) n
ys <- randomBool (Just o) n
pure $ zipWith xor xs ys
{-
searchSeeds :: Int -> IO [Int]
searchSeeds xs = mapM (\n -> randomWith (Just n) l) [1..]
where
l = length xs
-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Name = Text type Name = Text
type Term = Text type Term = Text
......
...@@ -52,7 +52,7 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer ...@@ -52,7 +52,7 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
, takeWhile, sqrt, identity , takeWhile, sqrt, identity
, abs, min, max, maximum, minimum, return, snd, truncate , abs, min, max, maximum, minimum, return, snd, truncate
, (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log , (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log
, Eq, (==), (>=), (<=), (<>), (/=) , Eq, (==), (>=), (<=), (<>), (/=), xor
, (&&), (||), not, any, all , (&&), (||), not, any, all
, concatMap , concatMap
, fst, snd, toS , fst, snd, toS
......
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