{-# LANGUAGE Safe #-} ----------------------------------------------------------------------------- -- | -- Module : Passman.Core.PassList -- Copyright : Matthew Harm Bekkema 2016 -- License : GPL-2 -- Maintainer : mbekkema97@gmail.com -- Stability : experimental -- Portability : POSIX -- -- This module handles the Haskell representation of a passlist. A passlist file -- should have the following format: -- -- Each entry separated by a newline. Each field of an entry separated by a tab. -- The fields in order are: `passListEntryInfo`, `passListEntryLength` and -- `passListEntryMode`. If any field is missing or unparsable, default values -- will be used. -- -- This example passlist file: -- -- >google.com -- >projecteuler.net 32 -- >wiki.haskell.org Max nl -- -- Would be parsed as the following `PassList`: -- -- >[ -- > PassListEntry {passListEntryInfo = "google.com", passListEntryLength = Nothing, passListEntryMode = ncl} -- >, PassListEntry {passListEntryInfo = "projecteuler.net", passListEntryLength = Just 32, passListEntryMode = ncl} -- >, PassListEntry {passListEntryInfo = "wiki.haskell.org", passListEntryLength = Nothing, passListEntryMode = nl} -- >] -- ----------------------------------------------------------------------------- module Passman.Core.PassList ( -- * Data structures PassList , PassListEntry(..) -- * Parsing , stringToEntry , fileToEntries -- * Saving , entryToString , entriesToFile ) where import Passman.Core.Internal.Util ( strip, unmapFile, fileMap, splitOn , lEitherToMaybe) import Passman.Core.Mode (Mode, readModeDef, defaultMode) import Data.Maybe (fromMaybe) import Control.Monad (mfilter) import Data.Functor ((<$>)) import Safe (readMay) import Control.Exception (try, IOException) -- | Represents the password list. type PassList = [PassListEntry] -- | Represents an entry in the password list. data PassListEntry = PassListEntry { -- | The info string to generate the password for. passListEntryInfo :: String -- | Maximum length of the generated password. `Nothing` if no maximum -- length. , passListEntryLength :: Maybe Int -- | The mode to use when generating the password. , passListEntryMode :: Mode } deriving (Show, Eq) readLength :: String -> Maybe Int readLength = mfilter (>0) . readMay -- | Turns a `PassListEntry` back into a string parsable by `stringToEntry`. entryToString :: PassListEntry -> String entryToString (PassListEntry i l m) = i ++ "\t" ++ lengthStr ++ "\t" ++ modeStr where lengthStr = fromMaybe "Max" (show <$> l) modeStr = show m -- | Parses a string into a `PassListEntry`. Should be used on each line of the -- passlist file. stringToEntry :: String -> PassListEntry stringToEntry = helper . map strip . splitOn '\t' where helper :: [String] -> PassListEntry helper (a:b:c:_) = PassListEntry a (readLength b) (readModeDef c) helper (a:b:_) = PassListEntry a (readLength b) defaultMode helper (a:_) = PassListEntry a Nothing defaultMode helper _ = PassListEntry "" Nothing defaultMode -- | Loads the specified file and parses it into a `PassList`. Catches and -- returns the `IOException` on failure. fileToEntries :: FilePath -> IO (Either IOException PassList) fileToEntries = try . fileMap stringToEntry -- | Saves the `PassList` to file. Catches and returns the `IOException` on -- failure. entriesToFile :: FilePath -> PassList -> IO (Maybe IOException) entriesToFile fn es = lEitherToMaybe <$> try (unmapFile entryToString es fn)