tidal-1.7.8: Pattern language for improvised music
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Tidal.Time

Synopsis

Documentation

type Time = Rational Source #

Time is rational

data ArcF a Source #

An arc of time, with a start time (or onset) and a stop time (or offset)

Constructors

Arc 

Fields

Instances

Instances details
Functor ArcF Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

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

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

Show Arc Source # 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Arc -> ShowS #

show :: Arc -> String #

showList :: [Arc] -> ShowS #

Applicative ArcF Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

pure :: a -> ArcF a #

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

liftA2 :: (a -> b -> c) -> ArcF a -> ArcF b -> ArcF c #

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

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

Eq a => Eq (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

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

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

Fractional a => Fractional (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

(/) :: ArcF a -> ArcF a -> ArcF a #

recip :: ArcF a -> ArcF a #

fromRational :: Rational -> ArcF a #

Num a => Num (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

(+) :: ArcF a -> ArcF a -> ArcF a #

(-) :: ArcF a -> ArcF a -> ArcF a #

(*) :: ArcF a -> ArcF a -> ArcF a #

negate :: ArcF a -> ArcF a #

abs :: ArcF a -> ArcF a #

signum :: ArcF a -> ArcF a #

fromInteger :: Integer -> ArcF a #

Ord a => Ord (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

compare :: ArcF a -> ArcF a -> Ordering #

(<) :: ArcF a -> ArcF a -> Bool #

(<=) :: ArcF a -> ArcF a -> Bool #

(>) :: ArcF a -> ArcF a -> Bool #

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

max :: ArcF a -> ArcF a -> ArcF a #

min :: ArcF a -> ArcF a -> ArcF a #

Show a => Show (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

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

show :: ArcF a -> String #

showList :: [ArcF a] -> ShowS #

Show a => Show (Event a) Source # 
Instance details

Defined in Sound.Tidal.Show

Methods

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

show :: Event a -> String #

showList :: [Event a] -> ShowS #

Generic (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Associated Types

type Rep (ArcF a) :: Type -> Type #

Methods

from :: ArcF a -> Rep (ArcF a) x #

to :: Rep (ArcF a) x -> ArcF a #

NFData a => NFData (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

Methods

rnf :: ArcF a -> () #

type Rep (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Time

type Rep (ArcF a) = D1 ('MetaData "ArcF" "Sound.Tidal.Time" "tidal-1.7.8-B9irVA2j0vG71xThH8XTiR" 'False) (C1 ('MetaCons "Arc" 'PrefixI 'True) (S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "stop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

sam :: Time -> Time Source #

The sam (start of cycle) for the given time value

toTime :: Real a => a -> Rational Source #

Turns a number into a (rational) time value. An alias for toRational.

fromTime :: Fractional a => Time -> a Source #

Turns a (rational) time value into another number. An alias for fromRational.

nextSam :: Time -> Time Source #

The end point of the current cycle (and starting point of the next cycle)

cyclePos :: Time -> Time Source #

The position of a time value relative to the start of its cycle.

hull :: Arc -> Arc -> Arc Source #

convex hull union

subArc :: Arc -> Arc -> Maybe Arc Source #

subArc i j is the timespan that is the intersection of i and j. intersection The definition is a bit fiddly as results might be zero-width, but not at the end of an non-zero-width arc - e.g. (0,1) and (1,2) do not intersect, but (1,1) (1,1) does.

sect :: Arc -> Arc -> Arc Source #

Simple intersection of two arcs

timeToCycleArc :: Time -> Arc Source #

The arc of the whole cycle that the given time value falls within

cycleArc :: Arc -> Arc Source #

Shifts an arc to the equivalent one that starts during cycle zero

cyclesInArc :: Integral a => Arc -> [a] Source #

A list of cycle numbers which are included in the given arc

cycleArcsInArc :: Arc -> [Arc] Source #

A list of arcs of the whole cycles which are included in the given arc

arcCycles :: Arc -> [Arc] Source #

Splits the given Arc into a list of Arcs, at cycle boundaries.

arcCyclesZW :: Arc -> [Arc] Source #

Like arcCycles, but returns zero-width arcs

mapCycle :: (Time -> Time) -> Arc -> Arc Source #

Similar to fmap but time is relative to the cycle (i.e. the sam of the start of the arc)

isIn :: Arc -> Time -> Bool Source #

isIn a t is True if t is inside the arc represented by a.