| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Sound.Tidal.Parse
Contents
Synopsis
- data TPat a- = TPat_Atom a
- | TPat_Density (TPat Time) (TPat a)
- | TPat_Slow (TPat Time) (TPat a)
- | TPat_Zoom Arc (TPat a)
- | TPat_DegradeBy Double (TPat a)
- | TPat_Silence
- | TPat_Foot
- | TPat_Elongate Int
- | TPat_EnumFromTo (TPat a) (TPat a)
- | TPat_Cat [TPat a]
- | TPat_TimeCat [TPat a]
- | TPat_Overlay (TPat a) (TPat a)
- | TPat_ShiftL Time (TPat a)
- | TPat_pE (TPat Int) (TPat Int) (TPat Integer) (TPat a)
 
- toPat :: Enumerable a => TPat a -> Pattern a
- durations :: [TPat a] -> [(Int, TPat a)]
- p :: (Enumerable a, Parseable a) => String -> Pattern a
- class Parseable a where
- class Enumerable a where- fromTo :: a -> a -> Pattern a
- fromThenTo :: a -> a -> a -> Pattern a
 
- enumFromTo' :: (Ord a, Enum a) => a -> a -> Pattern a
- enumFromThenTo' :: (Ord a, Enum a, Num a) => a -> a -> a -> Pattern a
- type ColourD = Colour Double
- lexer :: GenTokenParser String u Identity
- braces :: Parser a -> Parser a
- brackets :: Parser a -> Parser a
- parens :: Parser a -> Parser a
- angles :: Parser a -> Parser a
- symbol :: String -> Parser String
- natural :: Parser Integer
- integer :: Parser Integer
- float :: Parser Double
- naturalOrFloat :: Parser (Either Integer Double)
- data Sign
- applySign :: Num a => Sign -> a -> a
- sign :: Parser Sign
- intOrFloat :: Parser Double
- r :: (Enumerable a, Parseable a) => String -> Pattern a -> IO (Pattern a)
- parseRhythm :: Parseable a => Parser (TPat a) -> String -> TPat a
- pSequenceN :: Parseable a => Parser (TPat a) -> GenParser Char () (Int, TPat a)
- elongate :: [TPat a] -> TPat a
- splitFeet :: [TPat t] -> [[TPat t]]
- pSequence :: Parseable a => Parser (TPat a) -> GenParser Char () (TPat a)
- pSingle :: Parseable a => Parser (TPat a) -> Parser (TPat a)
- pPart :: Parseable a => Parser (TPat a) -> Parser [TPat a]
- pPolyIn :: Parseable a => Parser (TPat a) -> Parser (TPat a)
- pPolyOut :: Parseable a => Parser (TPat a) -> Parser (TPat a)
- pString :: Parser String
- pVocable :: Parser (TPat String)
- pDouble :: Parser (TPat Double)
- pBool :: Parser (TPat Bool)
- parseIntNote :: Integral i => Parser i
- parseInt :: Parser Int
- pIntegral :: Parseable a => Integral a => Parser (TPat a)
- parseNote :: Num a => Parser a
- fromNote :: Num a => Pattern String -> Pattern a
- pColour :: Parser (TPat ColourD)
- pMult :: Parseable a => TPat a -> Parser (TPat a)
- pRand :: Parseable a => TPat a -> Parser (TPat a)
- pE :: Parseable a => TPat a -> Parser (TPat a)
- eoff :: Pattern Int -> Pattern Int -> Pattern Integer -> Pattern a -> Pattern a
- _eoff :: Int -> Int -> Integer -> Pattern a -> Pattern a
- pReplicate :: Parseable a => TPat a -> Parser [TPat a]
- pStretch :: Parseable a => TPat a -> Parser [TPat a]
- pRatio :: Parser Rational
- pRational :: Parser (TPat Rational)
Documentation
AST representation of patterns
Constructors
| TPat_Atom a | |
| TPat_Density (TPat Time) (TPat a) | |
| TPat_Slow (TPat Time) (TPat a) | |
| TPat_Zoom Arc (TPat a) | |
| TPat_DegradeBy Double (TPat a) | |
| TPat_Silence | |
| TPat_Foot | |
| TPat_Elongate Int | |
| TPat_EnumFromTo (TPat a) (TPat a) | |
| TPat_Cat [TPat a] | |
| TPat_TimeCat [TPat a] | |
| TPat_Overlay (TPat a) (TPat a) | |
| TPat_ShiftL Time (TPat a) | |
| TPat_pE (TPat Int) (TPat Int) (TPat Integer) (TPat a) | 
class Enumerable a where Source #
parseIntNote :: Integral i => Parser i Source #
Orphan instances
| (Enumerable a, Parseable a) => IsString (Pattern a) Source # | |
| Methods fromString :: String -> Pattern a # | |