Skip to content

Commit

Permalink
Add tests for CUE sheet manipulation, polishing
Browse files Browse the repository at this point in the history
Also add the ‘wipeCueSheets’ function.
  • Loading branch information
mrkkrp committed Dec 26, 2016
1 parent e29f49e commit 2e6f31f
Show file tree
Hide file tree
Showing 7 changed files with 199 additions and 38 deletions.
9 changes: 9 additions & 0 deletions Codec/Audio/FLAC/Metadata.hs
Expand Up @@ -111,6 +111,7 @@ module Codec.Audio.FLAC.Metadata
, wipeVorbisComment
, wipeApplications
, wipeSeekTable
, wipeCueSheets
, wipePictures
-- * Debugging and testing
, MetadataType (..)
Expand Down Expand Up @@ -700,6 +701,14 @@ wipeSeekTable =
liftBool (iteratorDeleteBlock i)
setModified

-- | Delete all “CUE sheet” metadata blocks.

wipeCueSheets :: FlacMeta ()
wipeCueSheets =
void . FlacMeta . withMetaBlock CueSheetBlock $ \i -> do
liftBool (iteratorDeleteBlock i)
setModified

-- | Delete all “Picture” metadata blocks.

wipePictures :: FlacMeta ()
Expand Down
80 changes: 55 additions & 25 deletions Codec/Audio/FLAC/Metadata/Internal/Level2Interface/Helpers.hs
Expand Up @@ -15,6 +15,7 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}

