| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Apiary.Param
- class Path a where
- readPathAs :: Path a => proxy a -> Text -> Maybe a
- class Typeable a => Query a where
- data QueryRep
- data File = File {}
- type Param = (ByteString, ByteString)
- class ReqParam a where
- class Strategy w where
- newtype StrategyRep = StrategyRep {
- strategyInfo :: Text
- data First a = First
- data One a = One
- data Many a = Many
- data Some a = Some
- data Option a = Option
- data Optional a = Optional Text a
- pBool :: Proxy Bool
- pInt :: Proxy Int
- pWord :: Proxy Word
- pDouble :: Proxy Double
- pText :: Proxy Text
- pLazyText :: Proxy Text
- pByteString :: Proxy ByteString
- pLazyByteString :: Proxy ByteString
- pString :: Proxy String
- pMaybe :: proxy a -> Proxy (Maybe a)
- pFile :: Proxy File
- pFirst :: proxy a -> First a
- pOne :: proxy a -> One a
- pMany :: proxy a -> Many a
- pSome :: proxy a -> Some a
- pOption :: proxy a -> Option a
- pOptional :: Show a => a -> Optional a
route path parameter
Instances
| Path Bool Source # | javascript boolean. when "false", "0", "-0", "", "null", "undefined", "NaN" then False, else True. since 0.6.0.0. |
| Path Char Source # | |
| Path Double Source # | |
| Path Float Source # | |
| Path Int Source # | |
| Path Int8 Source # | |
| Path Int16 Source # | |
| Path Int32 Source # | |
| Path Int64 Source # | |
| Path Integer Source # | |
| Path Word Source # | |
| Path Word8 Source # | |
| Path Word16 Source # | |
| Path Word32 Source # | |
| Path Word64 Source # | |
| Path ByteString Source # | |
| Path ByteString Source # | |
| Path String Source # | |
| Path Text Source # | |
| Path Text Source # | |
| Path Day Source # | fuzzy date parse. three decimal split by 1 char. if year < 100 then + 2000. since 0.16.0. example:
|
query parameter
class Typeable a => Query a where Source #
Minimal complete definition
Methods
readQuery :: Maybe ByteString -> Maybe a Source #
read query parameter.
queryRep :: proxy a -> QueryRep Source #
pretty query parameter.
Instances
| Query Bool Source # | javascript boolean. when "false", "0", "-0", "", "null", "undefined", "NaN" then False, else True. since 0.6.0.0. |
| Query Double Source # | |
| Query Float Source # | |
| Query Int Source # | |
| Query Int8 Source # | |
| Query Int16 Source # | |
| Query Int32 Source # | |
| Query Int64 Source # | |
| Query Integer Source # | |
| Query Word Source # | |
| Query Word8 Source # | |
| Query Word16 Source # | |
| Query Word32 Source # | |
| Query Word64 Source # | |
| Query () Source # | always success. for check existence. |
| Query ByteString Source # | |
| Query ByteString Source # | |
| Query String Source # | |
| Query Text Source # | |
| Query Text Source # | |
| Query Day Source # | fuzzy date parse. three decimal split by 1 char. if year < 100 then + 2000. since 0.16.0. example:
|
| Query a => Query (Maybe a) Source # | allow no parameter. but check parameter type. |
Constructors
| File | |
Fields
| |
request parameter
type Param = (ByteString, ByteString) Source #
class ReqParam a where Source #
Minimal complete definition
Strategy
class Strategy w where Source #
Minimal complete definition
Methods
strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => w a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext w k a prms)) Source #
strategyRep :: w a -> StrategyRep Source #
Constructors
| First |
Constructors
| Many |
Constructors
| Some |
Constructors
| Option |