module Panda.Model.Tag where

import qualified Panda.Model.Post as Post

-- env
import Panda.Helper.Env hiding (name)
import Prelude hiding ((.), (/), (^), id, readFile)
import qualified Data.Set as S
import qualified Panda.Config.Global as G


data Tag = Tag 
  { uid :: String     -- tag/name
  , name :: String
  , resources :: S.Set String
  }
  deriving (Show, Eq)

instance Resource Tag where
  resource_title = uid >>> spaced_url

-- CRUD
list             = ls G.tag_uri ^ map from_utf8 ^ map (G.tag_id /) >>= mapM get

get id           = get_resources id ^ Tag id (get_name id)
get_name id      = id.split "/" .tail.join'
get_resources id = (G.flat_uri / id.to_utf8) .readFile
  ^ filter_comment ^ lines ^ map (G.post_id / ) ^ to_set

resource_title_from_name = name_to_id >>> spaced_url
tag_map' xs       = xs . map (name &&& resources) . to_h
tag_map           = list ^ tag_map'

for_resource xs x = xs.select (resources >>> has x) .map name
fill_tag xs x     = x { Post.tags = for_resource xs (x.Post.uid) }

-- extra
sorted xs    = xs.sortBy(compare_by (resources >>> S.size)).reverse
name_to_id x = G.tag_id / x