module Sound.Freesound.User.Type where
import Control.Monad (mzero)
import Data.Aeson (FromJSON(..), Value(..), (.:))
import Data.Text (Text)
import qualified Data.Text as T
import Sound.Freesound.API (Resource, URI)
import qualified Sound.Freesound.Bookmark.Internal as Bookmark
import Sound.Freesound.List (List)
import qualified Sound.Freesound.Pack.Type as Pack
import qualified Sound.Freesound.Sound.Type as Sound
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
class User a where
name :: a -> Text
ref :: a -> Resource Detail
url :: a -> URI
data Summary = Summary {
user_name :: Text
, user_ref :: Resource Detail
, user_url :: URI
} deriving (Eq, Show)
instance User Summary where
name = user_name
ref = user_ref
url = user_url
instance FromJSON Summary where
parseJSON (Object v) =
Summary
<$> v .: "username"
<*> v .: "ref"
<*> v .: "url"
parseJSON _ = mzero
data Detail = Detail {
summary :: Summary
, sounds :: Resource (List Sound.Summary)
, packs :: Resource (List Pack.Summary)
, firstName :: Maybe Text
, lastName :: Maybe Text
, about :: Maybe Text
, homePage :: Maybe Text
, signature :: Maybe Text
, dateJoined :: Text
, bookmarkCategories :: Resource Bookmark.Categories
} deriving (Eq, Show)
instance User Detail where
name = name . summary
ref = ref . summary
url = url . summary
textToMaybe :: Maybe Text -> Maybe Text
textToMaybe Nothing = Nothing
textToMaybe (Just s)
| T.null s = Nothing
| otherwise = Just s
instance FromJSON Detail where
parseJSON j@(Object v) =
Detail
<$> parseJSON j
<*> v .: "sounds"
<*> v .: "packs"
<*> (textToMaybe <$> (v .: "first_name"))
<*> (textToMaybe <$> (v .: "last_name"))
<*> (textToMaybe <$> (v .: "about"))
<*> (textToMaybe <$> (v .: "home_page"))
<*> (textToMaybe <$> (v .: "signature"))
<*> v .: "date_joined"
<*> v .: "bookmark_categories"
parseJSON _ = mzero