Code Monkey home page Code Monkey logo

servant-elm's Introduction

Servant Elm

Build Status

Generate Elm functions to query your Servant API!

Elm type generation coutesy of elm-bridge.

Installation

Servant Elm is available on Hackage.

Example

First, some language pragmas and imports.

{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE TypeOperators     #-}

import           Elm.Derive   (defaultOptions, deriveBoth)

import           Servant.API  ((:>), Capture, Get, JSON)
import           Servant.Elm  (DefineElm (DefineElm), Proxy (Proxy), defElmImports, defElmOptions,
                               generateElmModuleWith)

We have some Haskell-defined types and our Servant API.

data Book = Book
    { name :: String
    }

deriveBoth defaultOptions ''Book

type BooksApi = "books" :> Capture "bookId" Int :> Get '[JSON] Book

Now we can generate Elm functions to query the API:

main :: IO ()
main =
  generateElmModuleWith
    defElmOptions
    [ "Generated"
    , "MyApi"
    ]
    defElmImports
    "my-elm-dir"
    [ DefineElm (Proxy :: Proxy Book)
    ]
    (Proxy :: Proxy BooksApi)

Let's save this as example.hs and run it:

$ stack runghc example.hs
Writing: my-elm-dir/Generated/MyApi.elm

Here's what was generated:

module Generated.MyApi exposing(..)

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

type alias Book  =
   { name: String
   }

jsonDecBook : Json.Decode.Decoder ( Book )
jsonDecBook =
   Json.Decode.succeed (\pname -> {name = pname})
   |> required "name" (Json.Decode.string)

jsonEncBook : Book -> Value
jsonEncBook  val =
   Json.Encode.object
   [ ("name", Json.Encode.string val.name)
   ]


getBooksByBookId : Int -> Http.Request Book
getBooksByBookId capture_bookId =
    let
        params =
            List.filterMap identity
            (List.concat
                [])
    in
        Http.request
            { method =
                "GET"
            , headers =
                []
            , url =
                Url.Builder.absolute
                    [ "books"
                    , capture_bookId |> String.fromInt
                    ]
                    params
            , body =
                Http.emptyBody
            , expect =
                Http.expectJson <| jsonDecBook
            , timeout =
                Nothing
            , withCredentials =
                False
            }

See examples for a complete usage example, or take a look at mattjbray/servant-elm-example-app (elm 0.18) or haskell-servant/example-servant-elm (elm 0.19) for an example project using this library.

Development

$ git clone https://github.com/mattjbray/servant-elm.git
$ cd servant-elm
$ stack test
$ stack test --flag servant-elm:integration

To build all examples:

$ make examples

To run an example:

$ cd examples/e2e-tests
$ elm-reactor
# Open http://localhost:8000/elm/Main.elm

servant-elm's People

Contributors

1inguini avatar andys8 avatar cjmeeks avatar dawehner avatar dharanii avatar domenkozar avatar hadronized avatar ijaketak avatar ilyakooo0 avatar k-bx avatar mattjbray avatar nicklawls avatar purcell avatar sandydoo avatar soenkehahn avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

servant-elm's Issues

servant-elm-0.4.0.1 test suite failure with servant-0.13

As seen on the Stackage build server:

Failures:

  test/GenerateSpec.hs:98:
  1) encoding a simple api does it
       < generated
       > test/elm-sources/getBooksSource.elm
       7c7
       < getBooks : Bool -> Maybe (Maybe (String)) -> Maybe (Maybe (Int)) -> List (Maybe (Bool)) -> Http.Request (List (Book))
       ---
       > getBooks : Bool -> Maybe (String) -> Maybe (Int) -> List (Maybe (Bool)) -> Http.Request (List (Book))
       17c17
       <                     |> Maybe.map (toString >> Http.encodeUri >> (++) "sort=")
       ---
       >                     |> Maybe.map (Http.encodeUri >> (++) "sort=")

Randomized with seed 1283557679

Finished in 0.0027 seconds
2 examples, 1 failure

