hs-duktape: Haskell bindings for a very compact embedded ECMAScript (JavaScript) engine.

[ library, mit, web ] [ Propose Tags ]

Modules

[Last Documentation]

  • Scripting
    • Scripting.Duktape
      • Scripting.Duktape.Raw

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.1.1, 0.1.2, 0.1.3, 0.1.4, 0.1.5, 1.0.0
Dependencies aeson, base (>=4.3.0.0 && <5), bytestring, text, transformers, unordered-containers, vector [details]
License MIT
Copyright 2015-2017 Val Packett <val@packett.cool>, 2013-2017 Duktape authors (for Duktape)
Author Val Packett
Maintainer val@packett.cool
Revised Revision 1 made by myfreeweb at 2022-10-16T00:06:55Z
Category Web
Home page https://codeberg.org/valpackett/hs-duktape
Source repo head: git clone https://codeberg.org/valpackett/hs-duktape.git
Uploaded by myfreeweb at 2017-03-01T16:57:23Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 4863 total (22 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2017-03-01 [all 3 reports]

Readme for hs-duktape-0.1.4

[back to package description]

hs-duktape Hackage Build Status MIT License

Haskell bindings for duktape, a very compact embedded ECMAScript (JavaScript) engine.

Usage

Here's a simple REPL example:

module Main where

import Scripting.Duktape
import Control.Monad (forever)
import Data.ByteString.Char8 (pack)
import System.IO (hFlush, stdout)

main :: IO ()
main = do
  dukm <- createDuktapeCtx
  case dukm of
    Nothing -> putStrLn "I can't even (start Duktape)"
    Just duk -> forever $ do
      putStr "duktape> "
      hFlush stdout
      retVal <- evalDuktape duk =<< return . pack =<< getLine
      case retVal of
        Left e -> putStrLn $ "Duktape error: " ++ e
        Right Nothing -> putStrLn "No result"
        Right (Just v) -> print v

Aeson's Value type is used for exchanging values between Haskell and ECMAScript.
lens-aeson is a good library for working with Value, um, values.

You can also call functions that are on the global object (or any object that's on the global object):

dukm <- createDuktapeCtx
bresult <- callDuktape (fromJust dukm) Nothing "boolTest" [Bool True, Bool True, Bool False] -- boolTest(true, true, false)
aresult <- callDuktape (fromJust dukm) (Just "NumFuns") "sum" [Number 1, Number 2] -- NumFuns.sum(1, 2)

And expose Haskell functions (same as with calls: set on global or a property of global):

dukm <- createDuktapeCtx
let dbl (Number x) = return $ Number $ x * 2 ∷ IO Value
    dbl _ = return $ String "wtf"
reD ← exposeFnDuktape (fromJust ctx) Nothing "double" dbl 

The functions must be of type IO (), IO Value, Value -> IO Value, Value -> Value -> IO Value... and so on, up to 5 arguments. If you need more, use an Object Value, seriously.

Development

Use stack to build.

$ stack build

$ stack test && rm tests.tix

Contributing

Please feel free to submit pull requests!

By participating in this project you agree to follow the Contributor Code of Conduct.

The list of contributors is available on GitHub.

License

Licensed under the MIT license (see to the LICENSE file).
Haskell bindings: Copyright (c) 2015-2016 Greg V greg@unrelenting.technology
Duktape: Copyright (c) 2013-2016 by Duktape authors (see duktape/AUTHORS.rst)