alga-0.2.2: Algorithmic automation for various DAWs

Safe HaskellNone
LanguageHaskell2010

Alga.Language

Synopsis

Documentation

type SyntaxTree = [Sel] Source #

Syntax tree in our case is just a collection of syntactic elements.

data Sel Source #

Syntactic element corresponds to language tokens. Some of them have corresponding constructor in Element, others have to be simplified first.

Constructors

Value NRatio

Literal value

Section [Sel]

Section

Multi [Sel]

Multivalue

CMulti (NonEmpty ([Sel], [Sel]))

Conditional multivalue

Reference String

Reference (name of variable)

Range NRatio NRatio

Range of values

Product Sel Sel

Product of principles

Division Sel Sel

Division of principles

Sum Sel Sel

Sum of principles

Diff Sel Sel

Subtraction of principles

Loop Sel Sel

Loop

Rotation Sel Sel

Rotation

Reverse Sel

Reversed principle

Instances

Eq Sel Source # 

Methods

(==) :: Sel -> Sel -> Bool #

(/=) :: Sel -> Sel -> Bool #

Show Sel Source # 

Methods

showsPrec :: Int -> Sel -> ShowS #

show :: Sel -> String #

showList :: [Sel] -> ShowS #

Arbitrary Sel Source # 

Methods

arbitrary :: Gen Sel #

shrink :: Sel -> [Sel] #

data Statement Source #

Statement can be either definition or exposition. Expositions are only used in REPL.

type Principle = [Element NRatio] Source #

Collection of elements for evaluation, representation of some aspect of voice.

type NRatio = Ratio Natural Source #

Non-negative rational number is the best choice for our purposes, hence the synonym.

data Element a Source #

Fundamental type representing an atom for evaluation.

Constructors

Val a

Single value, evaluates to itself

Sec [Element a]

Universal container for other values

Mul [Element a]

Multivalue, the way to introduce varying elements

CMul (NonEmpty ([Element a], [Element a]))

Conditional multivalue

Instances

Functor Element Source # 

Methods

fmap :: (a -> b) -> Element a -> Element b #

(<$) :: a -> Element b -> Element a #

Applicative Element Source # 

Methods

pure :: a -> Element a #

(<*>) :: Element (a -> b) -> Element a -> Element b #

(*>) :: Element a -> Element b -> Element b #

(<*) :: Element a -> Element b -> Element a #

Foldable Element Source # 

Methods

fold :: Monoid m => Element m -> m #

foldMap :: Monoid m => (a -> m) -> Element a -> m #

foldr :: (a -> b -> b) -> b -> Element a -> b #

foldr' :: (a -> b -> b) -> b -> Element a -> b #

foldl :: (b -> a -> b) -> b -> Element a -> b #

foldl' :: (b -> a -> b) -> b -> Element a -> b #

foldr1 :: (a -> a -> a) -> Element a -> a #

foldl1 :: (a -> a -> a) -> Element a -> a #

toList :: Element a -> [a] #

null :: Element a -> Bool #

length :: Element a -> Int #

elem :: Eq a => a -> Element a -> Bool #

maximum :: Ord a => Element a -> a #

minimum :: Ord a => Element a -> a #

sum :: Num a => Element a -> a #

product :: Num a => Element a -> a #

Eq a => Eq (Element a) Source # 

Methods

(==) :: Element a -> Element a -> Bool #

(/=) :: Element a -> Element a -> Bool #

Show a => Show (Element a) Source # 

Methods

showsPrec :: Int -> Element a -> ShowS #

show :: Element a -> String #

showList :: [Element a] -> ShowS #

data AlgaEnv m a Source #

Monad that implements ALGA environment.

Instances

Monad m => Monad (AlgaEnv m) Source # 

Methods

(>>=) :: AlgaEnv m a -> (a -> AlgaEnv m b) -> AlgaEnv m b #

(>>) :: AlgaEnv m a -> AlgaEnv m b -> AlgaEnv m b #

return :: a -> AlgaEnv m a #

fail :: String -> AlgaEnv m a #

Functor m => Functor (AlgaEnv m) Source # 

Methods

fmap :: (a -> b) -> AlgaEnv m a -> AlgaEnv m b #

(<$) :: a -> AlgaEnv m b -> AlgaEnv m a #

