module Derive.Call.Tags where
import qualified Data.Set as Set
import Global
type Tags = Set Tag
newtype Tag = Tag Text deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show, Eq Tag
Tag -> Tag -> Bool
Tag -> Tag -> Ordering
Tag -> Tag -> Tag
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmax :: Tag -> Tag -> Tag
>= :: Tag -> Tag -> Bool
$c>= :: Tag -> Tag -> Bool
> :: Tag -> Tag -> Bool
$c> :: Tag -> Tag -> Bool
<= :: Tag -> Tag -> Bool
$c<= :: Tag -> Tag -> Bool
< :: Tag -> Tag -> Bool
$c< :: Tag -> Tag -> Bool
compare :: Tag -> Tag -> Ordering
$ccompare :: Tag -> Tag -> Ordering
Ord, Tag -> Tag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Eq)
tag :: Text -> Tags
tag :: Text -> Tags
tag = forall a. a -> Set a
Set.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Tag
Tag
untag :: Tags -> [Text]
untag :: Tags -> [Text]
untag = forall a b. (a -> b) -> [a] -> [b]
map (\(Tag Text
t) -> Text
t) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> [a]
Set.toList
contains :: Tags -> Tags -> Bool
contains :: Tags -> Tags -> Bool
contains Tags
super Tags
sub = forall a. Ord a => Set a -> Set a -> Bool
Set.isSubsetOf Tags
sub Tags
super
attr :: Tags
attr :: Tags
attr = Text -> Tags
tag Text
"attr"
cmod :: Tags
cmod :: Tags
cmod = Text -> Tags
tag Text
"cmod"
control_function :: Tags
control_function :: Tags
control_function = Text -> Tags
tag Text
"control-function"
curve :: Tags
curve :: Tags
curve = Tags
control_function forall a. Semigroup a => a -> a -> a
<> Text -> Tags
tag Text
"curve"
inst :: Tags
inst :: Tags
inst = Text -> Tags
tag Text
"inst"
inverting :: Tags
inverting :: Tags
inverting = Text -> Tags
tag Text
"inverting"
ly :: Tags
ly :: Tags
ly = Text -> Tags
tag Text
"ly"
next :: Tags
next :: Tags
next = Text -> Tags
tag Text
"next"
ornament :: Tags
ornament :: Tags
ornament = Text -> Tags
tag Text
"ornament"
postproc :: Tags
postproc :: Tags
postproc = Text -> Tags
tag Text
"postproc"
prev :: Tags
prev :: Tags
prev = Text -> Tags
tag Text
"prev"
random :: Tags
random :: Tags
random = Text -> Tags
tag Text
"random"
requires_postproc :: Tags
requires_postproc :: Tags
requires_postproc = Text -> Tags
tag Text
"requires-postproc"
subs :: Tags
subs :: Tags
subs = Text -> Tags
tag Text
"subs"
under_invert :: Tags
under_invert :: Tags
under_invert = Text -> Tags
tag Text
"under-invert"
delayed :: Tags
delayed :: Tags
delayed = Text -> Tags
tag Text
"delayed"
realize_delayed :: Tags
realize_delayed :: Tags
realize_delayed = Text -> Tags
tag Text
"realize-delayed"
prio_block :: Tags
prio_block :: Tags
prio_block = Text -> Tags
tag Text
"prio-block"
generator, transformer :: Tags
generator :: Tags
generator = Text -> Tags
tag Text
"generator"
transformer :: Tags
transformer = Text -> Tags
tag Text
"transformer"
note, pitch, control, val :: Tags
note :: Tags
note = Text -> Tags
tag Text
"note"
pitch :: Tags
pitch = Text -> Tags
tag Text
"pitch"
control :: Tags
control = Text -> Tags
tag Text
"control"
val :: Tags
val = Text -> Tags
tag Text
"val"