Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic usage:
import MyLib (MyServantApiType) import Servant.Elm spec :: Spec spec = Spec ["Generated", "MyApi"] (defElmImports : generateElmForAPI (Proxy :: Proxy MyServantApiType)) main :: IO () main = specsToDir [spec] "my-elm-dir"
- generateElmForAPI :: (HasForeign LangElm ElmDatatype api, GenerateList ElmDatatype (Foreign ElmDatatype api)) => Proxy api -> [Text]
- generateElmForAPIWith :: (HasForeign LangElm ElmDatatype api, GenerateList ElmDatatype (Foreign ElmDatatype api)) => ElmOptions -> Proxy api -> [Text]
- data ElmOptions = ElmOptions {
- urlPrefix :: Text
- elmExportOptions :: Options
- emptyResponseElmTypes :: [ElmDatatype]
- stringElmTypes :: [ElmDatatype]
- defElmOptions :: ElmOptions
- defElmImports :: Text
- data Spec :: * = Spec [Text] [Text]
- class ElmType a
- specsToDir :: [Spec] -> FilePath -> IO ()
- data Proxy k t :: forall k. k -> * = Proxy
Documentation
generateElmForAPI :: (HasForeign LangElm ElmDatatype api, GenerateList ElmDatatype (Foreign ElmDatatype api)) => Proxy api -> [Text] Source #
Generate Elm code for the API with default options.
Returns a list of Elm functions to query your Servant API from Elm.
You could spit these out to a file and call them from your Elm code, but you
would be better off creating a Spec
with the result and using specsToDir
,
which handles the module name for you.
generateElmForAPIWith :: (HasForeign LangElm ElmDatatype api, GenerateList ElmDatatype (Foreign ElmDatatype api)) => ElmOptions -> Proxy api -> [Text] Source #
Generate Elm code for the API with custom options.
data ElmOptions Source #
Options to configure how code is generated.
ElmOptions | |
|
defElmOptions :: ElmOptions Source #
Default options for generating Elm code.
The default options are:
{ urlPrefix = "" , elmExportOptions = Elm.defaultOptions , emptyResponseElmTypes = [ toElmType NoContent ] , stringElmTypes = [ toElmType "" ] }
defElmImports :: Text Source #
Default imports required by generated Elm code.
You probably want to include this at the top of your generated Elm module.
The default required imports are:
import Json.Decode exposing (..) import Json.Decode.Pipeline exposing (..) import Json.Encode import Http import String
Convenience re-exports from the Elm module
ElmType Bool | |
ElmType Char | |
ElmType Double | |
ElmType Float | |
ElmType Int | |
ElmType Int8 | |
ElmType Int16 | |
ElmType Int32 | |
ElmType Int64 | |
ElmType () | |
ElmType Text | |
ElmType UTCTime | |
ElmType Day | |
ElmType a => ElmType [a] | |
ElmType a => ElmType (Maybe a) | |
(ElmType a, ElmType b) => ElmType (a, b) | |
(HasElmComparable k, ElmType v) => ElmType (Map k v) | |
ElmType a => ElmType (Proxy * a) | |
specsToDir :: [Spec] -> FilePath -> IO () #
Convenience re-exports from Data.Proxy
data Proxy k t :: forall k. k -> * #
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Generic1 (Proxy *) | |
Contravariant (Proxy *) | |
Alternative (Proxy *) | |
MonadPlus (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy k t) | |
Monoid (Proxy k s) | |
ElmType a => ElmType (Proxy * a) | |
type Rep1 (Proxy *) | |
type Rep (Proxy k t) | |