I was able to reproduce the failure locally like so:

stack unpack servant-elm-0.4.0.1 && cd servant-elm-0.4.0.1
edit stack.yaml # add the following stack.yaml
stack test
# stack.yaml
resolver: nightly-2018-03-10
extra-deps:
- servant-0.13
- http-types-0.12.1
- servant-foreign-0.11

Creating output directory automatically

I was trying out servant-elm for the first time, and kept running into this issue:

Prelude Elm CodeGen> specsToDir specs "/tmp/elm"
Writing: /tmp/elm/AutoGenerated/Api.elm
*** Exception: /tmp/elm/AutoGenerated/Api.elm: openFile: does not exist (No such file or directory)

It would be a good idea to use the equivalent of mkdir -p to create the output directory.

servant-elm-0.4.0.0 test suite failure with latest servant

As seen on the stackage nightly build. This is presumably related to us upgrading to the latest version of servant.

[2 of 2] Compiling Main             ( test/GenerateSpec.hs, dist/build/servant-elm-test/servant-elm-test-tmp/Main.o )
Linking dist/build/servant-elm-test/servant-elm-test ...
> /tmp/stackage-build13/servant-elm-0.4.0.0$ dist/build/servant-elm-test/servant-elm-test

encoding a simple api
  does it FAILED [1]
  with dynamic URLs

Failures:

  test/GenerateSpec.hs:98:
  1) encoding a simple api does it
       < generated
       > test/elm-sources/getWithaheaderSource.elm
       7,8c7,8
       < getWith-a-header : String -> Int -> Http.Request (String)
       < getWith-a-header header_myStringHeader header_MyIntHeader =
       ---
       > getWithaheader : String -> Int -> Http.Request (String)
       > getWithaheader header_myStringHeader header_MyIntHeader =

Randomized with seed 977727191

Finished in 0.0083 seconds
2 examples, 1 failure

Imitation and flattery

Hey Matt, this is not so much an issue as a "hello", "thanks" and an offer of help, so feel free to immediately close -- I simply prefer to keep open source communication in the open! I'm a buddy of @krisajenkins, and embarrassingly I didn't know about your servant-elm when I started working on my own a couple of months ago: searching for prior art turned up nothing at that point.

I quickly started trying to use the new servant-foreign library which will be in servant 0.5: it removes the need to destructure all the servant type constructions in generation code, instead giving you a value-level tree of ADTs for all the endpoints in an API type. Wanting ultimately to generate decoders/encoders automatically, I bumped up against limitations of servant-foreign which I think nobody else has encountered because they haven't been as ambitious as you or I, and I've been trying to get changes pushed upstream to remove those limitations.

So firstly, congrats on the excellent work you've done, and I'll likely switch over to using your servant-elm over mine. If so, I'll be sure to pitch in and help if I encounter any roadblocks. And secondly, if you have any thoughts on whether it would ultimately help you to use servant-foreign, and what might be needed there, I'd be interested to hear it.

Cheers!

Test suite failure in Stackage build

Linking dist/build/servant-elm-test/servant-elm-test ...
> /tmp/stackage-build13/servant-elm-0.3.0.0$ dist/build/servant-elm-test/servant-elm-test
/bin/sh: 1: elm-package: not found

Compile
  generateElmForAPI
    creates compilable javascript FAILED [1]
Generate
  encoding a simple api
    does it

Failures:

  test/CompileSpec.hs:31: 
  1) Compile.generateElmForAPI creates compilable javascript
       uncaught exception: IOException of type OtherError (callCommand: elm-package install --yes (exit 127): failed)

Randomized with seed 496767063

Finished in 0.0188 seconds
2 examples, 1 failure

Don't add a "query_" prefix to query params

Currently the generated code for QueryParam "query" Text looks like:

getApiGoodreadsSearchjson : (Maybe String) -> (Result Error  ((List GRBook))  -> msg) -> Cmd msg
getApiGoodreadsSearchjson query_query toMsg =
    let
        params =
            List.filterMap identity
            (List.concat
                [ [ query_query
                    |> Maybe.map (Url.Builder.string "query_query") ]
                ])
...

Need to keep only "query" as param name.

test suite failure with servant-0.18.2

The servant-elm-0.7.2 test suite appears to fail when compiled against servant-0.18.2 (et al. Servant 0.18.x supporting libraries).

The errors are as follows:

    /var/stackage/work/unpack-dir/unpacked/servant-elm-0.7.2-4b10f1da950fea1a0bcaf74a9e68dc0a1c01
36e8c09a136b9c3f6c89e09ad21a/test/Common.hs:41:13: error:
        • Expected kind ‘[*] -> * -> *’, but ‘PostNoContent’ has kind ‘*’
        • In the second argument of ‘(:>)’, namely
            ‘PostNoContent '[JSON] ()’
          In the second argument of ‘(:>)’, namely
            ‘ReqBody '[JSON] Book :> PostNoContent '[JSON] ()’
          In the first argument of ‘(:<|>)’, namely
            ‘"books" :> ReqBody '[JSON] Book :> PostNoContent '[JSON] ()’
       |
    41 |          :> PostNoContent '[JSON] ()
       |
    /var/stackage/work/unpack-dir/unpacked/servant-elm-0.7.2-4b10f1da950fea1a0bcaf74a9e68dc0a1c01
36e8c09a136b9c3f6c89e09ad21a/test/Common.hs:43:13: error:
        • Expected kind ‘[*] -> * -> *’, but ‘GetNoContent’ has kind ‘*’
        • In the second argument of ‘(:>)’, namely
            ‘GetNoContent '[JSON] ()’
          In the first argument of ‘(:<|>)’, namely
            ‘"nothing" :> GetNoContent '[JSON] ()’
          In the second argument of ‘(:<|>)’, namely
            ‘"nothing" :> GetNoContent '[JSON] ()
             :<|>
             "nothing" :> Put '[JSON] ()
             :<|>
             "with-a-header"
             :>
             Header "Cookie" String
             :>
             Header "myStringHeader" String
             :>
             Header "MyIntHeader" Int
             :>
             Header' '[Required] "MyRequiredStringHeader" String
             :>
             Header' '[Required] "MyRequiredIntHeader" Int :> Get '[JSON] String
             :<|>
             "with-a-response-header"
             :> Get '[JSON] (Headers '[Header "myResponse" String] String)’
       |
    43 |          :> GetNoContent '[JSON] ()
       |             ^^^^^^^^^^^^^^^^^^^^^^^

Double `Maybe` for a QueryParam?

Here's what my routes look like (using servant-generic):

data Routes route = Routes
  { rTest :: route :- "test" :> Get '[JSON] Text
  , rOAuthReturn :: route :- "oauth-return" :> QueryParam "code" Text :> Get '[JSON] Text
  } deriving (Generic)

Here's the function that handles rOAuthReturn:

oauthReturn :: Maybe Text -> AppM Text
oauthReturn = -- some code

The generated Elm type-signature for this API was:

getOauthreturn : Maybe (Maybe (String)) -> Http.Request (String)
getOauthreturn query_code = -- some code

Is this correct?

Possibility to Generate For `AuthProtect` endpoints?

Hello,

I have been using this library in a personal project and it's pretty damn cool. Thank you for writing it and for releasing it.

I did have a question, though, about AuthProtect endpoints. I have been using the servant-auth-cookie library to generate sessions and enforce authentication for certain endpoints, but I have not been able to use servant-elm to generate Api calls for these endpoints.

Maybe an example would be illustrative. With an endpoint like this:

type AdminApi = 
  "admin" :> AuthProtect "cookie-auth" :> Get '[HTML] Html
  :<|> "admin" :> "post" :> ReqBody '[JSON] Post.BlogPost :> AuthProtect "cookie-auth" :> Post '[JSON] Post.BlogPost

If I try to generate Elm for this using servant-elm, I get a compiler error like this:

