{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module Solkattu.Instrument.Tabla where
import qualified Solkattu.Realize as Realize
import qualified Solkattu.S as S
import qualified Solkattu.Solkattu as Solkattu
import Global
data Stroke = Baya Baya | Daya Daya | Both Baya Daya
deriving (Stroke -> Stroke -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Stroke -> Stroke -> Bool
$c/= :: Stroke -> Stroke -> Bool
== :: Stroke -> Stroke -> Bool
$c== :: Stroke -> Stroke -> Bool
Eq, Eq Stroke
Stroke -> Stroke -> Bool
Stroke -> Stroke -> Ordering
Stroke -> Stroke -> Stroke
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 :: Stroke -> Stroke -> Stroke
$cmin :: Stroke -> Stroke -> Stroke
max :: Stroke -> Stroke -> Stroke
$cmax :: Stroke -> Stroke -> Stroke
>= :: Stroke -> Stroke -> Bool
$c>= :: Stroke -> Stroke -> Bool
> :: Stroke -> Stroke -> Bool
$c> :: Stroke -> Stroke -> Bool
<= :: Stroke -> Stroke -> Bool
$c<= :: Stroke -> Stroke -> Bool
< :: Stroke -> Stroke -> Bool
$c< :: Stroke -> Stroke -> Bool
compare :: Stroke -> Stroke -> Ordering
$ccompare :: Stroke -> Stroke -> Ordering
Ord, Int -> Stroke -> ShowS
[Stroke] -> ShowS
Stroke -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Stroke] -> ShowS
$cshowList :: [Stroke] -> ShowS
show :: Stroke -> String
$cshow :: Stroke -> String
showsPrec :: Int -> Stroke -> ShowS
$cshowsPrec :: Int -> Stroke -> ShowS
Show)
data Baya = Ka | Ge
deriving (Baya -> Baya -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Baya -> Baya -> Bool
$c/= :: Baya -> Baya -> Bool
== :: Baya -> Baya -> Bool
$c== :: Baya -> Baya -> Bool
Eq, Eq Baya
Baya -> Baya -> Bool
Baya -> Baya -> Ordering
Baya -> Baya -> Baya
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 :: Baya -> Baya -> Baya
$cmin :: Baya -> Baya -> Baya
max :: Baya -> Baya -> Baya
$cmax :: Baya -> Baya -> Baya
>= :: Baya -> Baya -> Bool
$c>= :: Baya -> Baya -> Bool
> :: Baya -> Baya -> Bool
$c> :: Baya -> Baya -> Bool
<= :: Baya -> Baya -> Bool
$c<= :: Baya -> Baya -> Bool
< :: Baya -> Baya -> Bool
$c< :: Baya -> Baya -> Bool
compare :: Baya -> Baya -> Ordering
$ccompare :: Baya -> Baya -> Ordering
Ord, Int -> Baya -> ShowS
[Baya] -> ShowS
Baya -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Baya] -> ShowS
$cshowList :: [Baya] -> ShowS
show :: Baya -> String
$cshow :: Baya -> String
showsPrec :: Int -> Baya -> ShowS
$cshowsPrec :: Int -> Baya -> ShowS
Show)
data Daya =
Ta
| Tin
| Tu
| Na
| Tet
| Te
deriving (Daya -> Daya -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Daya -> Daya -> Bool
$c/= :: Daya -> Daya -> Bool
== :: Daya -> Daya -> Bool
$c== :: Daya -> Daya -> Bool
Eq, Eq Daya
Daya -> Daya -> Bool
Daya -> Daya -> Ordering
Daya -> Daya -> Daya
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 :: Daya -> Daya -> Daya
$cmin :: Daya -> Daya -> Daya
max :: Daya -> Daya -> Daya
$cmax :: Daya -> Daya -> Daya
>= :: Daya -> Daya -> Bool
$c>= :: Daya -> Daya -> Bool
> :: Daya -> Daya -> Bool
$c> :: Daya -> Daya -> Bool
<= :: Daya -> Daya -> Bool
$c<= :: Daya -> Daya -> Bool
< :: Daya -> Daya -> Bool
$c< :: Daya -> Daya -> Bool
compare :: Daya -> Daya -> Ordering
$ccompare :: Daya -> Daya -> Ordering
Ord, Int -> Daya -> ShowS
[Daya] -> ShowS
Daya -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Daya] -> ShowS
$cshowList :: [Daya] -> ShowS
show :: Daya -> String
$cshow :: Daya -> String
showsPrec :: Int -> Daya -> ShowS
$cshowsPrec :: Int -> Daya -> ShowS
Show)
instance Pretty Stroke where pretty :: Stroke -> Text
pretty = forall a. Show a => a -> Text
showt
data Strokes a = Strokes {
forall a. Strokes a -> a
ka :: a, forall a. Strokes a -> a
ge :: a
, forall a. Strokes a -> a
ta :: a
, forall a. Strokes a -> a
tin :: a
, forall a. Strokes a -> a
tu :: a
, forall a. Strokes a -> a
tet :: a
, forall a. Strokes a -> a
te :: a
} deriving (forall a b. a -> Strokes b -> Strokes a
forall a b. (a -> b) -> Strokes a -> Strokes b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Strokes b -> Strokes a
$c<$ :: forall a b. a -> Strokes b -> Strokes a
fmap :: forall a b. (a -> b) -> Strokes a -> Strokes b
$cfmap :: forall a b. (a -> b) -> Strokes a -> Strokes b
Functor, Int -> Strokes a -> ShowS
forall a. Show a => Int -> Strokes a -> ShowS
forall a. Show a => [Strokes a] -> ShowS
forall a. Show a => Strokes a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Strokes a] -> ShowS
$cshowList :: forall a. Show a => [Strokes a] -> ShowS
show :: Strokes a -> String
$cshow :: forall a. Show a => Strokes a -> String
showsPrec :: Int -> Strokes a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Strokes a -> ShowS
Show)
strokes :: Strokes Stroke
strokes :: Strokes Stroke
strokes = Strokes
{ ka :: Stroke
ka = Baya -> Stroke
Baya Baya
Ka
, ge :: Stroke
ge = Baya -> Stroke
Baya Baya
Ge
, ta :: Stroke
ta = Daya -> Stroke
Daya Daya
Ta
, tin :: Stroke
tin = Daya -> Stroke
Daya Daya
Tin
, tu :: Stroke
tu = Daya -> Stroke
Daya Daya
Tu
, tet :: Stroke
tet = Daya -> Stroke
Daya Daya
Tet
, te :: Stroke
te = Daya -> Stroke
Daya Daya
Te
}
notes :: Strokes (S.Sequence g (Solkattu.Note (Realize.Stroke Stroke)))
notes :: forall g. Strokes (Sequence g (Note (Stroke Stroke)))
notes = forall stroke g. stroke -> Sequence g (Note (Stroke stroke))
Realize.strokeToSequence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strokes Stroke
strokes