Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Path a where
- readPathAs :: Path a => proxy a -> Text -> Maybe a
- class Query a where
- data QueryRep
- data File = File {}
- type Param = (ByteString, ByteString)
- class ReqParam a where
- reqParams :: proxy a -> Query -> [Param] -> [File] -> [(ByteString, Maybe a)]
- reqParamRep :: proxy a -> QueryRep
- class Strategy w where
- type SNext w k a prms :: [Elem]
- strategy :: (KnownSymbol k, NotMember k prms, MonadPlus m) => w a -> proxy' k -> [Maybe a] -> Dict prms -> m (Dict (SNext w k a prms))
- strategyRep :: w a -> StrategyRep
- 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
read route path parameter.
Path Bool | javascript boolean. when "false", "0", "-0", "", "null", "undefined", "NaN" then False, else True. since 0.6.0.0. |
Path Char | |
Path Double | |
Path Float | |
Path Int | |
Path Int8 | |
Path Int16 | |
Path Int32 | |
Path Int64 | |
Path Integer | |
Path Word | |
Path Word8 | |
Path Word16 | |
Path Word32 | |
Path Word64 | |
Path String | |
Path ByteString | |
Path ByteString | |
Path Text | |
Path Text | |
Path Day | fuzzy date parse. three decimal split by 1 char. if year < 100 then + 2000. since 0.16.0. example:
|
readPathAs :: Path a => proxy a -> Text -> Maybe a Source
readPath providing type using Proxy.
query parameter
:: Maybe ByteString | value of query parameter. Nothing is key only parameter. |
-> Maybe a | Noting is fail. |
read query parameter.
queryRep :: proxy a -> QueryRep Source
pretty query parameter.
Query Bool | javascript boolean. when "false", "0", "-0", "", "null", "undefined", "NaN" then False, else True. since 0.6.0.0. |
Query Double | |
Query Float | |
Query Int | |
Query Int8 | |
Query Int16 | |
Query Int32 | |
Query Int64 | |
Query Integer | |
Query Word | |
Query Word8 | |
Query Word16 | |
Query Word32 | |
Query Word64 | |
Query String | |
Query () | always success. for check existence. |
Query ByteString | |
Query ByteString | |
Query Text | |
Query Text | |
Query Day | fuzzy date parse. three decimal split by 1 char. if year < 100 then + 2000. since 0.16.0. example:
|
Query a => Query (Maybe a) | allow no parameter. but check parameter type. |
request parameter
type Param = (ByteString, ByteString) Source
reqParams :: proxy a -> Query -> [Param] -> [File] -> [(ByteString, Maybe a)] Source
reqParamRep :: proxy a -> QueryRep Source
Strategy
strategy :: (KnownSymbol k, NotMember k prms, MonadPlus m) => w a -> proxy' k -> [Maybe a] -> Dict prms -> m (Dict (SNext w k a prms)) Source
strategyRep :: w a -> StrategyRep Source