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

module Derive.Call.Module where
import qualified Data.String as String
import qualified Data.Text as Text

import Global


-- | The module name is dot-separated by convention, and should consist of
-- lowercase letters, digits, and dots.
newtype Module = Module Text.Text
    deriving (Module -> Module -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Module -> Module -> Bool
$c/= :: Module -> Module -> Bool
== :: Module -> Module -> Bool
$c== :: Module -> Module -> Bool
Eq, Eq Module
Module -> Module -> Bool
Module -> Module -> Ordering
Module -> Module -> Module
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 :: Module -> Module -> Module
$cmin :: Module -> Module -> Module
max :: Module -> Module -> Module
$cmax :: Module -> Module -> Module
>= :: Module -> Module -> Bool
$c>= :: Module -> Module -> Bool
> :: Module -> Module -> Bool
$c> :: Module -> Module -> Bool
<= :: Module -> Module -> Bool
$c<= :: Module -> Module -> Bool
< :: Module -> Module -> Bool
$c< :: Module -> Module -> Bool
compare :: Module -> Module -> Ordering
$ccompare :: Module -> Module -> Ordering
Ord, Int -> Module -> ShowS
[Module] -> ShowS
Module -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Module] -> ShowS
$cshowList :: [Module] -> ShowS
show :: Module -> String
$cshow :: Module -> String
showsPrec :: Int -> Module -> ShowS
$cshowsPrec :: Int -> Module -> ShowS
Show, String -> Module
forall a. (String -> a) -> IsString a
fromString :: String -> Module
$cfromString :: String -> Module
String.IsString)

instance Pretty Module where pretty :: Module -> Text
pretty (Module Text
m) = Text
m

instance Semigroup Module where
    Module Text
m1 <> :: Module -> Module -> Module
<> Module Text
m2
        | Text -> Bool
Text.null Text
m1 = Text -> Module
Module Text
m2
        | Text -> Bool
Text.null Text
m2 = Text -> Module
Module Text
m1
        | Bool
otherwise = Text -> Module
Module forall a b. (a -> b) -> a -> b
$ Text
m1 forall a. Semigroup a => a -> a -> a
<> Text
"." forall a. Semigroup a => a -> a -> a
<> Text
m2

instance Monoid Module where
    mempty :: Module
mempty = Module
""
    mappend :: Module -> Module -> Module
mappend = forall a. Semigroup a => a -> a -> a
(<>)

-- | This marks a standard library of \"fundamental\" calls.  They may also
-- interact more intimately with the builtin derivation machinery.  Imported
-- implicitly.
prelude :: Module
prelude :: Module
prelude = Module
"prelude"

-- | Internal calls are used to implement the basic track calls.  You should
-- never need to call them directly, and they can probably be omitted from the
-- documentation.  Imported implicitly.
internal :: Module
internal :: Module
internal = Module
"internal"

-- | Per-score calls, loaded from a definitions file.  Imported implicitly.
local :: Module
local :: Module
local = Module
"local"

-- | A pseudo-module that scale degree calls live in.
scale :: Module
scale :: Module
scale = Module
"scale"

-- | Parent module for instrument-specific calls.  This is also used for
-- instrument calls, though it doesn't really matter since the instrument
-- acts like an implicit import.
instrument :: Module
instrument :: Module
instrument = Module
"inst"

-- | Only emits lilypond, emits no \"normal\" events.  You never need to use
-- these if you aren't generating lilypond.  This is different from the @ly@
-- tag, which simply marks that the call can emit lilypond.
ly :: Module
ly :: Module
ly = Module
"ly"

-- | Calls for ornaments that occur in European music.  They generally
-- correspond to things you might see in staff notation, and many of them can
-- emit lilypond as well.
europe :: Module
europe :: Module
europe = Module
"europe"

bali :: Module
bali :: Module
bali = Module
"bali"

india :: Module
india :: Module
india = Module
"india"