Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- newtype Param = Param {}
- newtype ParamValue = ParamValue {}
- newtype QueryData = QueryData (Map Param ParamValue)
- singleton :: ToParam a => Param -> a -> QueryData
- insert :: ToParam a => Param -> a -> QueryData -> QueryData
- insertAll :: ToQuery a => a -> QueryData -> QueryData
- delete :: Param -> QueryData -> QueryData
- lookup :: FromParam a => Param -> QueryData -> Maybe a
- require :: FromParam a => Param -> QueryData -> Either Text a
- filterKey :: (Param -> Bool) -> QueryData -> QueryData
- member :: Param -> QueryData -> Bool
- elems :: QueryData -> [ParamValue]
- render :: QueryData -> ByteString
- parse :: ByteString -> QueryData
- queryData :: Query -> QueryData
- fromList :: [(Param, ParamValue)] -> QueryData
- toList :: QueryData -> [(Param, ParamValue)]
- class FromQuery a where
- parseQuery :: QueryData -> Either Text a
- class ToQuery a where
- class ToParam a where
- toParam :: a -> ParamValue
- class FromParam a where
- parseParam :: ParamValue -> Either Text a
- showQueryParam :: Show a => a -> ParamValue
- readQueryParam :: Read a => ParamValue -> Either Text a
- parseParams :: (Traversable t, FromParam a) => t ParamValue -> Either Text (t a)
- class GFromQuery (f :: k -> Type) where
- gParseQuery :: forall (p :: k). QueryData -> Either Text (f p)
- class GToQuery (f :: k -> Type) where
- class DefaultParam a where
- defaultParam :: a
Documentation
newtype ParamValue Source #
Instances
IsString ParamValue Source # | |
Defined in Web.Hyperbole.Data.QueryData fromString :: String -> ParamValue # | |
Show ParamValue Source # | |
Defined in Web.Hyperbole.Data.QueryData showsPrec :: Int -> ParamValue -> ShowS # show :: ParamValue -> String # showList :: [ParamValue] -> ShowS # | |
Eq ParamValue Source # | |
Defined in Web.Hyperbole.Data.QueryData (==) :: ParamValue -> ParamValue -> Bool # (/=) :: ParamValue -> ParamValue -> Bool # | |
Ord ParamValue Source # | |
Defined in Web.Hyperbole.Data.QueryData compare :: ParamValue -> ParamValue -> Ordering # (<) :: ParamValue -> ParamValue -> Bool # (<=) :: ParamValue -> ParamValue -> Bool # (>) :: ParamValue -> ParamValue -> Bool # (>=) :: ParamValue -> ParamValue -> Bool # max :: ParamValue -> ParamValue -> ParamValue # min :: ParamValue -> ParamValue -> ParamValue # |
Key-value store for query params and sessions
elems :: QueryData -> [ParamValue] Source #
render :: QueryData -> ByteString Source #
parse :: ByteString -> QueryData Source #
class FromQuery a where Source #
Decode a type from a QueryData
. Missing fields are set to defaultParam
data Filters = Filters { active :: Bool , term :: Text } deriving (Generic,FromQuery
,ToQuery
)
>>>
parseQuery $ parse "active=true&search=asdf"
Right (Filters True "asdf")
>>>
parseQuery $ parse "search=asdf"
Right (Filters False "asdf")
Nothing
parseQuery :: QueryData -> Either Text a Source #
default parseQuery :: (Generic a, GFromQuery (Rep a)) => QueryData -> Either Text a Source #
class ToQuery a where Source #
A page can store state in the browser query
string. ToQuery and FromQuery
control how a datatype is encoded to a full query string
data Filters = Filters { active :: Bool , term :: Text } deriving (Generic,FromQuery
,ToQuery
)
>>>
render $ toQuery $ Filter True "asdf"
"active=true&search=asdf"
If the value of a field is the same as DefaultParam
, it will be omitted from the query string
>>>
render $ toQuery $ Filter True ""
"active=true"
>>>
render $ toQuery $ Filter False ""
""
Nothing
class ToParam a where Source #
session
s, form
s, and query
s all encode data as query strings. ToParam and FromParam control how a datatype is encoded to a parameter. By default it simply url-encodes the show instance.
data Todo = Todo { id :: TodoId , task :: Text , completed :: Bool } deriving (Show, Read,ToParam
,FromParam
)
data Tags = Tags [Text]
instance ToParam
Tags where
toParam (Tags ts) = ParamValue $ Text.intercalate "," ts
Nothing
toParam :: a -> ParamValue Source #
default toParam :: Show a => a -> ParamValue Source #
Instances
class FromParam a where Source #
Decode data from a query
, session
, or form
parameter value
data Todo = Todo { id :: TodoId , task :: Text , completed :: Bool } deriving (Show, Read,ToParam
,FromParam
)
data Tags = Tags [Text]
instance FromParam
Tags where
parseParam (ParamValue t) =
pure $ Tags $ Text.splitOn "," t
Nothing
parseParam :: ParamValue -> Either Text a Source #
default parseParam :: Read a => ParamValue -> Either Text a Source #
Instances
showQueryParam :: Show a => a -> ParamValue Source #
Encode a Show as a query param
readQueryParam :: Read a => ParamValue -> Either Text a Source #
Decode a Read as a query param
parseParams :: (Traversable t, FromParam a) => t ParamValue -> Either Text (t a) Source #
Parse a Traversable (list) of params
class GFromQuery (f :: k -> Type) where Source #
Generic decoding of records from a Query
Instances
(GFromQuery f, GFromQuery g) => GFromQuery (f :*: g :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.QueryData | |
GFromQuery f => GFromQuery (M1 C c f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.QueryData | |
GFromQuery f => GFromQuery (M1 D d f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.QueryData | |
(Selector s, FromParam a, DefaultParam a) => GFromQuery (M1 S s (K1 R a :: k -> Type) :: k -> Type) Source # | |
class GToQuery (f :: k -> Type) where Source #
Generic encoding of records to a Query
Instances
class DefaultParam a where Source #
Data.Default doesn't have a Text instance. This class does
Nothing
defaultParam :: a Source #
default defaultParam :: Default a => a Source #
Instances
DefaultParam Text Source # | |
Defined in Web.Hyperbole.Data.QueryData defaultParam :: Text Source # | |
Default a => DefaultParam a Source # | |
Defined in Web.Hyperbole.Data.QueryData defaultParam :: a Source # |