servant-elm-0.6.0.2: Automatically derive Elm functions to query servant webservices.

Safe HaskellNone
LanguageHaskell2010

Servant.Elm

Contents

Description

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"
Synopsis

Documentation

generateElmForAPI :: (HasForeign LangElm EType api, GenerateList EType (Foreign EType 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 EType api, GenerateList EType (Foreign EType api)) => ElmOptions -> Proxy api -> [Text] Source #

Generate Elm code for the API with custom options.

generateElmModule :: (HasForeign LangElm EType api, GenerateList EType (Foreign EType api)) => Namespace -> Text -> FilePath -> [DefineElm] -> Proxy api -> IO () Source #

Calls generateElmModuleWith with defElmOptions.

generateElmModuleWith :: (HasForeign LangElm EType api, GenerateList EType (Foreign EType api)) => ElmOptions -> Namespace -> Text -> FilePath -> [DefineElm] -> Proxy api -> IO () Source #

Helper to generate a complete Elm module given a list of Elm type definitions and an API.

data ElmOptions Source #

Options to configure how code is generated.

Constructors

ElmOptions 

Fields

data UrlPrefix Source #

Constructors

Static Text 
Dynamic 

defElmOptions :: ElmOptions Source #

Default options for generating Elm code.

The default options are:

{ urlPrefix =
    Static ""
, elmAlterations =
    Elm.defaultTypeAlterations
, emptyResponseElmTypes =
    [ getType (Proxy :: Proxy ()) ]
, stringElmTypes =
    [ getType (Proxy :: Proxy String)
    , getType (Proxy :: Proxy T.Text) ]
}

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
import Json.Encode exposing (Value)
-- The following module comes from bartavelle/json-helpers
import Json.Helpers exposing (..)
import Dict exposing (Dict)
import Set
import Http
import String
import Url.Builder

Convenience re-exports from the Elm module

data DefineElm where #

Existential quantification wrapper for lists of type definitions

Constructors

DefineElm :: forall a. IsElmDefinition a => Proxy a -> DefineElm 

data EType #

Type construction : type variables, type constructors, tuples and type application.

Instances
Eq EType 
Instance details

Defined in Elm.TyRep

Methods

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

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

Ord EType 
Instance details

Defined in Elm.TyRep

Methods

compare :: EType -> EType -> Ordering #

(<) :: EType -> EType -> Bool #

(<=) :: EType -> EType -> Bool #

(>) :: EType -> EType -> Bool #

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

max :: EType -> EType -> EType #

min :: EType -> EType -> EType #

Show EType 
Instance details

Defined in Elm.TyRep

Methods

showsPrec :: Int -> EType -> ShowS #

show :: EType -> String #

showList :: [EType] -> ShowS #

ElmRenderable EType 
Instance details

Defined in Elm.TyRender

Methods

renderElm :: EType -> String #

Typeable a => HasForeignType LangElm EType (a :: Type) Source # 
Instance details

Defined in Servant.Elm.Internal.Foreign

Methods

typeFor :: Proxy LangElm -> Proxy EType -> Proxy a -> EType #

Typeable a => HasForeignType LangElm EType (Headers b a :: Type) Source # 
Instance details

Defined in Servant.Elm.Internal.Foreign

Methods

typeFor :: Proxy LangElm -> Proxy EType -> Proxy (Headers b a) -> EType #

toElmType :: Typeable a => Proxy a -> EType #

Get an elm-bridge type representation for a Haskell type. This can be used to render the type declaration via ElmRenderable or the the JSON serializer/parser names via jsonSerForType and jsonParserForType.

deriveBoth :: Options -> Name -> Q [Dec] #

Equivalent to running both deriveJSON and deriveElmDef with the same options, so as to ensure the code on the Haskell and Elm size is synchronized.

deriveElmDef :: Options -> Name -> Q [Dec] #

Just derive the elm-bridge definitions for generating the serialization/deserialization code. It must be kept synchronized with the Haskell code manually.

Convenience re-exports from Data.Proxy

data Proxy (t :: k) :: forall k. k -> Type #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Representable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy :: Type #

Methods

tabulate :: (Rep Proxy -> a) -> Proxy a #

index :: Proxy a -> Rep Proxy -> a #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> Type))
type Rep (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

type Rep (Proxy :: Type -> Type) = Void
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: Type -> Type))