apiary-1.2.3: 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

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:

  • 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

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:

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

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 

Instances

request parameter

class ReqParam a where Source

Methods

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

reqParamRep :: proxy a -> QueryRep Source

Instances

Strategy

class Strategy w where Source

Associated Types

type SNext w k a prms :: [Elem] Source

Methods

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

newtype StrategyRep Source

Constructors

StrategyRep 

Fields

strategyInfo :: Text
 

data First a Source

Constructors

First 

Instances

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

data One a Source

Constructors

One 

Instances

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

data Many a Source

Constructors

Many 

Instances

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

data Some a Source

Constructors

Some 

Instances

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

data Option a Source

Constructors

Option 

Instances

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

data Optional a Source

Constructors

Optional Text a 

Instances

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

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