module Vimeta.UI.Common.Movie
( tagMovie,
)
where
import qualified Data.Text as Text
import Network.API.TheMovieDB
import Vimeta.Core
tagMovie :: (MonadIO m) => FilePath -> Movie -> Vimeta m ()
tagMovie :: FilePath -> Movie -> Vimeta m ()
tagMovie FilePath
filename Movie
movie = do
Context
context <- Vimeta m Context
forall r (m :: * -> *). MonadReader r m => m r
ask
let format :: Text
format = Config -> Text
configFormatMovie (Context -> Config
ctxConfig Context
context)
tmdbCfg :: Configuration
tmdbCfg = Context -> Configuration
ctxTMDBCfg Context
context
[Text] -> (Maybe FilePath -> Vimeta IO ()) -> Vimeta m ()
forall (m :: * -> *) a.
MonadIO m =>
[Text] -> (Maybe FilePath -> Vimeta IO a) -> Vimeta m a
withArtwork (Configuration -> Movie -> [Text]
moviePosterURLs Configuration
tmdbCfg Movie
movie) ((Maybe FilePath -> Vimeta IO ()) -> Vimeta m ())
-> (Maybe FilePath -> Vimeta IO ()) -> Vimeta m ()
forall a b. (a -> b) -> a -> b
$ \Maybe FilePath
artwork ->
case FormatTable -> FilePath -> Text -> Either FilePath Text
fromFormatString (Maybe FilePath -> FormatTable
formatMap Maybe FilePath
artwork) FilePath
"config.cmd_movie" Text
format of
Left FilePath
e -> FilePath -> Vimeta IO ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError FilePath
e
Right Text
cmd -> Text -> Vimeta IO ()
tagFile Text
cmd
where
formatMap :: Maybe FilePath -> FormatTable
formatMap :: Maybe FilePath -> FormatTable
formatMap Maybe FilePath
artwork =
[Item FormatTable] -> FormatTable
forall l. IsList l => [Item l] -> l
fromList
[ (Char
'Y', Maybe Day -> Maybe Text
formatFullDate (Maybe Day -> Maybe Text) -> Maybe Day -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Movie -> Maybe Day
movieReleaseDate Movie
movie),
(Char
'a', FilePath -> Text
forall a. ToText a => a -> Text
toText (FilePath -> Text) -> Maybe FilePath -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FilePath
artwork),
(Char
'd', Text -> Maybe Text
forall a. a -> Maybe a
Just (Int -> Text -> Text
Text.take Int
255 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Movie -> Text
movieOverview Movie
movie)),
(Char
'g', Genre -> Text
genreName (Genre -> Text) -> Maybe Genre -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Genre] -> Maybe Genre
forall a. [a] -> Maybe a
listToMaybe (Movie -> [Genre]
movieGenres Movie
movie)),
(Char
't', Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Movie -> Text
movieTitle Movie
movie),
(Char
'y', Maybe Day -> Maybe Text
formatYear (Maybe Day -> Maybe Text) -> Maybe Day -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Movie -> Maybe Day
movieReleaseDate Movie
movie),
(Char
'f', Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
forall a. ToText a => a -> Text
toText FilePath
filename)
]