module Text.Hyphenation.Exception
(
Exceptions
, addException
, lookupException
, scoreException
, parseExceptions
) where
import qualified Data.HashMap.Strict as HM
import Data.Monoid
import Prelude hiding (lookup)
newtype Exceptions = Exceptions (HM.HashMap String [Int])
deriving Show
zipMin :: [Int] -> [Int] -> [Int]
zipMin (x:xs) (y:ys) = min x y : zipMin xs ys
zipMin _ _ = []
instance Monoid Exceptions where
mempty = Exceptions mempty
Exceptions m `mappend` Exceptions n = Exceptions (HM.unionWith zipMin m n)
addException :: String -> Exceptions -> Exceptions
addException s (Exceptions m) = Exceptions $
HM.insertWith zipMin (filter (/= '-') s) (scoreException s) m
lookupException :: String -> Exceptions -> Maybe [Int]
lookupException s (Exceptions m) = HM.lookup s m
scoreException :: String -> [Int]
scoreException [] = [0]
scoreException (x:ys)
| x == '-' = 1 : if null ys then [] else scoreException (tail ys)
| otherwise = 0 : scoreException ys
parseExceptions :: String -> Exceptions
parseExceptions = foldr addException mempty . lines