-- |
--
-- Copyright:
--   This file is part of the package themoviedb.  It is subject to
--   the license terms in the LICENSE file found in the top-level
--   directory of this distribution and at:
--
--     https://github.com/pjones/themoviedb
--
--   No part of this package, including this file, may be copied,
--   modified, propagated, or distributed except according to the terms
--   contained in the LICENSE file.
--
-- License: MIT
--
-- Utility type for processing movie search results.
module Network.API.TheMovieDB.Internal.SearchResults
  ( SearchResults (..),
  )
where

import Data.Aeson

-- | Internal wrapper to parse a list of results from JSON.
newtype SearchResults a = SearchResults {forall a. SearchResults a -> [a]
searchResults :: [a]}
  deriving (SearchResults a -> SearchResults a -> Bool
forall a. Eq a => SearchResults a -> SearchResults a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchResults a -> SearchResults a -> Bool
$c/= :: forall a. Eq a => SearchResults a -> SearchResults a -> Bool
== :: SearchResults a -> SearchResults a -> Bool
$c== :: forall a. Eq a => SearchResults a -> SearchResults a -> Bool
Eq, Int -> SearchResults a -> ShowS
forall a. Show a => Int -> SearchResults a -> ShowS
forall a. Show a => [SearchResults a] -> ShowS
forall a. Show a => SearchResults a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchResults a] -> ShowS
$cshowList :: forall a. Show a => [SearchResults a] -> ShowS
show :: SearchResults a -> String
$cshow :: forall a. Show a => SearchResults a -> String
showsPrec :: Int -> SearchResults a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> SearchResults a -> ShowS
Show)

instance (FromJSON a) => FromJSON (SearchResults a) where
  parseJSON :: Value -> Parser (SearchResults a)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Search Results" forall a b. (a -> b) -> a -> b
$ \Object
v ->
    forall a. [a] -> SearchResults a
SearchResults
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"results"