Skip to content

Instantly share code, notes, and snippets.

@rubenpieters
Last active December 7, 2017 12:37
Show Gist options
  • Save rubenpieters/487e0452e7c3f62363c07c26a182f08f to your computer and use it in GitHub Desktop.
Save rubenpieters/487e0452e7c3f62363c07c26a182f08f to your computer and use it in GitHub Desktop.
purescript passing impure callbacks
module Main where
import Prelude
import Data.Foreign.EasyFFI
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
-- code for wrapping impure functions
newtype Impure f = Impure f
mkImpureFn1 :: ∀ a e v. (a -> Eff e v) -> Impure (a -> v)
mkImpureFn1 f = Impure (unsafeForeignFunction ["f", "a"] "f(a)();" f)
-- original Eff function
test1 :: ∀ e. String -> Eff (console :: CONSOLE | e) Unit
test1 x = log ("test: " <> x)
-- impure version of test1
test2 :: Impure (String -> Unit)
test2 = mkImpureFn1 test1
-- external function expecting impure callback
testFunction = unsafeForeignProcedure ["cb",""] "console.log(\"expecting impure function\"); cb(\"a\");"
-- test Eff version and Impure version
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
let f1 = test1
let f2 = test2
log "test1 --"
_ <- testFunction f1
log "--"
log "test2 --"
_ <- testFunction f2
log "--"
pure unit
Compiling Main
PSCi, version 0.11.6
Type :? for help
import Prelude
> import Main
> main
test1 --
expecting impure function
--
test2 --
expecting impure function
test: a
--
unit
>
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment