module Readability.Types
( Article (..),
Settings (..),
Scores (..),
alterScores,
emptyScores,
lookupCursor,
lookupScore,
mapScores,
maxScore,
nullScores,
)
where
import Data.List (maximumBy)
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import Text.XML
import Text.XML.Cursor
data Article = Article
{
summary :: Document,
title :: Maybe T.Text,
shortTitle :: Maybe T.Text
}
deriving (Show)
data Settings = Settings
{
reRemoveAttributes :: Name -> Bool
}
newtype Scores = Scores {scoreMap :: M.Map Node (Cursor, Double)} deriving (Show)
alterScores :: (Maybe (Cursor, Double) -> Maybe (Cursor, Double)) -> Node -> Scores -> Scores
alterScores f n (Scores sm) = Scores (M.alter f n sm)
emptyScores :: Scores
emptyScores = Scores M.empty
nullScores :: Scores -> Bool
nullScores (Scores sm) = M.null sm
mapScores :: (Cursor -> Double -> (Cursor, Double)) -> Scores -> Scores
mapScores f (Scores sm) = Scores $ M.map (uncurry f) sm
lookupScore :: Node -> Scores -> Maybe Double
lookupScore n (Scores sm) = snd <$> M.lookup n sm
lookupCursor :: Node -> Scores -> Maybe Cursor
lookupCursor n (Scores sm) = fst <$> M.lookup n sm
maxScore :: Scores -> (Cursor, Double)
maxScore (Scores sm) = snd $ maximumBy (\a b -> compare (ssnd a) (ssnd b)) $ M.toList sm
where
ssnd = snd . snd