Giter Site home page Giter Site logo

servant-js's Introduction

servant-js

servant

This library lets you derive automatically Javascript functions that let you query each endpoint of a servant webservice.

It contains a powerful system allowing you to generate functions for several frameworks (Angular, AXios, JQuery) as well as vanilla (framework-free) javascript code.

Example

Read more about the following example here.

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

import Control.Concurrent.STM
import Control.Monad.IO.Class
import Data.Aeson
import Data.Proxy
import GHC.Generics
import Network.Wai.Handler.Warp (run)
import Servant
import Servant.JS
import System.FilePath

-- * A simple Counter data type
newtype Counter = Counter { value :: Int }
  deriving (Generic, Show, Num)

instance ToJSON Counter

-- * Shared counter operations

-- Creating a counter that starts from 0
newCounter :: IO (TVar Counter)
newCounter = newTVarIO 0

-- Increasing the counter by 1
counterPlusOne :: MonadIO m => TVar Counter -> m Counter
counterPlusOne counter = liftIO . atomically $ do
  oldValue <- readTVar counter
  let newValue = oldValue + 1
  writeTVar counter newValue
  return newValue

currentValue :: MonadIO m => TVar Counter -> m Counter
currentValue counter = liftIO $ readTVarIO counter

-- * Our API type
type TestApi = "counter" :> Post '[JSON] Counter -- endpoint for increasing the counter
          :<|> "counter" :> Get  '[JSON] Counter -- endpoint to get the current value

type TestApi' = TestApi -- The API we want a JS handler for
           :<|> Raw     -- used for serving static files

-- this proxy only targets the proper endpoints of our API,
-- not the static file serving bit
testApi :: Proxy TestApi
testApi = Proxy

-- this proxy targets everything
testApi' :: Proxy TestApi'
testApi' = Proxy

-- * Server-side handler

-- where our static files reside
www :: FilePath
www = "examples/www"

-- defining handlers
server :: TVar Counter -> Server TestApi
server counter = counterPlusOne counter     -- (+1) on the TVar
            :<|> currentValue counter       -- read the TVar

server' :: TVar Counter -> Server TestApi'
server' counter = server counter
             :<|> serveDirectory www         -- serve static files

runServer :: TVar Counter -- ^ shared variable for the counter
          -> Int          -- ^ port the server should listen on
          -> IO ()
runServer var port = run port (serve testApi' $ server' var)

main :: IO ()
main = do
  -- write the JS code to www/api.js at startup
  writeJSForAPI testApi jquery (www </> "api.js")

  -- setup a shared counter
  cnt <- newCounter

  -- listen to requests on port 8080
  runServer cnt 8080

servant-js's People

Contributors

alpmestan avatar andys8 avatar arianvp avatar berdario avatar codedmart avatar dredozubov avatar fisx avatar freezeboy avatar jkarni avatar jml avatar luigy avatar maksbotan avatar mattjbray avatar maxow avatar minad avatar ondrap avatar phadej avatar purcell avatar rvion avatar soenkehahn avatar sol avatar teofilc avatar timhabermaas avatar ysangkok 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

Watchers

 avatar  avatar  avatar  avatar  avatar

servant-js's Issues

Don't check the contents of responseType

The generated code makes a comparison to see if xhr.responseType === 'json' but in my current Chrome, for example, this variable is always set to the empty string.

The generated code should only rely on the content-type header, and even in the absence of this header I would suggest trying to parse it as json anyway, or at least making it an option.

Provide URL Prefix as JS function argument

I'm writing a server which isn't necessarily accessed from a browser front end or on the same domain as the server itself. Because of this, it would be necessary to provide the address of the server as an additional argument to the generated javascript functions as so:

var getX = function( onSuccess
                   , onError
                   , serverAddress) // The additional server address argument
{
  // ...
  xhr.open('GET'
          , serverAddress + '/x' // Preappend the server address to the route
          , true);
  // ...
}

But I've not found an option to do so that's not generating and modifying the API by hand constantly.

QueryFlag is not encoded correctly

If you try to use QueryFlag you get invalid JavaScript.

The reason is this line in paramToStr function:

paramToStr :: QueryArg f -> Bool -> Text
paramToStr qarg notTheEnd =
  case qarg ^. queryArgType of
    Normal -> name
           <> "=' + encodeURIComponent("
           <> name
           <> if notTheEnd then ") + '" else ")"
    Flag   -> name <> "=" -------------------- BAD CODE HERE
    List   -> name
           <> "[]=' + encodeURIComponent("
           <> name
           <> if notTheEnd then ") + '" else ")"
  where name = qarg ^. queryArgName . argName . _PathSegment

