问题
I try to create a program which displays a text when a button is clicked, using haskell & Qt, on ubuntu using sublime text 3. But apparently there is a problem when defining the signal key (the key which will identify the signal called when the button is clicked). Moreover, it's hard to find a documentation about HsQML, the binding joining haskell & Qt.
code:
module Main where
import Graphics.QML
import Control.Concurrent
import Control.Exception
import Data.IORef
import Data.Text (Text)
import qualified Data.Text as T
main :: IO ()
main = do
state <- newIORef $ T.pack ""
skey <- newSignalKey
clazz <- newClass [
defPropertySigRO' "my_label" skey (\_ -> readIORef state),
defMethod' "sayHello" (\obj txt -> do
writeIORef state txt
fireSignal skey obj
return ())]
ctx <- newObject clazz ()
runEngineLoop defaultEngineConfig {
initialDocument = fileDocument "exemple2.qml",
contextObject = Just $ anyObjRef ctx}
error message:
Build FAILED
/home/lowley/Documents/haskell/Qt/exemple-2.hs: line 13, column 10:
No instance for (SignalSuffix (IO a0))
arising from a use of `newSignalKey'
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there is a potential instance available:
instance SignalSuffix (IO ()) -- Defined in `Graphics.QML.Objects'
Possible fix:
add an instance declaration for (SignalSuffix (IO a0))
In a stmt of a 'do' block: skey <- newSignalKey
In the expression:
do { state <- newIORef $ T.pack "";
skey <- newSignalKey;
clazz <- newClass
[defPropertySigRO' "my_label" skey (\ _ -> readIORef state),
defMethod' "sayHello" (\ obj txt -> ...)];
ctx <- newObject clazz ();
.... }
In an equation for `main':
main
= do { state <- newIORef $ T.pack "";
skey <- newSignalKey;
clazz <- newClass
[defPropertySigRO' "my_label" skey (\ _ -> ...), ....];
.... }
SOLVED! but I wonder why this program can be compiled without the above error:
module Main where
import Graphics.QML
import Control.Concurrent
import Control.Exception
import Data.IORef
import qualified Data.Text as T
main :: IO ()
main = do
state <- newIORef $ T.pack ""
skey <- newSignalKey
clazz <- newClass [
defPropertySigRO' "result" skey (\_ ->
readIORef state),
defMethod' "factorial" (\obj txt -> do
let n = read $ T.unpack txt :: Integer
writeIORef state $ T.pack "Working..."
fireSignal skey obj
forkIO $ do
let out = T.take 1000 . T.pack . show $ product [1..n]
evaluate out
writeIORef state out
fireSignal skey obj
return ())]
ctx <- newObject clazz ()
runEngineLoop defaultEngineConfig {
initialDocument = fileDocument "factorial2.qml",
contextObject = Just $ anyObjRef ctx}
回答1:
There error tells you that GHC doesn't know what type the signal created by newSignalKey should have (newSignalKey :: SignalSuffix p => IO (SignalKey p)
. GHC does not know what p
should be, since you don't specify it). Adding an explicit type signature like this:
skey <- newSignalKey :: IO (SignalKey (IO ()))
should fix the error that you are seeing.
Ok, so now why does it work in the second example? To understand that, we have to look at what GHC knows and what it can determine about the type of skey
.
In the first example and in the second example, skey
is used as follows:
do
...
fireSignal skey obj
...
Because fireSignal :: SignalKey p -> ObjRef () -> p
(simplified type, the full type of fireSignal
is more general), GHC knows that p
must be IO something
, because it is used in a context where an IO something
action is expected (as part of a do block in IO
). It does not know what something
is though, since the return value of that IO
action is never used. So it is left with skey :: SignalKey (IO something)
, and rightly reports an error that something
is ambiguous (it doesn't know what type something
should be).
In the second example, skey is however also used in the following pattern:
forkIO $ do
...
fireSignal skey obj
Since forkIO
expects an IO
action that returns a value of type ()
, GHC now knows that fireSignal skey obj :: IO ()
(so in this case, it knows that something
must be ()
). That means that p
is no longer ambiguous, it must be IO ()
.
来源:https://stackoverflow.com/questions/35847550/qt-button-click-a-message-should-appear-in-a-haskell-program