module Codec.Audio.FLAC.Metadata.Internal.Level2Interface.Helpers
( -- * Stream info
Expand Down Expand Up @@ -59,7 +60,8 @@ import Control.Monad
import Control.Monad.Catch
import Data.Bool (bool)
import Data.ByteString (ByteString)
import Data.List.NonEmpty (NonEmpty (..))
import Data.List (uncons)
import Data.Maybe (isJust)
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Vector (Vector, (!))
Expand Down Expand Up @@ -332,11 +334,17 @@ getCueSheetData block = do
cueLeadIn <- c_get_cue_sheet_lead_in block
cueIsCd <- c_get_cue_sheet_is_cd block
numTracks <- c_get_cue_sheet_num_tracks block
cueTracks <- if numTracks == 0
-- NOTE Should probably never happen unless FLAC file is invalid with
-- respect to the spec.
then throwM (MetaInvalidCueSheet "Cannot read CUE sheet without tracks")
else mapM (getCueSheetTrack block) (0 :| [1..numTracks - 1])
(cueTracks, cueLeadOutTrack) <-
case numTracks of
0 ->
-- NOTE Should probably never happen unless FLAC file is invalid with
-- respect to the spec.
throwM (MetaInvalidCueSheet "Cannot read CUE sheet without tracks")
1 -> ([],) <$> getCueSheetTrack block 0
_ -> do
ts <- mapM (getCueSheetTrack block) [0..numTracks - 2]
t' <- getCueSheetTrack block (numTracks - 1)
return (ts,t')
return CueSheetData {..}

foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_mcn"
Expand All @@ -359,10 +367,22 @@ getCueSheetTrack block n = do
cueTrackIsrc <- c_get_cue_sheet_track_isrc block n >>= B.packCString
cueTrackAudio <- c_get_cue_sheet_track_audio block n
cueTrackPreEmphasis <- c_get_cue_sheet_track_preemphasis block n
numIndices <- c_get_cue_sheet_track_num_indices block n
cueTrackIndices <- if numIndices == 0
numIndices <- c_get_cue_sheet_track_num_indices block n
(cueTrackPregapIndex, cueTrackIndices) <- if numIndices == 0
then throwM (MetaInvalidCueSheet "Cannot read CUE track without indices")
else mapM (c_get_cue_sheet_track_index block n) (0 :| [1..numIndices - 1])
else do
hasPregap <- c_get_cue_sheet_track_has_pregap_index block n
let pregapOne :: Num a => a
pregapOne = if hasPregap then 1 else 0
range =
if numIndices > pregapOne
then [pregapOne..numIndices - 1]
else []
pregapIndex <- if hasPregap
then Just <$> c_get_cue_sheet_track_index block n 0
else return Nothing
trackIndices <- mapM (c_get_cue_sheet_track_index block n) (NE.fromList range)
return (pregapIndex, trackIndices)
return CueTrack {..}

foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_track_offset"
Expand All @@ -380,6 +400,9 @@ foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_track_preemphasis"
foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_track_num_indices"
c_get_cue_sheet_track_num_indices :: Metadata -> Word8 -> IO Word8

foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_track_has_pregap_index"
c_get_cue_sheet_track_has_pregap_index :: Metadata -> Word8 -> IO Bool

foreign import ccall unsafe "FLAC__metadata_get_cue_sheet_track_index"
c_get_cue_sheet_track_index :: Metadata -> Word8 -> Word8 -> IO Word64

Expand All @@ -391,21 +414,23 @@ setCueSheetData block CueSheetData {..} = do
c_set_cue_sheet_mcn block mcnPtr (fromIntegral mcnSize)
c_set_cue_sheet_lead_in block cueLeadIn
c_set_cue_sheet_is_cd block cueIsCd
let numTracks = fromIntegral (NE.length cueTracks)
let numTracks = fromIntegral (length cueTracks + 1)
res <- objectCueSheetResizeTracks block numTracks
goodOutcome <- if res
then
let go ts =
case NE.uncons ts of
((t,n), mts) -> do
res' <- setCueSheetTrack block t n
case uncons ts of
Nothing ->
setCueSheetTrack block cueLeadOutTrack (numTracks - 1) 170
Just ((t,n),ts') -> do
res' <- setCueSheetTrack block t n (n + 1)
if res'
then maybe (return True) go mts
then go ts'
else return False
in go (NE.zip cueTracks (NE.fromList [0..]))
in go (zip cueTracks [0..])
else return False
when goodOutcome $ do
res' <- objectPictureIsLegal block
res' <- objectCueSheetIsLegal block cueIsCd
case res' of
Nothing -> return ()
Just msg -> throwM (MetaInvalidCueSheet msg)
Expand All @@ -422,26 +447,31 @@ foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_is_cd"

-- | Poke a 'CueTrack' an specified index.

setCueSheetTrack :: Metadata -> CueTrack -> Word8 -> IO Bool
setCueSheetTrack block CueTrack {..} n = do
setCueSheetTrack :: Metadata -> CueTrack -> Word8 -> Word8 -> IO Bool
setCueSheetTrack block CueTrack {..} n n' = do
c_set_cue_sheet_track_offset block n cueTrackOffset
c_set_cue_sheet_track_number block n
c_set_cue_sheet_track_number block n n'
B.useAsCStringLen cueTrackIsrc $ \(isrcPtr, isrcSize) ->
c_set_cue_sheet_track_isrc block n isrcPtr (fromIntegral isrcSize)
c_set_cue_sheet_track_audio block n cueTrackAudio
c_set_cue_sheet_track_pre_emphasis block n cueTrackPreEmphasis
let numIndices = fromIntegral (NE.length cueTrackIndices)
let pregapOne :: Num a => a
pregapOne = if isJust cueTrackPregapIndex then 1 else 0
numIndices = fromIntegral (NE.length cueTrackIndices + pregapOne)
goodOutcome <- objectCueSheetTrackResizeIndices block n numIndices
when goodOutcome $
forM_ (NE.zip cueTrackIndices (NE.fromList [0..])) $ \(offset, i) ->
c_set_cue_sheet_track_index block n i offset
when goodOutcome $ do
forM_ cueTrackPregapIndex $ \offset ->
c_set_cue_sheet_track_index block n 0 0 offset
let range = zip [pregapOne..] [1..]
forM_ (NE.zip cueTrackIndices (NE.fromList range)) $ \(offset, (i,i')) ->
c_set_cue_sheet_track_index block n i i' offset
return goodOutcome

foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_track_offset"
c_set_cue_sheet_track_offset :: Metadata -> Word8 -> Word64 -> IO ()

foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_track_number"
c_set_cue_sheet_track_number :: Metadata -> Word8 -> IO ()
c_set_cue_sheet_track_number :: Metadata -> Word8 -> Word8 -> IO ()

foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_track_isrc"
c_set_cue_sheet_track_isrc :: Metadata -> Word8 -> CString -> CUInt -> IO ()
Expand All @@ -453,7 +483,7 @@ foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_track_pre_emphasis"
c_set_cue_sheet_track_pre_emphasis :: Metadata -> Word8 -> Bool -> IO ()

foreign import ccall unsafe "FLAC__metadata_set_cue_sheet_track_index"
c_set_cue_sheet_track_index :: Metadata -> Word8 -> Word8 -> Word64 -> IO ()
c_set_cue_sheet_track_index :: Metadata -> Word8 -> Word8 -> Word8 -> Word64 -> IO ()

----------------------------------------------------------------------------
-- Picture
Expand Down
10 changes: 3 additions & 7 deletions Codec/Audio/FLAC/Metadata/Internal/Object.hs
Expand Up @@ -92,13 +92,9 @@ foreign import ccall unsafe "FLAC__metadata_object_cuesheet_track_resize_indices
-- something is wrong, the explanation is return in 'Just', otherwise
-- 'Nothing' is returned.

objectCueSheetIsLegal :: Metadata -> IO (Maybe Text)
objectCueSheetIsLegal block = alloca $ \cstrPtr -> do
-- NOTE The second Boolean argument of c_object_cuesheet_is_legal controls
-- whether to check against “more stringent requirements for a CD-DA
-- (audio) disc”. The checking should probably be controllable in some
-- way, but let's put 'True' here for now.
res <- c_object_cuesheet_is_legal block True cstrPtr
objectCueSheetIsLegal :: Metadata -> Bool -> IO (Maybe Text)
objectCueSheetIsLegal block checkCdda = alloca $ \cstrPtr -> do
res <- c_object_cuesheet_is_legal block checkCdda cstrPtr
if res
then return Nothing
else Just <$> (peek cstrPtr >>= peekCStringText)
Expand Down
7 changes: 6 additions & 1 deletion Codec/Audio/FLAC/Metadata/Internal/Types.hs
Expand Up @@ -189,8 +189,10 @@ data CueSheetData = CueSheetData
-- the first track may have INDEX 00 data.
, cueIsCd :: !Bool
-- ^ 'True' if CUE sheet corresponds to a Compact Disc, else 'False'.
, cueTracks :: !(NonEmpty CueTrack)
, cueTracks :: ![CueTrack]
-- ^ Collection of actual tracks in the CUE sheet, see 'CueTrack'.
, cueLeadOutTrack :: !CueTrack
-- ^ The obligatory lead-out track, will be written with index 170.
} deriving (Eq, Ord, Show, Read)

-- | Data type representing a single track is CUE sheet.
Expand All @@ -212,6 +214,9 @@ data CueTrack = CueTrack
-- ^ 'True' for audio tracks, 'False' for non-audio tracks.
, cueTrackPreEmphasis :: !Bool
-- ^ 'False' for no pre-emphasis, 'True' for pre-emphasis.
, cueTrackPregapIndex :: !(Maybe Word64)
-- ^ INDEX 00 (pregap) offset, see 'cueTrackIndices' for more info about
-- indices.
, cueTrackIndices :: !(NonEmpty Word64)
-- ^ Track's index points. Offset in samples, relative to the track
-- offset, of the index point. For CD-DA, the offset must be evenly
Expand Down
13 changes: 10 additions & 3 deletions cbits/metadata_level2_helpers.c
Expand Up @@ -253,6 +253,12 @@ FLAC__byte FLAC__metadata_get_cue_sheet_track_num_indices
return (block->data.cue_sheet.tracks + n)->num_indices;
}

FLAC__bool FLAC__metadata_get_cue_sheet_track_has_pregap_index
(FLAC__StreamMetadata *block, FLAC__byte n)
{
return ((block->data.cue_sheet.tracks + n)->indices + 0)-> number == 0;
}

FLAC__uint64 FLAC__metadata_get_cue_sheet_track_index
(FLAC__StreamMetadata *block, FLAC__byte n, FLAC__byte i)
{
Expand Down Expand Up @@ -292,9 +298,9 @@ void FLAC__metadata_set_cue_sheet_track_offset
}

void FLAC__metadata_set_cue_sheet_track_number
(FLAC__StreamMetadata *block, FLAC__byte n)
(FLAC__StreamMetadata *block, FLAC__byte n, FLAC__byte n_)
{
(block->data.cue_sheet.tracks + n)->number = n + 1;
(block->data.cue_sheet.tracks + n)->number = n_;
}

void FLAC__metadata_set_cue_sheet_track_isrc
Expand Down Expand Up @@ -324,9 +330,10 @@ void FLAC__metadata_set_cue_sheet_track_pre_emphasis
}

void FLAC__metadata_set_cue_sheet_track_index
(FLAC__StreamMetadata *block, FLAC__byte n, FLAC__byte i, FLAC__uint64 offset)
(FLAC__StreamMetadata *block, FLAC__byte n, FLAC__byte i, FLAC__byte i_, FLAC__uint64 offset)
{
((block->data.cue_sheet.tracks + n)->indices + i)->offset = offset;
((block->data.cue_sheet.tracks + n)->indices + i)->number = i_;
}

/* Picture */
Expand Down
5 changes: 3 additions & 2 deletions cbits/metadata_level2_helpers.h
Expand Up @@ -83,18 +83,19 @@ char *FLAC__metadata_get_cue_sheet_track_isrc(FLAC__StreamMetadata *, FLAC__byte
FLAC__bool FLAC__metadata_get_cue_sheet_track_audio(FLAC__StreamMetadata *, FLAC__byte);
FLAC__bool FLAC__metadata_get_cue_sheet_track_preemphasis(FLAC__StreamMetadata *, FLAC__byte);
FLAC__byte FLAC__metadata_get_cue_sheet_track_num_indices(FLAC__StreamMetadata *, FLAC__byte);
FLAC__bool FLAC__metadata_get_cue_sheet_track_has_pregap_index(FLAC__StreamMetadata *, FLAC__byte);
FLAC__uint64 FLAC__metadata_get_cue_sheet_track_index(FLAC__StreamMetadata *, FLAC__byte, FLAC__byte);

void FLAC__metadata_set_cue_sheet_mcn(FLAC__StreamMetadata *, char *, unsigned);
void FLAC__metadata_set_cue_sheet_lead_in(FLAC__StreamMetadata *, FLAC__uint64);
void FLAC__metadata_set_cue_sheet_is_cd(FLAC__StreamMetadata *, FLAC__bool);

void FLAC__metadata_set_cue_sheet_track_offset(FLAC__StreamMetadata *, FLAC__byte, FLAC__uint64);
void FLAC__metadata_set_cue_sheet_track_number(FLAC__StreamMetadata *, FLAC__byte);
void FLAC__metadata_set_cue_sheet_track_number(FLAC__StreamMetadata *, FLAC__byte, FLAC__byte);
void FLAC__metadata_set_cue_sheet_track_isrc(FLAC__StreamMetadata *, FLAC__byte, char *, unsigned);
void FLAC__metadata_set_cue_sheet_track_audio(FLAC__StreamMetadata *, FLAC__byte, FLAC__bool);
void FLAC__metadata_set_cue_sheet_track_pre_emphasis(FLAC__StreamMetadata *, FLAC__byte, FLAC__bool);
void FLAC__metadata_set_cue_sheet_track_index(FLAC__StreamMetadata *, FLAC__byte, FLAC__byte, FLAC__uint64);
void FLAC__metadata_set_cue_sheet_track_index(FLAC__StreamMetadata *, FLAC__byte, FLAC__byte, FLAC__byte, FLAC__uint64);

/* Picture */

Expand Down

0 comments on commit 2e6f31f

Please sign in to comment.