-
Alice Brenon authored5c766a5a
Metadata.hs 1.34 KiB
{-# LANGUAGE OverloadedStrings #-}
module GEODE.Metadata
( module ArticleRecord
, module Contrastive
, module Entry
, module Record
, module SplitContext
, module TSV
, module TSV_Header
, module Types
, module Work
, groupBy
, indexBy
, sortBy ) where
import Data.Foldable as Foldable (toList)
import Data.List (sortOn)
import Data.Map.Strict as Map (Map, alter, empty, insert, toList)
import GEODE.Metadata.Contrastive as Contrastive
import GEODE.Metadata.Entry as Entry
( Entry(headword, name, page), newEntry, normalize )
import GEODE.Metadata.ArticleRecord as ArticleRecord
import GEODE.Metadata.Record as Record
import GEODE.Metadata.SplitContext as SplitContext hiding (get, page, rank)
import GEODE.Metadata.TSV as TSV
import GEODE.Metadata.TSV.Header as TSV_Header
( DefaultFields(..), HasDefaultHeader(..), WithDefaultHeader(..), glue )
import GEODE.Metadata.Types as Types
import GEODE.Metadata.Work as Work
sortBy :: (Foldable t, Ord k) => (a -> k) -> t a -> [a]
sortBy field = sortOn field . Foldable.toList
groupBy :: (Foldable t, Ord k) => (v -> k) -> t v -> [(k, [v])]
groupBy field = Map.toList . foldr group Map.empty
where
group article = Map.alter (Just . maybe [article] (article:)) (field article)
indexBy :: (Foldable t, Ord k) => (a -> k) -> t a -> Map k a
indexBy f = foldr (\a -> Map.insert (f a) a) Map.empty