{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#include "overlapping-compat.h"
module Web.Internal.FormUrlEncoded where
import Prelude ()
import Prelude.Compat
import Control.Arrow ((***))
import Control.Monad ((<=<))
import Data.ByteString.Builder (shortByteString, toLazyByteString)
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Char8 as BSL8
import Data.Coerce (coerce)
import qualified Data.Foldable as F
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Int (Int16, Int32, Int64, Int8)
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List (intersperse, sortBy)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Monoid (All (..), Any (..), Dual (..),
Product (..), Sum (..))
import Data.Ord (comparing)
import Data.Proxy (Proxy (..))
import Data.Semigroup (Semigroup (..))
import qualified Data.Semigroup as Semi
import Data.Tagged (Tagged (..))
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Text.Encoding.Error (lenientDecode)
import qualified Data.Text.Lazy as Lazy
import Data.Time.Compat (Day, LocalTime, NominalDiffTime,
UTCTime, ZonedTime)
import Data.Void (Void)
import Data.Word (Word16, Word32, Word64, Word8)
import GHC.Exts (Constraint, IsList (..))
import GHC.Generics
import GHC.TypeLits
import Network.HTTP.Types.URI (urlDecode, urlEncodeBuilder)
import Numeric.Natural (Natural)
import Web.Internal.HttpApiData
class ToFormKey k where
toFormKey :: k -> Text
instance ToFormKey () where toFormKey = toQueryParam
instance ToFormKey Char where toFormKey = toQueryParam
instance ToFormKey Bool where toFormKey = toQueryParam
instance ToFormKey Ordering where toFormKey = toQueryParam
instance ToFormKey Double where toFormKey = toQueryParam
instance ToFormKey Float where toFormKey = toQueryParam
instance ToFormKey Int where toFormKey = toQueryParam
instance ToFormKey Int8 where toFormKey = toQueryParam
instance ToFormKey Int16 where toFormKey = toQueryParam
instance ToFormKey Int32 where toFormKey = toQueryParam
instance ToFormKey Int64 where toFormKey = toQueryParam
instance ToFormKey Integer where toFormKey = toQueryParam
instance ToFormKey Word where toFormKey = toQueryParam
instance ToFormKey Word8 where toFormKey = toQueryParam
instance ToFormKey Word16 where toFormKey = toQueryParam
instance ToFormKey Word32 where toFormKey = toQueryParam
instance ToFormKey Word64 where toFormKey = toQueryParam
instance ToFormKey Day where toFormKey = toQueryParam
instance ToFormKey LocalTime where toFormKey = toQueryParam
instance ToFormKey ZonedTime where toFormKey = toQueryParam
instance ToFormKey UTCTime where toFormKey = toQueryParam
instance ToFormKey NominalDiffTime where toFormKey = toQueryParam
instance ToFormKey String where toFormKey = toQueryParam
instance ToFormKey Text where toFormKey = toQueryParam
instance ToFormKey Lazy.Text where toFormKey = toQueryParam
instance ToFormKey All where toFormKey = toQueryParam
instance ToFormKey Any where toFormKey = toQueryParam
instance ToFormKey a => ToFormKey (Dual a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Sum a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Product a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Semi.Min a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Semi.Max a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Semi.First a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Semi.Last a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey a => ToFormKey (Tagged b a) where toFormKey = coerce (toFormKey :: a -> Text)
instance ToFormKey Void where toFormKey = toQueryParam
instance ToFormKey Natural where toFormKey = toQueryParam
class FromFormKey k where
parseFormKey :: Text -> Either Text k
instance FromFormKey () where parseFormKey = parseQueryParam
instance FromFormKey Char where parseFormKey = parseQueryParam
instance FromFormKey Bool where parseFormKey = parseQueryParam
instance FromFormKey Ordering where parseFormKey = parseQueryParam
instance FromFormKey Double where parseFormKey = parseQueryParam
instance FromFormKey Float where parseFormKey = parseQueryParam
instance FromFormKey Int where parseFormKey = parseQueryParam
instance FromFormKey Int8 where parseFormKey = parseQueryParam
instance FromFormKey Int16 where parseFormKey = parseQueryParam
instance FromFormKey Int32 where parseFormKey = parseQueryParam
instance FromFormKey Int64 where parseFormKey = parseQueryParam
instance FromFormKey Integer where parseFormKey = parseQueryParam
instance FromFormKey Word where parseFormKey = parseQueryParam
instance FromFormKey Word8 where parseFormKey = parseQueryParam
instance FromFormKey Word16 where parseFormKey = parseQueryParam
instance FromFormKey Word32 where parseFormKey = parseQueryParam
instance FromFormKey Word64 where parseFormKey = parseQueryParam
instance FromFormKey Day where parseFormKey = parseQueryParam
instance FromFormKey LocalTime where parseFormKey = parseQueryParam
instance FromFormKey ZonedTime where parseFormKey = parseQueryParam
instance FromFormKey UTCTime where parseFormKey = parseQueryParam
instance FromFormKey NominalDiffTime where parseFormKey = parseQueryParam
instance FromFormKey String where parseFormKey = parseQueryParam
instance FromFormKey Text where parseFormKey = parseQueryParam
instance FromFormKey Lazy.Text where parseFormKey = parseQueryParam
instance FromFormKey All where parseFormKey = parseQueryParam
instance FromFormKey Any where parseFormKey = parseQueryParam
instance FromFormKey a => FromFormKey (Dual a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Sum a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Product a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Semi.Min a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Semi.Max a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Semi.First a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Semi.Last a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey a => FromFormKey (Tagged b a) where parseFormKey = coerce (parseFormKey :: Text -> Either Text a)
instance FromFormKey Void where parseFormKey = parseQueryParam
instance FromFormKey Natural where parseFormKey = parseQueryParam
newtype Form = Form { unForm :: HashMap Text [Text] }
deriving (Eq, Read, Generic, Semigroup, Monoid)
instance Show Form where
showsPrec d form = showParen (d > 10) $
showString "fromList " . shows (toListStable form)
instance IsList Form where
type Item Form = (Text, Text)
fromList = Form . HashMap.fromListWith (flip (<>)) . fmap (\(k, v) -> (k, [v]))
toList = concatMap (\(k, vs) -> map ((,) k) vs) . HashMap.toList . unForm
toListStable :: Form -> [(Text, Text)]
toListStable = sortOn fst . toList
class ToForm a where
toForm :: a -> Form
default toForm :: (Generic a, GToForm a (Rep a)) => a -> Form
toForm = genericToForm defaultFormOptions
instance ToForm Form where toForm = id
instance (ToFormKey k, ToHttpApiData v) => ToForm [(k, v)] where
toForm = fromList . map (toFormKey *** toQueryParam)
instance (ToFormKey k, ToHttpApiData v) => ToForm (Map k [v]) where
toForm = fromEntriesByKey . Map.toList
instance (ToFormKey k, ToHttpApiData v) => ToForm (HashMap k [v]) where
toForm = fromEntriesByKey . HashMap.toList
instance ToHttpApiData v => ToForm (IntMap [v]) where
toForm = fromEntriesByKey . IntMap.toList
fromEntriesByKey :: (ToFormKey k, ToHttpApiData v) => [(k, [v])] -> Form
fromEntriesByKey = Form . HashMap.fromListWith (<>) . map (toFormKey *** map toQueryParam)
data Proxy3 a b c = Proxy3
type family NotSupported (cls :: k1) (a :: k2) (reason :: Symbol) :: Constraint where
#if __GLASGOW_HASKELL__ < 800
NotSupported cls a "this type family is actually empty" = ()
#else
NotSupported cls a reason = TypeError
( 'Text "Cannot derive a Generic-based " ':<>: 'ShowType cls ':<>: 'Text " instance for " ':<>: 'ShowType a ':<>: 'Text "." ':$$:
'ShowType a ':<>: 'Text " " ':<>: 'Text reason ':<>: 'Text "," ':$$:
'Text "but Generic-based " ':<>: 'ShowType cls ':<>: 'Text " instances can be derived only for records" ':$$:
'Text "(i.e. product types with named fields)." )
#endif
genericToForm :: forall a. (Generic a, GToForm a (Rep a)) => FormOptions -> a -> Form
genericToForm opts = gToForm (Proxy :: Proxy a) opts . from
class GToForm t (f :: * -> *) where
gToForm :: Proxy t -> FormOptions -> f x -> Form
instance (GToForm t f, GToForm t g) => GToForm t (f :*: g) where
gToForm p opts (a :*: b) = gToForm p opts a <> gToForm p opts b
instance (GToForm t f) => GToForm t (M1 D x f) where
gToForm p opts (M1 a) = gToForm p opts a
instance (GToForm t f) => GToForm t (M1 C x f) where
gToForm p opts (M1 a) = gToForm p opts a
instance OVERLAPPABLE_ (Selector s, ToHttpApiData c) => GToForm t (M1 S s (K1 i c)) where
gToForm _ opts (M1 (K1 c)) = fromList [(key, toQueryParam c)]
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance (Selector s, ToHttpApiData c) => GToForm t (M1 S s (K1 i (Maybe c))) where
gToForm _ opts (M1 (K1 c)) =
case c of
Nothing -> mempty
Just x -> fromList [(key, toQueryParam x)]
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance (Selector s, ToHttpApiData c) => GToForm t (M1 S s (K1 i [c])) where
gToForm _ opts (M1 (K1 cs)) = fromList (map (\c -> (key, toQueryParam c)) cs)
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance OVERLAPPING_ (Selector s) => GToForm t (M1 S s (K1 i String)) where
gToForm _ opts (M1 (K1 c)) = fromList [(key, toQueryParam c)]
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance NotSupported ToForm t "is a sum type" => GToForm t (f :+: g) where gToForm = error "impossible"
class FromForm a where
fromForm :: Form -> Either Text a
default fromForm :: (Generic a, GFromForm a (Rep a)) => Form -> Either Text a
fromForm = genericFromForm defaultFormOptions
instance FromForm Form where fromForm = pure
instance (FromFormKey k, FromHttpApiData v) => FromForm [(k, v)] where
fromForm = fmap (concatMap (\(k, vs) -> map ((,) k) vs)) . toEntriesByKey
instance (Ord k, FromFormKey k, FromHttpApiData v) => FromForm (Map k [v]) where
fromForm = fmap (Map.fromListWith (<>)) . toEntriesByKey
instance (Eq k, Hashable k, FromFormKey k, FromHttpApiData v) => FromForm (HashMap k [v]) where
fromForm = fmap (HashMap.fromListWith (<>)) . toEntriesByKey
instance FromHttpApiData v => FromForm (IntMap [v]) where
fromForm = fmap (IntMap.fromListWith (<>)) . toEntriesByKey
toEntriesByKey :: (FromFormKey k, FromHttpApiData v) => Form -> Either Text [(k, [v])]
toEntriesByKey = traverse parseGroup . HashMap.toList . unForm
where
parseGroup (k, vs) = (,) <$> parseFormKey k <*> traverse parseQueryParam vs
toEntriesByKeyStable :: (Ord k, FromFormKey k, FromHttpApiData v) => Form -> Either Text [(k, [v])]
toEntriesByKeyStable = fmap (sortOn fst) . toEntriesByKey
genericFromForm :: forall a. (Generic a, GFromForm a (Rep a)) => FormOptions -> Form -> Either Text a
genericFromForm opts f = to <$> gFromForm (Proxy :: Proxy a) opts f
class GFromForm t (f :: * -> *) where
gFromForm :: Proxy t -> FormOptions -> Form -> Either Text (f x)
instance (GFromForm t f, GFromForm t g) => GFromForm t (f :*: g) where
gFromForm p opts f = (:*:) <$> gFromForm p opts f <*> gFromForm p opts f
instance GFromForm t f => GFromForm t (M1 D x f) where
gFromForm p opts f = M1 <$> gFromForm p opts f
instance GFromForm t f => GFromForm t (M1 C x f) where
gFromForm p opts f = M1 <$> gFromForm p opts f
instance OVERLAPPABLE_ (Selector s, FromHttpApiData c) => GFromForm t (M1 S s (K1 i c)) where
gFromForm _ opts form = M1 . K1 <$> parseUnique key form
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance (Selector s, FromHttpApiData c) => GFromForm t (M1 S s (K1 i (Maybe c))) where
gFromForm _ opts form = M1 . K1 <$> parseMaybe key form
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance (Selector s, FromHttpApiData c) => GFromForm t (M1 S s (K1 i [c])) where
gFromForm _ opts form = M1 . K1 <$> parseAll key form
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance OVERLAPPING_ (Selector s) => GFromForm t (M1 S s (K1 i String)) where
gFromForm _ opts form = M1 . K1 <$> parseUnique key form
where
key = Text.pack $ fieldLabelModifier opts $ selName (Proxy3 :: Proxy3 s g p)
instance NotSupported FromForm t "is a sum type" => GFromForm t (f :+: g) where gFromForm = error "impossible"
urlEncodeForm :: Form -> BSL.ByteString
urlEncodeForm = urlEncodeParams . toList
urlEncodeFormStable :: Form -> BSL.ByteString
urlEncodeFormStable = urlEncodeParams . sortOn fst . toList
urlEncodeParams :: [(Text, Text)] -> BSL.ByteString
urlEncodeParams = toLazyByteString . mconcat . intersperse (shortByteString "&") . map encodePair
where
escape = urlEncodeBuilder True . Text.encodeUtf8
encodePair (k, "") = escape k
encodePair (k, v) = escape k <> shortByteString "=" <> escape v
urlDecodeForm :: BSL.ByteString -> Either Text Form
urlDecodeForm = fmap toForm . urlDecodeParams
urlDecodeParams :: BSL.ByteString -> Either Text [(Text, Text)]
urlDecodeParams bs = traverse parsePair pairs
where
pairs = map (BSL8.split '=') (BSL8.split '&' bs)
unescape = Text.decodeUtf8With lenientDecode . urlDecode True . BSL.toStrict
parsePair p =
case map unescape p of
[k, v] -> return (k, v)
[k] -> return (k, "")
xs -> Left $ "not a valid pair: " <> Text.intercalate "=" xs
urlDecodeAsForm :: FromForm a => BSL.ByteString -> Either Text a
urlDecodeAsForm = fromForm <=< urlDecodeForm
urlEncodeAsForm :: ToForm a => a -> BSL.ByteString
urlEncodeAsForm = urlEncodeForm . toForm
urlEncodeAsFormStable :: ToForm a => a -> BSL.ByteString
urlEncodeAsFormStable = urlEncodeFormStable . toForm
lookupAll :: Text -> Form -> [Text]
lookupAll key = F.concat . HashMap.lookup key . unForm
lookupMaybe :: Text -> Form -> Either Text (Maybe Text)
lookupMaybe key form =
case lookupAll key form of
[] -> pure Nothing
[v] -> pure (Just v)
_ -> Left $ "Duplicate key " <> Text.pack (show key)
lookupUnique :: Text -> Form -> Either Text Text
lookupUnique key form = do
mv <- lookupMaybe key form
case mv of
Just v -> pure v
Nothing -> Left $ "Could not find key " <> Text.pack (show key)
parseAll :: FromHttpApiData v => Text -> Form -> Either Text [v]
parseAll key = parseQueryParams . lookupAll key
parseMaybe :: FromHttpApiData v => Text -> Form -> Either Text (Maybe v)
parseMaybe key = parseQueryParams <=< lookupMaybe key
parseUnique :: FromHttpApiData v => Text -> Form -> Either Text v
parseUnique key form = lookupUnique key form >>= parseQueryParam
data FormOptions = FormOptions
{
fieldLabelModifier :: String -> String
}
defaultFormOptions :: FormOptions
defaultFormOptions = FormOptions
{ fieldLabelModifier = id
}
sortOn :: Ord b => (a -> b) -> [a] -> [a]
sortOn f = sortBy (comparing f)