It should be

    Flag   -> name <> "='" -- close the '

or

    Flag   -> name <> "'" -- close the '

The generated native else branch shouldn't try to parse json

In my case I had a simple connection issue, but because it attempted to parse that result I coudln't see the error.

else {
        try { res = JSON.parse(xhr.responseText); } catch (e) { onError(e); }
        if (res) onError(res);
      }

should become:

else {
       onError(xhr); // let t he user figure it out
      }

jsForAPI + jQuery = TTFB 500 ms

Hi!

I use jsForAPI for jQuery-based AJAX call:

apiAJAXCall :: Text
apiAJAXCall = jsForAPI api' jquery

where api' is an API from one single endpoint. After that I embed this text into <script>-tag in the index page (it's important detail, see below).

It works perfectly, but I see that the first request is too slow: TTFB is ~500 ms (on localhost!). Important: it's not AJAX-request for this endpoint, it's a request to index page! Such a big delay occurs only for the first request to the index page (after app reload), all other requests are very fast. How can I fix it?

Cannot generate function for API's that use Servant.Auth

I have an endpoint that looks approximately like this:

SAS.Auth [SAS.Cookie] LoggedIn :> Capture "tournamentId" TournamentId :> "start" :> Post '[JSON] (Entity Tournament)

Unfortunately, attempt to generate JS for this API does not typecheck. The error is:

app\Main.hs:24:14: error:
    * No instance for (servant-foreign-0.15.4:Servant.Foreign.Internal.HasForeign
                         NoTypes NoContent StartTournamentApi)
        arising from a use of `jsForAPI'
    * In the expression:
        jsForAPI (Proxy :: Proxy StartTournamentApi) jquery
      In an equation for `js':
          js = jsForAPI (Proxy :: Proxy StartTournamentApi) jquery
      In the expression:
        do let js = jsForAPI (Proxy :: Proxy StartTournamentApi) jquery
           TIO.writeFile "static/js/api.js" js
   |
24 |     let js = jsForAPI (Proxy :: Proxy StartTournamentApi) jquery

I assume that js generator should completely ignore auth requirement because XMLHttpRequest sends cookies which are used for authentication.

The workaround I found is to create a following instance:

instance HasForeign lang ftype api => HasForeign lang ftype (Auth auths val :> api) where
    type Foreign ftype (Auth auths val :> api) = Foreign ftype api
    foreignFor lang ftype Proxy = foreignFor lang ftype (Proxy :: Proxy api)

Invalid requests with query flags

We've recently encountered a couple of issues when generating Vanilla JS code.

Firstly, when a query flag is followed by something else, the generated request looks like this:

... + '&flag'&param=' + encodeURIComponent(param) ...

Instead of:

... + '&flag' + '&param=' + encodeURIComponent(param) ...

It is related to #11 and is even mentioned in a comment there. This part is easy to fix and I can propose a PR for it.

The second issue is that query flags are always added to the request (see valid code above), the actual argument of the client function is not even checked. This one is similar to #16, but I think it's better to have a separate issue for query flags processing.

How about append default header for axios and typescript style.

Hi there, very thanks to make js interface from type based safety api!

I used 'type to axios style api', and thought that it is more useful for development(flexibility) to inject default header "Content-value 'application/json'" and body as {}(this maybe axios behavior likely bug. When none body is passed, header is not inject if header value is passed.).

How about inject axios default header Content-Type 'application/json' and body as {} or merged with body like {...body}?
Example output like below.

export interface XRequest {
  xId: XID;
  message: string;
}

// this setting supports cors(of course when server support)
export const postX = (body: XRequest) => {
  return axios.post(
    endpoint + "/conv",
    { ...body },
    {
      headers: {
        "Content-Type": "application/json"
      }
    }
  );
};

I think it is easy to fix and provide more seamless work for api with client lib also under development environment.

Module ‘Servant.Foreign’ does not export ‘header'

Running cabal new-build fails with:

Building library for servant-js-0.9.4..
[1 of 6] Compiling Servant.JS.Internal ( src/Servant/JS/Internal.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS/Internal.o )
[2 of 6] Compiling Servant.JS.Axios ( src/Servant/JS/Axios.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS/Axios.o )
[3 of 6] Compiling Servant.JS.Angular ( src/Servant/JS/Angular.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS/Angular.o )
[4 of 6] Compiling Servant.JS.JQuery ( src/Servant/JS/JQuery.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS/JQuery.o )
[5 of 6] Compiling Servant.JS.Vanilla ( src/Servant/JS/Vanilla.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS/Vanilla.o )

