{-# LANGUAGE Safe #-} {- | This is code written by Bob to check the strength of password. Observe that this module is marked as @Safe@. Untrusted code should be always compiled with the @-XSafe@ flag. -} module Bob ( strength , existsUser , updateDB , avgPass ) where import SecLib.Sec import SecLib.LowHigh import SecLib.Ref import Data.List import Data.Char import Data.Maybe import SecLib.SecIO type DB = [(Sec L String, Sec H String)] -- | This function encodes the policy "a password is strong enough". strength :: Sec l String -> Sec l Bool strength secp = do pass <- secp let len = length pass char = find isAlpha pass num = find isDigit pass return $ and $ [len > 8, isJust char, isJust num] {- | Function that checks if a user exists in the database. -} existsUser :: Ref L DB -> String -> SecIO L Bool existsUser ref user = do secdb <- readRefSecIO ref let db = public secdb let secnames = (sequence . (map fst)) db names <- toSecIO secnames return $ isJust $ find (==user) names {- | Adds a new user into the database. -} updateDB :: Ref L DB -> Sec L String -> Sec H String -> SecIO L () updateDB ref user pass = do secdb <- readRefSecIO ref let db = public secdb writeRefSecIO ref ((user,pass):db) {- | It computes the average length of the password in the system. (that information can be declassified) and reports back the overall security. -} avgPass :: Ref L DB -> (Sec H [String] -> Sec L Int) -> SecIO L Bool avgPass ref hatch = do secdb <- readRefSecIO ref let db = public secdb let secpass = sequence $ map snd db let num = hatch secpass if public num > 13 then return True else return False