client/GenerateElm.hs:21:9: error:
     No instance for (Servant.Foreign.Internal.HasForeign
                         servant-elm-0.1.0.2:Servant.Elm.Foreign.LangElm
                         elm-export-0.3.0.0:Elm.Type.ElmTypeExpr
                         (Servant.API.Experimental.Auth.AuthProtect "cookie-auth"
                          Servant.API.Sub.:> Servant.API.Verbs.Post
                                               '[Servant.API.ContentTypes.JSON]
                                               Post.BlogPost))
        arising from a use of generateElmForAPI
     In the second argument of (:), namely
        generateElmForAPI adminProxyApi
      In the second argument of (:), namely
        defElmImports : generateElmForAPI adminProxyApi
      In the second argument of (:), namely
        "import Exts.Date exposing (..)"
         : defElmImports : generateElmForAPI adminProxyApi
make: *** [Api.elm] Error 1

Am I doing something wrong or must there be an instance defined to be able to handle AuthProtected endpoints?

Thanks for any suggestions.

Clarify that servant-elm does support elm/http 2.0.0

https://package.elm-lang.org/packages/elm/http/latest/Http

There is no obvious CHANGELOG, but it's described (in very little detail) here:
https://elm-lang.org/blog/working-with-files

The basic changes we had to do on our project was change Http.Request resp to Cmd msg. This removes Http.send and instead you pass your msg constructor into the expect helper. There's also a small change to the record passed to request.

There might as well be more things that I've overlooked :)

Transfer repo to @haskell-servant

Continued from #45.

cc @alpmestan @domenkozar @k-bx

It seems that to transfer ownership I need permission to create repos in the @haskell-servant org.

I see three options:

  1. Add me to the @haskell-servant org, temporarily or otherwise, and I'll transfer the repo;
  2. I can transfer the repo to the user account of someone with access, who can then transfer the repo from their account to @haskell-servant; or
  3. Someone with access can fork this repo into @haskell-servant and I'll put a note here that this repo is deprecated (probably not ideal).

How should we proceed?

Text is converted to an Elm String, but still uses toString

If I change tests as following:

diff --git a/test/Common.hs b/test/Common.hs
index 09ae9c2..44ec34c 100644
--- a/test/Common.hs
+++ b/test/Common.hs
@@ -3,6 +3,7 @@
 {-# LANGUAGE TypeOperators #-}
 module Common where
 
+import           Data.Text
 import           Data.Aeson   (ToJSON)
 import           Data.Proxy   (Proxy(Proxy))
 import           Elm          (ElmType)
@@ -28,7 +29,7 @@ type TestApi =
          :> Capture "id" Int
          :> Get '[JSON] Book
   :<|> "books"
-         :> Capture "title" String
+         :> Capture "title" Text
          :> Get '[JSON] Book
   :<|> "books"
          :> QueryFlag "published"

Tests fail with:

Failures:

  test/GenerateSpec.hs:98: 
  1) encoding a simple api does it
       < generated
       > test/elm-sources/getBooksByTitleSource.elm
       17c17
       <                 , capture_title |> toString |> Http.encodeUri
       ---
       >                 , capture_title |> Http.encodeUri

servant-elm generates elm file the same as before, as String. But it adds toString which in elm wraps the value in quotes.

@mattjbray would you consider a patch that changes Text to behave as String?

generating elm for polymorphic data type and type synonym is broken

In my project I use opaleye lib.
I have to define polymorphic data type that corresponds to db table and several type synonyms with concrete fixed type parameters. For example:

data People' a b c = People { name :: a, lastname :: b, birthday :: s}
type People = People' Text Text Int

And in API type I use type synonym:

type PeopleApi =
"people" :> Capture "code" Int :> Get '[JSON] People

Generating elm api client is broken for this case.
Full example you can see here: https://github.com/nlv/servant-elm-test

Use elm-bridge instead of elm-export?

