-- Copyright 2014 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

-- | 'Flags' constants, analogous to "Derive.Attrs".
module Derive.Flags where
import qualified Control.DeepSeq as DeepSeq
import qualified Data.Set as Set

import Global


-- | Flags are like 'Derive.Environ.attributes', but are used for internal
-- communication between calls, while attributes are used for to configure
-- a note for the instrument.  Keeping them separate avoids confusing the
-- performer with various internal attributes that have nothing to do with
-- instrument.
type Flags = Set Flag
newtype Flag = Flag Text
    deriving (Flag -> Flag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flag -> Flag -> Bool
$c/= :: Flag -> Flag -> Bool
== :: Flag -> Flag -> Bool
$c== :: Flag -> Flag -> Bool
Eq, Eq Flag
Flag -> Flag -> Bool
Flag -> Flag -> Ordering
Flag -> Flag -> Flag
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 :: Flag -> Flag -> Flag
$cmin :: Flag -> Flag -> Flag
max :: Flag -> Flag -> Flag
$cmax :: Flag -> Flag -> Flag
>= :: Flag -> Flag -> Bool
$c>= :: Flag -> Flag -> Bool
> :: Flag -> Flag -> Bool
$c> :: Flag -> Flag -> Bool
<= :: Flag -> Flag -> Bool
$c<= :: Flag -> Flag -> Bool
< :: Flag -> Flag -> Bool
$c< :: Flag -> Flag -> Bool
compare :: Flag -> Flag -> Ordering
$ccompare :: Flag -> Flag -> Ordering
Ord, Int -> Flag -> ShowS
[Flag] -> ShowS
Flag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flag] -> ShowS
$cshowList :: [Flag] -> ShowS
show :: Flag -> String
$cshow :: Flag -> String
showsPrec :: Int -> Flag -> ShowS
$cshowsPrec :: Int -> Flag -> ShowS
Show, Flag -> ()
forall a. (a -> ()) -> NFData a
rnf :: Flag -> ()
$crnf :: Flag -> ()
DeepSeq.NFData)

instance Pretty Flag where pretty :: Flag -> Text
pretty (Flag Text
t) = Text
t

flag :: Text -> Flags
flag :: Text -> Flags
flag = forall a. a -> Set a
Set.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Flag
Flag

-- | Does the first argument contain the second argument?
has :: Flags -> Flags -> Bool
has :: Flags -> Flags -> Bool
has = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => Set a -> Set a -> Bool
Set.isSubsetOf

-- | This note needs to wait until postproc to figure out its duration.  This
-- is used to implement final notes, where a zero duration note at the end
-- of a block can replace the first note of the next block.
infer_duration :: Flags
infer_duration :: Flags
infer_duration = Text -> Flags
flag Text
"infer-duration"

-- | This indicates that a note can be cancelled by a coincident note.  Among
-- other things, it supports 'infer_duration': a note with inferred duration
-- will replace any following note with 'weak'.
weak :: Flags
weak :: Flags
weak = Text -> Flags
flag Text
"weak"

-- | Cancel coincident notes on the same track.  This is like forcing
-- concurrent events to have 'weak'.
strong :: Flags
strong :: Flags
strong = Text -> Flags
flag Text
"strong"

-- | Mark events with lilypond code in them.  By convention, events with zero
-- duration and lilypond code are score directives, not notes at all.  This
-- is important because postprocessing dealing with notes might want to ignore
-- them.
ly_code :: Flags
ly_code :: Flags
ly_code = Text -> Flags
flag Text
"ly-code"