taglib-0.1.0: Haskell binding to TagLibSource codeContentsIndex
Sound.TagLib
Portabilityonly tested with GHC
Stabilityexperimental
MaintainerBrandon Bickford <bickfordb@gmail.com>
Contents
Data Types
TagFile operations
Tag Operations
AudioProperties Operations
Example
Description
High level interface to read and write ID3 tag fields (album, artist, comment, genre, title, track number, year) and get audio properties (length, bit rate, sample rate, channels)
Synopsis
data AudioProperties
data Tag
type TagFile = ForeignPtr Void
open :: String -> IO (Maybe TagFile)
save :: TagFile -> IO Integer
tag :: TagFile -> IO (Maybe Tag)
album :: Tag -> IO String
artist :: Tag -> IO String
comment :: Tag -> IO String
genre :: Tag -> IO String
setAlbum :: Tag -> String -> IO ()
setArtist :: Tag -> String -> IO ()
setComment :: Tag -> String -> IO ()
setGenre :: Tag -> String -> IO ()
setTrack :: Tag -> Integer -> IO ()
setYear :: Tag -> Integer -> IO ()
title :: Tag -> IO String
track :: Tag -> IO Integer
year :: Tag -> IO Integer
audioProperties :: TagFile -> IO (Maybe AudioProperties)
bitRate :: AudioProperties -> IO Integer
channels :: AudioProperties -> IO Integer
duration :: AudioProperties -> IO Integer
sampleRate :: AudioProperties -> IO Integer
Data Types
data AudioProperties Source
data Tag Source
type TagFile = ForeignPtr VoidSource
TagFile operations
open :: String -> IO (Maybe TagFile)Source
Open a filename and possibly get a TagFile
save :: TagFile -> IO IntegerSource
Save changes to a tag
Tag Operations
tag :: TagFile -> IO (Maybe Tag)Source
Get a Tag from a TagFile, if it has one
album :: Tag -> IO StringSource
Get an album string from a Tag
artist :: Tag -> IO StringSource
Get an artist string from a Tag
comment :: Tag -> IO StringSource
Get the comment string from a Tag
genre :: Tag -> IO StringSource
Get the comment string from a Tag
setAlbum :: Tag -> String -> IO ()Source
Set the album of a tag
setArtist :: Tag -> String -> IO ()Source
Set the artist of a tag
setComment :: Tag -> String -> IO ()Source
Set the comment of a tag
setGenre :: Tag -> String -> IO ()Source
Set the genre of a tag
setTrack :: Tag -> Integer -> IO ()Source
Set the track of a tag
setYear :: Tag -> Integer -> IO ()Source
Set the year of a tag
title :: Tag -> IO StringSource
Get a title string from a Tag
track :: Tag -> IO IntegerSource
Get the track number from a Tag. Empty values will be 0
year :: Tag -> IO IntegerSource
Get the year from a Tag. Empty values will be 0
AudioProperties Operations
audioProperties :: TagFile -> IO (Maybe AudioProperties)Source
Get the AudioProperties from a TagFile
bitRate :: AudioProperties -> IO IntegerSource
Get the bitRate from AudioProperties
channels :: AudioProperties -> IO IntegerSource
Get the number of channels from AudioProperties
duration :: AudioProperties -> IO IntegerSource
Get the duration (in seconds) from AudioProperties In TagLib, this is named length. This is renamed so that it doesn't conflict with the Prelude length
sampleRate :: AudioProperties -> IO IntegerSource
Get the sampleRate from AudioProperties
Example
 module Main where 
 
 import qualified Sound.TagLib as TagLib
 import Data.Maybe
 import Control.Monad
 import System
 
 main = do
     args <- getArgs 
     mapM showFile args
 
 withMaybe :: (Maybe j) -> (j -> IO ()) -> IO () 
 withMaybe mebbe action = do
     case mebbe of 
         Just x -> do action x 
                      return ()
         Nothing -> return ()
 
 showFile filename = do
     t <- TagLib.open filename
     withMaybe t showTagFile
 
 showTagFile :: TagLib.TagFile -> IO ()
 showTagFile tagFile = do
     t <- TagLib.tag tagFile
     withMaybe t showTag
     p <- TagLib.audioProperties tagFile
     withMaybe p showAudioProperties 
 
 showTag :: TagLib.Tag -> IO ()
 showTag tag = do 
     artist <- TagLib.artist tag
     album <- TagLib.album tag
     title <- TagLib.title tag
     comment <- TagLib.comment tag
     year <- TagLib.year tag
     track <- TagLib.track tag
     print (artist, album, title, year, track)
 
 showAudioProperties :: TagLib.AudioProperties -> IO ()
 showAudioProperties props = do
     bitrate <- TagLib.bitRate props
     length <- TagLib.duration props
     samplerate <- TagLib.sampleRate props
     channels <- TagLib.channels props
     print (bitrate, length, channels, samplerate)
 
Produced by Haddock version 2.4.2