{-# LINE 1 "Audio/TagLib/TagLib.hsc" #-}
module Audio.TagLib.TagLib (
{-# LINE 2 "Audio/TagLib/TagLib.hsc" #-}
-- * Types
    TagFile,
    Tag,
    AudioProperties,
    
-- * TagFile operations    
    tagFileOpen,
    tagFileSave,
    tagFileIsValid,
    tagFileGetTag,
    tagFileGetAudioProperties,

-- * Tag operations    
    tagGetAlbum,
    tagSetAlbum,
    tagGetArtist,
    tagSetArtist,
    tagGetComment,
    tagSetComment,
    tagGetGenre,
    tagSetGenre,
    tagGetTitle,
    tagSetTitle,
    tagGetTrack,
    tagSetTrack,
    tagGetYear,
    tagSetYear,

-- * AudioProperties Operations
    audioPropertiesGetBitRate,
    audioPropertiesGetDuration,
    audioPropertiesGetSampleRate,
    audioPropertiesGetChannels,
) where

import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import Data.ByteString (ByteString, useAsCString)

type Void = Word8    
type TagFilePtr = Ptr Void
type TagFile = ForeignPtr Void

type TagPtr = Ptr Void
type Tag = TagPtr

type AudioPropertiesPtr = Ptr Void
type AudioProperties = AudioPropertiesPtr
    
-- | Creates a 'TagFile' file based on @filename@,
-- TagLib will try to guess the file type.
-- Return 'Nothing' if the file type cannot be determined 
-- or the file cannot opened.
tagFileOpen :: ByteString -> IO (Maybe TagFile)
tagFileOpen filename = do
  -- This use withCString, not utf8 string.
  useAsCString filename $ \filenamePtr -> do
    ptr <- taglib_file_new filenamePtr
    if ptr == nullPtr 
        then return Nothing
        else liftM Just $ newForeignPtr ptr taglib_file_free
             
-- | Save file to disk.
tagFileSave :: TagFile -> IO Bool             
tagFileSave tagFile = 
  liftM toBool $
  withForeignPtr tagFile taglib_file_save 
    
-- | Returns 'True' if the file is open and readble and valid information for
-- the 'Tag' and 'AudioProperties' was found.
tagFileIsValid :: TagFile -> IO Bool             
tagFileIsValid tagFile = 
  liftM toBool $
  withForeignPtr tagFile taglib_file_is_valid 
                 
-- | Returns 'Tag' associated with this file. 
tagFileGetTag :: TagFile -> IO (Maybe Tag)
tagFileGetTag tagFile = do
  tagPtr <- withForeignPtr tagFile taglib_file_tag 
  return $ if tagPtr == nullPtr 
              then Nothing
              else Just tagPtr

-- | Returns a string with this tag's title.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetTitle :: Tag -> IO String
tagGetTitle tagPtr = 
  taglib_tag_title tagPtr
  >>= readUTFString

-- | Returns a string with this tag's album.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetAlbum :: Tag -> IO String
tagGetAlbum tagPtr = 
  taglib_tag_album tagPtr
  >>= readUTFString

-- | Returns a string with this tag's artist.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetArtist :: Tag -> IO String
tagGetArtist tagPtr = 
  taglib_tag_artist tagPtr
  >>= readUTFString

-- | Returns a string with this tag's comment.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetComment :: Tag -> IO String
tagGetComment tagPtr = 
  taglib_tag_comment tagPtr
  >>= readUTFString

-- | Returns a string with this tag's genre.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetGenre :: Tag -> IO String
tagGetGenre tagPtr = 
  taglib_tag_genre tagPtr
  >>= readUTFString

-- | Returns a string with this tag's year.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetYear :: Tag -> IO Int
tagGetYear tagPtr =
  liftM fromIntegral $
  taglib_tag_year tagPtr

-- | Returns a string with this tag's track.
--
-- NOTE: by default this string should be UTF8 encoded.
tagGetTrack :: Tag -> IO Int
tagGetTrack tagPtr =
  liftM fromIntegral $
  taglib_tag_track tagPtr

-- | Set tag's title.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetTitle :: Tag -> String -> IO ()
tagSetTitle tagPtr str = 
  withUTFString str $ \ strPtr -> 
  taglib_tag_set_title tagPtr strPtr 

-- | Set tag's album.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetAlbum :: Tag -> String -> IO ()
tagSetAlbum tagPtr str = 
  withUTFString str $ \ strPtr -> 
  taglib_tag_set_album tagPtr strPtr 

-- | Set tag's artist.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetArtist :: Tag -> String -> IO ()
tagSetArtist tagPtr str =
  withUTFString str $ \ strPtr -> 
  taglib_tag_set_artist tagPtr strPtr 

-- | Set tag's comment.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetComment :: Tag -> String -> IO ()
tagSetComment tagPtr str =
  withUTFString str $ \ strPtr -> 
  taglib_tag_set_comment tagPtr strPtr 

-- | Set tag's genre.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetGenre :: Tag -> String -> IO ()
tagSetGenre tagPtr str = 
  withUTFString str $ \ strPtr -> 
  taglib_tag_set_genre tagPtr strPtr 

-- | Set tag's year.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetYear :: Tag -> Int -> IO ()
tagSetYear tagPtr year = 
  taglib_tag_set_year tagPtr (fromIntegral year)

-- | Set tag's track.
--
-- NOTE: by default this string should be UTF8 encoded.
tagSetTrack :: Tag -> Int -> IO ()
tagSetTrack tagPtr track = 
  taglib_tag_set_track tagPtr (fromIntegral track)

-- | Returns 'AudioProperties' associated with this file.  
tagFileGetAudioProperties :: TagFile -> IO (Maybe AudioProperties)
tagFileGetAudioProperties tagFile = do
  ptr <- withForeignPtr tagFile taglib_file_audioproperties
  return $ if ptr == nullPtr 
              then Nothing
              else Just ptr

-- | Returns the bitrate of the file in kb/s.
audioPropertiesGetBitRate :: AudioProperties -> IO Int
audioPropertiesGetBitRate ptr =
  liftM fromIntegral $
  taglib_audioproperties_bitrate ptr

-- | Returns the duration of the file in seconds.
audioPropertiesGetDuration :: AudioProperties -> IO Int
audioPropertiesGetDuration ptr =
  liftM fromIntegral $
  taglib_audioproperties_length ptr

-- | Returns the sample rate of the file in Hz.
audioPropertiesGetSampleRate :: AudioProperties -> IO Int
audioPropertiesGetSampleRate ptr =
  liftM fromIntegral $
  taglib_audioproperties_samplerate ptr

-- | Returns the number of channels in the audio stream.
audioPropertiesGetChannels :: AudioProperties -> IO Int
audioPropertiesGetChannels ptr =
  liftM fromIntegral $
  taglib_audioproperties_channels ptr

foreign import ccall unsafe "taglib_file_new" 
  taglib_file_new :: CString -> IO TagFilePtr
foreign import ccall unsafe "&taglib_file_free" 
  taglib_file_free :: FinalizerPtr Void
foreign import ccall unsafe "taglib_set_string_management_enabled" 
  taglib_set_string_management_enabled :: CInt -> IO ()
foreign import ccall unsafe "taglib_file_save" 
  taglib_file_save :: TagFilePtr -> IO CInt
foreign import ccall unsafe "taglib_file_is_valid" 
  taglib_file_is_valid :: TagFilePtr -> IO CInt
foreign import ccall unsafe "taglib_file_tag" 
  taglib_file_tag :: TagFilePtr -> IO TagPtr

foreign import ccall unsafe "taglib_tag_artist" 
  taglib_tag_artist :: TagPtr -> IO CString
foreign import ccall unsafe "taglib_tag_album" 
  taglib_tag_album :: TagPtr -> IO CString
foreign import ccall unsafe "taglib_tag_title" 
  taglib_tag_title :: TagPtr -> IO CString
foreign import ccall unsafe "taglib_tag_comment" 
  taglib_tag_comment :: TagPtr -> IO CString
foreign import ccall unsafe "taglib_tag_genre" 
  taglib_tag_genre :: TagPtr -> IO CString
foreign import ccall unsafe "taglib_tag_year" 
  taglib_tag_year :: TagPtr -> IO CUInt
foreign import ccall unsafe "taglib_tag_track" 
  taglib_tag_track :: TagPtr -> IO CUInt

foreign import ccall unsafe "taglib_tag_set_track" 
  taglib_tag_set_track :: TagPtr -> CUInt -> IO () 
foreign import ccall unsafe "taglib_tag_set_year" 
  taglib_tag_set_year :: TagPtr -> CUInt -> IO () 
foreign import ccall unsafe "taglib_tag_set_genre" 
  taglib_tag_set_genre :: TagPtr -> CString -> IO () 
foreign import ccall unsafe "taglib_tag_set_comment" 
  taglib_tag_set_comment :: TagPtr -> CString -> IO () 
foreign import ccall unsafe "taglib_tag_set_album" 
  taglib_tag_set_album :: TagPtr -> CString -> IO () 
foreign import ccall unsafe "taglib_tag_set_title" 
  taglib_tag_set_title :: TagPtr -> CString -> IO () 
foreign import ccall unsafe "taglib_tag_set_artist" 
  taglib_tag_set_artist :: TagPtr -> CString -> IO () 

foreign import ccall unsafe "taglib_file_audioproperties" 
  taglib_file_audioproperties :: TagFilePtr -> IO AudioPropertiesPtr
foreign import ccall unsafe "taglib_audioproperties_length" 
  taglib_audioproperties_length :: AudioPropertiesPtr -> IO CInt
foreign import ccall unsafe "taglib_audioproperties_bitrate" 
  taglib_audioproperties_bitrate :: AudioPropertiesPtr -> IO CInt 
foreign import ccall unsafe "taglib_audioproperties_samplerate" 
  taglib_audioproperties_samplerate :: AudioPropertiesPtr -> IO CInt 
foreign import ccall unsafe "taglib_audioproperties_channels" 
  taglib_audioproperties_channels :: AudioPropertiesPtr -> IO CInt