src/Servant/JS/Vanilla.hs:12:1: warning: [-Wdodgy-imports]
    Module ‘Servant.Foreign’ does not export ‘header’
   |
12 | import           Servant.Foreign hiding (header)
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
[6 of 6] Compiling Servant.JS       ( src/Servant/JS.hs, /home/kb/workspace/servant-js/dist-newstyle/build/x86_64-linux/ghc-8.6.4/servant-js-0.9.4/build/Servant/JS.o )

"JSON expected in list ..." compile error

Hi,
I'm getting this error because some routes do not support JSON, and yet they are on the same endpoint branch.

Would ignoring such routes even be possible?
Is there some reason why such routes are not silently ignored?
Would add JSON, although not used, to the list have any side-effects?

Change of requestBody not honoured in JQuery 'data:' generation

Hi, when using
jqueryWith $ defCommonGeneratorOptions {requestBody = "payload"}
generated JS is this

var postUsers = function(payload, onSuccess, onError)   /// changed
{
  $.ajax(
    { url: '/api/users'
    , success: onSuccess
    , data: JSON.stringify(body)   /// not changed
    , contentType: 'application/json'
    , error: onError
    , type: 'POST'
    });
}

Generated vanilla code does not properly handle arrays (QueryParams)

It seems like the generated code builds arrays like so ?myParam=var1,var2,var3 which is not properly parsed by most servers, and in fact as far as I can tell this format is not even handled by Servant's own QueryParams.

The correctly generated javascript should look like: ?myParam=var1&myParam=var2&myParam=var3 and this list should itself be generated in javascript, at runtime, because it depends on the array parameter passed into the function.

Some servers also accept ?myParam[]=var1&myParam[]=var2&myParam[]=var3, but not all.

It doesn't seem like anybody has really tried using this generated JS code...

Support withCredentials in generated vanilla JS.

Including the withCredentials option should be useful for the Vanilla JS backend too, as it is included in the Axios backend.

  ...
  xhr.setRequestHeader("Accept","application/json");
  xhr.withCredentials = true;
  ...

Can't build with GHCJS (via GHC 8)

GHCJS (via GHC 8) can't build server-side code. Specifically because of kazu-yamamoto/logger#97.

servant-js does not depend on servant-server or fast-logger. However, its example does...

Even with example turned off explicitly, stack apparently builds dependencies for it, including servant-server:

$ stack build servant-js --dry-run --flag servant-js:-example
- Implicitly adding servant-js to extra-deps based on command line flag
No packages would be unregistered.