Monad m => Applicative (AlgaEnv m) Source # 

Methods

pure :: a -> AlgaEnv m a #

(<*>) :: AlgaEnv m (a -> b) -> AlgaEnv m a -> AlgaEnv m b #

(*>) :: AlgaEnv m a -> AlgaEnv m b -> AlgaEnv m b #

(<*) :: AlgaEnv m a -> AlgaEnv m b -> AlgaEnv m a #

MonadIO m => MonadIO (AlgaEnv m) Source # 

Methods

liftIO :: IO a -> AlgaEnv m a #

MonadThrow m => MonadThrow (AlgaEnv m) Source # 

Methods

throwM :: Exception e => e -> AlgaEnv m a #

MonadCatch m => MonadCatch (AlgaEnv m) Source # 

Methods

catch :: Exception e => AlgaEnv m a -> (e -> AlgaEnv m a) -> AlgaEnv m a #

MonadMask m => MonadMask (AlgaEnv m) Source # 

Methods

mask :: ((forall a. AlgaEnv m a -> AlgaEnv m a) -> AlgaEnv m b) -> AlgaEnv m b #

uninterruptibleMask :: ((forall a. AlgaEnv m a -> AlgaEnv m a) -> AlgaEnv m b) -> AlgaEnv m b #

MonadException m => MonadException (AlgaEnv m) Source # 

Methods

controlIO :: (RunIO (AlgaEnv m) -> IO (AlgaEnv m a)) -> AlgaEnv m a #

Monad m => HasEnv (AlgaEnv m) Source # 

class Monad m => HasEnv m where Source #

Type class for things that can be considered ALGA environment.

Minimal complete definition

getDefs, setDefs, setRandGen, newRandGen

Methods

getDefs :: m Defs Source #

Get collection of all definitions.

setDefs :: Defs -> m () Source #

Update definitions with given ones.

setRandGen :: Natural -> m () Source #

Set random generator seed.

newRandGen :: m TFGen Source #

Split current random generator, update it, and return new one.

Instances

Monad m => HasEnv (AlgaEnv m) Source # 
HasEnv m => HasEnv (StateT e m) Source # 

Methods

getDefs :: StateT e m Defs Source #

setDefs :: Defs -> StateT e m () Source #

setRandGen :: Natural -> StateT e m () Source #

newRandGen :: StateT e m TFGen Source #

HasEnv m => HasEnv (ReaderT * e m) Source # 

Methods

getDefs :: ReaderT * e m Defs Source #

setDefs :: Defs -> ReaderT * e m () Source #

setRandGen :: Natural -> ReaderT * e m () Source #

newRandGen :: ReaderT * e m TFGen Source #

runAlgaEnv :: Monad m => AlgaEnv m a -> m a Source #

Run state monad with ALGA environment.

addDef Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> SyntaxTree

AST of its principle

-> m () 

Add a new definition to the environment.

remDef Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> m () 

Remove definition given its name.

clearDefs :: HasEnv m => m () Source #

Remove all definitions, restoring default state of environment.

getPrin Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> m SyntaxTree

Syntax tree

Get principle corresponding to given variable name.

getSrc Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> m Text

Textual representation of source code

Get source code of definition given its name.

fullSrc :: HasEnv m => m Text Source #

Reconstruct source code for all existing definitions.

getRefs :: HasEnv m => m [String] Source #

Get all reference names defined at the moment.

purgeEnv Source #

Arguments

:: HasEnv m 
=> [String]

Top-level definitions

-> m () 

Purge environment removing definitions that are not used in construction of “top-level” definitions.

checkRecur Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> SyntaxTree

Its syntax tree

-> m Bool 

Check if definition with given name is depends on itself.

evalDef Source #

Arguments

:: HasEnv m 
=> String

Reference name

-> m [NRatio]

Infinite stream of naturals or empty list

Evaluate definition given its name.

eval Source #

Arguments

:: HasEnv m 
=> SyntaxTree

Syntax tree

-> m [NRatio]

Infinite stream of ratios or empty list

Evaluate given syntax tree.

toPrin Source #

Arguments

:: HasEnv m 
=> SyntaxTree

Syntax tree to transform

-> m Principle

Resulting principle

Transform SyntaxTree into Principle applying all necessary transformations and resolving references.