Have you considered using elm-bridge instead of elm-export? Elm-bridge has a couple of compelling features:

  • Support for Sum (union) types
  • Re-use of aeson decoding options

elm-bridge is also being actively maintained. I have looked into this a little bit, and it seems like it would require a fair amount of modification to the Generate module, but that's about it.

Support for named routes in servant

Are there plans to add support for named routes in servant?

It would be really nice, since the name of the generated functions could be defined by the developers, and functions corresponding to the same route would have the same name in both Haskell and Elm.

No instance for Servant.Foreign.Internal.GenerateList

Hi all,

I'm getting

    • No instance for (Servant.Foreign.Internal.GenerateList
                         elm-export-0.3.0.0:Elm.Type.ElmTypeExpr
                         (Servant.Foreign.Internal.Foreign
                            elm-export-0.3.0.0:Elm.Type.ElmTypeExpr
                            (Servant.API.BasicAuth.BasicAuth
                               "my-api" BodyType
                             Servant.API.Sub.:> MyApiSpec)))

where BodyType is a body type for one of the routes in my API, and MyApiSpec is part of my Servant API specification.

I'm not seeing where that instance should be created. I created ElmType instances for all my things, as you did for the Book type in the example, but I don't see any instances for BooksApi. I'm on Servant v0.8.1 and the master version of servant-elm.

Thanks!

Elm code generation problem

Hi
I am trying to generate Elm code from servant proxy : Api.hs

I see that for following Types.hs :

newtype JobId = JobId Int deriving (Eq, Ord, Show, Generic)

Elm code generated is :

type JobId
  = JobId  : Int

which should be

type JobId = JobId Int

Also code like decode-code

decodeJobId : Json.Decode.Decoder JobId
decodeJobId =
<Constructor "JobId" (Selector "" (Field (Primitive "Int")))>

is being generated.

Any suggestions on how to solve the problem ?
To reproduce, please clone sanskell and run make ui-setup ui-build

Type generation does not descend into Map

If you run this modification of the Book example:

{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}

import           GHC.Generics (Generic)
import           Servant.API  ((:>), Capture, Get, JSON)
import           Servant.Elm  (ElmType, Proxy (Proxy), Spec (Spec),
                               defElmImports, generateElmForAPI, specsToDir,
                               specsToDir)
import           Data.Map      (Map)

data Page = Page {content :: String} deriving (Generic)
instance ElmType Page

data Book = Book
 { name :: String,
   page :: Map Int Page
 } deriving (Generic)

instance ElmType Book

type BooksApi = "books" :> Capture "bookId" Int :> Get '[JSON] Book

spec :: Spec
spec = Spec ["Generated", "MyApi"]
            (defElmImports
             : generateElmForAPI (Proxy :: Proxy BooksApi))

main :: IO ()
main = specsToDir [spec] "my-elm-dir"

you'll see that the generated Elm code doesn't include a type for Page:

module Generated.MyApi where

import Json.Decode exposing ((:=))
import Json.Decode.Extra exposing ((|:))
import Json.Encode
import Http
import String
import Task


type alias Book =
  { name : String
  , page : Dict Int Page
  }

decodeBook : Json.Decode.Decoder Book
decodeBook =
  Json.Decode.succeed Book
    |: ("name" := Json.Decode.string)
    |: ("page" := Json.Decode.map Dict.fromList (Json.Decode.list (Json.Decode.tuple2 (,) Json.Decode.int decodePage)))

getBooksByBookId : Int -> Task.Task Http.Error (Book)
getBooksByBookId bookId =
  let
    request =
      { verb =
          "GET"
      , headers =
          [("Content-Type", "application/json")]
      , url =
          "/" ++ "books"
          ++ "/" ++ (bookId |> toString |> Http.uriEncode)
      , body =
          Http.empty
      }
  in
    Http.fromJson
      decodeBook
      (Http.send Http.defaultSettings request)

Uppercase header names result in invalid elm code

Given an API like

type SecureApi =
  Header "Authentication" String :> "item" :> Get '[JSON] [Item]

servant-elm will generate

