servant-elm-0.2.0.0: 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 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.

Constructors

ElmOptions 

Fields

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
import Task

Convenience re-exports from the Elm module

data Spec :: * #

Constructors

Spec [Text] [Text] 

class ElmType a #

Instances

ElmType Bool 

Methods

toElmType :: Bool -> ElmDatatype

ElmType Char 

Methods

toElmType :: Char -> ElmDatatype

ElmType Double 

Methods

toElmType :: Double -> ElmDatatype

ElmType Float 

Methods

toElmType :: Float -> ElmDatatype

ElmType Int 

Methods

toElmType :: Int -> ElmDatatype

ElmType Int8 

Methods

toElmType :: Int8 -> ElmDatatype

ElmType Int16 

Methods

toElmType :: Int16 -> ElmDatatype

ElmType Int32 

Methods

toElmType :: Int32 -> ElmDatatype

ElmType Int64 

Methods

toElmType :: Int64 -> ElmDatatype

ElmType () 

Methods

toElmType :: () -> ElmDatatype

ElmType Text 

Methods

toElmType :: Text -> ElmDatatype

ElmType UTCTime 

Methods

toElmType :: UTCTime -> ElmDatatype

ElmType Day 

Methods

toElmType :: Day -> ElmDatatype

ElmType a => ElmType [a] 

Methods

toElmType :: [a] -> ElmDatatype

ElmType a => ElmType (Maybe a) 

Methods

toElmType :: Maybe a -> ElmDatatype

(ElmType a, ElmType b) => ElmType (a, b) 

Methods

toElmType :: (a, b) -> ElmDatatype

(HasElmComparable k, ElmType v) => ElmType (Map k v) 

Methods

toElmType :: Map k v -> ElmDatatype

ElmType a => ElmType (Proxy * a) 

Methods

toElmType :: Proxy * a -> ElmDatatype

specsToDir :: [Spec] -> FilePath -> IO () #

Convenience re-exports from Data.Proxy

data Proxy k t :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (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 *) 

Methods

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

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

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

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

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

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

Foldable (Proxy *) 

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 #

Generic1 (Proxy *) 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a #

to1 :: Rep1 (Proxy *) a -> Proxy * a #

Contravariant (Proxy *) 

Methods

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

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

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

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

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

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

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

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

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

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

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

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

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

Eq (Proxy k s) 

Methods

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

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

Ord (Proxy k s) 

Methods

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

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

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

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

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

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

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

Read (Proxy k s) 
Show (Proxy k s) 

Methods

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

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) 

Methods

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

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

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

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

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

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

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

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

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

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

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

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

ElmType a => ElmType (Proxy * a) 

Methods

toElmType :: Proxy * a -> ElmDatatype

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)