Commit 986a7aa9 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Warning-free compilation

parent e7b5aff0
......@@ -18,7 +18,6 @@ module Gargantext.Prelude.Crypto.Pass.User
-- 1) Quick password generator imports
import Data.Text (Text)
import Data.String (String)
import Control.Monad
import Control.Monad.Random
......@@ -72,17 +71,17 @@ gargPassUserEasy n = gargPassUserEasy' (100 * fromIntegral n) n
gargPassUserEasy' :: (Num a, Enum a) => Int -> a -> [b] -> IO [b]
gargPassUserEasy' threshold size wlist
| length wlist > threshold = generatePassword size wlist
| otherwise = panic "List to short"
| otherwise = panicTrace "List to short"
generatePassword :: (Num a, Enum a) => a -> [b] -> IO [b]
generatePassword size wlist = shuffle wlist
>>= \wlist' -> mapM (\_ -> getRandomElement wlist') [1..size]
getRandomIndex :: Foldable t => t a -> IO Int
getRandomIndex list = randomRIO (0, (length list - 1))
getRandomIndex xs = randomRIO (0, (length xs - 1))
getRandomElement :: [b] -> IO b
getRandomElement list = do
index <- (getRandomIndex list)
pure (list List.!! index)
getRandomElement xs = do
index <- (getRandomIndex xs)
pure (xs List.!! index)
......@@ -14,7 +14,7 @@ module Gargantext.Prelude.Mail
where
-- import Data.Text.Internal.Lazy (Text)
import Data.Text (Text, unpack)
import Data.Text (unpack)
import Data.Maybe
import Network.Mail.SMTP hiding (htmlPart, STARTTLS)
import Gargantext.Prelude
......@@ -22,7 +22,6 @@ import Gargantext.Prelude.Config (readIniFile', val)
import Gargantext.Prelude.Mail.Types (LoginType(..), MailConfig(..))
import Network.Mail.Mime (plainPart)
import Prelude (read)
import System.IO (FilePath)
type Email = Text
......@@ -61,9 +60,9 @@ gargMail (MailConfig {..}) (GargMail { .. }) = do
TLS -> sendMailWithLoginTLS' host _mc_mail_port user password mail
STARTTLS -> sendMailWithLoginSTARTTLS' host _mc_mail_port user password mail
where
mail = simpleMail from to cc bcc gm_subject [plainPart $ cs gm_body]
mail = simpleMail sender receiver cc bcc gm_subject [plainPart $ cs gm_body]
from = Address (Just "GarganText Email") _mc_mail_from
to = [Address gm_name gm_to]
sender = Address (Just "GarganText Email") _mc_mail_from
receiver = [Address gm_name gm_to]
cc = []
bcc = []
......@@ -15,7 +15,6 @@ module Gargantext.Prelude.NLP
import qualified Data.Ini as Ini
import qualified Data.Map.Strict as Map
import Data.Text (Text, unpack)
import qualified Data.Text as T
import Data.Maybe
import Gargantext.Prelude
......@@ -23,12 +22,8 @@ import Gargantext.Prelude.Config (readIniFile', val)
import Gargantext.Prelude.NLP.Types (NLPConfig(..))
import Gargantext.Prelude.Utils (listToMaybeAll)
import Network.URI (parseURI)
import Protolude hiding (show)
import System.IO (FilePath)
type URL = Text
iniSection :: Text
iniSection = "nlp"
......@@ -45,8 +40,8 @@ readConfig fp = do
let mRet = NLPConfig <$> m_nlp_all <*> (Map.fromList <$> m_nlp_other)
case mRet of
Nothing -> panic $ T.concat [ "Cannot read config file: _nlp_all = "
, T.pack $ show m_nlp_all
, ", _nlp_other = "
, T.pack $ show m_nlp_other ]
Nothing -> panicTrace $ T.concat [ "Cannot read config file: _nlp_all = "
, T.pack $ show m_nlp_all
, ", _nlp_other = "
, T.pack $ show m_nlp_other ]
Just ret -> pure ret
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