Working saltine encryption and decryption
This commit is contained in:
parent
f9c3a40c99
commit
9ad3d1ee7a
@ -3,6 +3,7 @@ module Core.SQLite where
|
|||||||
import Core.Types
|
import Core.Types
|
||||||
|
|
||||||
import Control.Monad.Reader (ask, lift, liftIO)
|
import Control.Monad.Reader (ask, lift, liftIO)
|
||||||
|
import Data.ByteString as B
|
||||||
import Database.SQLite.Simple
|
import Database.SQLite.Simple
|
||||||
import Database.SQLite.Simple.FromRow
|
import Database.SQLite.Simple.FromRow
|
||||||
|
|
||||||
@ -15,6 +16,7 @@ main db = do
|
|||||||
"CREATE TABLE IF NOT EXISTS pws\
|
"CREATE TABLE IF NOT EXISTS pws\
|
||||||
\ (link TEXT PRIMARY KEY,\
|
\ (link TEXT PRIMARY KEY,\
|
||||||
\ secret TEXT,\
|
\ secret TEXT,\
|
||||||
|
\ nonce TEXT,\
|
||||||
\ date DATETIME DEFAULT CURRENT_TIMESTAMP,\
|
\ date DATETIME DEFAULT CURRENT_TIMESTAMP,\
|
||||||
\ life INT,\
|
\ life INT,\
|
||||||
\ views INT,\
|
\ views INT,\
|
||||||
@ -24,8 +26,8 @@ main db = do
|
|||||||
dbPath :: PurrAction String
|
dbPath :: PurrAction String
|
||||||
dbPath = lift ask >>= (\a -> return $ dbFile a)
|
dbPath = lift ask >>= (\a -> return $ dbFile a)
|
||||||
|
|
||||||
encKey :: PurrAction String
|
encKey :: IO ByteString
|
||||||
encKey = lift ask >>= (\a -> return $ dbKey a)
|
encKey = B.readFile "./data/key"
|
||||||
|
|
||||||
confLinkLength :: PurrAction Int
|
confLinkLength :: PurrAction Int
|
||||||
confLinkLength = lift ask >>= (\a -> return $ linkLength a)
|
confLinkLength = lift ask >>= (\a -> return $ linkLength a)
|
||||||
|
@ -2,7 +2,7 @@ module Core.Types where
|
|||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Lazy as LT
|
import qualified Data.Text.Lazy as LT
|
||||||
|
import Data.ByteString as B
|
||||||
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT)
|
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT)
|
||||||
import Data.Text
|
import Data.Text
|
||||||
import Database.SQLite.Simple (ToRow)
|
import Database.SQLite.Simple (ToRow)
|
||||||
@ -34,7 +34,6 @@ data DhallConfig = DhallConfig
|
|||||||
, applicationHost :: String
|
, applicationHost :: String
|
||||||
, applicationPort :: Int
|
, applicationPort :: Int
|
||||||
, dbFile :: String
|
, dbFile :: String
|
||||||
, dbKey :: String
|
|
||||||
, linkLength :: Int
|
, linkLength :: Int
|
||||||
, adminEmail :: String
|
, adminEmail :: String
|
||||||
} deriving (Generic, Show)
|
} deriving (Generic, Show)
|
||||||
@ -42,6 +41,7 @@ data DhallConfig = DhallConfig
|
|||||||
data SecretEntry = SecretEntry
|
data SecretEntry = SecretEntry
|
||||||
{ link :: T.Text
|
{ link :: T.Text
|
||||||
, secret :: T.Text
|
, secret :: T.Text
|
||||||
|
, nonce :: B.ByteString
|
||||||
, date :: Integer
|
, date :: Integer
|
||||||
, life :: Integer
|
, life :: Integer
|
||||||
, views :: Integer
|
, views :: Integer
|
||||||
|
@ -6,14 +6,15 @@ import Feature.Generation.Passwords (Password)
|
|||||||
|
|
||||||
import Control.Monad.Reader (ask, lift, liftIO)
|
import Control.Monad.Reader (ask, lift, liftIO)
|
||||||
import Data.List.Split (splitOn)
|
import Data.List.Split (splitOn)
|
||||||
import Data.Maybe (listToMaybe, fromMaybe)
|
import Data.Maybe (listToMaybe, fromMaybe, Maybe(Just))
|
||||||
import Data.Time.Clock.POSIX (getPOSIXTime)
|
import Data.Time.Clock.POSIX (getPOSIXTime)
|
||||||
import Database.SQLite.Simple
|
import Database.SQLite.Simple
|
||||||
|
|
||||||
import qualified Crypto.Saltine.Core.SecretBox as Box
|
import qualified Crypto.Saltine.Core.SecretBox as Box
|
||||||
import qualified Crypto.Saltine.Internal.SecretBox as IBox
|
import qualified Crypto.Saltine.Class as CL
|
||||||
import qualified Data.ByteString.Base64 as B64
|
import qualified Data.ByteString.Base64 as B64
|
||||||
import qualified Data.ByteString.Char8 as B
|
import qualified Data.ByteString.Char8 as BSC8
|
||||||
|
import qualified Data.ByteString as B
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as ET
|
import qualified Data.Text.Encoding as ET
|
||||||
import qualified Data.Text.Lazy as LT
|
import qualified Data.Text.Lazy as LT
|
||||||
@ -21,7 +22,7 @@ import qualified Data.Text.Lazy as LT
|
|||||||
findByLink :: String -> PurrAction (Maybe T.Text)
|
findByLink :: String -> PurrAction (Maybe T.Text)
|
||||||
findByLink link = do
|
findByLink link = do
|
||||||
db <- dbPath
|
db <- dbPath
|
||||||
key <- encKey
|
key <- liftIO encKey
|
||||||
conn <- liftIO $ open db
|
conn <- liftIO $ open db
|
||||||
res <- liftIO $ query conn "SELECT * from pws WHERE link = ?" (Only (last $ splitOn "/" link))
|
res <- liftIO $ query conn "SELECT * from pws WHERE link = ?" (Only (last $ splitOn "/" link))
|
||||||
liftIO $ close conn
|
liftIO $ close conn
|
||||||
@ -30,26 +31,26 @@ findByLink link = do
|
|||||||
insertNewSecret :: T.Text -> Integer -> T.Text -> Integer -> PurrAction ()
|
insertNewSecret :: T.Text -> Integer -> T.Text -> Integer -> PurrAction ()
|
||||||
insertNewSecret sec life link maxViews = do
|
insertNewSecret sec life link maxViews = do
|
||||||
db <- dbPath
|
db <- dbPath
|
||||||
key <- encKey
|
key <- liftIO encKey
|
||||||
nonce <- liftIO $ Box.newNonce
|
nonce <- liftIO $ Box.newNonce
|
||||||
let encSec = encryptSecret key sec nonce
|
let encSec = encryptSecret key sec nonce
|
||||||
conn <- liftIO $ open db
|
conn <- liftIO $ open db
|
||||||
time <- liftIO $ epochTime
|
time <- liftIO $ epochTime
|
||||||
liftIO $ execute conn
|
liftIO $ execute conn
|
||||||
"INSERT INTO pws (link, secret, date, life, views, maxViews) VALUES (?, ?, ?, ?, ?, ?)"
|
"INSERT INTO pws (link, secret, nonce, date, life, views, maxViews) VALUES (?, ?, ?, ?, ?, ?, ?)"
|
||||||
(SecretEntry link (encodeSecret encSec) time life 0 maxViews)
|
(SecretEntry link (encodeSecret encSec) (CL.encode nonce) time life 0 maxViews)
|
||||||
liftIO $ close conn
|
liftIO $ close conn
|
||||||
|
|
||||||
readEncryptedSecret :: String -> [SecretEntry] -> PurrAction (Maybe T.Text)
|
readEncryptedSecret :: B.ByteString -> [SecretEntry] -> PurrAction (Maybe T.Text)
|
||||||
readEncryptedSecret key sec = do
|
readEncryptedSecret key sec = do
|
||||||
db <- dbPath
|
db <- dbPath
|
||||||
nonce <- liftIO $ Box.newNonce
|
let secNonce = nonce $ safeHead failedSecret sec
|
||||||
liftIO $ incViews sec db
|
liftIO $ incViews sec db
|
||||||
delete <- liftIO $ deleteExpiredSecret sec db
|
delete <- liftIO $ deleteExpiredSecret sec db
|
||||||
let decKey = decryptSecret key nonce $ decodeSecret $ safeHead failedSecret sec
|
let decSec = decryptSecret key secNonce $ decodeSecret $ safeHead failedSecret sec
|
||||||
if (delete)
|
if (delete)
|
||||||
then return Nothing
|
then return Nothing
|
||||||
else return (ET.decodeLatin1 <$> decKey)
|
else return (ET.decodeLatin1 <$> decSec)
|
||||||
where
|
where
|
||||||
incViews :: [SecretEntry] -> String -> IO ()
|
incViews :: [SecretEntry] -> String -> IO ()
|
||||||
incViews [] _ = return ()
|
incViews [] _ = return ()
|
||||||
@ -83,18 +84,25 @@ encodeSecret b = ET.decodeUtf8 $ B64.encode b
|
|||||||
decodeSecret :: SecretEntry -> B.ByteString
|
decodeSecret :: SecretEntry -> B.ByteString
|
||||||
decodeSecret s = B64.decodeLenient $ ET.encodeUtf8 (secret s)
|
decodeSecret s = B64.decodeLenient $ ET.encodeUtf8 (secret s)
|
||||||
|
|
||||||
encryptSecret :: String -> T.Text -> Box.Nonce -> B.ByteString
|
encryptSecret :: B.ByteString -> T.Text -> Box.Nonce -> B.ByteString
|
||||||
encryptSecret k s n = do
|
encryptSecret k s n = do
|
||||||
Box.secretbox (IBox.Key $ B.pack k) n (ET.encodeUtf8 s)
|
case (CL.decode k) of
|
||||||
|
(Just key) -> Box.secretbox key n (ET.encodeUtf8 s)
|
||||||
|
Nothing -> error "fail"
|
||||||
|
|
||||||
decryptSecret :: String -> Box.Nonce -> B.ByteString -> Maybe B.ByteString
|
decryptSecret :: B.ByteString -> B.ByteString -> B.ByteString -> Maybe B.ByteString
|
||||||
decryptSecret k n b = Box.secretboxOpen (IBox.Key $ B.pack k) n b
|
decryptSecret k n b = do
|
||||||
|
case (CL.decode k) of
|
||||||
|
(Just key) -> case (CL.decode n) of
|
||||||
|
(Just nonce) -> Box.secretboxOpen key nonce b
|
||||||
|
Nothing -> error "Failed to decode nonce"
|
||||||
|
Nothing -> error "Failed to decode secret key"
|
||||||
|
|
||||||
epochTime :: IO Integer
|
epochTime :: IO Integer
|
||||||
epochTime = fmap round getPOSIXTime
|
epochTime = fmap round getPOSIXTime
|
||||||
|
|
||||||
failedSecret :: SecretEntry
|
failedSecret :: SecretEntry
|
||||||
failedSecret = SecretEntry "fail" "fail" 0 0 0 0
|
failedSecret = SecretEntry "fail" "fail" (BSC8.pack "fail") 0 0 0 0
|
||||||
|
|
||||||
safeHead :: a -> [a] -> a
|
safeHead :: a -> [a] -> a
|
||||||
safeHead x [] = x
|
safeHead x [] = x
|
||||||
|
Loading…
x
Reference in New Issue
Block a user