Commit 18b8fd0b authored by Andrew Gibiansky's avatar Andrew Gibiansky

Read from printed output as UTF-8 (fixes #671).

parent db351598
......@@ -8,6 +8,7 @@ This module exports all functions used for evaluation of IHaskell input.
module IHaskell.Eval.Evaluate (
interpret,
testInterpret,
testEvaluate,
evaluate,
flushWidgetMessages,
Interpreter,
......@@ -37,7 +38,7 @@ import System.Directory
import System.Posix.IO (createPipe)
#endif
import System.Posix.IO (fdToHandle)
import System.IO (hGetChar, hFlush)
import System.IO (hGetChar, hSetEncoding, utf8, hFlush)
import System.Random (getStdGen, randomRs)
import Unsafe.Coerce
import Control.Monad (guard)
......@@ -147,10 +148,15 @@ ihaskellGlobalImports =
, "import qualified IHaskell.Eval.Widgets"
]
-- | Evaluation function for testing.
-- | Interpreting function for testing.
testInterpret :: Interpreter a -> IO a
testInterpret val = interpret GHC.Paths.libdir False (const val)
-- | Evaluation function for testing.
testEvaluate :: String -> IO ()
testEvaluate str = void $ testInterpret $
evaluate defaultKernelState str (const $ return ()) (\state _ -> return state)
-- | Run an interpreting action. This is effectively runGhc with initialization and importing. First
-- argument indicates whether `stdin` is handled specially, which cannot be done in a testing
-- environment. The argument passed to the action indicates whether Haskell support libraries are
......@@ -1134,7 +1140,9 @@ capturedEval output stmt = do
-- Then convert the HValue into an executable bit, and read the value.
pipe <- liftIO $ do
fd <- head <$> unsafeCoerce hValues
fdToHandle fd
handle <- fdToHandle fd
hSetEncoding handle utf8
return handle
-- Keep track of whether execution has completed.
completed <- liftIO $ newMVar False
......
{-# LANGUAGE CPP #-}
module IHaskell.Test.Completion (testCompletions) where
import Prelude
......@@ -21,6 +22,10 @@ import IHaskell.Eval.Completion (complete, CompletionType(..), complet
completionTarget)
import IHaskell.Test.Util (replace, shouldBeAmong, ghc)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
-- | @readCompletePrompt "xs*ys"@ return @(xs, i)@ where i is the location of
-- @'*'@ in the input string.
readCompletePrompt :: String -> (String, Int)
......
......@@ -143,6 +143,10 @@ testEval =
"import qualified Control.Monad as CM" `becomes` []
"import Control.Monad (when)" `becomes` []
it "prints Unicode characters correctly" $ do
"putStrLn \"Héllö, Üñiço∂e!\"" `becomes` ["Héllö, Üñiço∂e!"]
"putStrLn \"Привет!\"" `becomes` ["Привет!"]
it "evaluates directives" $ do
":typ 3" `becomes` ["3 :: forall a. Num a => a"]
":k Maybe" `becomes` ["Maybe :: * -> *"]
......
......@@ -15,6 +15,10 @@ import IHaskell.Eval.Parser (parseString, getModuleName, unloc, layout
CodeBlock(..), DirectiveType(..), StringLoc(..))
import IHaskell.Eval.ParseShell (parseShell)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
parses :: String -> IO [CodeBlock]
parses str = map unloc <$> ghc (parseString str)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment