{-# OPTIONS -fno-monomorphism-restriction #-} module Panda.Model.Tag where import qualified Panda.Model.Post as Post -- env import Panda.Helper.Env import Prelude hiding ((.), (/), id) import qualified Data.Set as Set import qualified Data.Map as Map import qualified Data.List as List import Panda.Config.Global as Config data Tag = Tag { uid :: String -- tag/name , resources :: Set.Set String } deriving (Show, Eq) name x = x.uid.name_from_id name_from_id x = x.split "/" .tail.join' sorted xs = xs.List.sortBy(\a b -> (b.resources.Set.size) `compare` (a.resources.Set.size)) id_from_name x = tag_id / x list = do ids <- getDirectoryContents Config.tag_uri <.> (\\ [".", ".."]) <.> map ("" / Config.tag_id /) mapM get ids get id = get_resources id <.> Tag id get_resources id = (Config.flat_uri / id) .readFile <.> lines <.> map strip <.> reject empty <.> reject (head >>> (== '#')) <.> map (blog_id / ) <.> to_set -- many to many relationship is modeled using 2 maps -- one from tags, and the other from resources to_tuple x = (x.name, x.resources) tag_map' xs = xs . map (to_tuple) . to_h tag_map = list <.> tag_map' tag_reverse_map' xs = res.labeling (for_resource xs) where res = xs.map resources .reduce Set.union .to_list tag_reverse_map = list <.> tag_reverse_map' uncategorized = [] for_resource xs x = case tags of [] -> uncategorized otherwise -> tags where tags = xs.select (resources >>> Set.member x) .map name fill_tag xs x = x { Post.tags = for_resource xs (x.Post.uid) }