{-# Language CPP #-}
module Csound.Dynamic.Types.Flags(
Flags(..),
AudioFileOutput(..),
FormatHeader(..), FormatSamples(..), FormatType(..),
Dither(..), IdTags(..),
Rtaudio(..), PulseAudio(..),
MidiIO(..),
MidiRT(..), Rtmidi(..),
Displays(..), DisplayMode(..),
Config(..)
) where
import Control.Applicative
import Data.Char
import Data.Default
import Data.Maybe
import Data.Monoid
import Data.Text (Text)
import Data.Text qualified as Text
import Text.PrettyPrint.Leijen.Text
mappendBool :: Bool -> Bool -> Bool
mappendBool :: Bool -> Bool -> Bool
mappendBool Bool
a Bool
b = Any -> Bool
getAny (Any -> Bool) -> Any -> Bool
forall a b. (a -> b) -> a -> b
$ Any -> Any -> Any
forall a. Monoid a => a -> a -> a
mappend (Bool -> Any
Any Bool
a) (Bool -> Any
Any Bool
b)
data Flags = Flags
{ Flags -> AudioFileOutput
audioFileOutput :: AudioFileOutput
, Flags -> IdTags
idTags :: IdTags
, Flags -> Maybe Rtaudio
rtaudio :: Maybe Rtaudio
, Flags -> Maybe PulseAudio
pulseAudio :: Maybe PulseAudio
, Flags -> MidiIO
midiIO :: MidiIO
, Flags -> MidiRT
midiRT :: MidiRT
, Flags -> Maybe Rtmidi
rtmidi :: Maybe Rtmidi
, Flags -> Displays
displays :: Displays
, Flags -> Config
config :: Config
, Flags -> Maybe Text
flagsVerbatim :: Maybe Text
} deriving (Flags -> Flags -> Bool
(Flags -> Flags -> Bool) -> (Flags -> Flags -> Bool) -> Eq Flags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Flags -> Flags -> Bool
== :: Flags -> Flags -> Bool
$c/= :: Flags -> Flags -> Bool
/= :: Flags -> Flags -> Bool
Eq, Int -> Flags -> ShowS
[Flags] -> ShowS
Flags -> String
(Int -> Flags -> ShowS)
-> (Flags -> String) -> ([Flags] -> ShowS) -> Show Flags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Flags -> ShowS
showsPrec :: Int -> Flags -> ShowS
$cshow :: Flags -> String
show :: Flags -> String
$cshowList :: [Flags] -> ShowS
showList :: [Flags] -> ShowS
Show, ReadPrec [Flags]
ReadPrec Flags
Int -> ReadS Flags
ReadS [Flags]
(Int -> ReadS Flags)
-> ReadS [Flags]
-> ReadPrec Flags
-> ReadPrec [Flags]
-> Read Flags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Flags
readsPrec :: Int -> ReadS Flags
$creadList :: ReadS [Flags]
readList :: ReadS [Flags]
$creadPrec :: ReadPrec Flags
readPrec :: ReadPrec Flags
$creadListPrec :: ReadPrec [Flags]
readListPrec :: ReadPrec [Flags]
Read)
instance Default Flags where
def :: Flags
def = AudioFileOutput
-> IdTags
-> Maybe Rtaudio
-> Maybe PulseAudio
-> MidiIO
-> MidiRT
-> Maybe Rtmidi
-> Displays
-> Config
-> Maybe Text
-> Flags
Flags AudioFileOutput
forall a. Default a => a
def IdTags
forall a. Default a => a
def Maybe Rtaudio
forall a. Default a => a
def Maybe PulseAudio
forall a. Default a => a
def MidiIO
forall a. Default a => a
def MidiRT
forall a. Default a => a
def Maybe Rtmidi
forall a. Default a => a
def Displays
forall a. Default a => a
def Config
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup Flags where
Flags
x <> :: Flags -> Flags -> Flags
<> Flags
y = Flags
x Flags -> Flags -> Flags
`mappendFlags` Flags
y
instance Monoid Flags where
mempty :: Flags
mempty = Flags
forall a. Default a => a
def
#else
instance Monoid Flags where
mempty = def
mappend = mappendFlags
#endif
mappendFlags :: Flags -> Flags -> Flags
mappendFlags :: Flags -> Flags -> Flags
mappendFlags Flags
a Flags
b = Flags
{ audioFileOutput :: AudioFileOutput
audioFileOutput = AudioFileOutput -> AudioFileOutput -> AudioFileOutput
forall a. Monoid a => a -> a -> a
mappend (Flags -> AudioFileOutput
audioFileOutput Flags
a) (Flags -> AudioFileOutput
audioFileOutput Flags
b)
, idTags :: IdTags
idTags = IdTags -> IdTags -> IdTags
forall a. Monoid a => a -> a -> a
mappend (Flags -> IdTags
idTags Flags
a) (Flags -> IdTags
idTags Flags
b)
, rtaudio :: Maybe Rtaudio
rtaudio = Flags -> Maybe Rtaudio
rtaudio Flags
a Maybe Rtaudio -> Maybe Rtaudio -> Maybe Rtaudio
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Flags -> Maybe Rtaudio
rtaudio Flags
b
, pulseAudio :: Maybe PulseAudio
pulseAudio = Flags -> Maybe PulseAudio
pulseAudio Flags
a Maybe PulseAudio -> Maybe PulseAudio -> Maybe PulseAudio
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Flags -> Maybe PulseAudio
pulseAudio Flags
b
, midiIO :: MidiIO
midiIO = MidiIO -> MidiIO -> MidiIO
forall a. Monoid a => a -> a -> a
mappend (Flags -> MidiIO
midiIO Flags
a) (Flags -> MidiIO
midiIO Flags
b)
, midiRT :: MidiRT
midiRT = MidiRT -> MidiRT -> MidiRT
forall a. Monoid a => a -> a -> a
mappend (Flags -> MidiRT
midiRT Flags
a) (Flags -> MidiRT
midiRT Flags
b)
, rtmidi :: Maybe Rtmidi
rtmidi = Flags -> Maybe Rtmidi
rtmidi Flags
a Maybe Rtmidi -> Maybe Rtmidi -> Maybe Rtmidi
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Flags -> Maybe Rtmidi
rtmidi Flags
b
, displays :: Displays
displays = Displays -> Displays -> Displays
forall a. Monoid a => a -> a -> a
mappend (Flags -> Displays
displays Flags
a) (Flags -> Displays
displays Flags
b)
, config :: Config
config = Config -> Config -> Config
forall a. Monoid a => a -> a -> a
mappend (Flags -> Config
config Flags
a) (Flags -> Config
config Flags
b)
, flagsVerbatim :: Maybe Text
flagsVerbatim = Maybe Text -> Maybe Text -> Maybe Text
forall a. Monoid a => a -> a -> a
mappend (Flags -> Maybe Text
flagsVerbatim Flags
a) (Flags -> Maybe Text
flagsVerbatim Flags
b)
}
data AudioFileOutput = AudioFileOutput
{ AudioFileOutput -> Maybe FormatSamples
formatSamples :: Maybe FormatSamples
, AudioFileOutput -> Maybe FormatType
formatType :: Maybe FormatType
, AudioFileOutput -> Maybe Text
output :: Maybe Text
, AudioFileOutput -> Maybe Text
input :: Maybe Text
, AudioFileOutput -> Bool
nosound :: Bool
, AudioFileOutput -> Bool
nopeaks :: Bool
, AudioFileOutput -> Maybe Dither
dither :: Maybe Dither
} deriving (AudioFileOutput -> AudioFileOutput -> Bool
(AudioFileOutput -> AudioFileOutput -> Bool)
-> (AudioFileOutput -> AudioFileOutput -> Bool)
-> Eq AudioFileOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioFileOutput -> AudioFileOutput -> Bool
== :: AudioFileOutput -> AudioFileOutput -> Bool
$c/= :: AudioFileOutput -> AudioFileOutput -> Bool
/= :: AudioFileOutput -> AudioFileOutput -> Bool
Eq, Int -> AudioFileOutput -> ShowS
[AudioFileOutput] -> ShowS
AudioFileOutput -> String
(Int -> AudioFileOutput -> ShowS)
-> (AudioFileOutput -> String)
-> ([AudioFileOutput] -> ShowS)
-> Show AudioFileOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioFileOutput -> ShowS
showsPrec :: Int -> AudioFileOutput -> ShowS
$cshow :: AudioFileOutput -> String
show :: AudioFileOutput -> String
$cshowList :: [AudioFileOutput] -> ShowS
showList :: [AudioFileOutput] -> ShowS
Show, ReadPrec [AudioFileOutput]
ReadPrec AudioFileOutput
Int -> ReadS AudioFileOutput
ReadS [AudioFileOutput]
(Int -> ReadS AudioFileOutput)
-> ReadS [AudioFileOutput]
-> ReadPrec AudioFileOutput
-> ReadPrec [AudioFileOutput]
-> Read AudioFileOutput
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AudioFileOutput
readsPrec :: Int -> ReadS AudioFileOutput
$creadList :: ReadS [AudioFileOutput]
readList :: ReadS [AudioFileOutput]
$creadPrec :: ReadPrec AudioFileOutput
readPrec :: ReadPrec AudioFileOutput
$creadListPrec :: ReadPrec [AudioFileOutput]
readListPrec :: ReadPrec [AudioFileOutput]
Read)
instance Default AudioFileOutput where
def :: AudioFileOutput
def = Maybe FormatSamples
-> Maybe FormatType
-> Maybe Text
-> Maybe Text
-> Bool
-> Bool
-> Maybe Dither
-> AudioFileOutput
AudioFileOutput Maybe FormatSamples
forall a. Default a => a
def Maybe FormatType
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Bool
False Bool
False Maybe Dither
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup AudioFileOutput where
AudioFileOutput
x <> :: AudioFileOutput -> AudioFileOutput -> AudioFileOutput
<> AudioFileOutput
y = AudioFileOutput
x AudioFileOutput -> AudioFileOutput -> AudioFileOutput
`mappendAudioFileOutput` AudioFileOutput
y
instance Monoid AudioFileOutput where
mempty :: AudioFileOutput
mempty = AudioFileOutput
forall a. Default a => a
def
#else
instance Monoid AudioFileOutput where
mempty = def
mappend = mappendAudioFileOutput
#endif
mappendAudioFileOutput :: AudioFileOutput -> AudioFileOutput -> AudioFileOutput
mappendAudioFileOutput :: AudioFileOutput -> AudioFileOutput -> AudioFileOutput
mappendAudioFileOutput AudioFileOutput
a AudioFileOutput
b = AudioFileOutput
{ formatSamples :: Maybe FormatSamples
formatSamples = AudioFileOutput -> Maybe FormatSamples
formatSamples AudioFileOutput
a Maybe FormatSamples -> Maybe FormatSamples -> Maybe FormatSamples
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AudioFileOutput -> Maybe FormatSamples
formatSamples AudioFileOutput
b
, formatType :: Maybe FormatType
formatType = AudioFileOutput -> Maybe FormatType
formatType AudioFileOutput
a Maybe FormatType -> Maybe FormatType -> Maybe FormatType
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AudioFileOutput -> Maybe FormatType
formatType AudioFileOutput
b
, output :: Maybe Text
output = AudioFileOutput -> Maybe Text
output AudioFileOutput
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AudioFileOutput -> Maybe Text
output AudioFileOutput
b
, input :: Maybe Text
input = AudioFileOutput -> Maybe Text
input AudioFileOutput
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AudioFileOutput -> Maybe Text
input AudioFileOutput
b
, nosound :: Bool
nosound = Bool -> Bool -> Bool
mappendBool (AudioFileOutput -> Bool
nosound AudioFileOutput
a) (AudioFileOutput -> Bool
nosound AudioFileOutput
b)
, nopeaks :: Bool
nopeaks = Bool -> Bool -> Bool
mappendBool (AudioFileOutput -> Bool
nopeaks AudioFileOutput
a) (AudioFileOutput -> Bool
nopeaks AudioFileOutput
b)
, dither :: Maybe Dither
dither = AudioFileOutput -> Maybe Dither
dither AudioFileOutput
a Maybe Dither -> Maybe Dither -> Maybe Dither
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AudioFileOutput -> Maybe Dither
dither AudioFileOutput
b }
data = |
deriving (FormatHeader -> FormatHeader -> Bool
(FormatHeader -> FormatHeader -> Bool)
-> (FormatHeader -> FormatHeader -> Bool) -> Eq FormatHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatHeader -> FormatHeader -> Bool
== :: FormatHeader -> FormatHeader -> Bool
$c/= :: FormatHeader -> FormatHeader -> Bool
/= :: FormatHeader -> FormatHeader -> Bool
Eq, Int -> FormatHeader -> ShowS
[FormatHeader] -> ShowS
FormatHeader -> String
(Int -> FormatHeader -> ShowS)
-> (FormatHeader -> String)
-> ([FormatHeader] -> ShowS)
-> Show FormatHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatHeader -> ShowS
showsPrec :: Int -> FormatHeader -> ShowS
$cshow :: FormatHeader -> String
show :: FormatHeader -> String
$cshowList :: [FormatHeader] -> ShowS
showList :: [FormatHeader] -> ShowS
Show, ReadPrec [FormatHeader]
ReadPrec FormatHeader
Int -> ReadS FormatHeader
ReadS [FormatHeader]
(Int -> ReadS FormatHeader)
-> ReadS [FormatHeader]
-> ReadPrec FormatHeader
-> ReadPrec [FormatHeader]
-> Read FormatHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FormatHeader
readsPrec :: Int -> ReadS FormatHeader
$creadList :: ReadS [FormatHeader]
readList :: ReadS [FormatHeader]
$creadPrec :: ReadPrec FormatHeader
readPrec :: ReadPrec FormatHeader
$creadListPrec :: ReadPrec [FormatHeader]
readListPrec :: ReadPrec [FormatHeader]
Read)
data FormatSamples
= Bit24 | Alaw | Uchar | Schar
| FloatSamples | Ulaw | Short | Long
deriving (FormatSamples -> FormatSamples -> Bool
(FormatSamples -> FormatSamples -> Bool)
-> (FormatSamples -> FormatSamples -> Bool) -> Eq FormatSamples
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatSamples -> FormatSamples -> Bool
== :: FormatSamples -> FormatSamples -> Bool
$c/= :: FormatSamples -> FormatSamples -> Bool
/= :: FormatSamples -> FormatSamples -> Bool
Eq, Int -> FormatSamples -> ShowS
[FormatSamples] -> ShowS
FormatSamples -> String
(Int -> FormatSamples -> ShowS)
-> (FormatSamples -> String)
-> ([FormatSamples] -> ShowS)
-> Show FormatSamples
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatSamples -> ShowS
showsPrec :: Int -> FormatSamples -> ShowS
$cshow :: FormatSamples -> String
show :: FormatSamples -> String
$cshowList :: [FormatSamples] -> ShowS
showList :: [FormatSamples] -> ShowS
Show, ReadPrec [FormatSamples]
ReadPrec FormatSamples
Int -> ReadS FormatSamples
ReadS [FormatSamples]
(Int -> ReadS FormatSamples)
-> ReadS [FormatSamples]
-> ReadPrec FormatSamples
-> ReadPrec [FormatSamples]
-> Read FormatSamples
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FormatSamples
readsPrec :: Int -> ReadS FormatSamples
$creadList :: ReadS [FormatSamples]
readList :: ReadS [FormatSamples]
$creadPrec :: ReadPrec FormatSamples
readPrec :: ReadPrec FormatSamples
$creadListPrec :: ReadPrec [FormatSamples]
readListPrec :: ReadPrec [FormatSamples]
Read)
data Dither = Triangular | Uniform
deriving (Dither -> Dither -> Bool
(Dither -> Dither -> Bool)
-> (Dither -> Dither -> Bool) -> Eq Dither
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dither -> Dither -> Bool
== :: Dither -> Dither -> Bool
$c/= :: Dither -> Dither -> Bool
/= :: Dither -> Dither -> Bool
Eq, Int -> Dither -> ShowS
[Dither] -> ShowS
Dither -> String
(Int -> Dither -> ShowS)
-> (Dither -> String) -> ([Dither] -> ShowS) -> Show Dither
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dither -> ShowS
showsPrec :: Int -> Dither -> ShowS
$cshow :: Dither -> String
show :: Dither -> String
$cshowList :: [Dither] -> ShowS
showList :: [Dither] -> ShowS
Show, ReadPrec [Dither]
ReadPrec Dither
Int -> ReadS Dither
ReadS [Dither]
(Int -> ReadS Dither)
-> ReadS [Dither]
-> ReadPrec Dither
-> ReadPrec [Dither]
-> Read Dither
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Dither
readsPrec :: Int -> ReadS Dither
$creadList :: ReadS [Dither]
readList :: ReadS [Dither]
$creadPrec :: ReadPrec Dither
readPrec :: ReadPrec Dither
$creadListPrec :: ReadPrec [Dither]
readListPrec :: ReadPrec [Dither]
Read)
data FormatType
= Aiff | Au | Avr | Caf | Flac | Htk
| Ircam | Mat4 | Mat5 | Nis | Paf | Pvf
| Raw | Sd2 | Sds | Svx | Voc | W64
| Wav | Wavex | Xi
deriving (FormatType -> FormatType -> Bool
(FormatType -> FormatType -> Bool)
-> (FormatType -> FormatType -> Bool) -> Eq FormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatType -> FormatType -> Bool
== :: FormatType -> FormatType -> Bool
$c/= :: FormatType -> FormatType -> Bool
/= :: FormatType -> FormatType -> Bool
Eq, Int -> FormatType -> ShowS
[FormatType] -> ShowS
FormatType -> String
(Int -> FormatType -> ShowS)
-> (FormatType -> String)
-> ([FormatType] -> ShowS)
-> Show FormatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatType -> ShowS
showsPrec :: Int -> FormatType -> ShowS
$cshow :: FormatType -> String
show :: FormatType -> String
$cshowList :: [FormatType] -> ShowS
showList :: [FormatType] -> ShowS
Show, ReadPrec [FormatType]
ReadPrec FormatType
Int -> ReadS FormatType
ReadS [FormatType]
(Int -> ReadS FormatType)
-> ReadS [FormatType]
-> ReadPrec FormatType
-> ReadPrec [FormatType]
-> Read FormatType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FormatType
readsPrec :: Int -> ReadS FormatType
$creadList :: ReadS [FormatType]
readList :: ReadS [FormatType]
$creadPrec :: ReadPrec FormatType
readPrec :: ReadPrec FormatType
$creadListPrec :: ReadPrec [FormatType]
readListPrec :: ReadPrec [FormatType]
Read)
data IdTags = IdTags
{ IdTags -> Maybe Text
idArtist :: Maybe Text
, :: Maybe Text
, IdTags -> Maybe Text
idCopyright :: Maybe Text
, IdTags -> Maybe Text
idDate :: Maybe Text
, IdTags -> Maybe Text
idSoftware :: Maybe Text
, IdTags -> Maybe Text
idTitle :: Maybe Text
} deriving (IdTags -> IdTags -> Bool
(IdTags -> IdTags -> Bool)
-> (IdTags -> IdTags -> Bool) -> Eq IdTags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IdTags -> IdTags -> Bool
== :: IdTags -> IdTags -> Bool
$c/= :: IdTags -> IdTags -> Bool
/= :: IdTags -> IdTags -> Bool
Eq, Int -> IdTags -> ShowS
[IdTags] -> ShowS
IdTags -> String
(Int -> IdTags -> ShowS)
-> (IdTags -> String) -> ([IdTags] -> ShowS) -> Show IdTags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IdTags -> ShowS
showsPrec :: Int -> IdTags -> ShowS
$cshow :: IdTags -> String
show :: IdTags -> String
$cshowList :: [IdTags] -> ShowS
showList :: [IdTags] -> ShowS
Show, ReadPrec [IdTags]
ReadPrec IdTags
Int -> ReadS IdTags
ReadS [IdTags]
(Int -> ReadS IdTags)
-> ReadS [IdTags]
-> ReadPrec IdTags
-> ReadPrec [IdTags]
-> Read IdTags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IdTags
readsPrec :: Int -> ReadS IdTags
$creadList :: ReadS [IdTags]
readList :: ReadS [IdTags]
$creadPrec :: ReadPrec IdTags
readPrec :: ReadPrec IdTags
$creadListPrec :: ReadPrec [IdTags]
readListPrec :: ReadPrec [IdTags]
Read)
instance Default IdTags where
def :: IdTags
def = Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> IdTags
IdTags Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup IdTags where
IdTags
x <> :: IdTags -> IdTags -> IdTags
<> IdTags
y = IdTags
x IdTags -> IdTags -> IdTags
`mappendIdTags` IdTags
y
instance Monoid IdTags where
mempty :: IdTags
mempty = IdTags
forall a. Default a => a
def
#else
instance Monoid IdTags where
mempty = def
mappend = mappendIdTags
#endif
mappendIdTags :: IdTags -> IdTags -> IdTags
mappendIdTags :: IdTags -> IdTags -> IdTags
mappendIdTags IdTags
a IdTags
b = IdTags
{ idArtist :: Maybe Text
idArtist = IdTags -> Maybe Text
idArtist IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idArtist IdTags
b
, idComment :: Maybe Text
idComment = IdTags -> Maybe Text
idComment IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idComment IdTags
b
, idCopyright :: Maybe Text
idCopyright = IdTags -> Maybe Text
idCopyright IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idCopyright IdTags
b
, idDate :: Maybe Text
idDate = IdTags -> Maybe Text
idDate IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idDate IdTags
b
, idSoftware :: Maybe Text
idSoftware = IdTags -> Maybe Text
idSoftware IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idSoftware IdTags
b
, idTitle :: Maybe Text
idTitle = IdTags -> Maybe Text
idTitle IdTags
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IdTags -> Maybe Text
idTitle IdTags
b }
data Rtaudio
= PortAudio | Alsa
| Jack
{ Rtaudio -> Text
jackClient :: Text
, Rtaudio -> Text
jackInport :: Text
, Rtaudio -> Text
jackOutport :: Text }
| Mme | CoreAudio
| NoRtaudio
deriving (Rtaudio -> Rtaudio -> Bool
(Rtaudio -> Rtaudio -> Bool)
-> (Rtaudio -> Rtaudio -> Bool) -> Eq Rtaudio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rtaudio -> Rtaudio -> Bool
== :: Rtaudio -> Rtaudio -> Bool
$c/= :: Rtaudio -> Rtaudio -> Bool
/= :: Rtaudio -> Rtaudio -> Bool
Eq, Int -> Rtaudio -> ShowS
[Rtaudio] -> ShowS
Rtaudio -> String
(Int -> Rtaudio -> ShowS)
-> (Rtaudio -> String) -> ([Rtaudio] -> ShowS) -> Show Rtaudio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rtaudio -> ShowS
showsPrec :: Int -> Rtaudio -> ShowS
$cshow :: Rtaudio -> String
show :: Rtaudio -> String
$cshowList :: [Rtaudio] -> ShowS
showList :: [Rtaudio] -> ShowS
Show, ReadPrec [Rtaudio]
ReadPrec Rtaudio
Int -> ReadS Rtaudio
ReadS [Rtaudio]
(Int -> ReadS Rtaudio)
-> ReadS [Rtaudio]
-> ReadPrec Rtaudio
-> ReadPrec [Rtaudio]
-> Read Rtaudio
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Rtaudio
readsPrec :: Int -> ReadS Rtaudio
$creadList :: ReadS [Rtaudio]
readList :: ReadS [Rtaudio]
$creadPrec :: ReadPrec Rtaudio
readPrec :: ReadPrec Rtaudio
$creadListPrec :: ReadPrec [Rtaudio]
readListPrec :: ReadPrec [Rtaudio]
Read)
data PulseAudio = PulseAudio
{ PulseAudio -> Text
paServer :: Text
, PulseAudio -> Text
paOutput :: Text
, PulseAudio -> Text
paInput :: Text
} deriving (PulseAudio -> PulseAudio -> Bool
(PulseAudio -> PulseAudio -> Bool)
-> (PulseAudio -> PulseAudio -> Bool) -> Eq PulseAudio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PulseAudio -> PulseAudio -> Bool
== :: PulseAudio -> PulseAudio -> Bool
$c/= :: PulseAudio -> PulseAudio -> Bool
/= :: PulseAudio -> PulseAudio -> Bool
Eq, Int -> PulseAudio -> ShowS
[PulseAudio] -> ShowS
PulseAudio -> String
(Int -> PulseAudio -> ShowS)
-> (PulseAudio -> String)
-> ([PulseAudio] -> ShowS)
-> Show PulseAudio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PulseAudio -> ShowS
showsPrec :: Int -> PulseAudio -> ShowS
$cshow :: PulseAudio -> String
show :: PulseAudio -> String
$cshowList :: [PulseAudio] -> ShowS
showList :: [PulseAudio] -> ShowS
Show, ReadPrec [PulseAudio]
ReadPrec PulseAudio
Int -> ReadS PulseAudio
ReadS [PulseAudio]
(Int -> ReadS PulseAudio)
-> ReadS [PulseAudio]
-> ReadPrec PulseAudio
-> ReadPrec [PulseAudio]
-> Read PulseAudio
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PulseAudio
readsPrec :: Int -> ReadS PulseAudio
$creadList :: ReadS [PulseAudio]
readList :: ReadS [PulseAudio]
$creadPrec :: ReadPrec PulseAudio
readPrec :: ReadPrec PulseAudio
$creadListPrec :: ReadPrec [PulseAudio]
readListPrec :: ReadPrec [PulseAudio]
Read)
data MidiIO = MidiIO
{ MidiIO -> Maybe Text
midiFile :: Maybe Text
, MidiIO -> Maybe Text
midiOutFile :: Maybe Text
, MidiIO -> Maybe Text
muteTracks :: Maybe Text
, MidiIO -> Bool
rawControllerMode :: Bool
, MidiIO -> Bool
terminateOnMidi :: Bool
} deriving (MidiIO -> MidiIO -> Bool
(MidiIO -> MidiIO -> Bool)
-> (MidiIO -> MidiIO -> Bool) -> Eq MidiIO
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MidiIO -> MidiIO -> Bool
== :: MidiIO -> MidiIO -> Bool
$c/= :: MidiIO -> MidiIO -> Bool
/= :: MidiIO -> MidiIO -> Bool
Eq, Int -> MidiIO -> ShowS
[MidiIO] -> ShowS
MidiIO -> String
(Int -> MidiIO -> ShowS)
-> (MidiIO -> String) -> ([MidiIO] -> ShowS) -> Show MidiIO
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MidiIO -> ShowS
showsPrec :: Int -> MidiIO -> ShowS
$cshow :: MidiIO -> String
show :: MidiIO -> String
$cshowList :: [MidiIO] -> ShowS
showList :: [MidiIO] -> ShowS
Show, ReadPrec [MidiIO]
ReadPrec MidiIO
Int -> ReadS MidiIO
ReadS [MidiIO]
(Int -> ReadS MidiIO)
-> ReadS [MidiIO]
-> ReadPrec MidiIO
-> ReadPrec [MidiIO]
-> Read MidiIO
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MidiIO
readsPrec :: Int -> ReadS MidiIO
$creadList :: ReadS [MidiIO]
readList :: ReadS [MidiIO]
$creadPrec :: ReadPrec MidiIO
readPrec :: ReadPrec MidiIO
$creadListPrec :: ReadPrec [MidiIO]
readListPrec :: ReadPrec [MidiIO]
Read)
instance Default MidiIO where
def :: MidiIO
def = Maybe Text -> Maybe Text -> Maybe Text -> Bool -> Bool -> MidiIO
MidiIO Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Bool
False Bool
False
#if MIN_VERSION_base(4,11,0)
instance Semigroup MidiIO where
MidiIO
x <> :: MidiIO -> MidiIO -> MidiIO
<> MidiIO
y = MidiIO
x MidiIO -> MidiIO -> MidiIO
`mappendMidiIO` MidiIO
y
instance Monoid MidiIO where
mempty :: MidiIO
mempty = MidiIO
forall a. Default a => a
def
#else
instance Monoid MidiIO where
mempty = def
mappend = mappendMidiIO
#endif
mappendMidiIO :: MidiIO -> MidiIO -> MidiIO
mappendMidiIO :: MidiIO -> MidiIO -> MidiIO
mappendMidiIO MidiIO
a MidiIO
b = MidiIO
{ midiFile :: Maybe Text
midiFile = MidiIO -> Maybe Text
midiFile MidiIO
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiIO -> Maybe Text
midiFile MidiIO
b
, midiOutFile :: Maybe Text
midiOutFile = MidiIO -> Maybe Text
midiOutFile MidiIO
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiIO -> Maybe Text
midiOutFile MidiIO
b
, muteTracks :: Maybe Text
muteTracks = MidiIO -> Maybe Text
muteTracks MidiIO
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiIO -> Maybe Text
muteTracks MidiIO
b
, rawControllerMode :: Bool
rawControllerMode = Bool -> Bool -> Bool
mappendBool (MidiIO -> Bool
rawControllerMode MidiIO
a) (MidiIO -> Bool
rawControllerMode MidiIO
b)
, terminateOnMidi :: Bool
terminateOnMidi = Bool -> Bool -> Bool
mappendBool (MidiIO -> Bool
terminateOnMidi MidiIO
a) (MidiIO -> Bool
terminateOnMidi MidiIO
b) }
data MidiRT = MidiRT
{ MidiRT -> Maybe Text
midiDevice :: Maybe Text
, MidiRT -> Maybe Int
midiKey :: Maybe Int
, MidiRT -> Maybe Int
midiKeyCps :: Maybe Int
, MidiRT -> Maybe Int
midiKeyOct :: Maybe Int
, MidiRT -> Maybe Int
midiKeyPch :: Maybe Int
, MidiRT -> Maybe Int
midiVelocity :: Maybe Int
, MidiRT -> Maybe Int
midiVelocityAmp :: Maybe Int
, MidiRT -> Maybe Text
midiOutDevice :: Maybe Text
} deriving (MidiRT -> MidiRT -> Bool
(MidiRT -> MidiRT -> Bool)
-> (MidiRT -> MidiRT -> Bool) -> Eq MidiRT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MidiRT -> MidiRT -> Bool
== :: MidiRT -> MidiRT -> Bool
$c/= :: MidiRT -> MidiRT -> Bool
/= :: MidiRT -> MidiRT -> Bool
Eq, Int -> MidiRT -> ShowS
[MidiRT] -> ShowS
MidiRT -> String
(Int -> MidiRT -> ShowS)
-> (MidiRT -> String) -> ([MidiRT] -> ShowS) -> Show MidiRT
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MidiRT -> ShowS
showsPrec :: Int -> MidiRT -> ShowS
$cshow :: MidiRT -> String
show :: MidiRT -> String
$cshowList :: [MidiRT] -> ShowS
showList :: [MidiRT] -> ShowS
Show, ReadPrec [MidiRT]
ReadPrec MidiRT
Int -> ReadS MidiRT
ReadS [MidiRT]
(Int -> ReadS MidiRT)
-> ReadS [MidiRT]
-> ReadPrec MidiRT
-> ReadPrec [MidiRT]
-> Read MidiRT
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MidiRT
readsPrec :: Int -> ReadS MidiRT
$creadList :: ReadS [MidiRT]
readList :: ReadS [MidiRT]
$creadPrec :: ReadPrec MidiRT
readPrec :: ReadPrec MidiRT
$creadListPrec :: ReadPrec [MidiRT]
readListPrec :: ReadPrec [MidiRT]
Read)
instance Default MidiRT where
def :: MidiRT
def = Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> MidiRT
MidiRT Maybe Text
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def
Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup MidiRT where
MidiRT
x <> :: MidiRT -> MidiRT -> MidiRT
<> MidiRT
y = MidiRT
x MidiRT -> MidiRT -> MidiRT
`mappendMidiRT` MidiRT
y
instance Monoid MidiRT where
mempty :: MidiRT
mempty = MidiRT
forall a. Default a => a
def
#else
instance Monoid MidiRT where
mempty = def
mappend = mappendMidiRT
#endif
mappendMidiRT :: MidiRT -> MidiRT -> MidiRT
mappendMidiRT :: MidiRT -> MidiRT -> MidiRT
mappendMidiRT MidiRT
a MidiRT
b = MidiRT
{ midiDevice :: Maybe Text
midiDevice = MidiRT -> Maybe Text
midiDevice MidiRT
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Text
midiDevice MidiRT
b
, midiKey :: Maybe Int
midiKey = MidiRT -> Maybe Int
midiKey MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiKey MidiRT
b
, midiKeyCps :: Maybe Int
midiKeyCps = MidiRT -> Maybe Int
midiKeyCps MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiKeyCps MidiRT
b
, midiKeyOct :: Maybe Int
midiKeyOct = MidiRT -> Maybe Int
midiKeyOct MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiKeyOct MidiRT
b
, midiKeyPch :: Maybe Int
midiKeyPch = MidiRT -> Maybe Int
midiKeyPch MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiKeyPch MidiRT
b
, midiVelocity :: Maybe Int
midiVelocity = MidiRT -> Maybe Int
midiVelocity MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiVelocity MidiRT
b
, midiVelocityAmp :: Maybe Int
midiVelocityAmp = MidiRT -> Maybe Int
midiVelocityAmp MidiRT
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Int
midiVelocityAmp MidiRT
b
, midiOutDevice :: Maybe Text
midiOutDevice = MidiRT -> Maybe Text
midiOutDevice MidiRT
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> MidiRT -> Maybe Text
midiOutDevice MidiRT
b }
data Rtmidi = PortMidi | AlsaMidi | AlsaSeq | CoreMidi | MmeMidi | WinmmeMidi | VirtualMidi | NoRtmidi
deriving (Rtmidi -> Rtmidi -> Bool
(Rtmidi -> Rtmidi -> Bool)
-> (Rtmidi -> Rtmidi -> Bool) -> Eq Rtmidi
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rtmidi -> Rtmidi -> Bool
== :: Rtmidi -> Rtmidi -> Bool
$c/= :: Rtmidi -> Rtmidi -> Bool
/= :: Rtmidi -> Rtmidi -> Bool
Eq, Int -> Rtmidi -> ShowS
[Rtmidi] -> ShowS
Rtmidi -> String
(Int -> Rtmidi -> ShowS)
-> (Rtmidi -> String) -> ([Rtmidi] -> ShowS) -> Show Rtmidi
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rtmidi -> ShowS
showsPrec :: Int -> Rtmidi -> ShowS
$cshow :: Rtmidi -> String
show :: Rtmidi -> String
$cshowList :: [Rtmidi] -> ShowS
showList :: [Rtmidi] -> ShowS
Show, ReadPrec [Rtmidi]
ReadPrec Rtmidi
Int -> ReadS Rtmidi
ReadS [Rtmidi]
(Int -> ReadS Rtmidi)
-> ReadS [Rtmidi]
-> ReadPrec Rtmidi
-> ReadPrec [Rtmidi]
-> Read Rtmidi
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Rtmidi
readsPrec :: Int -> ReadS Rtmidi
$creadList :: ReadS [Rtmidi]
readList :: ReadS [Rtmidi]
$creadPrec :: ReadPrec Rtmidi
readPrec :: ReadPrec Rtmidi
$creadListPrec :: ReadPrec [Rtmidi]
readListPrec :: ReadPrec [Rtmidi]
Read)
data Displays = Displays
{ Displays -> Maybe Int
csdLineNums :: Maybe Int
, Displays -> Maybe DisplayMode
displayMode :: Maybe DisplayMode
, Displays -> Maybe Int
displayHeartbeat :: Maybe Int
, Displays -> Maybe Int
messageLevel :: Maybe Int
, Displays -> Maybe Int
mAmps :: Maybe Int
, Displays -> Maybe Int
mRange :: Maybe Int
, Displays -> Maybe Int
mWarnings :: Maybe Int
, Displays -> Maybe Int
mDb :: Maybe Int
, Displays -> Maybe Int
mColours :: Maybe Int
, Displays -> Maybe Int
mBenchmarks :: Maybe Int
, Displays -> Bool
msgColor :: Bool
, Displays -> Bool
displayVerbose :: Bool
, Displays -> Maybe Int
listOpcodes :: Maybe Int
} deriving (Displays -> Displays -> Bool
(Displays -> Displays -> Bool)
-> (Displays -> Displays -> Bool) -> Eq Displays
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Displays -> Displays -> Bool
== :: Displays -> Displays -> Bool
$c/= :: Displays -> Displays -> Bool
/= :: Displays -> Displays -> Bool
Eq, Int -> Displays -> ShowS
[Displays] -> ShowS
Displays -> String
(Int -> Displays -> ShowS)
-> (Displays -> String) -> ([Displays] -> ShowS) -> Show Displays
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Displays -> ShowS
showsPrec :: Int -> Displays -> ShowS
$cshow :: Displays -> String
show :: Displays -> String
$cshowList :: [Displays] -> ShowS
showList :: [Displays] -> ShowS
Show, ReadPrec [Displays]
ReadPrec Displays
Int -> ReadS Displays
ReadS [Displays]
(Int -> ReadS Displays)
-> ReadS [Displays]
-> ReadPrec Displays
-> ReadPrec [Displays]
-> Read Displays
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Displays
readsPrec :: Int -> ReadS Displays
$creadList :: ReadS [Displays]
readList :: ReadS [Displays]
$creadPrec :: ReadPrec Displays
readPrec :: ReadPrec Displays
$creadListPrec :: ReadPrec [Displays]
readListPrec :: ReadPrec [Displays]
Read)
data DisplayMode = NoDisplay | PostScriptDisplay | AsciiDisplay
deriving (DisplayMode -> DisplayMode -> Bool
(DisplayMode -> DisplayMode -> Bool)
-> (DisplayMode -> DisplayMode -> Bool) -> Eq DisplayMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisplayMode -> DisplayMode -> Bool
== :: DisplayMode -> DisplayMode -> Bool
$c/= :: DisplayMode -> DisplayMode -> Bool
/= :: DisplayMode -> DisplayMode -> Bool
Eq, Int -> DisplayMode -> ShowS
[DisplayMode] -> ShowS
DisplayMode -> String
(Int -> DisplayMode -> ShowS)
-> (DisplayMode -> String)
-> ([DisplayMode] -> ShowS)
-> Show DisplayMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisplayMode -> ShowS
showsPrec :: Int -> DisplayMode -> ShowS
$cshow :: DisplayMode -> String
show :: DisplayMode -> String
$cshowList :: [DisplayMode] -> ShowS
showList :: [DisplayMode] -> ShowS
Show, ReadPrec [DisplayMode]
ReadPrec DisplayMode
Int -> ReadS DisplayMode
ReadS [DisplayMode]
(Int -> ReadS DisplayMode)
-> ReadS [DisplayMode]
-> ReadPrec DisplayMode
-> ReadPrec [DisplayMode]
-> Read DisplayMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DisplayMode
readsPrec :: Int -> ReadS DisplayMode
$creadList :: ReadS [DisplayMode]
readList :: ReadS [DisplayMode]
$creadPrec :: ReadPrec DisplayMode
readPrec :: ReadPrec DisplayMode
$creadListPrec :: ReadPrec [DisplayMode]
readListPrec :: ReadPrec [DisplayMode]
Read)
instance Default Displays where
def :: Displays
def = Maybe Int
-> Maybe DisplayMode
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bool
-> Bool
-> Maybe Int
-> Displays
Displays Maybe Int
forall a. Default a => a
def (DisplayMode -> Maybe DisplayMode
forall a. a -> Maybe a
Just DisplayMode
NoDisplay)
Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def
Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def
Bool
False Bool
False
Maybe Int
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup Displays where
Displays
x <> :: Displays -> Displays -> Displays
<> Displays
y = Displays
x Displays -> Displays -> Displays
`mappendDisplays` Displays
y
instance Monoid Displays where
mempty :: Displays
mempty = Displays
forall a. Default a => a
def
#else
instance Monoid Displays where
mempty = def
mappend = mappendDisplays
#endif
mappendDisplays :: Displays -> Displays -> Displays
mappendDisplays :: Displays -> Displays -> Displays
mappendDisplays Displays
a Displays
b = Displays
{ csdLineNums :: Maybe Int
csdLineNums = Displays -> Maybe Int
csdLineNums Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
csdLineNums Displays
b
, displayMode :: Maybe DisplayMode
displayMode = Displays -> Maybe DisplayMode
displayMode Displays
a Maybe DisplayMode -> Maybe DisplayMode -> Maybe DisplayMode
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe DisplayMode
displayMode Displays
b
, displayHeartbeat :: Maybe Int
displayHeartbeat = Displays -> Maybe Int
displayHeartbeat Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
displayHeartbeat Displays
b
, messageLevel :: Maybe Int
messageLevel = Displays -> Maybe Int
messageLevel Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
messageLevel Displays
b
, mAmps :: Maybe Int
mAmps = Displays -> Maybe Int
mAmps Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mAmps Displays
b
, mRange :: Maybe Int
mRange = Displays -> Maybe Int
mRange Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mRange Displays
b
, mWarnings :: Maybe Int
mWarnings = Displays -> Maybe Int
mWarnings Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mWarnings Displays
b
, mDb :: Maybe Int
mDb = Displays -> Maybe Int
mDb Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mDb Displays
b
, mColours :: Maybe Int
mColours = Displays -> Maybe Int
mColours Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mColours Displays
b
, mBenchmarks :: Maybe Int
mBenchmarks = Displays -> Maybe Int
mBenchmarks Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
mBenchmarks Displays
b
, msgColor :: Bool
msgColor = Bool -> Bool -> Bool
mappendBool (Displays -> Bool
msgColor Displays
a) (Displays -> Bool
msgColor Displays
b)
, displayVerbose :: Bool
displayVerbose = Bool -> Bool -> Bool
mappendBool (Displays -> Bool
displayVerbose Displays
a) (Displays -> Bool
displayVerbose Displays
b)
, listOpcodes :: Maybe Int
listOpcodes = Displays -> Maybe Int
listOpcodes Displays
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Displays -> Maybe Int
listOpcodes Displays
b }
data Config = Config
{ Config -> Maybe Int
hwBuf :: Maybe Int
, Config -> Maybe Int
ioBuf :: Maybe Int
, Config -> Maybe Int
newKr :: Maybe Int
, Config -> Maybe Int
newSr :: Maybe Int
, Config -> Maybe Text
scoreIn :: Maybe Text
, Config -> Maybe (Text, Text)
omacro :: Maybe (Text, Text)
, Config -> Maybe (Text, Text)
smacro :: Maybe (Text, Text)
, Config -> Bool
setSched :: Bool
, Config -> Maybe Int
schedNum :: Maybe Int
, Config -> Maybe (Int, Text)
strsetN :: Maybe (Int, Text)
, Config -> Maybe Double
skipSeconds :: Maybe Double
, Config -> Maybe Int
setTempo :: Maybe Int
} deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show, ReadPrec [Config]
ReadPrec Config
Int -> ReadS Config
ReadS [Config]
(Int -> ReadS Config)
-> ReadS [Config]
-> ReadPrec Config
-> ReadPrec [Config]
-> Read Config
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Config
readsPrec :: Int -> ReadS Config
$creadList :: ReadS [Config]
readList :: ReadS [Config]
$creadPrec :: ReadPrec Config
readPrec :: ReadPrec Config
$creadListPrec :: ReadPrec [Config]
readListPrec :: ReadPrec [Config]
Read)
instance Default Config where
def :: Config
def = Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (Text, Text)
-> Maybe (Text, Text)
-> Bool
-> Maybe Int
-> Maybe (Int, Text)
-> Maybe Double
-> Maybe Int
-> Config
Config Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Text
forall a. Default a => a
def Maybe (Text, Text)
forall a. Default a => a
def Maybe (Text, Text)
forall a. Default a => a
def
Bool
False
Maybe Int
forall a. Default a => a
def Maybe (Int, Text)
forall a. Default a => a
def Maybe Double
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup Config where
Config
x <> :: Config -> Config -> Config
<> Config
y = Config
x Config -> Config -> Config
`mappendConfig` Config
y
instance Monoid Config where
mempty :: Config
mempty = Config
forall a. Default a => a
def
#else
instance Monoid Config where
mempty = def
mappend = mappendConfig
#endif
mappendConfig :: Config -> Config -> Config
mappendConfig :: Config -> Config -> Config
mappendConfig Config
a Config
b = Config
{ hwBuf :: Maybe Int
hwBuf = Config -> Maybe Int
hwBuf Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
hwBuf Config
b
, ioBuf :: Maybe Int
ioBuf = Config -> Maybe Int
ioBuf Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
ioBuf Config
b
, newKr :: Maybe Int
newKr = Config -> Maybe Int
newKr Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
newKr Config
b
, newSr :: Maybe Int
newSr = Config -> Maybe Int
newSr Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
newSr Config
b
, scoreIn :: Maybe Text
scoreIn = Config -> Maybe Text
scoreIn Config
a Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Text
scoreIn Config
b
, omacro :: Maybe (Text, Text)
omacro = Config -> Maybe (Text, Text)
omacro Config
a Maybe (Text, Text) -> Maybe (Text, Text) -> Maybe (Text, Text)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe (Text, Text)
omacro Config
b
, smacro :: Maybe (Text, Text)
smacro = Config -> Maybe (Text, Text)
smacro Config
a Maybe (Text, Text) -> Maybe (Text, Text) -> Maybe (Text, Text)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe (Text, Text)
smacro Config
b
, setSched :: Bool
setSched = Bool -> Bool -> Bool
mappendBool (Config -> Bool
setSched Config
a) (Config -> Bool
setSched Config
b)
, schedNum :: Maybe Int
schedNum = Config -> Maybe Int
schedNum Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
schedNum Config
b
, strsetN :: Maybe (Int, Text)
strsetN = Config -> Maybe (Int, Text)
strsetN Config
a Maybe (Int, Text) -> Maybe (Int, Text) -> Maybe (Int, Text)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe (Int, Text)
strsetN Config
b
, skipSeconds :: Maybe Double
skipSeconds = Config -> Maybe Double
skipSeconds Config
a Maybe Double -> Maybe Double -> Maybe Double
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Double
skipSeconds Config
b
, setTempo :: Maybe Int
setTempo = Config -> Maybe Int
setTempo Config
a Maybe Int -> Maybe Int -> Maybe Int
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> Maybe Int
setTempo Config
b }
p :: Pretty b => (a -> Maybe b) -> (a -> Maybe Doc)
p :: forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p = ((b -> Doc) -> Maybe b -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Doc
forall a. Pretty a => a -> Doc
pretty (Maybe b -> Maybe Doc) -> (a -> Maybe b) -> a -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. )
pe :: Pretty b => (a -> b) -> (a -> Maybe Doc)
pe :: forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe a -> b
f = b -> Maybe Doc
forall {p}. Pretty p => p -> Maybe Doc
phi (b -> Maybe Doc) -> (a -> b) -> a -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f
where phi :: p -> Maybe Doc
phi p
x
| String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Doc -> String
forall a. Show a => a -> String
show Doc
res) = Maybe Doc
forall a. Maybe a
Nothing
| Bool
otherwise = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
res
where res :: Doc
res = p -> Doc
forall a. Pretty a => a -> Doc
pretty p
x
bo :: Text -> (a -> Bool) -> (a -> Maybe Doc)
bo :: forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
property a -> Bool
extract a
a
| a -> Bool
extract a
a = Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ Text -> Doc
textStrict Text
property
| Bool
otherwise = Maybe Doc
forall a. Maybe a
Nothing
mp :: Pretty b => (Doc -> Doc) -> (a -> Maybe b) -> (a -> Maybe Doc)
mp :: forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp Doc -> Doc
f a -> Maybe b
a = (b -> Doc) -> Maybe b -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Doc -> Doc
f (Doc -> Doc) -> (b -> Doc) -> b -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Doc
forall a. Pretty a => a -> Doc
pretty) (Maybe b -> Maybe Doc) -> (a -> Maybe b) -> a -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe b
a
p1 :: Doc -> Doc -> Doc
p1 :: Doc -> Doc -> Doc
p1 Doc
pref Doc
x = [Doc] -> Doc
hcat [Char -> Doc
char Char
'-', Doc
pref, Char -> Doc
char Char
' ', Doc
x]
p2 :: Doc -> Doc -> Doc
p2 :: Doc -> Doc -> Doc
p2 Doc
pref Doc
x = [Doc] -> Doc
hcat [Char -> Doc
char Char
'-', Char -> Doc
char Char
'-', Doc
pref, Char -> Doc
char Char
'=', Doc
x]
p3 :: Doc -> Doc -> Doc
p3 :: Doc -> Doc -> Doc
p3 Doc
pref Doc
x = [Doc] -> Doc
hcat [Char -> Doc
char Char
'-', Char -> Doc
char Char
'+', Doc
pref, Char -> Doc
char Char
'=', Doc
x]
fields :: [a -> Maybe Doc] -> a -> Doc
fields :: forall a. [a -> Maybe Doc] -> a -> Doc
fields [a -> Maybe Doc]
fs a
a = [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((a -> Maybe Doc) -> Maybe Doc) -> [a -> Maybe Doc] -> [Doc]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ( (a -> Maybe Doc) -> a -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ a
a) [a -> Maybe Doc]
fs
instance Pretty Flags where
pretty :: Flags -> Doc
pretty = [Flags -> Maybe Doc] -> Flags -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Flags -> Displays) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> Displays
displays
, (Flags -> Config) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> Config
config
, (Flags -> AudioFileOutput) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> AudioFileOutput
audioFileOutput
, (Flags -> IdTags) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> IdTags
idTags
, (Flags -> Maybe Rtaudio) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p Flags -> Maybe Rtaudio
rtaudio
, (Flags -> Maybe PulseAudio) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p Flags -> Maybe PulseAudio
pulseAudio
, (Flags -> Maybe Rtmidi) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p Flags -> Maybe Rtmidi
rtmidi
, (Flags -> MidiIO) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> MidiIO
midiIO
, (Flags -> MidiRT) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> b) -> a -> Maybe Doc
pe Flags -> MidiRT
midiRT
, (Flags -> Maybe Text) -> Flags -> Maybe Doc
forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p Flags -> Maybe Text
flagsVerbatim ]
instance Pretty AudioFileOutput where
pretty :: AudioFileOutput -> Doc
pretty = [AudioFileOutput -> Maybe Doc] -> AudioFileOutput -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Maybe FormatSamples, Maybe FormatType) -> Maybe Doc
pSamplesAndType ((Maybe FormatSamples, Maybe FormatType) -> Maybe Doc)
-> (AudioFileOutput -> (Maybe FormatSamples, Maybe FormatType))
-> AudioFileOutput
-> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\AudioFileOutput
x -> (AudioFileOutput -> Maybe FormatSamples
formatSamples AudioFileOutput
x, AudioFileOutput -> Maybe FormatType
formatType AudioFileOutput
x))
, (Doc -> Doc)
-> (AudioFileOutput -> Maybe Text) -> AudioFileOutput -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"output") AudioFileOutput -> Maybe Text
output
, (Doc -> Doc)
-> (AudioFileOutput -> Maybe Text) -> AudioFileOutput -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"input") AudioFileOutput -> Maybe Text
input
, Text -> (AudioFileOutput -> Bool) -> AudioFileOutput -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"--nosound" AudioFileOutput -> Bool
nosound
, Text -> (AudioFileOutput -> Bool) -> AudioFileOutput -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"--nopeaks" AudioFileOutput -> Bool
nopeaks
, (Doc -> Doc)
-> (AudioFileOutput -> Maybe Text) -> AudioFileOutput -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"d/Mither") ((AudioFileOutput -> Maybe Text) -> AudioFileOutput -> Maybe Doc)
-> (AudioFileOutput -> Maybe Text) -> AudioFileOutput -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ (Dither -> Text) -> Maybe Dither -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text
firstToLower (Text -> Text) -> (Dither -> Text) -> Dither -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (Dither -> String) -> Dither -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dither -> String
forall a. Show a => a -> String
show) (Maybe Dither -> Maybe Text)
-> (AudioFileOutput -> Maybe Dither)
-> AudioFileOutput
-> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioFileOutput -> Maybe Dither
dither ]
pSamplesAndType :: (Maybe FormatSamples, Maybe FormatType) -> Maybe Doc
pSamplesAndType :: (Maybe FormatSamples, Maybe FormatType) -> Maybe Doc
pSamplesAndType (Maybe FormatSamples
ma, Maybe FormatType
mb) = (Doc -> Doc) -> Maybe Doc -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Doc -> Doc
forall a. Pretty a => a -> Doc
pretty (Maybe Doc -> Maybe Doc) -> Maybe Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ case (Maybe FormatSamples
ma, Maybe FormatType
mb) of
(Maybe FormatSamples
Nothing, Maybe FormatType
Nothing) -> Maybe Doc
forall a. Maybe a
Nothing
(Just FormatSamples
a, Maybe FormatType
Nothing) -> Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc -> Doc
p2 Doc
"format" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ FormatSamples -> Doc
samplesToStr FormatSamples
a
(Maybe FormatSamples
Nothing, Just FormatType
b) -> Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc -> Doc
p2 Doc
"format" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ FormatType -> Doc
typeToStr FormatType
b
(Just FormatSamples
a, Just FormatType
b) -> Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc -> Doc
p2 Doc
"format" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ FormatSamples -> FormatType -> Doc
samplesAndTypeToStr FormatSamples
a FormatType
b
where
samplesToStr :: FormatSamples -> Doc
samplesToStr FormatSamples
x = case FormatSamples
x of
FormatSamples
Bit24 -> Doc
"24bit"
FormatSamples
FloatSamples -> Doc
"float"
FormatSamples
_ -> Text -> Doc
textStrict (Text -> Doc) -> Text -> Doc
forall a b. (a -> b) -> a -> b
$ Text -> Text
firstToLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ FormatSamples -> String
forall a. Show a => a -> String
show FormatSamples
x
typeToStr :: FormatType -> Doc
typeToStr = Text -> Doc
textStrict (Text -> Doc) -> (FormatType -> Text) -> FormatType -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
firstToLower (Text -> Text) -> (FormatType -> Text) -> FormatType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (FormatType -> String) -> FormatType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormatType -> String
forall a. Show a => a -> String
show
samplesAndTypeToStr :: FormatSamples -> FormatType -> Doc
samplesAndTypeToStr FormatSamples
a FormatType
b = [Doc] -> Doc
hcat [FormatSamples -> Doc
samplesToStr FormatSamples
a, Doc
":", FormatType -> Doc
typeToStr FormatType
b]
instance Pretty Dither where
pretty :: Dither -> Doc
pretty = Doc -> Doc -> Doc
p2 Doc
"dither" (Doc -> Doc) -> (Dither -> Doc) -> Dither -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Doc
textStrict (Text -> Doc) -> (Dither -> Text) -> Dither -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (Dither -> String) -> Dither -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dither -> String
forall a. Show a => a -> String
show
instance Pretty IdTags where
pretty :: IdTags -> Doc
pretty = [IdTags -> Maybe Doc] -> IdTags -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_artist") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idArtist)
, (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_comment") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idComment)
, (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_copyright") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idCopyright)
, (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_date") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idDate)
, (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_software") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idSoftware)
, (Doc -> Doc) -> (IdTags -> Maybe Text) -> IdTags -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"id_title") ((IdTags -> Maybe Text) -> IdTags -> Maybe Text
forall {f :: * -> *} {a}. Functor f => (a -> f Text) -> a -> f Text
subst IdTags -> Maybe Text
idTitle) ]
where
subst :: (a -> f Text) -> a -> f Text
subst a -> f Text
f = (Text -> Text) -> f Text -> f Text
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char -> Char) -> Text -> Text
Text.map Char -> Char
substSpaces) (f Text -> f Text) -> (a -> f Text) -> a -> f Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f Text
f
substSpaces :: Char -> Char
substSpaces Char
x
| Char -> Bool
isSpace Char
x = Char
'_'
| Bool
otherwise = Char
x
instance Pretty Rtaudio where
pretty :: Rtaudio -> Doc
pretty Rtaudio
x = case Rtaudio
x of
Rtaudio
PortAudio -> Doc -> Doc
rt Doc
"PortAudio"
Jack Text
name Text
ins Text
outs -> Doc -> Doc
rt Doc
"jack" Doc -> Doc -> Doc
<+> Text -> Text -> Text -> Doc
jackFields Text
name Text
ins Text
outs
Rtaudio
Mme -> Doc -> Doc
rt Doc
"mme"
Rtaudio
Alsa -> Doc -> Doc
rt Doc
"alsa"
Rtaudio
CoreAudio -> Doc -> Doc
rt Doc
"auhal"
Rtaudio
NoRtaudio -> Doc -> Doc
rt Doc
"0"
where
rt :: Doc -> Doc
rt = Doc -> Doc -> Doc
p3 Doc
"rtaudio"
jackFields :: Text -> Text -> Text -> Doc
jackFields Text
name Text
ins Text
outs =
[Doc] -> Doc
hsep
[ Doc -> Doc -> Doc
p3 Doc
"jack_client" (Text -> Doc
textStrict Text
name)
, Doc -> Doc -> Doc
p3 Doc
"jack_inportname" (Text -> Doc
textStrict Text
ins)
, Doc -> Doc -> Doc
p3 Doc
"jack_outportname" (Text -> Doc
textStrict Text
outs) ]
instance Pretty PulseAudio where
pretty :: PulseAudio -> Doc
pretty PulseAudio
a =
[Doc] -> Doc
hsep
[ Doc -> Doc -> Doc
p3 Doc
"server" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Text -> Doc
textStrict (PulseAudio -> Text
paServer PulseAudio
a)
, Doc -> Doc -> Doc
p3 Doc
"output_stream" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Text -> Doc
textStrict (PulseAudio -> Text
paOutput PulseAudio
a)
, Doc -> Doc -> Doc
p3 Doc
"input_stream" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Text -> Doc
textStrict (PulseAudio -> Text
paInput PulseAudio
a)
]
instance Pretty MidiIO where
pretty :: MidiIO -> Doc
pretty = [MidiIO -> Maybe Doc] -> MidiIO -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Doc -> Doc) -> (MidiIO -> Maybe Text) -> MidiIO -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midifile") MidiIO -> Maybe Text
midiFile
, (Doc -> Doc) -> (MidiIO -> Maybe Text) -> MidiIO -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midioutfile") MidiIO -> Maybe Text
midiOutFile
, (Doc -> Doc) -> (MidiIO -> Maybe Text) -> MidiIO -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"mute_tracks") MidiIO -> Maybe Text
muteTracks
, Text -> (MidiIO -> Bool) -> MidiIO -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"-+raw_controller_mode" MidiIO -> Bool
rawControllerMode
, Text -> (MidiIO -> Bool) -> MidiIO -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"--terminate-on-midi" MidiIO -> Bool
terminateOnMidi ]
instance Pretty MidiRT where
pretty :: MidiRT -> Doc
pretty = [MidiRT -> Maybe Doc] -> MidiRT -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Doc -> Doc) -> (MidiRT -> Maybe Text) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-device") MidiRT -> Maybe Text
midiDevice
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-key") MidiRT -> Maybe Int
midiKey
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-key-cps") MidiRT -> Maybe Int
midiKeyCps
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-key-oct") MidiRT -> Maybe Int
midiKeyOct
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-key-pch") MidiRT -> Maybe Int
midiKeyPch
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-velocity") MidiRT -> Maybe Int
midiVelocity
, (Doc -> Doc) -> (MidiRT -> Maybe Int) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"midi-velocity-amp") MidiRT -> Maybe Int
midiVelocityAmp
, (Doc -> Doc) -> (MidiRT -> Maybe Text) -> MidiRT -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p1 Doc
"Q") MidiRT -> Maybe Text
midiOutDevice ]
instance Pretty Rtmidi where
pretty :: Rtmidi -> Doc
pretty Rtmidi
x = Doc -> Doc -> Doc
p3 Doc
"rtmidi" (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ case Rtmidi
x of
Rtmidi
VirtualMidi -> Doc
"virtual"
Rtmidi
PortMidi -> Doc
"PortMidi"
Rtmidi
AlsaMidi -> Doc
"alsa"
Rtmidi
AlsaSeq -> Doc
"alsaseq"
Rtmidi
CoreMidi -> Doc
"coremidi"
Rtmidi
MmeMidi -> Doc
"mme"
Rtmidi
WinmmeMidi -> Doc
"winmme"
Rtmidi
NoRtmidi -> Doc
"0"
instance Pretty Displays where
pretty :: Displays -> Doc
pretty = [Displays -> Maybe Doc] -> Displays -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"csd-line-nums") Displays -> Maybe Int
csdLineNums
, (Displays -> Maybe DisplayMode) -> Displays -> Maybe Doc
forall b a. Pretty b => (a -> Maybe b) -> a -> Maybe Doc
p Displays -> Maybe DisplayMode
displayMode
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"heartbeat") Displays -> Maybe Int
displayHeartbeat
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"messagelevel") Displays -> Maybe Int
messageLevel
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-amps") Displays -> Maybe Int
mAmps
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-range") Displays -> Maybe Int
mRange
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-warnings") Displays -> Maybe Int
mWarnings
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-dB") Displays -> Maybe Int
mDb
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-colours") Displays -> Maybe Int
mColours
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"m-benchmarks") Displays -> Maybe Int
mBenchmarks
, Text -> (Displays -> Bool) -> Displays -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"-+msg_color" Displays -> Bool
msgColor
, Text -> (Displays -> Bool) -> Displays -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"--verbose" Displays -> Bool
displayVerbose
, (Doc -> Doc) -> (Displays -> Maybe Int) -> Displays -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"list-opcodes") Displays -> Maybe Int
listOpcodes ]
instance Pretty DisplayMode where
pretty :: DisplayMode -> Doc
pretty DisplayMode
x = case DisplayMode
x of
DisplayMode
NoDisplay -> Doc
"--nodisplays"
DisplayMode
PostScriptDisplay -> Doc
"--postscriptdisplay"
DisplayMode
AsciiDisplay -> Doc
"--asciidisplay"
instance Pretty Config where
pretty :: Config -> Doc
pretty = [Config -> Maybe Doc] -> Config -> Doc
forall a. [a -> Maybe Doc] -> a -> Doc
fields
[ (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"hardwarebufsamps") Config -> Maybe Int
hwBuf
, (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"iobufsamps") Config -> Maybe Int
ioBuf
, (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"control-rate") Config -> Maybe Int
newKr
, (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"sample-rate") Config -> Maybe Int
newSr
, (Doc -> Doc) -> (Config -> Maybe Text) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"score-in") Config -> Maybe Text
scoreIn
, Doc -> (Config -> Maybe (Text, Text)) -> Config -> Maybe Doc
forall a. Doc -> (a -> Maybe (Text, Text)) -> a -> Maybe Doc
macro Doc
"omacro" Config -> Maybe (Text, Text)
omacro
, Doc -> (Config -> Maybe (Text, Text)) -> Config -> Maybe Doc
forall a. Doc -> (a -> Maybe (Text, Text)) -> a -> Maybe Doc
macro Doc
"smacro" Config -> Maybe (Text, Text)
smacro
, Text -> (Config -> Bool) -> Config -> Maybe Doc
forall a. Text -> (a -> Bool) -> a -> Maybe Doc
bo Text
"--sched" Config -> Bool
setSched
, (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"sched") Config -> Maybe Int
schedNum
, (Config -> Maybe (Int, Text)) -> Config -> Maybe Doc
forall {f :: * -> *} {a}.
Functor f =>
(a -> f (Int, Text)) -> a -> f Doc
strset Config -> Maybe (Int, Text)
strsetN
, (Doc -> Doc) -> (Config -> Maybe Double) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p3 Doc
"skip_seconds") Config -> Maybe Double
skipSeconds
, (Doc -> Doc) -> (Config -> Maybe Int) -> Config -> Maybe Doc
forall b a.
Pretty b =>
(Doc -> Doc) -> (a -> Maybe b) -> a -> Maybe Doc
mp (Doc -> Doc -> Doc
p2 Doc
"tempo") Config -> Maybe Int
setTempo ]
where
macro :: Doc -> (a -> Maybe (Text, Text)) -> a -> Maybe Doc
macro :: forall a. Doc -> (a -> Maybe (Text, Text)) -> a -> Maybe Doc
macro Doc
name a -> Maybe (Text, Text)
f = ((Text, Text) -> Doc) -> Maybe (Text, Text) -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> Doc
phi (Maybe (Text, Text) -> Maybe Doc)
-> (a -> Maybe (Text, Text)) -> a -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe (Text, Text)
f
where phi :: (Text, Text) -> Doc
phi (Text
a, Text
b) = [Doc] -> Doc
hcat [Doc
"--", Doc -> Doc
forall a. Pretty a => a -> Doc
pretty Doc
name, Doc
":", Text -> Doc
textStrict Text
a, Doc
"=", Text -> Doc
textStrict Text
b]
strset :: (a -> f (Int, Text)) -> a -> f Doc
strset a -> f (Int, Text)
f = ((Int, Text) -> Doc) -> f (Int, Text) -> f Doc
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Text) -> Doc
phi (f (Int, Text) -> f Doc) -> (a -> f (Int, Text)) -> a -> f Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f (Int, Text)
f
where phi :: (Int, Text) -> Doc
phi (Int
n, Text
a) = [Doc] -> Doc
hcat [Doc
"--strset", Int -> Doc
int Int
n,Doc
"=", Text -> Doc
textStrict Text
a]
firstToLower :: Text -> Text
firstToLower :: Text -> Text
firstToLower Text
x = case Text -> Maybe (Char, Text)
Text.uncons Text
x of
Just (Char
a, Text
as) -> Char -> Text -> Text
Text.cons (Char -> Char
toLower Char
a) Text
as
Maybe (Char, Text)
Nothing -> Text
x