{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards     #-}


{-

This file is part of the Haskell package playlists. It is subject to
the license terms in the LICENSE file found in the top-level directory
of this distribution and at git://pmade.com/playlists/LICENSE. No part
of playlists package, including this file, may be copied, modified,
propagated, or distributed except according to the terms contained in
the LICENSE file.

-}

--------------------------------------------------------------------------------
module Text.Playlist.Internal.Resolve
       ( resolve
       ) where

--------------------------------------------------------------------------------
import Control.Monad
import Data.Text (Text)
import qualified Data.Text as Text

--------------------------------------------------------------------------------
import Text.Playlist.Internal.Format
import Text.Playlist.Types

--------------------------------------------------------------------------------
-- Internal type to track when a playlist may need to be processed a
-- another time.  (Such as when a remote playlist refers to other
-- remote playlists.)
data Resolution = Flat Playlist | Again Playlist

--------------------------------------------------------------------------------
-- | If the given 'Playlist' contains tracks that reference remote
-- playlists, this function will recursively download and process
-- these playlists.  Returns a flattened playlist that should not
-- contain any references to other playlists.
--
-- You supply the downloading function as the second argument.  Use
-- whichever HTTP library that makes you happy.
--
-- There are two error conditions that are ignored by this function:
--
--   1. The nesting of playlists exceeds a (hard-coded) limit.  In
--      this case no playlists beyond the limit are processed.  Open a
--      pull request if you'd like to have a resolveN function that
--      allows you to specific the depth limit or one that returns an
--      error.
--
--   2. A downloaded playlist contains a syntax error.  In this case
--      the playlist is consider to have no tracks and is ignored.
--      Open a pull request if you want a version of this function
--      that returns some sort of an error instead of ignoring bad
--      playlists.
resolve :: forall m. (Monad m)
        => Playlist
        -- ^ A 'Playlist' that may contain references to other
        -- playlists.

        -> (Text -> m Playlist)
        -- ^ Downloading function.  This function should take a URL
        -- and return a parsed playlist.
        --
        -- It's expected that the URL points to another playlist that
        -- needs to be parsed and possibly resolved.

        -> m Playlist
        -- ^ A fully resolved 'Playlist'.  (All tracks should be files
        -- and not links to other playlists.)
resolve :: Playlist -> (Text -> m Playlist) -> m Playlist
resolve Playlist
playlist Text -> m Playlist
download = Int -> Playlist -> m Playlist
go Int
10 Playlist
playlist where

  ----------------------------------------------------------------------------
  -- Recursively process tracks in the 'Playlist' with a maximum depth
  -- of @n@.
  go :: Int -> Playlist -> m Playlist
  go :: Int -> Playlist -> m Playlist
go Int
_ [] = Playlist -> m Playlist
forall (m :: * -> *) a. Monad m => a -> m a
return []
  go Int
0 Playlist
xs = Playlist -> m Playlist
forall (m :: * -> *) a. Monad m => a -> m a
return Playlist
xs
  go Int
n Playlist
xs = ([Playlist] -> Playlist) -> m [Playlist] -> m Playlist
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Playlist] -> Playlist
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (m [Playlist] -> m Playlist) -> m [Playlist] -> m Playlist
forall a b. (a -> b) -> a -> b
$ Playlist -> (Track -> m Playlist) -> m [Playlist]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM Playlist
xs ((Track -> m Playlist) -> m [Playlist])
-> (Track -> m Playlist) -> m [Playlist]
forall a b. (a -> b) -> a -> b
$ \Track
track -> do
    Resolution
r <- Track -> m Resolution
process Track
track

    case Resolution
r of
      Flat Playlist
p  -> Playlist -> m Playlist
forall (m :: * -> *) a. Monad m => a -> m a
return Playlist
p
      Again Playlist
p -> Int -> Playlist -> m Playlist
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Playlist
p

  ----------------------------------------------------------------------------
  -- Process a single track.
  process :: Track -> m Resolution
  process :: Track -> m Resolution
process t :: Track
t@Track {Maybe Float
Maybe Text
Text
trackDuration :: Track -> Maybe Float
trackTitle :: Track -> Maybe Text
trackURL :: Track -> Text
trackDuration :: Maybe Float
trackTitle :: Maybe Text
trackURL :: Text
..} =
    case FilePath -> Maybe Format
fileNameToFormat (Text -> FilePath
Text.unpack Text
trackURL) of
      Maybe Format
Nothing -> Resolution -> m Resolution
forall (m :: * -> *) a. Monad m => a -> m a
return (Playlist -> Resolution
Flat [Track
t])
      Just Format
_  -> Playlist -> Resolution
Again (Playlist -> Resolution) -> m Playlist -> m Resolution
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> m Playlist
download Text
trackURL