tagtree-0.1.0.0: Hierarchical Tags & Tag Trees
Safe HaskellNone
LanguageHaskell2010

Data.TagTree

Synopsis

Types

newtype Tag Source #

A hierarchical tag

Tag nodes are separated by /

Constructors

Tag 

Fields

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in Data.TagTree

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Ord Tag Source # 
Instance details

Defined in Data.TagTree

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 
Instance details

Defined in Data.TagTree

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Data.TagTree

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

ToJSON Tag Source # 
Instance details

Defined in Data.TagTree

ToJSONKey Tag Source # 
Instance details

Defined in Data.TagTree

FromJSON Tag Source # 
Instance details

Defined in Data.TagTree

type Rep Tag Source # 
Instance details

Defined in Data.TagTree

type Rep Tag = D1 ('MetaData "Tag" "Data.TagTree" "tagtree-0.1.0.0-JgLsqpUm4lQJAmGKWf2tdS" 'True) (C1 ('MetaCons "Tag" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data TagPattern Source #

A glob-based pattern to match hierarchical tags

For example, the pattern

foo/**

matches both the following

foo/bar/baz
foo/baz

Instances

Instances details
Eq TagPattern Source # 
Instance details

Defined in Data.TagTree

Ord TagPattern Source # 
Instance details

Defined in Data.TagTree

Show TagPattern Source # 
Instance details

Defined in Data.TagTree

Generic TagPattern Source # 
Instance details

Defined in Data.TagTree

Associated Types

type Rep TagPattern :: Type -> Type #

ToJSON TagPattern Source # 
Instance details

Defined in Data.TagTree

FromJSON TagPattern Source # 
Instance details

Defined in Data.TagTree

type Rep TagPattern Source # 
Instance details

Defined in Data.TagTree

type Rep TagPattern = D1 ('MetaData "TagPattern" "Data.TagTree" "tagtree-0.1.0.0-JgLsqpUm4lQJAmGKWf2tdS" 'True) (C1 ('MetaCons "TagPattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTagPattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePattern)))

newtype TagNode Source #

An individual component of a hierarchical tag

The following hierarchical tag,

foo/bar/baz

has three tag nodes: foo, bar and baz

Constructors

TagNode 

Fields

Instances

Instances details
Eq TagNode Source # 
Instance details

Defined in Data.TagTree

Methods

(==) :: TagNode -> TagNode -> Bool #

(/=) :: TagNode -> TagNode -> Bool #

Ord TagNode Source # 
Instance details

Defined in Data.TagTree

Show TagNode Source # 
Instance details

Defined in Data.TagTree

Generic TagNode Source # 
Instance details

Defined in Data.TagTree

Associated Types

type Rep TagNode :: Type -> Type #

Methods

from :: TagNode -> Rep TagNode x #

to :: Rep TagNode x -> TagNode #

ToJSON TagNode Source # 
Instance details

Defined in Data.TagTree

type Rep TagNode Source # 
Instance details

Defined in Data.TagTree

type Rep TagNode = D1 ('MetaData "TagNode" "Data.TagTree" "tagtree-0.1.0.0-JgLsqpUm4lQJAmGKWf2tdS" 'True) (C1 ('MetaCons "TagNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTagNode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Create Tags

Creating Tag Trees

tagTree :: (Eq a, Default a) => Map Tag a -> Forest (TagNode, a) Source #

Construct the tree from a list of hierarchical tags

Searching Tags

Working with Tag Trees