{-# LANGUAGE PatternSynonyms #-}
module MusicScroll.TrackSuplement
( tsTitle,
tsArtist,
tsKeepArtist,
TrackSuplement (),
trackSuplement,
suplement,
mergeSuplement,
suplementOnlyArtist,
)
where
import Data.Text
import MusicScroll.TrackInfo
( TrackByPath (..),
TrackIdentifier,
TrackInfo (..),
pattern OnlyMissingArtist,
)
import Pipes (Pipe)
import qualified Pipes.Prelude as PP (map)
data TrackSuplement = TrackSuplement
{ TrackSuplement -> Text
tsTitle :: Text,
TrackSuplement -> Text
tsArtist :: Text,
TrackSuplement -> Bool
tsKeepArtist :: Bool
}
trackSuplement :: Text -> Text -> Bool -> Maybe TrackSuplement
trackSuplement :: Text -> Text -> Bool -> Maybe TrackSuplement
trackSuplement Text
title Text
artist Bool
keep
| Text -> Text
strip Text
artist Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
artist = TrackSuplement -> Maybe TrackSuplement
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Text -> Bool -> TrackSuplement
TrackSuplement Text
title Text
artist Bool
keep)
| Bool
otherwise = Maybe TrackSuplement
forall a. Maybe a
Nothing
suplement :: TrackSuplement -> TrackIdentifier -> TrackInfo
suplement :: TrackSuplement -> TrackIdentifier -> TrackInfo
suplement TrackSuplement
supl = (TrackByPath -> TrackInfo)
-> (TrackInfo -> TrackInfo) -> TrackIdentifier -> TrackInfo
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either TrackByPath -> TrackInfo
byPath TrackInfo -> TrackInfo
byInfo
where
byPath :: TrackByPath -> TrackInfo
byPath :: TrackByPath -> TrackInfo
byPath TrackByPath
path =
TrackInfo
{ tTitle :: Text
tTitle = TrackSuplement -> Text
tsTitle TrackSuplement
supl,
tArtist :: Text
tArtist = TrackSuplement -> Text
tsArtist TrackSuplement
supl,
tUrl :: SongFilePath
tUrl = TrackByPath -> SongFilePath
tpPath TrackByPath
path
}
byInfo :: TrackInfo -> TrackInfo
byInfo :: TrackInfo -> TrackInfo
byInfo TrackInfo
info = TrackInfo
info {tTitle :: Text
tTitle = TrackSuplement -> Text
tsTitle TrackSuplement
supl, tArtist :: Text
tArtist = TrackSuplement -> Text
tsArtist TrackSuplement
supl}
mergeSuplement :: Functor m => TrackSuplement -> Pipe TrackIdentifier TrackInfo m a
mergeSuplement :: forall (m :: * -> *) a.
Functor m =>
TrackSuplement -> Pipe TrackIdentifier TrackInfo m a
mergeSuplement = (TrackIdentifier -> TrackInfo)
-> Pipe TrackIdentifier TrackInfo m a
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
PP.map ((TrackIdentifier -> TrackInfo)
-> Pipe TrackIdentifier TrackInfo m a)
-> (TrackSuplement -> TrackIdentifier -> TrackInfo)
-> TrackSuplement
-> Pipe TrackIdentifier TrackInfo m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TrackSuplement -> TrackIdentifier -> TrackInfo
suplement
suplementOnlyArtist :: TrackSuplement -> TrackIdentifier -> TrackIdentifier
suplementOnlyArtist :: TrackSuplement -> TrackIdentifier -> TrackIdentifier
suplementOnlyArtist TrackSuplement
supl (Left byPath :: TrackByPath
byPath@TrackByPath
OnlyMissingArtist) =
let trackinfo :: TrackInfo
trackinfo =
TrackInfo
{ tTitle :: Text
tTitle = Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty Text -> Text
forall a. a -> a
id (TrackByPath -> Maybe Text
tpTitle TrackByPath
byPath),
tArtist :: Text
tArtist = TrackSuplement -> Text
tsArtist TrackSuplement
supl,
tUrl :: SongFilePath
tUrl = TrackByPath -> SongFilePath
tpPath TrackByPath
byPath
}
in TrackInfo -> TrackIdentifier
forall a b. b -> Either a b
Right TrackInfo
trackinfo
suplementOnlyArtist TrackSuplement
_ TrackIdentifier
other = TrackIdentifier
other