#include "overlapping-compat.h"
module Servant.API.ContentTypes
    (
    
      JSON
    , PlainText
    , FormUrlEncoded
    , OctetStream
    
    , Accept(..)
    , MimeRender(..)
    , MimeUnrender(..)
    
    , NoContent(..)
    
    , AcceptHeader(..)
    , AllCTRender(..)
    , AllCTUnrender(..)
    , AllMime(..)
    , AllMimeRender(..)
    , AllMimeUnrender(..)
    , FromFormUrlEncoded(..)
    , ToFormUrlEncoded(..)
    , eitherDecodeLenient
    , canHandleAcceptH
    ) where
import           Control.Arrow                    (left)
import           Control.Monad.Compat
import           Data.Aeson                       (FromJSON(..), ToJSON(..), encode)
import           Data.Aeson.Parser                (value)
import           Data.Aeson.Types                 (parseEither)
import           Data.Attoparsec.ByteString.Char8 (endOfInput, parseOnly,
                                                   skipSpace, (<?>))
import qualified Data.ByteString                  as BS
import           Data.ByteString.Lazy             (ByteString, fromStrict,
                                                   toStrict)
import qualified Data.ByteString.Lazy             as B
import qualified Data.ByteString.Lazy.Char8       as BC
import           Data.Maybe                       (isJust)
import           Data.Monoid.Compat
import           Data.String.Conversions          (cs)
import qualified Data.Text                        as TextS
import qualified Data.Text.Encoding               as TextS
import qualified Data.Text.Lazy                   as TextL
import qualified Data.Text.Lazy.Encoding          as TextL
import           Data.Typeable
import           GHC.Generics                     (Generic)
import qualified Network.HTTP.Media               as M
import           Network.URI                      (escapeURIString,
                                                   isUnreserved, unEscapeString)
import           Prelude                          ()
import           Prelude.Compat
data JSON deriving Typeable
data PlainText deriving Typeable
data FormUrlEncoded deriving Typeable
data OctetStream deriving Typeable
class Accept ctype where
    contentType   :: Proxy ctype -> M.MediaType
instance Accept JSON where
    contentType _ = "application" M.// "json"
instance Accept FormUrlEncoded where
    contentType _ = "application" M.// "x-www-form-urlencoded"
instance Accept PlainText where
    contentType _ = "text" M.// "plain" M./: ("charset", "utf-8")
instance Accept OctetStream where
    contentType _ = "application" M.// "octet-stream"
newtype AcceptHeader = AcceptHeader BS.ByteString
    deriving (Eq, Show, Read, Typeable, Generic)
class Accept ctype => MimeRender ctype a where
    mimeRender  :: Proxy ctype -> a -> ByteString
class (AllMime list) => AllCTRender (list :: [*]) a where
    
    
    
    handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString)
