-- Copyright 2013 Evan Laforge
-- This program is distributed under the terms of the GNU General Public
-- License 3.0, see COPYING or http://www.gnu.org/licenses/gpl-3.0.txt

-- | Tags categorize calls, and can be used to organize or filter
-- documentation.
--
-- TODO many of these document internal properties of a call, and it would be
-- better to extract them automatically, e.g. 'next', 'inverting', 'subs', etc.
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

-- * documentation

-- | Adds (or removes) attributes from notes.
attr :: Tags
attr :: Tags
attr = Text -> Tags
tag Text
"attr"

-- | Uses control modification, this is a control or pitch call that can modify
-- controls other than the control track in appears in.
cmod :: Tags
cmod :: Tags
cmod = Text -> Tags
tag Text
"cmod"

-- | This call returns a 'TrackLang.VCFunction'.
control_function :: Tags
control_function :: Tags
control_function = Text -> Tags
tag Text
"control-function"

-- | This call is a curve intorpolator, intended for the curve argument for
-- calls that interpolate curves.
curve :: Tags
curve :: Tags
curve = Tags
control_function forall a. Semigroup a => a -> a -> a
<> Text -> Tags
tag Text
"curve"

-- | Adds or transforms note in a style idiomatic to a particular instrument.
inst :: Tags
inst :: Tags
inst = Text -> Tags
tag Text
"inst"

-- | Inverting call.
inverting :: Tags
inverting :: Tags
inverting = Text -> Tags
tag Text
"inverting"

-- | Can emit lilypond.
ly :: Tags
ly :: Tags
ly = Text -> Tags
tag Text
"ly"

-- | Depends on the next event.
next :: Tags
next :: Tags
next = Text -> Tags
tag Text
"next"

-- | Adds ornaments an existing note, generally to its attack.
ornament :: Tags
ornament :: Tags
ornament = Text -> Tags
tag Text
"ornament"

-- | Transforms Score.Events.
postproc :: Tags
postproc :: Tags
postproc = Text -> Tags
tag Text
"postproc"

-- | Depends on the previous event.
prev :: Tags
prev :: Tags
prev = Text -> Tags
tag Text
"prev"

-- | Call uses randomness, and depends on the random seed.
random :: Tags
random :: Tags
random = Text -> Tags
tag Text
"random"

-- | This call emits events with the 'Derive.Environ.args' set, and requires
-- a 'postproc' call to emit the proper events.
requires_postproc :: Tags
requires_postproc :: Tags
requires_postproc = Text -> Tags
tag Text
"requires-postproc"

-- | Takes sub-events.
subs :: Tags
subs :: Tags
subs = Text -> Tags
tag Text
"subs"

-- | This transformer runs under inversion, via 'Derive.Call.Sub.under_invert'.
under_invert :: Tags
under_invert :: Tags
under_invert = Text -> Tags
tag Text
"under-invert"

-- | Saves an argument in 'Derive.Score.event_delayed_args', which means it
-- applies an Attribute, and relies on a postproc to complete the
-- transformation.
delayed :: Tags
delayed :: Tags
delayed = Text -> Tags
tag Text
"delayed"

-- | This is the other half of a 'delayed' call.  It expects an entry in
-- 'Derive.Score.event_delayed_args'.
realize_delayed :: Tags
realize_delayed :: Tags
realize_delayed = Text -> Tags
tag Text
"realize-delayed"

-- * tags with effects

-- | Give this call Derive.PrioBlock when imported.  This is a special hack
-- just for the block call.
prio_block :: Tags
prio_block :: Tags
prio_block = Text -> Tags
tag Text
"prio-block"

-- * automatically applied

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"