Skip to content
Snippets Groups Projects
Commit 2f571afe authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Fix GHCJS OS platform (fix #23346)

parent 5ae81842
No related branches found
No related tags found
No related merge requests found
......@@ -208,6 +208,7 @@ osElfTarget OSQNXNTO = False
osElfTarget OSAIX = False
osElfTarget OSHurd = True
osElfTarget OSWasi = False
osElfTarget OSGhcjs = False
osElfTarget OSUnknown = False
-- Defaulting to False is safe; it means don't rely on any
-- ELF-specific functionality. It is important to have a default for
......
......@@ -98,6 +98,7 @@ data OS
| OSAIX
| OSHurd
| OSWasi
| OSGhcjs
deriving (Read, Show, Eq, Ord)
......@@ -157,3 +158,4 @@ stringEncodeOS = \case
OSAIX -> "aix"
OSHurd -> "hurd"
OSWasi -> "wasi"
OSGhcjs -> "ghcjs"
......@@ -119,7 +119,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS_SHELL_FUNCTIONS],
test -z "[$]2" || eval "[$]2=OSHurd"
;;
ghcjs|js)
test -z "[$]2" || eval "[$]2=OSUnknown"
test -z "[$]2" || eval "[$]2=OSGhcjs"
;;
*)
echo "Unknown OS '[$]1'"
......
{-# LANGUAGE CPP #-}
module Main where
main :: IO ()
main = print (correct_host && correct_arch)
#ifdef ghcjs_HOST_OS
correct_host = True
#else
correct_host = False
#endif
#ifdef javascript_HOST_ARCH
correct_arch = True
#else
correct_arch = False
#endif
True
......@@ -15,3 +15,5 @@ test('js-callback02', normal, compile_and_run, [''])
test('js-callback03', normal, compile_and_run, [''])
test('js-callback04', js_skip, compile_and_run, [''])
test('js-callback05', js_skip, compile_and_run, [''])
test('T23346', normal, compile_and_run, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment