Commit 1474451e authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Merge branch 'ghc964' into 'master'

Make it compile with GHC 9.6.6

See merge request !15
parents bb15d828 07121388
with-compiler: ghc-9.4.7
packages:
./
packages: .
......@@ -53,7 +53,6 @@ library
Gargantext.Prelude.Clock
Gargantext.Prelude.Crypto.Auth
Gargantext.Prelude.Crypto.Hash
Gargantext.Prelude.Crypto.Pass.Machine
Gargantext.Prelude.Crypto.Pass.User
Gargantext.Prelude.Crypto.QRCode
Gargantext.Prelude.Crypto.Share
......@@ -74,9 +73,7 @@ library
, bytestring
, clock
, containers
, cprng-aes
, crypto-random
, cryptonite
, crypton
, directory
, filepath
, formatting
......
......@@ -26,12 +26,9 @@ dependencies:
- base >= 4.7 && < 5
- binary
- bytestring
- cipher-aes
- clock
- containers
- cprng-aes
- crypto-random
- cryptonite
- crypton
- directory
- extra
- filepath
......
{-|
Module : Gargantext.Prelude.Crypto.Pass.Machine
Description :
Copyright : (c) CNRS, 2017-Present
License : Public Domain
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Random Text generator (for machines mainly)
Thanks to
https://zuttobenkyou.wordpress.com/2011/12/23/simple-password-generation-with-haskell/
-}
{-# LANGUAGE PackageImports #-}
module Gargantext.Prelude.Crypto.Pass.Machine
where
import Data.List (nub)
-- import System.Environment (getArgs)
-- import System.IO (hSetEcho)
import Control.Monad.State
import "crypto-random" Crypto.Random (cprgGenerate)
import Crypto.Random.AESCtr
import Data.Binary (decode)
import Prelude
import qualified Data.ByteString.Lazy as B
import Data.ByteString as S (ByteString, unpack)
import Data.ByteString.Char8 as C8 (pack)
import Data.Char (chr)
strToBS :: String -> S.ByteString
strToBS = C8.pack
bsToStr :: S.ByteString -> String
bsToStr = map (chr . fromEnum) . S.unpack
keysChar, keysNum, keysPunc, keysCharNum, keysAll, keysHex :: String
keysChar = ['a'..'z'] ++ ['A'..'Z']
keysHex = ['a'..'f']
keysNum = ['0'..'9']
keysPunc = "`~!@#$%^&*()-_=+[{]}\\|;:'\",<.>/? "
keysCharNum = keysChar ++ keysNum
keysAll = keysChar ++ keysNum ++ keysPunc
giveKey :: String -> Char -> Int -> Char
giveKey keysCustom c n = extractChar $ case c of
'i' -> (keysNum ++ keysHex)
'j' -> keysNum
'k' -> keysChar
'l' -> keysCharNum
';' -> keysPunc
'h' -> (keysCharNum ++ keysCustom)
'\n' -> ['\n']
_ -> keysAll
where
extractChar xs = xs!!mod n (length xs)
showRandomKey :: Int -> String -> StateT AESRNG IO ()
showRandomKey len keysCustom = handleKey =<< liftIO getChar
where
handleKey key = case key of
'\n' -> liftIO (putChar '\n') >> showRandomKey len keysCustom
'q' -> (liftIO $ putStrLn "\nBye!") >> return ()
_ -> mapM_ f [0..len] >> (liftIO $ putStrLn []) >> showRandomKey len keysCustom
where
f _ = liftIO
. putChar
. giveKey keysCustom key
. (\n -> mod n (length (keysAll ++ keysCustom) - 1))
=<< aesRandomInt
aesRandomInt :: StateT AESRNG IO Int
aesRandomInt = do
aesState <- get
-- aesState <- liftIO makeSystem
-- let aesState = 128
let (bs, aesState') = cprgGenerate 64 aesState
put aesState'
return (decode $ B.fromChunks [bs])
printPass :: Int -> IO ()
printPass len = do
let as = ["alphanumeric","punctuation"]
let as' = filter (\c -> elem c keysAll) . nub $ unwords as
aesState <- makeSystem -- gather entropy from the system to use as the initial seed
_ <- runStateT (showRandomKey len as') aesState -- enter loop
return ()
gargPassMachine :: IO (Int, AESRNG)
gargPassMachine = do
aesState <- makeSystem -- gather entropy from the system to use as the initial seed
pass <- runStateT aesRandomInt aesState -- enter loop
pure pass
{-
main :: IO ()
main = do
hSetBuffering stdin NoBuffering -- disable buffering from STDIN
hSetBuffering stdout NoBuffering -- disable buffering from STDOUT
hSetEcho stdin False -- disable terminal echo
as <- getArgs
let as' = filter (\c -> elem c keysAll) . nub $ unwords as
mapM_ putStrLn
[ []
, "poke: 'q' quit"
, " 'j' number"
, " 'k' letter"
, " 'l' alphanumeric"
, " ';' punctuation"
, " 'h' alphanumeric" ++ (if null as' then [] else " + " ++ as')
, " 'i' hexadecimal"
, " 'ENTER' newline"
, " else any"
, []
]
aesState <- makeSystem -- gather entropy from the system to use as the initial seed
_ <- runStateT (showRandomKey as') aesState -- enter loop
return ()
-}
......@@ -16,14 +16,14 @@ Portability : POSIX
module Gargantext.Prelude.Crypto.Symmetric where
import "cryptonite" Crypto.Cipher.AES (AES256)
import "crypton" Crypto.Cipher.AES (AES256)
import Crypto.Cipher.Types (BlockCipher(..), Cipher(..), IV, makeIV)
import Crypto.Error (CryptoFailable(..), CryptoError(..))
import Data.ByteArray (ByteArray)
import Data.Either
import Data.Maybe
import Protolude -- (IO, Int, show, (++), ($), putStrLn, panic, (<*>), (<$>), (=<<), undefined, return)
import qualified "cryptonite" Crypto.Random.Types as CRT
import qualified "crypton" Crypto.Random.Types as CRT
-- | Not required, but most general implementation
data Key c 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