apiary-2.0.1: Simple and type safe web framework that generate web API documentation.

Safe HaskellNone
LanguageHaskell2010

Data.Apiary.Param

Contents

Synopsis

route path parameter

class Path a where Source

Methods

readPath Source

Arguments

:: Text 
-> Maybe a

Nothing is failed. | pretty type of route path parameter.

read route path parameter.

pathRep :: proxy a -> TypeRep Source

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 String Source 
Path ByteString Source 
Path ByteString 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:

  • 2014-02-05
  • 14-2-5
  • 14.2.05

readPathAs :: Path a => proxy a -> Text -> Maybe a Source

readPath providing type using Proxy.

query parameter

class Query a where Source

Minimal complete definition

readQuery, qTypeRep

Methods

readQuery Source

Arguments

:: 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.

qTypeRep :: proxy a -> TypeRep Source

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 String Source 
Query () Source

always success. for check existence.

Query ByteString Source 
Query ByteString 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:

  • 2014-02-05
  • 14-2-5
  • 14.2.05
Query a => Query (Maybe a) Source

allow no parameter. but check parameter type.

data QueryRep Source

Constructors

Strict TypeRep

require value

Nullable TypeRep

allow key only value

Check

check existance

NoValue 

data File Source

Constructors

File 

Fields

fileParameter :: ByteString
 
fileName :: ByteString
 
fileContentType :: ByteString
 
fileContent :: Either ByteString FilePath

check out uploadFilePath. since 2.0.0

a Left value store file in memmory, a Right value contain FilePath of uploaded file.

request parameter

class ReqParam a where Source

Methods

reqParams :: proxy a -> Query -> [Param] -> [File] -> [(ByteString, Maybe a)] Source

reqParamRep :: proxy a -> QueryRep Source

Strategy

class Strategy w where Source

Associated Types

type SNext w k a prms :: [KV *] Source

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

data First a Source

Constructors

First 

Instances

Strategy First Source 
type SNext First k a ps = (:) (KV *) ((:=) * k a) ps Source 

data One a Source

Constructors

One 

Instances

Strategy One Source 
type SNext One k a ps = (:) (KV *) ((:=) * k a) ps Source 

data Many a Source

Constructors

Many 

Instances

Strategy Many Source 
type SNext Many k a ps = (:) (KV *) ((:=) * k [a]) ps Source 

data Some a Source

Constructors

Some 

Instances

Strategy Some Source 
type SNext Some k a ps = (:) (KV *) ((:=) * k [a]) ps Source 

data Option a Source

Constructors

Option 

Instances

Strategy Option Source 
type SNext Option k a ps = (:) (KV *) ((:=) * k (Maybe a)) ps Source 

data Optional a Source

Constructors

Optional Text a 

Instances

Strategy Optional Source 
type SNext Optional k a ps = (:) (KV *) ((:=) * k a) ps Source 

Proxies

pMaybe :: proxy a -> Proxy (Maybe a) Source

strategy

pFirst :: proxy a -> First a Source

pOne :: proxy a -> One a Source

pMany :: proxy a -> Many a Source

pSome :: proxy a -> Some a Source

pOption :: proxy a -> Option a Source

pOptional :: Show a => a -> Optional a Source