5

I am new to Haskell and reflex-dom, but really like the language. I've been using https://github.com/hansroland/reflex-dom-inbits/blob/master/tutorial.md to learn, and it's been very helpful.

I am currently trying to create a function that takes in a dynamic and creates an element and calls an FFI function every time the value changes in the dynamic. Here is a simplified version of what I'm trying to do.

{-# LANGUAGE OverloadedStrings #-}
import Data.Text as T
import qualified GHCJS.DOM.Types as GDT
import GHCJS.Types
import Reflex.Dom

foreign import javascript safe
  "$1.value = $2"
  testSet :: JSVal -> JSVal -> IO()

testTB :: DomBuilder t m => Dynamic t T.Text -> m ()
testTB dt = do
  (e, _) <- elAttr' "input" ("type" =: "text") blank
  bob <- (testSet (GDT.pToJSVal e) . GDT.pToJSVal) <$> dt
  return ()

main = mainWidget $ testTB $ constDyn "Hello World!"

This results in the compile time error:

reflex-canvas.hs:14:10: error:
    • Couldn't match type ‘m’ with ‘Dynamic t’
      ‘m’ is a rigid type variable bound by
        the type signature for:
          testTB :: forall t (m :: * -> *).
                    DomBuilder t m =>
                    Dynamic t Text -> m ()
        at reflex-canvas.hs:11:11
      Expected type: m (IO ())
        Actual type: Dynamic t (IO ())
    • In a stmt of a 'do' block:
        bob <- (testSet (GDT.pToJSVal e) . GDT.pToJSVal) <$> dt
      In the expression:
        do { (e, _) <- elAttr' "input" ("type" =: "text") blank;
             bob <- (testSet (GDT.pToJSVal e) . GDT.pToJSVal) <$> dt;
             return () }
      In an equation for ‘testTB’:
          testTB dt
            = do { (e, _) <- elAttr' "input" ("type" =: "text") blank;
                   bob <- (testSet (GDT.pToJSVal e) . GDT.pToJSVal) <$> dt;
                   return () }
    • Relevant bindings include
        e :: Element EventResult (DomBuilderSpace m) t
          (bound at reflex-canvas.hs:13:4)
        dt :: Dynamic t Text (bound at reflex-canvas.hs:12:8)
        testTB :: Dynamic t Text -> m () (bound at reflex-canvas.hs:12:1)

I've tried various ways to convert the Dynamic to a m() but cannot figure it out. What is the best practice for doing this?

Thanacles
  • 75
  • 4
  • have you tried `liftIO`ing? i mean `liftIO (testSet (GDTpToJSVal e) . GDT.pToJSVal) =<< (sample $ current dt)`? I am no expert on Reflex -but this should typecheck, though I have to say that I have not verified. – epsilonhalbe Nov 26 '17 at 03:14
  • You've chosen to omit the majority of the error, which is typically very informative in its entirety. Understanding the error would likely tell you how to fix it; and a good answer would give the fix and explain the error (teach a man to fish and all that...). – user2407038 Nov 26 '17 at 20:40
  • @epsilonhalbe Just tried a few variations of liftM and liftIO, but can't seem to get it to work. – Thanacles Nov 26 '17 at 21:02
  • @user2407038 Just added the full error message. – Thanacles Nov 26 '17 at 21:03
  • You can't get the T.Text value out of the Dynamic monad and use it directly as parameter for the _testSet_ function. You have to run the _testSet_ function in applicative mode inside the monad. Something like `testSet <$> ptrToHTMLControl <*> ptrToText`. – Jogger Nov 26 '17 at 21:36

1 Answers1

3

The function performEvent_ will force execution of a javascript function but performEvent_ wants an Event t (WidgetHost m ()) and, as the error message points out, you've got a Dynamic t (IO ()).

You can use updated to convert your Dynamic t (IO ()) to an Event t (IO ()) and you can use fmap liftIO to change the IO () in the Event to a WidgetHost m () leaving you with Event t (WidgetHost m ()) which you can pass to performEvent_

Here's your code with those modifications. I removed the first argument to testSet and the element creation inside testTB because those were not relevant to the problem/solution. I also added some extra type declarations. These were not required but may make things clearer.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Text as T (Text)
import qualified GHCJS.DOM.Types as GDT (pToJSVal)
import GHCJS.Types (JSVal)
import Reflex.Dom
import Control.Monad.Trans (liftIO)

foreign import javascript safe
  "console.log $1"
  testSet :: JSVal -> IO()

testTB :: forall t m.  MonadWidget t m => Dynamic t T.Text -> m ()
testTB dt = do 
    let bob :: Dynamic t (IO ())
        bob = (testSet.(GDT.pToJSVal)) <$> dt  

        bobIOEvent :: Event t (IO ())
        bobIOEvent = updated bob

        bobWidgetHostEvent :: Event t (WidgetHost m ())
        bobWidgetHostEvent = fmap liftIO bobIOEvent

    performEvent_ bobWidgetHostEvent

main = mainWidget $ do
    ti <- textInput def 
    let dt = value ti
    testTB dt
Dave Compton
  • 1,421
  • 1
  • 11
  • 18