| Copyright | Plow Technologies 2017 |
|---|---|
| License | BSD3 |
| Maintainer | mchaver@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
OCaml.Export
Description
- data OCamlPackage (packageName :: Symbol) (packageDependencies :: [*])
- type NoDependency = '[]
- data OCamlModule (modules :: [Symbol])
- data OCamlSubModule (subModules :: Symbol)
- data OCamlTypeInFile a (filePath :: Symbol)
- data HaskellTypeName (name :: Symbol) a
- data PackageOptions = PackageOptions {}
- defaultPackageOptions :: PackageOptions
- data SpecOptions = SpecOptions {}
- defaultSpecOptions :: SpecOptions
- data EmbeddedOCamlFiles = EmbeddedOCamlFiles {}
- mkPackage :: HasOCamlPackage a => Proxy a -> PackageOptions -> IO ()
- mkFiles :: HasEmbeddedFile api => Bool -> Bool -> Proxy api -> Q Exp
- mkOCamlTypeMetaData :: HasOCamlTypeMetaData a => Proxy a -> Map HaskellTypeMetaData OCamlTypeMetaData
- class OCamlType a where
- typeableToOCamlType :: forall a. Typeable a => Proxy a -> OCamlDatatype
- data TypeParameterRef0
- data TypeParameterRef1
- data TypeParameterRef2
- data TypeParameterRef3
- data TypeParameterRef4
- data TypeParameterRef5
- mkOCamlSpecServer :: forall ocamlPackage. OCamlPackageTypeCount ocamlPackage => String -> Proxy ocamlPackage -> Q [Dec]
- type family MkOCamlSpecAPI a :: * where ...
- mkGoldenFiles :: HasMkGoldenFiles a => Proxy a -> Int -> FilePath -> IO ()
- data Proxy k (t :: k) :: forall k. k -> * = Proxy
- data (k :> k1) (path :: k) (a :: k1) :: forall k k1. k -> k1 -> *
- data a :<|> b :: * -> * -> * = a :<|> b
- type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
- type Server k (api :: k) = ServerT k api Handler
- serve :: HasServer * api ([] *) => Proxy * api -> Server * api -> Application
Documentation
data OCamlPackage (packageName :: Symbol) (packageDependencies :: [*]) Source #
Instances
| (HasOCamlTypeMetaData * (OCamlPackage packageName deps), HasOCamlTypeMetaData * rest) => HasOCamlTypeMetaData * ((:<|>) (OCamlPackage packageName deps) rest) Source # | packages |
| (HasOCamlTypeMetaData [*] deps, HasOCamlTypeMetaData k1 modules) => HasOCamlTypeMetaData * ((:>) * k1 (OCamlPackage packageName deps) modules) Source # | build a packages dependencies and its declared modules |
| (HasOCamlTypeMetaData [*] deps, HasOCamlTypeMetaData k1 a, HasOCamlPackage' k1 a) => HasOCamlPackage * ((:>) * k1 (OCamlPackage packageName deps) a) Source # | |
type NoDependency = '[] Source #
data OCamlModule (modules :: [Symbol]) Source #
An OCamlModule as a Haskell type. File level modules is relative to a
root directory prvoiided in the mkPackage function.
Instances
| (KnownSymbols modules, HasOCamlTypeMetaData' k1 api) => HasOCamlTypeMetaData * ((:>) * k1 (OCamlModule modules) api) Source # | single module |
| (KnownSymbols modules, HasOCamlModule' k1 api) => HasOCamlModule * ((:>) * k1 (OCamlModule modules) api) Source # | |
data OCamlSubModule (subModules :: Symbol) Source #
Symobl will be expaneded to "module SymbolName = struct ... end".
data OCamlTypeInFile a (filePath :: Symbol) Source #
A handwritten OCaml type, encoder and decoder from a file.
data HaskellTypeName (name :: Symbol) a Source #
In case Generic is not derived, manually provide the type name user is responsible for making sure it is correct. otherwise it may lead to a compile error.
data PackageOptions Source #
Options for creating an OCaml package based on Haskell types.
Constructors
| PackageOptions | |
Fields
| |
defaultPackageOptions :: PackageOptions Source #
Default PackageOptions.
data SpecOptions Source #
Details for OCaml spec.
Constructors
| SpecOptions | |
Fields
| |
defaultSpecOptions :: SpecOptions Source #
Default SpecOptions.
data EmbeddedOCamlFiles Source #
Store OCamlFileInType data.
Constructors
| EmbeddedOCamlFiles | |
Fields | |
Instances
mkPackage :: HasOCamlPackage a => Proxy a -> PackageOptions -> IO () Source #
mkOCamlTypeMetaData :: HasOCamlTypeMetaData a => Proxy a -> Map HaskellTypeMetaData OCamlTypeMetaData Source #
class OCamlType a where Source #
Create an OCaml type from a Haskell type. Use the Generic
definition when possible. It also expects ToJSON and FromJSON
to be derived generically.
Methods
toOCamlType :: a -> OCamlDatatype Source #
toOCamlType :: (Generic a, GenericOCamlDatatype (Rep a)) => a -> OCamlDatatype Source #
Instances
typeableToOCamlType :: forall a. Typeable a => Proxy a -> OCamlDatatype Source #
data TypeParameterRef0 Source #
Used to fill the type parameters of proxy types. `Proxy :: Proxy (Maybe TypeParameterRef0)`, `Proxy :: Proxy Either TypeParameterRef0 TypeParameterRef1`. JSON representation is as an Int to simplify the automated tests.
Instances
data TypeParameterRef1 Source #
Second unique TypeParameterRef.
Instances
data TypeParameterRef2 Source #
Third unique TypeParameterRef.
Instances
data TypeParameterRef3 Source #
Fourth unique TypeParameterRef.
Instances
data TypeParameterRef4 Source #
Fifth unique TypeParameterRef.
Instances
data TypeParameterRef5 Source #
Sixth unique TypeParameterRef.
Instances
mkOCamlSpecServer :: forall ocamlPackage. OCamlPackageTypeCount ocamlPackage => String -> Proxy ocamlPackage -> Q [Dec] Source #
type family MkOCamlSpecAPI a :: * where ... Source #
Convert an OCamlPackage into a servant API.
Equations
| MkOCamlSpecAPI (OCamlPackage a deps :> rest) = MkOCamlSpecAPI rest | |
| MkOCamlSpecAPI ((OCamlModule modules :> api) :<|> rest) = MkOCamlSpecAPI' modules '[] api :<|> MkOCamlSpecAPI rest | |
| MkOCamlSpecAPI (OCamlModule modules :> api) = MkOCamlSpecAPI' modules '[] api |
data Proxy k (t :: k) :: forall k. k -> * #
A concrete, poly-kinded proxy type
Constructors
| Proxy |
Instances
| Generic1 k (Proxy k) | |
| Monad (Proxy *) | Since: 4.7.0.0 |
| Functor (Proxy *) | Since: 4.7.0.0 |
| Applicative (Proxy *) | Since: 4.7.0.0 |
| Foldable (Proxy *) | Since: 4.7.0.0 |
| Traversable (Proxy *) | Since: 4.7.0.0 |
| ToJSON1 (Proxy *) | |
| FromJSON1 (Proxy *) | |
| Alternative (Proxy *) | Since: 4.9.0.0 |
| MonadPlus (Proxy *) | Since: 4.9.0.0 |
| Eq1 (Proxy *) | Since: 4.9.0.0 |
| Ord1 (Proxy *) | Since: 4.9.0.0 |
| Read1 (Proxy *) | Since: 4.9.0.0 |
| Show1 (Proxy *) | Since: 4.9.0.0 |
| Hashable1 (Proxy *) | |
| Bounded (Proxy k t) | |
| Enum (Proxy k s) | Since: 4.7.0.0 |
| Eq (Proxy k s) | Since: 4.7.0.0 |
| Ord (Proxy k s) | Since: 4.7.0.0 |
| Read (Proxy k s) | Since: 4.7.0.0 |
| Show (Proxy k s) | Since: 4.7.0.0 |
| Ix (Proxy k s) | Since: 4.7.0.0 |
| Generic (Proxy k t) | |
| Semigroup (Proxy k s) | Since: 4.9.0.0 |
| Monoid (Proxy k s) | Since: 4.7.0.0 |
| Hashable (Proxy k a) | |
| ToJSON (Proxy k a) | |
| FromJSON (Proxy k a) | |
| OCamlType a => OCamlType (Proxy * a) Source # | |
| type Rep1 k (Proxy k) | |
| type Rep (Proxy k t) | |
data (k :> k1) (path :: k) (a :: k1) :: forall k k1. k -> k1 -> * infixr 4 #
The contained API (second argument) can be found under ("/" ++ path)
(path being the first argument).
Example:
>>>-- GET /hello/world>>>-- returning a JSON encoded World value>>>type MyApi = "hello" :> "world" :> Get '[JSON] World
Instances
| (KnownSymbol sym, ToHttpApiData v, HasLink k sub) => HasLink * ((:>) * k (QueryParam * sym v) sub) | |
| (KnownSymbol sym, ToHttpApiData v, HasLink k sub) => HasLink * ((:>) * k (QueryParams * sym v) sub) | |
| (KnownSymbol sym, HasLink k sub) => HasLink * ((:>) * k (QueryFlag sym) sub) | |
| HasLink k2 sub => HasLink * ((:>) * k2 (ReqBody k1 ct a) sub) | |
| (ToHttpApiData v, HasLink k sub) => HasLink * ((:>) * k (Capture * sym v) sub) | |
| (ToHttpApiData v, HasLink k sub) => HasLink * ((:>) * k (CaptureAll * sym v) sub) | |
| HasLink k sub => HasLink * ((:>) * k (Header sym a) sub) | |
| HasLink k sub => HasLink * ((:>) * k RemoteHost sub) | |
| HasLink k sub => HasLink * ((:>) * k (BasicAuth realm a) sub) | |
| HasLink k2 sub => HasLink * ((:>) * k2 (AuthProtect k1 tag) sub) | |
| (KnownSymbol sym, HasLink k sub) => HasLink * ((:>) Symbol k sym sub) | |
| (HasOCamlTypeMetaData [*] deps, HasOCamlTypeMetaData k1 modules) => HasOCamlTypeMetaData * ((:>) * k1 (OCamlPackage packageName deps) modules) Source # | build a packages dependencies and its declared modules |
| (KnownSymbols modules, HasOCamlTypeMetaData' k1 api) => HasOCamlTypeMetaData * ((:>) * k1 (OCamlModule modules) api) Source # | single module |
| (KnownSymbols modules, HasOCamlModule' k1 api) => HasOCamlModule * ((:>) * k1 (OCamlModule modules) api) Source # | |
| (HasOCamlTypeMetaData [*] deps, HasOCamlTypeMetaData k1 a, HasOCamlPackage' k1 a) => HasOCamlPackage * ((:>) * k1 (OCamlPackage packageName deps) a) Source # | |
| HasServer k1 api ctx => HasServer * ((:>) * k1 (Summary desc) api) ctx | Ignore |
| HasServer k1 api ctx => HasServer * ((:>) * k1 (Description desc) api) ctx | Ignore |
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (Header sym a) api) context | If you use All it asks is for a Example: newtype Referer = Referer Text
deriving (Eq, Show, FromHttpApiData)
-- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer
server :: Server MyApi
server = viewReferer
where viewReferer :: Referer -> Handler referer
viewReferer referer = return referer |
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryParam * sym a) api) context | If you use This lets servant worry about looking it up in the query string
and turning it into a value of the type you specify, enclosed
in You can control how it'll be converted from Example: type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]
server :: Server MyApi
server = getBooksBy
where getBooksBy :: Maybe Text -> Handler [Book]
getBooksBy Nothing = ...return all books...
getBooksBy (Just author) = ...return books by the given author... |
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryParams * sym a) api) context | If you use This lets servant worry about looking up 0 or more values in the query string
associated to You can control how the individual values are converted from Example: type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
server :: Server MyApi
server = getBooksBy
where getBooksBy :: [Text] -> Handler [Book]
getBooksBy authors = ...return all books by these authors... |
| (KnownSymbol sym, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryFlag sym) api) context | If you use Example: type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
server :: Server MyApi
server = getBooks
where getBooks :: Bool -> Handler [Book]
getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument... |
| (AllCTUnrender list a, HasServer k1 api context) => HasServer * ((:>) * k1 (ReqBody * list a) api) context | If you use All it asks is for a Example: type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book
server :: Server MyApi
server = postBook
where postBook :: Book -> Handler Book
postBook book = ...insert into your db... |
| HasServer k1 api context => HasServer * ((:>) * k1 RemoteHost api) context | |
| HasServer k1 api context => HasServer * ((:>) * k1 IsSecure api) context | |
| (KnownSymbol capture, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (Capture * capture a) api) context | If you use You can control how it'll be converted from Example: type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book
server :: Server MyApi
server = getBook
where getBook :: Text -> Handler Book
getBook isbn = ... |
| (KnownSymbol capture, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (CaptureAll * capture a) api) context | If you use You can control how they'll be converted from Example: type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile
server :: Server MyApi
server = getSourceFile
where getSourceFile :: [Text] -> Handler Book
getSourceFile pathSegments = ... |
| HasServer k1 api context => HasServer * ((:>) * k1 Vault api) context | |
| HasServer k1 api context => HasServer * ((:>) * k1 HttpVersion api) context | |
| (KnownSymbol realm, HasServer k1 api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) * k1 (BasicAuth realm usr) api) context | Basic Authentication |
| (KnownSymbol path, HasServer k1 api context) => HasServer * ((:>) Symbol k1 path api) context | Make sure the incoming request starts with |
| type MkLink * ((:>) * k1 (AuthProtect k2 tag) sub) | |
| type MkLink * ((:>) * k (BasicAuth realm a) sub) | |
| type MkLink * ((:>) * k RemoteHost sub) | |
| type MkLink * ((:>) * k (Header sym a) sub) | |
| type MkLink * ((:>) * k (CaptureAll * sym v) sub) | |
| type MkLink * ((:>) * k (Capture * sym v) sub) | |
| type MkLink * ((:>) * k1 (ReqBody k2 ct a) sub) | |
| type MkLink * ((:>) * k (QueryFlag sym) sub) | |
| type MkLink * ((:>) * k (QueryParams * sym v) sub) | |
| type MkLink * ((:>) * k (QueryParam * sym v) sub) | |
| type MkLink * ((:>) Symbol k sym sub) | |
| type ServerT * ((:>) * k1 (BasicAuth realm usr) api) m | |
| type ServerT * ((:>) * k1 (Description desc) api) m | |
| type ServerT * ((:>) * k1 (Summary desc) api) m | |
| type ServerT * ((:>) * k1 HttpVersion api) m | |
| type ServerT * ((:>) * k1 Vault api) m | |
| type ServerT * ((:>) * k1 IsSecure api) m | |
| type ServerT * ((:>) * k1 RemoteHost api) m | |
| type ServerT * ((:>) * k1 (ReqBody * list a) api) m | |
| type ServerT * ((:>) * k1 (QueryFlag sym) api) m | |
| type ServerT * ((:>) * k1 (QueryParams * sym a) api) m | |
| type ServerT * ((:>) * k1 (QueryParam * sym a) api) m | |
| type ServerT * ((:>) * k1 (Header sym a) api) m | |
| type ServerT * ((:>) * k1 (CaptureAll * capture a) api) m | |
| type ServerT * ((:>) * k1 (Capture * capture a) api) m | |
| type ServerT * ((:>) Symbol k1 path api) m | |
data a :<|> b :: * -> * -> * infixr 3 #
Union of two APIs, first takes precedence in case of overlap.
Example:
>>>:{type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books :}
Constructors
| a :<|> b infixr 3 |
Instances
| Functor ((:<|>) a) | |
| Foldable ((:<|>) a) | |
| Traversable ((:<|>) a) | |
| (HasLink * a, HasLink * b) => HasLink * ((:<|>) a b) | |
| (HasOCamlTypeMetaData * modul, HasOCamlTypeMetaData * rst) => HasOCamlTypeMetaData * ((:<|>) modul rst) Source # | modules |
| (HasOCamlTypeMetaData * (OCamlPackage packageName deps), HasOCamlTypeMetaData * rest) => HasOCamlTypeMetaData * ((:<|>) (OCamlPackage packageName deps) rest) Source # | packages |
| (HasServer * a context, HasServer * b context) => HasServer * ((:<|>) a b) context | A server for type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
:<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books
server :: Server MyApi
server = listAllBooks :<|> postBook
where listAllBooks = ...
postBook book = ... |
| (Bounded b, Bounded a) => Bounded ((:<|>) a b) | |
| (Eq b, Eq a) => Eq ((:<|>) a b) | |
| (Show b, Show a) => Show ((:<|>) a b) | |
| (Semigroup a, Semigroup b) => Semigroup ((:<|>) a b) | |
| (Monoid a, Monoid b) => Monoid ((:<|>) a b) | |
| type MkLink * ((:<|>) a b) | |
| type ServerT * ((:<|>) a b) m | |
type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #
The WAI application.
Note that, since WAI 3.0, this type is structured in continuation passing
style to allow for proper safe resource handling. This was handled in the
past via other means (e.g., ResourceT). As a demonstration:
app :: Application
app req respond = bracket_
(putStrLn "Allocating scarce resource")
(putStrLn "Cleaning up")
(respond $ responseLBS status200 [] "Hello World")
serve :: HasServer * api ([] *) => Proxy * api -> Server * api -> Application #
serve allows you to implement an API and produce a wai Application.
Example:
type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
:<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books
server :: Server MyApi
server = listAllBooks :<|> postBook
where listAllBooks = ...
postBook book = ...
myApi :: Proxy MyApi
myApi = Proxy
app :: Application
app = serve myApi server
main :: IO ()
main = Network.Wai.Handler.Warp.run 8080 app