instance OVERLAPPABLE_
         (Accept ct, AllMime cts, AllMimeRender (ct ': cts) a) => AllCTRender (ct ': cts) a where
    handleAcceptH _ (AcceptHeader accept) val = M.mapAcceptMedia lkup accept
      where pctyps = Proxy :: Proxy (ct ': cts)
            amrs = allMimeRender pctyps val
            lkup = fmap (\(a,b) -> (a, (fromStrict $ M.renderHeader a, b))) amrs
class Accept ctype => MimeUnrender ctype a where
    mimeUnrender :: Proxy ctype -> ByteString -> Either String a
class AllCTUnrender (list :: [*]) a where
    handleCTypeH :: Proxy list
                 -> ByteString     
                 -> ByteString     
                 -> Maybe (Either String a)
instance ( AllMimeUnrender ctyps a ) => AllCTUnrender ctyps a where
    handleCTypeH _ ctypeH body = M.mapContentMedia lkup (cs ctypeH)
      where lkup = allMimeUnrender (Proxy :: Proxy ctyps) body
class AllMime (list :: [*]) where
    allMime :: Proxy list -> [M.MediaType]
instance AllMime '[] where
    allMime _ = []
instance (Accept ctyp, AllMime ctyps) => AllMime (ctyp ': ctyps) where
    allMime _ = (contentType pctyp):allMime pctyps
      where pctyp  = Proxy :: Proxy ctyp
            pctyps = Proxy :: Proxy ctyps
canHandleAcceptH :: AllMime list => Proxy list -> AcceptHeader -> Bool
canHandleAcceptH p (AcceptHeader h ) = isJust $ M.matchAccept (allMime p) h
class (AllMime list) => AllMimeRender (list :: [*]) a where
    allMimeRender :: Proxy list
                  -> a                              
                  -> [(M.MediaType, ByteString)]    
instance OVERLAPPABLE_ ( MimeRender ctyp a ) => AllMimeRender '[ctyp] a where
    allMimeRender _ a = [(contentType pctyp, mimeRender pctyp a)]
        where pctyp = Proxy :: Proxy ctyp
instance OVERLAPPABLE_
         ( MimeRender ctyp a
         , AllMimeRender (ctyp' ': ctyps) a
         ) => AllMimeRender (ctyp ': ctyp' ': ctyps) a where
    allMimeRender _ a = (contentType pctyp, mimeRender pctyp a)
                       :(allMimeRender pctyps a)
        where pctyp = Proxy :: Proxy ctyp
              pctyps = Proxy :: Proxy (ctyp' ': ctyps)
instance OVERLAPPING_ ( Accept ctyp ) => AllMimeRender '[ctyp] NoContent where
    allMimeRender _ _ = [(contentType pctyp, "")]
      where pctyp = Proxy :: Proxy ctyp
instance OVERLAPPING_
         ( AllMime (ctyp ': ctyp' ': ctyps)
         ) => AllMimeRender (ctyp ': ctyp' ': ctyps) NoContent where
    allMimeRender p _ = zip (allMime p) (repeat "")
class (AllMime list) => AllMimeUnrender (list :: [*]) a where
    allMimeUnrender :: Proxy list
                    -> ByteString
                    -> [(M.MediaType, Either String a)]
instance AllMimeUnrender '[] a where
    allMimeUnrender _ _ = []
instance ( MimeUnrender ctyp a
         , AllMimeUnrender ctyps a
         ) => AllMimeUnrender (ctyp ': ctyps) a where
    allMimeUnrender _ val = (contentType pctyp, mimeUnrender pctyp val)
                           :(allMimeUnrender pctyps val)
        where pctyp = Proxy :: Proxy ctyp
              pctyps = Proxy :: Proxy ctyps
instance OVERLAPPABLE_
         ToJSON a => MimeRender JSON a where
    mimeRender _ = encode
instance OVERLAPPABLE_
         ToFormUrlEncoded a => MimeRender FormUrlEncoded a where
    mimeRender _ = encodeFormUrlEncoded . toFormUrlEncoded
instance MimeRender PlainText TextL.Text where
    mimeRender _ = TextL.encodeUtf8
instance MimeRender PlainText TextS.Text where
    mimeRender _ = fromStrict . TextS.encodeUtf8
instance MimeRender PlainText String where
    mimeRender _ = BC.pack
instance MimeRender OctetStream ByteString where
    mimeRender _ = id
instance MimeRender OctetStream BS.ByteString where
    mimeRender _ = fromStrict
data NoContent = NoContent
  deriving (Show, Eq, Read)
eitherDecodeLenient :: FromJSON a => ByteString -> Either String a
eitherDecodeLenient input =
    parseOnly parser (cs input) >>= parseEither parseJSON
  where
    parser = skipSpace
          *> Data.Aeson.Parser.value
          <* skipSpace
          <* (endOfInput <?> "trailing junk after valid JSON")
instance FromJSON a => MimeUnrender JSON a where
    mimeUnrender _ = eitherDecodeLenient
instance FromFormUrlEncoded a => MimeUnrender FormUrlEncoded a where
    mimeUnrender _ = decodeFormUrlEncoded >=> fromFormUrlEncoded
instance MimeUnrender PlainText TextL.Text where
    mimeUnrender _ = left show . TextL.decodeUtf8'
instance MimeUnrender PlainText TextS.Text where
    mimeUnrender _ = left show . TextS.decodeUtf8' . toStrict
instance MimeUnrender PlainText String where
    mimeUnrender _ = Right . BC.unpack
instance MimeUnrender OctetStream ByteString where
    mimeUnrender _ = Right . id
instance MimeUnrender OctetStream BS.ByteString where
    mimeUnrender _ = Right . toStrict
class ToFormUrlEncoded a where
  toFormUrlEncoded :: a -> [(TextS.Text, TextS.Text)]
instance ToFormUrlEncoded [(TextS.Text, TextS.Text)] where
  toFormUrlEncoded = id
class FromFormUrlEncoded a where
  fromFormUrlEncoded :: [(TextS.Text, TextS.Text)] -> Either String a
instance FromFormUrlEncoded [(TextS.Text, TextS.Text)] where
  fromFormUrlEncoded = return
encodeFormUrlEncoded :: [(TextS.Text, TextS.Text)] -> ByteString
encodeFormUrlEncoded xs =
    let escape :: TextS.Text -> ByteString
        escape = cs . escapeURIString isUnreserved . cs
        encodePair :: (TextS.Text, TextS.Text) -> ByteString
        encodePair (k, "") = escape k
        encodePair (k, v) = escape k <> "=" <> escape v
    in B.intercalate "&" $ map encodePair xs
decodeFormUrlEncoded :: ByteString -> Either String [(TextS.Text, TextS.Text)]
decodeFormUrlEncoded "" = return []
decodeFormUrlEncoded q = do
    let xs :: [TextS.Text]
        xs = TextS.splitOn "&" . cs $ q
        parsePair :: TextS.Text -> Either String (TextS.Text, TextS.Text)
        parsePair p =
            case TextS.splitOn "=" p of
                [k,v] -> return ( unescape k
                                , unescape v
                                )
                [k] -> return ( unescape k, "" )
                _ -> Left $ "not a valid pair: " <> cs p
        unescape :: TextS.Text -> TextS.Text
        unescape = cs . unEscapeString . cs . TextS.intercalate "%20" . TextS.splitOn "+"
    mapM parsePair xs