apiary-2.1.2: 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 #

Minimal complete definition

readPath, pathRep

Methods

readPath :: Text -> Maybe a Source #

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 # 

Methods

readPath :: Text -> Maybe Int Source #

pathRep :: proxy Int -> TypeRep 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:

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

Methods

readPath :: Text -> Maybe Day Source #

pathRep :: proxy Day -> TypeRep Source #

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

readPath providing type using Proxy.

query parameter

class Typeable a => Query a where Source #

Minimal complete definition

readQuery

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:

  • 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

Instances

Eq File Source # 

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Show File Source # 

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

ReqParam File Source # 

Methods

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

reqParamRep :: proxy File -> QueryRep Source #

request parameter

class ReqParam a where Source #

Minimal complete definition

reqParams, reqParamRep

Methods

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

reqParamRep :: proxy a -> QueryRep Source #

Instances

Query a => ReqParam a Source # 

Methods

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

reqParamRep :: proxy a -> QueryRep Source #

ReqParam File Source # 

Methods

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

reqParamRep :: proxy File -> QueryRep Source #

Strategy

class Strategy w where Source #

Minimal complete definition

strategy, strategyRep

Associated Types

type SNext w (k :: Symbol) a (prms :: [KV *]) :: [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 #

Instances

Strategy Optional Source # 

Associated Types

type SNext (Optional :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Optional a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Optional k a prms)) Source #

strategyRep :: Optional a -> StrategyRep Source #

Strategy Option Source # 

Associated Types

type SNext (Option :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Option a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Option k a prms)) Source #

strategyRep :: Option a -> StrategyRep Source #

Strategy Some Source # 

Associated Types

type SNext (Some :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Some a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Some k a prms)) Source #

strategyRep :: Some a -> StrategyRep Source #

Strategy Many Source # 

Associated Types

type SNext (Many :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Many a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Many k a prms)) Source #

strategyRep :: Many a -> StrategyRep Source #

Strategy One Source # 

Associated Types

type SNext (One :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => One a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext One k a prms)) Source #

strategyRep :: One a -> StrategyRep Source #

Strategy First Source # 

Associated Types

type SNext (First :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => First a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext First k a prms)) Source #

strategyRep :: First a -> StrategyRep Source #

data First a Source #

Constructors

First 

Instances

Strategy First Source # 

Associated Types

type SNext (First :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => First a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext First k a prms)) Source #

strategyRep :: First a -> StrategyRep Source #

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

data One a Source #

Constructors

One 

Instances

Strategy One Source # 

Associated Types

type SNext (One :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => One a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext One k a prms)) Source #

strategyRep :: One a -> StrategyRep Source #

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

data Many a Source #

Constructors

Many 

Instances

Strategy Many Source # 

Associated Types

type SNext (Many :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Many a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Many k a prms)) Source #

strategyRep :: Many a -> StrategyRep Source #

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

data Some a Source #

Constructors

Some 

Instances

Strategy Some Source # 

Associated Types

type SNext (Some :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Some a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Some k a prms)) Source #

strategyRep :: Some a -> StrategyRep Source #

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

data Option a Source #

Constructors

Option 

Instances

Strategy Option Source # 

Associated Types

type SNext (Option :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Option a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Option k a prms)) Source #

strategyRep :: Option a -> StrategyRep Source #

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

data Optional a Source #

Constructors

Optional Text a 

Instances

Strategy Optional Source # 

Associated Types

type SNext (Optional :: * -> *) (k :: Symbol) a (prms :: [KV *]) :: [KV *] Source #

Methods

strategy :: (KnownSymbol k, k </ prms, MonadPlus m) => Optional a -> proxy' k -> [Maybe a] -> Store prms -> m (Store (SNext Optional k a prms)) Source #

strategyRep :: Optional a -> StrategyRep Source #

type SNext Optional k a ps Source # 
type SNext Optional k a ps = (:) (KV *) ((:=) * 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 #