audacity-0.0.2: Interchange with the Audacity sound signal editor

Safe HaskellSafe
LanguageHaskell2010

Sound.Audacity.LabelTrack

Synopsis

Documentation

newtype T time label Source #

Constructors

Cons 

Fields

Instances

Functor (T time) Source # 

Methods

fmap :: (a -> b) -> T time a -> T time b #

(<$) :: a -> T time b -> T time a #

Foldable (T time) Source # 

Methods

fold :: Monoid m => T time m -> m #

foldMap :: Monoid m => (a -> m) -> T time a -> m #

foldr :: (a -> b -> b) -> b -> T time a -> b #

foldr' :: (a -> b -> b) -> b -> T time a -> b #

foldl :: (b -> a -> b) -> b -> T time a -> b #

foldl' :: (b -> a -> b) -> b -> T time a -> b #

foldr1 :: (a -> a -> a) -> T time a -> a #

foldl1 :: (a -> a -> a) -> T time a -> a #

toList :: T time a -> [a] #

null :: T time a -> Bool #

length :: T time a -> Int #

elem :: Eq a => a -> T time a -> Bool #

maximum :: Ord a => T time a -> a #

minimum :: Ord a => T time a -> a #

sum :: Num a => T time a -> a #

product :: Num a => T time a -> a #

Traversable (T time) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> T time a -> f (T time b) #

sequenceA :: Applicative f => T time (f a) -> f (T time a) #

mapM :: Monad m => (a -> m b) -> T time a -> m (T time b) #

sequence :: Monad m => T time (m a) -> m (T time a) #

(Show time, Show label) => Show (T time label) Source # 

Methods

showsPrec :: Int -> T time label -> ShowS #

show :: T time label -> String #

showList :: [T time label] -> ShowS #

Semigroup (T time label) Source # 

Methods

(<>) :: T time label -> T time label -> T time label #

sconcat :: NonEmpty (T time label) -> T time label #

stimes :: Integral b => b -> T time label -> T time label #

Monoid (T time label) Source # 

Methods

mempty :: T time label #

mappend :: T time label -> T time label -> T time label #

mconcat :: [T time label] -> T time label #

(NFData time, NFData label) => NFData (T time label) Source # 

Methods

rnf :: T time label -> () #

type Interval time label = ((time, time), label) Source #

empty :: T time label Source #

null :: T time label -> Bool Source #

singleton :: (time, time) -> label -> T time label Source #

fromAdjacentChunks :: Num time => [(time, label)] -> T time label Source #

lift :: ([Interval time0 label0] -> [Interval time1 label1]) -> T time0 label0 -> T time1 label1 Source #

lift2 :: ([Interval time0 label0] -> [Interval time1 label1] -> [Interval time2 label2]) -> T time0 label0 -> T time1 label1 -> T time2 label2 Source #

formatTime :: RealFrac time => time -> String Source #

Format the times using a comma, which is certainly only correct in German locale.

mapTime :: (time0 -> time1) -> T time0 label -> T time1 label Source #

You must make sure, that the time mapping function preserves the order. This is not checked.

mapWithTime :: ((time, time) -> label0 -> label1) -> T time label0 -> T time label1 Source #

realTimes :: Fractional time => time -> T Int label -> T time label Source #

mask :: Ord time => (time, time) -> T time label -> T time label Source #

zipWithList :: (label0 -> label1 -> label2) -> [label0] -> T time label1 -> T time label2 Source #

writeFile :: RealFrac time => FilePath -> T time String -> IO () Source #

writeFileInt :: RealFrac time => time -> FilePath -> T Int String -> IO () Source #

readFile :: Fractional time => FilePath -> IO (T time String) Source #

Read label file in a strict way.