2018-06-29 21:08:26 +02:00
{- # LANGUAGE CPP # -}
{- # LANGUAGE ConstraintKinds # -}
{- # LANGUAGE DeriveDataTypeable # -}
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE FlexibleInstances # -}
2018-01-17 11:52:47 +01:00
{- # LANGUAGE GeneralizedNewtypeDeriving # -}
2018-06-29 21:08:26 +02:00
{- # LANGUAGE MultiParamTypeClasses # -}
{- # LANGUAGE OverloadedStrings # -}
{- # LANGUAGE PolyKinds # -}
{- # LANGUAGE ScopedTypeVariables # -}
{- # LANGUAGE TemplateHaskell # -}
{- # LANGUAGE TypeFamilies # -}
{- # LANGUAGE TypeOperators # -}
{- # LANGUAGE UndecidableInstances # -}
2015-09-21 12:31:00 +02:00
2015-11-16 18:40:15 +01:00
module Servant.Foreign.Internal where
2015-09-21 12:31:00 +02:00
2018-06-29 21:08:26 +02:00
import Prelude ( )
import Prelude.Compat
2017-12-10 13:25:14 +01:00
2018-06-29 21:08:26 +02:00
import Control.Lens
( Getter , makeLenses , makePrisms , ( %~ ) , ( & ) , ( .~ ) , ( <>~ ) )
import Data.Data
( Data )
2015-10-08 23:33:32 +02:00
import Data.Proxy
2016-02-17 22:47:30 +01:00
import Data.String
2015-10-08 23:33:32 +02:00
import Data.Text
2018-06-29 21:08:26 +02:00
import Data.Text.Encoding
( decodeUtf8 )
import Data.Typeable
( Typeable )
2015-10-08 23:33:32 +02:00
import GHC.TypeLits
2018-06-29 21:08:26 +02:00
import qualified Network.HTTP.Types as HTTP
2015-10-08 23:33:32 +02:00
import Servant.API
2018-06-29 21:08:26 +02:00
import Servant.API.Modifiers
( RequiredArgument )
2016-01-20 16:23:10 +01:00
import Servant.API.TypeLevel
2016-02-11 11:41:34 +01:00
2021-02-03 07:52:28 +01:00
-- | Canonical name of the endpoint, can be used to generate a function name.
--
-- You can use the functions in "Servant.Foreign.Inflections", like 'Servant.Foreign.Inflections.camelCase' to transform to `Text`.
2016-02-17 22:47:30 +01:00
newtype FunctionName = FunctionName { unFunctionName :: [ Text ] }
2018-03-15 09:46:30 +01:00
deriving ( Data , Show , Eq , Semigroup , Monoid , Typeable )
2015-09-21 12:31:00 +02:00
2016-02-17 22:47:30 +01:00
makePrisms ''FunctionName
2015-09-21 12:31:00 +02:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | See documentation of 'Arg'
2016-02-17 22:47:30 +01:00
newtype PathSegment = PathSegment { unPathSegment :: Text }
2018-03-15 09:46:30 +01:00
deriving ( Data , Show , Eq , IsString , Semigroup , Monoid , Typeable )
2016-02-17 22:47:30 +01:00
makePrisms ''PathSegment
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Maps a name to the foreign type that belongs to the annotated value.
--
-- Used for header args, query args, and capture args.
data Arg ftype = Arg
2016-03-13 05:02:00 +01:00
{ _argName :: PathSegment
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ The name to be captured.
--
-- Only for capture args it really denotes a path segment.
, _argType :: ftype
-- ^ Foreign type the associated value will have
}
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2016-02-17 22:47:30 +01:00
makeLenses ''Arg
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
argPath :: Getter ( Arg ftype ) Text
2016-03-13 05:02:00 +01:00
argPath = argName . _PathSegment
2015-09-21 12:31:00 +02:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
data SegmentType ftype
2016-02-17 22:47:30 +01:00
= Static PathSegment
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ Static path segment.
--
-- @"foo\/bar\/baz"@
--
-- contains the static segments @"foo"@, @"bar"@ and @"baz"@.
| Cap ( Arg ftype )
-- ^ A capture.
--
-- @"user\/{userid}\/name"@
--
-- would capture the arg @userid@ with type @ftype@.
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
makePrisms ''SegmentType
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | A part of the Url’ s path.
newtype Segment ftype = Segment { unSegment :: SegmentType ftype }
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
makePrisms ''Segment
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Whether a segment is a 'Cap'.
isCapture :: Segment ftype -> Bool
2016-02-17 22:47:30 +01:00
isCapture ( Segment ( Cap _ ) ) = True
isCapture _ = False
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Crashing Arg extraction from segment, TODO: remove
captureArg :: Segment ftype -> Arg ftype
2016-02-17 22:47:30 +01:00
captureArg ( Segment ( Cap s ) ) = s
captureArg _ = error " captureArg called on non capture "
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- TODO: remove, unnecessary indirection
type Path ftype = [ Segment ftype ]
2015-09-21 12:31:00 +02:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Type of a 'QueryArg'.
2016-02-11 11:41:34 +01:00
data ArgType
= Normal
2015-09-21 12:31:00 +02:00
| Flag
| List
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
makePrisms ''ArgType
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Url Query argument.
--
-- Urls can contain query arguments, which is a list of key-value pairs.
-- In a typical url, query arguments look like this:
--
-- @?foo=bar&alist[]=el1&alist[]=el2&aflag@
--
-- Each pair can be
--
-- * @?foo=bar@: a plain key-val pair, either optional or required ('QueryParam')
-- * @?aflag@: a flag (no value, implicitly Bool with default `false` if it’ s missing) ('QueryFlag')
-- * @?alist[]=el1&alist[]=el2@: list of values ('QueryParams')
--
-- @_queryArgType@ will be set accordingly.
--
-- For the plain key-val pairs ('QueryParam'), @_queryArgName@’ s @ftype@ will be wrapped in a @Maybe@ if the argument is optional.
data QueryArg ftype = QueryArg
{ _queryArgName :: Arg ftype
-- ^ Name and foreign type of the argument. Will be wrapped in `Maybe` if the query is optional and in a `[]` if the query is a list
2016-03-13 05:02:00 +01:00
, _queryArgType :: ArgType
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ one of normal/plain, list or flag
2016-03-13 06:35:49 +01:00
}
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
makeLenses ''QueryArg
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
data HeaderArg ftype =
-- | The name of the header and the foreign type of its value.
HeaderArg
{ _headerArg :: Arg ftype }
-- | Unused, will never be set.
--
-- TODO: remove
2015-09-21 12:31:00 +02:00
| ReplaceHeaderArg
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
{ _headerArg :: Arg ftype
2016-02-17 22:47:30 +01:00
, _headerPattern :: Text
2016-03-13 06:35:49 +01:00
}
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-22 12:17:43 +02:00
2016-02-11 11:41:34 +01:00
makeLenses ''HeaderArg
makePrisms ''HeaderArg
2015-09-21 12:31:00 +02:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Full endpoint url, with all captures and parameters
data Url ftype = Url
{ _path :: Path ftype
-- ^ Url path, list of either static segments or captures
--
-- @"foo\/{id}\/bar"@
, _queryStr :: [ QueryArg ftype ]
-- ^ List of query args
--
-- @"?foo=bar&a=b"@
, _frag :: Maybe ftype
-- ^ Url fragment.
--
-- Not sent to the HTTP server, so only useful for frontend matters (e.g. inter-page linking).
--
-- @#fragmentText@
2016-03-13 06:35:49 +01:00
}
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2016-03-13 06:35:49 +01:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
defUrl :: Url ftype
2020-11-18 19:57:20 +01:00
defUrl = Url [] [] Nothing
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
makeLenses ''Url
2015-09-21 12:31:00 +02:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | See documentation of '_reqBodyContentType'
2018-09-17 23:19:41 +02:00
data ReqBodyContentType = ReqBodyJSON | ReqBodyMultipart
deriving ( Data , Eq , Show , Read )
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Full description of an endpoint in your API, generated by 'listFromAPI'. It should give you all the information needed to generate foreign language bindings.
--
-- Every field containing @ftype@ will use the foreign type mapping specified via 'HasForeignType' (see its docstring on how to set that up).
--
-- See https://docs.servant.dev/en/stable/tutorial/ApiType.html for accessible documentation of the possible content of an endpoint.
data Req ftype = Req
{ _reqUrl :: Url ftype
-- ^ Full list of URL segments, including captures
2018-09-17 23:19:41 +02:00
, _reqMethod :: HTTP . Method
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ @\"GET\"@\/@\"POST\"@\/@\"PUT\"@\/…
, _reqHeaders :: [ HeaderArg ftype ]
-- ^ Headers required by this endpoint, with their type
, _reqBody :: Maybe ftype
-- ^ Foreign type of the expected request body ('ReqBody'), if any
, _reqReturnType :: Maybe ftype
-- ^ The foreign type of the response, if any
2018-09-17 23:19:41 +02:00
, _reqFuncName :: FunctionName
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ The URL segments rendered in a way that they can be easily concatenated into a canonical function name
2018-09-17 23:19:41 +02:00
, _reqBodyContentType :: ReqBodyContentType
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- ^ The content type the request body is transferred as.
--
-- This is a severe limitation of @servant-foreign@ currently,
-- as we only allow the content type to be `JSON`
-- no user-defined content types. ('ReqBodyMultipart' is not
-- actually implemented.)
--
-- Thus, any routes looking like this will work:
--
-- @"foo" :> Get '[JSON] Foo@
--
-- while routes like
--
-- @"foo" :> Get '[MyFancyContentType] Foo@
--
-- will fail with an error like
--
-- @• JSON expected in list '[MyFancyContentType]@
2016-03-13 06:35:49 +01:00
}
2017-11-06 11:29:43 +01:00
deriving ( Data , Eq , Show , Typeable )
2015-09-21 12:31:00 +02:00
makeLenses ''Req
2016-03-13 22:21:36 +01:00
defReq :: Req ftype
2018-09-17 23:19:41 +02:00
defReq = Req defUrl " GET " [] Nothing Nothing ( FunctionName [] ) ReqBodyJSON
2015-09-21 12:31:00 +02:00
2015-12-02 15:10:30 +01:00
-- | 'HasForeignType' maps Haskell types with types in the target
-- language of your backend. For example, let's say you're
2016-03-13 22:21:36 +01:00
-- implementing a backend to some language __X__, and you want
-- a Text representation of each input/output type mentioned in the API:
2015-12-02 15:10:30 +01:00
--
-- > -- First you need to create a dummy type to parametrize your
-- > -- instances.
-- > data LangX
-- >
-- > -- Otherwise you define instances for the types you need
2016-03-13 22:21:36 +01:00
-- > instance HasForeignType LangX Text Int where
-- > typeFor _ _ _ = "intX"
2015-12-02 15:10:30 +01:00
-- >
-- > -- Or for example in case of lists
2016-03-13 22:21:36 +01:00
-- > instance HasForeignType LangX Text a => HasForeignType LangX Text [a] where
-- > typeFor lang type _ = "listX of " <> typeFor lang ftype (Proxy :: Proxy a)
2015-12-02 15:10:30 +01:00
--
-- Finally to generate list of information about all the endpoints for
-- an API you create a function of a form:
--
2016-03-13 22:21:36 +01:00
-- > getEndpoints :: (HasForeign LangX Text api, GenerateList Text (Foreign Text api))
-- > => Proxy api -> [Req Text]
-- > getEndpoints api = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy Text) api
2015-12-02 15:10:30 +01:00
--
2015-12-02 16:56:56 +01:00
-- > -- If language __X__ is dynamically typed then you can use
2016-07-08 09:11:34 +02:00
-- > -- a predefined NoTypes parameter with the NoContent output type:
2016-03-13 22:21:36 +01:00
--
2016-07-08 09:11:34 +02:00
-- > getEndpoints :: (HasForeign NoTypes NoContent api, GenerateList Text (Foreign NoContent api))
-- > => Proxy api -> [Req NoContent]
-- > getEndpoints api = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) api
2015-12-02 16:56:56 +01:00
-- >
--
2016-03-13 22:21:36 +01:00
class HasForeignType lang ftype a where
typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype
2015-11-28 09:13:26 +01:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | The language definition without any foreign types. It can be used for dynamic languages which do not /do/ type annotations.
2015-12-02 16:56:56 +01:00
data NoTypes
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Use if the foreign language does not have any types.
instance HasForeignType NoTypes NoContent a where
2016-07-08 09:11:34 +02:00
typeFor _ _ _ = NoContent
2015-12-02 16:56:56 +01:00
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I
thought I’d write the documentation I would have liked to see.
The strategy here is that a user not necessarily has insight into how
servant works internally, or even how to write complex servant routes,
they just want to generate a list of endpoints and convert the `Req`
type into e.g. generated code in $language. Thus, they need to know
the semantics of all fields of Req, how they interact and how they
relate to a plain http route.
I made sure every `f` is replaced with `ftype`, so we have one
conventional way of referring to the foreign type argument everywhere.
Some enums are not set at all, they are marked as such.
`_reqBodyContentType` introduces a major restriction of the module, so
that is mentioned in the documentation for now, until the time it will
be fixed.
A few TODO’s describe places where types don’t make sense but would
introduce API-breaking changes, so these should probably be
simplified,
but bundled in one go.
2021-02-03 17:12:57 +01:00
-- | Implementation of the Servant framework types.
--
-- Relevant instances: Everything containing 'HasForeignType'.
2016-06-02 09:49:55 +02:00
class HasForeign lang ftype ( api :: * ) where
type Foreign ftype api :: *
foreignFor :: Proxy lang -> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
instance ( HasForeign lang ftype a , HasForeign lang ftype b )
=> HasForeign lang ftype ( a :<|> b ) where
type Foreign ftype ( a :<|> b ) = Foreign ftype a :<|> Foreign ftype b
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
foreignFor lang ftype ( Proxy :: Proxy a ) req
:<|> foreignFor lang ftype ( Proxy :: Proxy b ) req
2015-09-21 12:31:00 +02:00
2017-05-16 12:01:33 +02:00
data EmptyForeignAPI = EmptyForeignAPI
instance HasForeign lang ftype EmptyAPI where
type Foreign ftype EmptyAPI = EmptyForeignAPI
foreignFor Proxy Proxy Proxy _ = EmptyForeignAPI
2016-06-02 09:49:55 +02:00
instance ( KnownSymbol sym , HasForeignType lang ftype t , HasForeign lang ftype api )
2018-02-09 11:05:30 +01:00
=> HasForeign lang ftype ( Capture' mods sym t :> api ) where
type Foreign ftype ( Capture' mods sym t :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang Proxy Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang Proxy ( Proxy :: Proxy api ) $
2016-02-17 22:47:30 +01:00
req & reqUrl . path <>~ [ Segment ( Cap arg ) ]
& reqFuncName . _FunctionName %~ ( ++ [ " by " , str ] )
2015-11-28 09:13:26 +01:00
where
2016-02-17 22:47:30 +01:00
str = pack . symbolVal $ ( Proxy :: Proxy sym )
2016-03-13 22:21:36 +01:00
ftype = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy t )
2016-02-17 22:47:30 +01:00
arg = Arg
2016-03-13 05:02:00 +01:00
{ _argName = PathSegment str
, _argType = ftype }
2015-09-21 12:31:00 +02:00
2016-05-26 21:51:28 +02:00
instance ( KnownSymbol sym , HasForeignType lang ftype [ t ] , HasForeign lang ftype sublayout )
=> HasForeign lang ftype ( CaptureAll sym t :> sublayout ) where
type Foreign ftype ( CaptureAll sym t :> sublayout ) = Foreign ftype sublayout
foreignFor lang Proxy Proxy req =
foreignFor lang Proxy ( Proxy :: Proxy sublayout ) $
req & reqUrl . path <>~ [ Segment ( Cap arg ) ]
& reqFuncName . _FunctionName %~ ( ++ [ " by " , str ] )
where
str = pack . symbolVal $ ( Proxy :: Proxy sym )
ftype = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy [ t ] )
arg = Arg
{ _argName = PathSegment str
, _argType = ftype }
2016-03-13 22:21:36 +01:00
instance ( Elem JSON list , HasForeignType lang ftype a , ReflectMethod method )
=> HasForeign lang ftype ( Verb method status list a ) where
type Foreign ftype ( Verb method status list a ) = Req ftype
2015-09-21 12:31:00 +02:00
2018-06-23 22:09:28 +02:00
foreignFor lang Proxy Proxy req =
req & reqFuncName . _FunctionName %~ ( methodLC : )
& reqMethod .~ method
& reqReturnType .~ Just retType
where
retType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy a )
method = reflectMethod ( Proxy :: Proxy method )
methodLC = toLower $ decodeUtf8 method
2019-09-07 17:25:11 +02:00
instance ( HasForeignType lang ftype NoContent , ReflectMethod method )
=> HasForeign lang ftype ( NoContentVerb method ) where
type Foreign ftype ( NoContentVerb method ) = Req ftype
foreignFor lang Proxy Proxy req =
req & reqFuncName . _FunctionName %~ ( methodLC : )
& reqMethod .~ method
& reqReturnType .~ Just retType
where
retType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy NoContent )
method = reflectMethod ( Proxy :: Proxy method )
methodLC = toLower $ decodeUtf8 method
2018-06-23 22:09:28 +02:00
-- | TODO: doesn't taking framing into account.
instance ( ct ~ JSON , HasForeignType lang ftype a , ReflectMethod method )
=> HasForeign lang ftype ( Stream method status framing ct a ) where
type Foreign ftype ( Stream method status framing ct a ) = Req ftype
2016-03-13 22:21:36 +01:00
foreignFor lang Proxy Proxy req =
2016-02-17 22:47:30 +01:00
req & reqFuncName . _FunctionName %~ ( methodLC : )
2016-01-06 18:20:20 +01:00
& reqMethod .~ method
2016-03-13 22:21:36 +01:00
& reqReturnType .~ Just retType
2015-11-28 09:13:26 +01:00
where
2016-03-13 22:21:36 +01:00
retType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy a )
2016-02-11 11:41:34 +01:00
method = reflectMethod ( Proxy :: Proxy method )
methodLC = toLower $ decodeUtf8 method
2015-09-21 12:31:00 +02:00
2017-12-10 13:25:14 +01:00
instance ( KnownSymbol sym , HasForeignType lang ftype ( RequiredArgument mods a ) , HasForeign lang ftype api )
=> HasForeign lang ftype ( Header' mods sym a :> api ) where
type Foreign ftype ( Header' mods sym a :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang Proxy Proxy req =
foreignFor lang Proxy subP $ req & reqHeaders <>~ [ HeaderArg arg ]
2015-11-28 09:13:26 +01:00
where
2016-02-11 11:41:34 +01:00
hname = pack . symbolVal $ ( Proxy :: Proxy sym )
2016-02-17 22:47:30 +01:00
arg = Arg
2016-03-13 05:02:00 +01:00
{ _argName = PathSegment hname
2017-12-10 13:25:14 +01:00
, _argType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy ( RequiredArgument mods a ) ) }
2016-06-02 09:49:55 +02:00
subP = Proxy :: Proxy api
2015-09-21 12:31:00 +02:00
2017-12-10 13:25:14 +01:00
instance ( KnownSymbol sym , HasForeignType lang ftype ( RequiredArgument mods a ) , HasForeign lang ftype api )
=> HasForeign lang ftype ( QueryParam' mods sym a :> api ) where
type Foreign ftype ( QueryParam' mods sym a :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang Proxy Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy api ) $
2015-11-28 09:13:26 +01:00
req & reqUrl . queryStr <>~ [ QueryArg arg Normal ]
where
2016-02-11 11:41:34 +01:00
str = pack . symbolVal $ ( Proxy :: Proxy sym )
2016-02-17 22:47:30 +01:00
arg = Arg
2016-03-13 05:02:00 +01:00
{ _argName = PathSegment str
2017-12-10 13:25:14 +01:00
, _argType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy ( RequiredArgument mods a ) ) }
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
instance
2016-06-02 09:49:55 +02:00
( KnownSymbol sym , HasForeignType lang ftype [ a ] , HasForeign lang ftype api )
=> HasForeign lang ftype ( QueryParams sym a :> api ) where
type Foreign ftype ( QueryParams sym a :> api ) = Foreign ftype api
2016-03-13 22:21:36 +01:00
foreignFor lang Proxy Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy api ) $
2015-11-28 09:13:26 +01:00
req & reqUrl . queryStr <>~ [ QueryArg arg List ]
where
2016-02-11 11:41:34 +01:00
str = pack . symbolVal $ ( Proxy :: Proxy sym )
2016-02-17 22:47:30 +01:00
arg = Arg
2016-03-13 05:02:00 +01:00
{ _argName = PathSegment str
2016-03-13 22:21:36 +01:00
, _argType = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy [ a ] ) }
2015-09-21 12:31:00 +02:00
2016-02-11 11:41:34 +01:00
instance
2016-06-02 09:49:55 +02:00
( KnownSymbol sym , HasForeignType lang ftype Bool , HasForeign lang ftype api )
=> HasForeign lang ftype ( QueryFlag sym :> api ) where
type Foreign ftype ( QueryFlag sym :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) $
2015-11-28 09:13:26 +01:00
req & reqUrl . queryStr <>~ [ QueryArg arg Flag ]
where
2016-02-11 11:41:34 +01:00
str = pack . symbolVal $ ( Proxy :: Proxy sym )
2016-02-17 22:47:30 +01:00
arg = Arg
2016-03-13 05:02:00 +01:00
{ _argName = PathSegment str
2016-03-13 22:21:36 +01:00
, _argType = typeFor lang ftype ( Proxy :: Proxy Bool ) }
2015-09-21 12:31:00 +02:00
2020-11-18 19:57:20 +01:00
instance
( HasForeignType lang ftype ( Maybe a ) , HasForeign lang ftype api )
=> HasForeign lang ftype ( Fragment a :> api ) where
type Foreign ftype ( Fragment a :> api ) = Foreign ftype api
foreignFor lang Proxy Proxy req =
foreignFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy api ) $
req & reqUrl . frag .~ Just argT
where
argT = typeFor lang ( Proxy :: Proxy ftype ) ( Proxy :: Proxy ( Maybe a ) )
2016-03-13 22:21:36 +01:00
instance HasForeign lang ftype Raw where
type Foreign ftype Raw = HTTP . Method -> Req ftype
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor _ Proxy Proxy req method =
2016-02-17 22:47:30 +01:00
req & reqFuncName . _FunctionName %~ ( ( toLower $ decodeUtf8 method ) : )
2015-09-21 12:31:00 +02:00
& reqMethod .~ method
2016-06-02 09:49:55 +02:00
instance ( Elem JSON list , HasForeignType lang ftype a , HasForeign lang ftype api )
2017-12-10 13:25:14 +01:00
=> HasForeign lang ftype ( ReqBody' mods list a :> api ) where
type Foreign ftype ( ReqBody' mods list a :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) $
2016-03-13 22:21:36 +01:00
req & reqBody .~ ( Just $ typeFor lang ftype ( Proxy :: Proxy a ) )
2015-09-21 12:31:00 +02:00
2018-06-26 19:11:28 +02:00
instance
( HasForeign lang ftype api
2018-11-09 20:49:53 +01:00
) => HasForeign lang ftype ( StreamBody' mods framing ctype a :> api )
2018-06-26 19:11:28 +02:00
where
2018-11-09 20:49:53 +01:00
type Foreign ftype ( StreamBody' mods framing ctype a :> api ) = Foreign ftype api
2018-06-26 19:11:28 +02:00
foreignFor _lang Proxy Proxy _req = error " HasForeign @StreamBody "
2016-06-02 09:49:55 +02:00
instance ( KnownSymbol path , HasForeign lang ftype api )
=> HasForeign lang ftype ( path :> api ) where
type Foreign ftype ( path :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) $
2016-02-17 22:47:30 +01:00
req & reqUrl . path <>~ [ Segment ( Static ( PathSegment str ) ) ]
& reqFuncName . _FunctionName %~ ( ++ [ str ] )
2015-11-28 09:13:26 +01:00
where
2016-07-24 15:46:55 +02:00
str = pack . symbolVal $ ( Proxy :: Proxy path )
2015-09-21 12:31:00 +02:00
2016-06-02 09:49:55 +02:00
instance HasForeign lang ftype api
=> HasForeign lang ftype ( RemoteHost :> api ) where
type Foreign ftype ( RemoteHost :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) req
2015-09-21 12:31:00 +02:00
2016-06-02 09:49:55 +02:00
instance HasForeign lang ftype api
=> HasForeign lang ftype ( IsSecure :> api ) where
type Foreign ftype ( IsSecure :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) req
2015-09-21 12:31:00 +02:00
2016-06-02 09:49:55 +02:00
instance HasForeign lang ftype api => HasForeign lang ftype ( Vault :> api ) where
type Foreign ftype ( Vault :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) req
2015-09-21 12:31:00 +02:00
2016-06-02 09:49:55 +02:00
instance HasForeign lang ftype api =>
HasForeign lang ftype ( WithNamedContext name context api ) where
2016-01-18 21:27:19 +01:00
2016-06-02 09:49:55 +02:00
type Foreign ftype ( WithNamedContext name context api ) = Foreign ftype api
2016-01-18 21:27:19 +01:00
2016-06-02 09:49:55 +02:00
foreignFor lang ftype Proxy = foreignFor lang ftype ( Proxy :: Proxy api )
2016-01-18 21:27:19 +01:00
2016-06-02 09:49:55 +02:00
instance HasForeign lang ftype api
=> HasForeign lang ftype ( HttpVersion :> api ) where
type Foreign ftype ( HttpVersion :> api ) = Foreign ftype api
2015-09-21 12:31:00 +02:00
2016-03-13 22:21:36 +01:00
foreignFor lang ftype Proxy req =
2016-06-02 09:49:55 +02:00
foreignFor lang ftype ( Proxy :: Proxy api ) req
2015-12-02 12:21:37 +01:00
2017-06-08 17:27:36 +02:00
instance HasForeign lang ftype api
=> HasForeign lang ftype ( Summary desc :> api ) where
type Foreign ftype ( Summary desc :> api ) = Foreign ftype api
foreignFor lang ftype Proxy req =
foreignFor lang ftype ( Proxy :: Proxy api ) req
instance HasForeign lang ftype api
=> HasForeign lang ftype ( Description desc :> api ) where
type Foreign ftype ( Description desc :> api ) = Foreign ftype api
foreignFor lang ftype Proxy req =
foreignFor lang ftype ( Proxy :: Proxy api ) req
2015-12-02 12:21:37 +01:00
-- | Utility class used by 'listFromAPI' which computes
-- the data needed to generate a function for each endpoint
-- and hands it all back in a list.
2016-03-13 22:21:36 +01:00
class GenerateList ftype reqs where
generateList :: reqs -> [ Req ftype ]
2015-12-02 12:21:37 +01:00
2017-05-16 12:01:33 +02:00
instance GenerateList ftype EmptyForeignAPI where
generateList _ = []
2016-03-13 22:21:36 +01:00
instance GenerateList ftype ( Req ftype ) where
2015-12-02 12:21:37 +01:00
generateList r = [ r ]
2016-03-13 22:21:36 +01:00
instance ( GenerateList ftype start , GenerateList ftype rest )
=> GenerateList ftype ( start :<|> rest ) where
2015-12-02 12:21:37 +01:00
generateList ( start :<|> rest ) = ( generateList start ) ++ ( generateList rest )
-- | Generate the necessary data for codegen as a list, each 'Req'
-- describing one endpoint from your API type.
2016-02-11 11:41:34 +01:00
listFromAPI
2016-03-13 22:21:36 +01:00
:: ( HasForeign lang ftype api , GenerateList ftype ( Foreign ftype api ) )
2016-02-11 11:41:34 +01:00
=> Proxy lang
2016-03-13 22:21:36 +01:00
-> Proxy ftype
2016-02-11 11:41:34 +01:00
-> Proxy api
2016-03-13 22:21:36 +01:00
-> [ Req ftype ]
listFromAPI lang ftype p = generateList ( foreignFor lang ftype p defReq )