getItem : String -> Http.Request (List (Item))
getItem Authentication =
    Http.request
        { method =
            "GET"
        , headers =
            [ Http.header "Authentication" Authentication
            ]
        , url =
            String.join "/"
                [ ""
                , "item"
                ]
        , body =
            Http.emptyBody
        , expect =
            Http.expectJson (list decodeItem)
        , timeout =
            Nothing
        , withCredentials =
            False
        }

...

which will result in the compile error Cannot find pattern 'Authentication'.

A trivial fix would be to convert the header name to lowercase before generating the elm code, resulting in a valid variable name.

Note that, although

type SecureApi =
  Header "Authentication" String :> Header "authentication" String :> "item" :> Get '[JSON] [Item]

will compile into a valid servant API, it is not a valid definition: the relevant RFC states that header names are case-insensitive. If either variant is is set by the client, both variants will have that value in servant, with the uppercase one having precedence if both are set.
Converting the header name to lowercase can therefore never result in a name clash with another header.

newtype encoding for query param does not match decoding by Servant

First of all, thank you for your work in creating this library!

I've hit a small snag: I have a newtype that is used as a capture parameter in an endpoint:

newtype Id = Id Int32 deriving ( Eq, Generic, Show, FromHttpApiData)

type API = Capture "id" Id :> ReqBody '[ JSON] Resource :> Put '[ JSON] NoContent

The generated API function generates a URL that looks like this: /Id%206, because it whereas servant's default decoder for this newtype expects a URL that simply reads /6. It looks like this happens when the Elm version of the newtype (type Id = Id Int) is passed through toString.

Is there something I can do to make this work, short of getting rid of getting rid of the newtype?

One potential avenue: We also generate an elm encodeId : Int -> Json.Encode.Value function. If for encoding the parameter in the query string we'd call that function first, then encode the Json value into a string it looks like we would generate the correct URI.

When query param is a bool, Elm code attempts to use String.fromInt on it

Problem description

I ran into a problem with version 6.0.2.

One of my endpoints accept a boolean parameter:

"todo" :> QueryParam "done" Bool :> Get '[JSON] [Todo]

The generated Elm code looks like this:

getTodo : Maybe Bool -> (Result Http.Error (List Todo) -> msg) -> Cmd msg
getTodo query_done toMsg =
    let
        params =
            List.filterMap identity
                (List.concat
                    [ [ query_done
                            |> Maybe.map (String.fromInt >> Url.Builder.string "done")
                      ]
                    ]
                )
    in
    Http.request { ... }

The problem is with the String.fromInt function. The query_done is a Maybe Bool, but it tries to stringfy it with the wrong funciton.

Solution

After looking at the code, my guess is there is no distinction of types in the toStringSrc function.
(Elm 0.18 used to have a toString function that stringifies any type but in 19, we need different functions for different types).

https://github.com/haskell-servant/servant-elm/blob/master/src/Servant/Elm/Internal/Generate.hs#L400

elm-0.18: Content-Type is set twice for JSON

It looks like Http already adds Content-Type: application/json when using jsonBody:

https://github.com/elm-lang/http/blob/99c00a2dac21dda1d4954515c79e6f28e431573f/src/Http.elm#L287-L292

The generated code also adds it, causing application/json to appear twice in the Content-Type header. This causes servant to reject the request with 415: Unsupported Media Type

My current workaround:

find frontend/src/Generated -name '*.elm' -exec \
  sed -i 's/Http.header "Content-Type" "application\/json"//' {} \;

Is it possible to use this with headers?

I have several endpoints that wrap the response type with headers, such as the following,

