jordan-servant-0.1.0.0: Servant Combinators for Jordan
Safe HaskellNone
LanguageHaskell2010

Jordan.Servant.Query.Parse

Description

Turn your jordan parsers into query-string parsers.

This module should be considered internal. Import Jordan.Servant.Query instead.

Synopsis

Documentation

data QueryKeyComponent Source #

Instances

Instances details
Eq QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Ord QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Read QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Show QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Generic QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Associated Types

type Rep QueryKeyComponent :: Type -> Type #

type Rep QueryKeyComponent Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

type Rep QueryKeyComponent = D1 ('MetaData "QueryKeyComponent" "Jordan.Servant.Query.Parse" "jordan-servant-0.1.0.0-4pWi47ZOJ6bHDVnhgja79c" 'False) (C1 ('MetaCons "RawValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "EmptyBraces" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BracedValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

newtype QueryKey Source #

Instances

Instances details
Eq QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Ord QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Read QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Show QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Generic QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Associated Types

type Rep QueryKey :: Type -> Type #

Methods

from :: QueryKey -> Rep QueryKey x #

to :: Rep QueryKey x -> QueryKey #

type Rep QueryKey Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

type Rep QueryKey = D1 ('MetaData "QueryKey" "Jordan.Servant.Query.Parse" "jordan-servant-0.1.0.0-4pWi47ZOJ6bHDVnhgja79c" 'True) (C1 ('MetaCons "QueryKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "queryKeyComponents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QueryKeyComponent])))

newtype QueryParser a Source #

Instances

Instances details
Monad QueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

(>>=) :: QueryParser a -> (a -> QueryParser b) -> QueryParser b #

(>>) :: QueryParser a -> QueryParser b -> QueryParser b #

return :: a -> QueryParser a #

Functor QueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

fmap :: (a -> b) -> QueryParser a -> QueryParser b #

(<$) :: a -> QueryParser b -> QueryParser a #

Applicative QueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

pure :: a -> QueryParser a #

(<*>) :: QueryParser (a -> b) -> QueryParser a -> QueryParser b #

liftA2 :: (a -> b -> c) -> QueryParser a -> QueryParser b -> QueryParser c #

(*>) :: QueryParser a -> QueryParser b -> QueryParser b #

(<*) :: QueryParser a -> QueryParser b -> QueryParser a #

Alternative QueryParser Source #

Alternative tries the left, than the right.

Both brances will be sparked off and tried in parallel.

Instance details

Defined in Jordan.Servant.Query.Parse

takeValue :: QueryParser (Maybe ByteString) Source #

Take the value at the head, ensuring along the way that the entire query matches.

newtype JordanQueryParser a Source #

Instances

Instances details
Functor JordanQueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Applicative JordanQueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

JSONTupleParser JordanQueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

consumeItemWith :: (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> JordanQueryParser a #

consumeItem :: FromJSON v => JordanQueryParser v #

JSONParser JordanQueryParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

parseObject :: (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> JordanQueryParser a #

parseObjectStrict :: (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> JordanQueryParser a #

parseDictionary :: (forall (jsonParser :: Type -> Type). JSONParser jsonParser => jsonParser a) -> JordanQueryParser [(Text, a)] #

parseText :: JordanQueryParser Text #

parseTextConstant :: Text -> JordanQueryParser () #

parseTuple :: (forall (arrayParser :: Type -> Type). JSONTupleParser arrayParser => arrayParser o) -> JordanQueryParser o #

parseArray :: FromJSON a => JordanQueryParser [a] #

parseArrayWith :: (forall (jsonParser :: Type -> Type). JSONParser jsonParser => jsonParser a) -> JordanQueryParser [a] #

parseNumber :: JordanQueryParser Scientific #

parseInteger :: JordanQueryParser Integer #

parseNull :: JordanQueryParser () #

parseBool :: JordanQueryParser Bool #

validateJSON :: JordanQueryParser (Either Text a) -> JordanQueryParser a #

nameParser :: Text -> JordanQueryParser a -> JordanQueryParser a #

addFormat :: Text -> JordanQueryParser a -> JordanQueryParser a #

Semigroup (JordanQueryParser a) Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

newtype JordanQueryObjectParser a Source #

Instances

Instances details
Functor JordanQueryObjectParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Applicative JordanQueryObjectParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

JSONObjectParser JordanQueryObjectParser Source # 
Instance details

Defined in Jordan.Servant.Query.Parse

Methods

parseFieldWith :: Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> JordanQueryObjectParser a #

parseDescribeFieldWith :: Text -> Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> JordanQueryObjectParser a #

parseField :: FromJSON v => Text -> JordanQueryObjectParser v #

parseDescribeField :: FromJSON v => Text -> Text -> JordanQueryObjectParser v #

parseFieldWithDefault :: Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> a -> JordanQueryObjectParser a #

parseDescribeFieldWithDefault :: Text -> Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> a -> JordanQueryObjectParser a #

parseQueryAtKeyWith Source #

Arguments

:: (forall jsonParser. JSONParser jsonParser => jsonParser a)

JSON parser to use. Note the rank-N type.

-> Text

Base key to use in the query string.

-> Query

Query string

-> Either String a

Either a value, or a brief (not super helpful) description of what went wrong.

Use Jordan to parse a query at a given "base" key.

We need a base key in case the JSON type is "just an int" or something.

hasQueryAtKey :: Text -> Query -> Bool Source #

Determine if there are any query keys that match this base key.

>>> hasQueryAtKey "foo" (parseQuery "foo[bar][baz]=true")
True
>>> hasQueryAtKey "foo" (parseQuery "bar[baz]=true&bar[foo]=true&foo=true")
True
>>> hasQueryAtKey "foo" (parseQuery "bar[baz]=true&bar[foo]=true")
False

parseQueryAtKey :: FromJSON a => Text -> Query -> Either String a Source #

Like parseQueryAtKeyWith, but uses the FromJSON instance, which is what you want 90% of the time.