Would build:
aeson-pretty-0.8.5: database=snapshot, source=package index, after: cmdargs-0.10.17
appar-0.1.4: database=snapshot, source=package index
attoparsec-iso8601-1.0.0.0: database=snapshot, source=package index
auto-update-0.1.4: database=snapshot, source=package index
base64-bytestring-1.0.0.1: database=snapshot, source=package index
blaze-html-0.9.0.1: database=snapshot, source=package index, after: blaze-markup-0.8.0.0
blaze-markup-0.8.0.0: database=snapshot, source=package index
byteorder-1.0.4: database=snapshot, source=package index
bytestring-builder-0.10.8.1.0: database=snapshot, source=package index
charset-0.3.7.1: database=snapshot, source=package index
cmdargs-0.10.17: database=snapshot, source=package index
cookie-0.4.2.1: database=snapshot, source=package index, after: data-default-class-0.1.2.0
cryptonite-0.23: database=snapshot, source=package index, after: foundation-0.0.12,memory-0.14.6
data-default-class-0.1.2.0: database=snapshot, source=package index
easy-file-0.2.1: database=snapshot, source=package index
fast-logger-2.4.10: database=snapshot, source=package index, after: auto-update-0.1.4,easy-file-0.2.1,unix-time-0.3.7
file-embed-0.0.10: database=snapshot, source=package index
foundation-0.0.12: database=snapshot, source=package index
hex-0.1.2: database=snapshot, source=package index
http-api-data-0.3.7.1: database=snapshot, source=package index, after: attoparsec-iso8601-1.0.0.0,http-types-0.9.1,uri-bytestring-0.2.3.3
http-date-0.0.6.1: database=snapshot, source=package index
http-types-0.9.1: database=snapshot, source=package index
http2-1.6.3: database=snapshot, source=package index, after: aeson-pretty-0.8.5,bytestring-builder-0.10.8.1.0,hex-0.1.2,psqueues-0.2.3.0,word8-0.1.2
iproute-1.7.1: database=snapshot, source=package index, after: appar-0.1.4,byteorder-1.0.4
lifted-base-0.2.3.11: database=snapshot, source=package index, after: monad-control-1.0.2.1,transformers-base-0.4.4
memory-0.14.6: database=snapshot, source=package index, after: foundation-0.0.12
mime-types-0.1.0.7: database=snapshot, source=package index
mmorph-1.0.9: database=snapshot, source=package index
monad-control-1.0.2.1: database=snapshot, source=package index, after: transformers-base-0.4.4
natural-transformation-0.4: database=snapshot, source=package index
network-uri-2.6.1.0: database=snapshot, source=package index
psqueues-0.2.3.0: database=snapshot, source=package index
resourcet-1.1.9: database=snapshot, source=package index, after: lifted-base-0.2.3.11,mmorph-1.0.9,monad-control-1.0.2.1,transformers-base-0.4.4
servant-0.11: database=snapshot, source=package index, after: http-api-data-0.3.7.1,http-types-0.9.1,mmorph-1.0.9,natural-transformation-0.4,network-uri-2.6.1.0,string-conversions-0.4.0.1,vault-0.3.0.7
servant-foreign-0.10.1: database=snapshot, source=package index, after: http-types-0.9.1,servant-0.11
servant-js-0.9.3: database=local, source=package index, after: charset-0.3.7.1,servant-0.11,servant-foreign-0.10.1,servant-server-0.11,warp-3.2.13
servant-server-0.11: database=snapshot, source=package index, after: base64-bytestring-1.0.0.1,http-api-data-0.3.7.1,http-types-0.9.1,monad-control-1.0.2.1,network-uri-2.6.1.0,resourcet-1.1.9,servant-0.11,split-0.2.3.2,string-conversions-0.4.0.1,transformers-base-0.4.4,wai-3.2.1.1,wai-app-static-3.1.6.1,warp-3.2.13,word8-0.1.2
simple-sendfile-0.2.25: database=snapshot, source=package index
split-0.2.3.2: database=snapshot, source=package index
streaming-commons-0.1.17: database=snapshot, source=package index, after: zlib-0.6.1.2
string-conversions-0.4.0.1: database=snapshot, source=package index, after: utf8-string-1.0.1.1
stringsearch-0.3.6.6: database=snapshot, source=package index
transformers-base-0.4.4: database=snapshot, source=package index
unix-time-0.3.7: database=snapshot, source=package index
uri-bytestring-0.2.3.3: database=snapshot, source=package index
utf8-string-1.0.1.1: database=snapshot, source=package index
vault-0.3.0.7: database=snapshot, source=package index
wai-3.2.1.1: database=snapshot, source=package index, after: bytestring-builder-0.10.8.1.0,http-types-0.9.1,vault-0.3.0.7
wai-app-static-3.1.6.1: database=snapshot, source=package index, after: blaze-html-0.9.0.1,blaze-markup-0.8.0.0,cryptonite-0.23,file-embed-0.0.10,http-date-0.0.6.1,http-types-0.9.1,memory-0.14.6,mime-types-0.1.0.7,wai-3.2.1.1,wai-extra-3.0.20.0,warp-3.2.13,zlib-0.6.1.2
wai-extra-3.0.20.0: database=snapshot, source=package index, after: base64-bytestring-1.0.0.1,cookie-0.4.2.1,data-default-class-0.1.2.0,fast-logger-2.4.10,http-types-0.9.1,iproute-1.7.1,lifted-base-0.2.3.11,resourcet-1.1.9,streaming-commons-0.1.17,stringsearch-0.3.6.6,vault-0.3.0.7,wai-3.2.1.1,wai-logger-2.3.0,word8-0.1.2,zlib-0.6.1.2
wai-logger-2.3.0: database=snapshot, source=package index, after: byteorder-1.0.4,fast-logger-2.4.10,http-types-0.9.1,unix-time-0.3.7,wai-3.2.1.1
warp-3.2.13: database=snapshot, source=package index, after: auto-update-0.1.4,bytestring-builder-0.10.8.1.0,http-date-0.0.6.1,http-types-0.9.1,http2-1.6.3,iproute-1.7.1,simple-sendfile-0.2.25,streaming-commons-0.1.17,vault-0.3.0.7,wai-3.2.1.1,word8-0.1.2
word8-0.1.2: database=snapshot, source=package index
zlib-0.6.1.2: database=snapshot, source=package index

No executables to be installed.

Generated Vanilla js attempts to parse error bodies as json

When servant-server returns an error with a body (e.g. on failure to parse, or missing required arguments), it's not json-encoded (it's plain-text) "by default" (e.g. when using ReqBody).

However the Vanilla generated functions always attempt to parse the error response body as json, which fails (because of missing double quotes).

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.