Post '[JSON] 
    (Headers '[Header "Cache-Control" T.Text, Header "Pragma" T.Text] OauthTokenResponse)

I tried fix this with the following

instance (ElmType a) => ElmType (Headers b a) where
    toElmType = toElmType

Which compiled, but segfaulted on run.

Is this supported? Did I do something wrong?

I'm using macOS 10.12.6
And GHC version 8.0.2 with stack

Support generate elm api as HttpBuilder ?

Now it seems generating elm api is as only Http.
http://package.elm-lang.org/packages/elm-lang/http/1.0.0/Http

There may be something like that Want to add some header parameter

But Http (unfortunately...) insists that Do not support for modifying existing request
(it means generated request code cannot be modified)
ref : https://github.com/elm-lang/http/issues/27

Against this kind of problem,
I think support generate elm api as HttpBuilder (extra Http library) is one of a flexible solution.
http://package.elm-lang.org/packages/lukewestby/elm-http-builder/5.1.0/HttpBuilder

What do you think about this ?

Custom Aeson instances

Is there a way to derive the end points using a custom aeson instance? When I try to use a custom aeson instance I get:

*** Exception: Library Bug: This should never happen!

Which is a pretty poor error message.

Support for algebraic sum types

First, let me say great work. I've really enjoyed working with servant-elm so far.

The only trouble I've run into so far with servant-elm occurs when the api for which I'm generating elm code involves algebraic sum types in some way.

E.g. Let's say my api looks like this:

type NameCompletionAPI = "nameCompletion" :> ReqBody '[JSON] NameCompletionRequest :> Get '[JSON] [Name]

And suppose the NameCompletionRequest type looks like this:

data NameCompletionRequest = NameCompletionRequest { nameSubstring :: Text , fromNationality :: Nationality , position :: Position } deriving (Generic)

and Position is a simple algebraic sum type:

data Position = Beginning | Middle | End deriving (Eq, Generic)

(Suppose too Nationality is just a new type wrapper around Text, and that we've defined all the ToJSON, FromJSON, and ElmType or ToElmType instances for these data types.)

Then on the main branch, when I go to generate this code, I'll get something like:
*** Exception: toElmTypeWithSources: Sum (Constructor "Beginning" Unit) (Sum (Constructor "Middle" Unit) (Constructor "End" Unit))

And on the devel branch, I'll get something like:

*** Exception: src/Elm/Encoder.hs:(13,1)-(58,28): Non-exhaustive patterns in function render

I was wondering if support for algebraic sum types was in the cards any time soon.

I guess this may be fundamentally more of an issue with elm-export. Let me know if it's best brought up somewhere else.

Incoherent parameter order

I have an endpoint that mixes both ReqBody and QueryParams:

filterOccurrences :: [Tag] -> [QueryFilter] -> 

However, the generated Elm reverses the order:

postOccurrencesFiltered : List (QueryFilter) -> List (String) -> Http.Request

It’s clearly not a big deal, but it’s confusing and error prone (I can’t imagine the madness if both the arguments resolve to the exact same type).

NoContent is not translated to an Elm type

Currently I am trying to port haskell-servant/example-servant-elm to Elm 0.18 and hence updated the used resolver to lts-8.0 the version of elm-export to commit 94b939b and the version of servant-elm to 301179e which went exceptionally well.

Unfortunately I am now stuck with a little API issue:

type Api =
  "api" :>
    ("item" :> Get '[JSON] [ItemId] :<|>
     "item" :> Capture "itemId" ItemId :> Get '[JSON] Item :<|>
     "item" :> ReqBody '[JSON] String :> Post '[JSON] ItemId :<|>
     "item" :> Capture "itemId" ItemId :> Delete '[JSON] NoContent)

The NoContent return type will result in a NoContent type in the generated api file which is not what I expect (since NoContent is unspecified on the elm side).

In the ElmOptions which get passed to generateElmForAPIWith I also specified explicitly

emptyResponseElmTypes =
      [ Elm.toElmType NoContent
      , Elm.toElmType ()
      ]

Additionally I tried toElmTypeSource (Proxy :: Proxy NoContent) without any effect.
So how do I get the NoContent type translated into a known elm value?

P. s. since I fear to misunderstand servant-elm at this point I thought this would be the appropriate place to ask. If this is not the case, it would be nice if you could point me into the right direction. Thanks!

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.