diff --git a/.travis.yml b/.travis.yml
index 40a132c8ce121b747feced1f89500eae45b413e0..5ccb00e0e244b05123a575c9ee2ce7dffa1b6bf4 100644
--- a/.travis.yml
+++ b/.travis.yml
@@ -27,11 +27,12 @@ before_cache:
 matrix:
   include:
     - compiler: "ghc-7.0.4"
-      env: INSTALLED=false
-    # env: TEST=--disable-tests BENCH=--disable-benchmarks
+      # can't build the testsuites dependencies with 7.0
+      env: INSTALLED=false TEST=--disable-tests BENCH=--disable-benchmarks
       addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-7.0.4], sources: [hvr-ghc]}}
     - compiler: "ghc-7.2.2"
-    # env: TEST=--disable-tests BENCH=--disable-benchmarks
+    # can't build the testsuites dependencies with 7.2
+      env: TEST=--disable-tests BENCH=--disable-benchmarks
       addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-7.2.2], sources: [hvr-ghc]}}
     - compiler: "ghc-7.4.2"
     # env: TEST=--disable-tests BENCH=--disable-benchmarks
diff --git a/ATTParser.hs b/ATTParser.hs
new file mode 100644
index 0000000000000000000000000000000000000000..93d332e20b9771e148d9f88c460574c3716b5f2c
--- /dev/null
+++ b/ATTParser.hs
@@ -0,0 +1,122 @@
+-- A rather crude asm parser.
+--
+--
+-- we only handle a subset of AT&T assembly
+-- right now.  This is what gcc and clang can
+-- emit.  For clang using llvm-ir might be
+-- even better.  For gcc gimple if that can
+-- be consumed reliably somehow.
+--
+-- For now we'll rely on the at&t assembly
+-- to be sufficient for constants.
+--
+
+
+module ATTParser where
+
+import Control.Applicative ((<|>))
+import Data.Word (Word32, Word64)
+import Data.Int (Int64)
+import Data.Char (isDigit, isSpace)
+import Data.Bits (shiftL, shiftR, (.|.))
+import Data.Maybe (fromMaybe)
+
+data Inst = Ident String
+          | Long Word32
+          | Quad Word64
+          | Ref String
+          | Ascii String
+          deriving Show
+
+type ASM = [(String, Inst)]
+
+isIdent :: Inst -> Bool
+isIdent (Ident _) = True
+isIdent _ = False
+
+trim :: String -> String
+trim = reverse . dropWhile (`elem` " \t") . reverse . dropWhile (`elem` " \t")
+-- | generalized @words@.
+words' :: (a -> Bool) -> [a] -> [[a]]
+words' p s = case dropWhile p s of
+             [] -> []
+             s' -> w : words' p s''
+                   where (w, s'') = break p s'
+
+isNumber :: String -> Bool
+isNumber ('-':x) = all isDigit x
+isNumber ('+':x) = all isDigit x
+isNumber x       = all isDigit x
+
+-- | process the assembly instructions, filtering out
+-- identifiers and constant values.
+preprocess :: String -> [Inst]
+preprocess [] = []
+preprocess ('\t':attr) = let (h, t) = break isSpace attr
+                         in case h:words' (=='\t') t of
+                         (".quad":x:_) | isNumber (w x) -> [Quad $ read (w x)]
+                                       | otherwise      -> [Ref  $ (w x)]
+                         (".xword":x:_)| isNumber (w x) -> [Quad $ read (w x)]
+                                       | otherwise      -> [Ref  $ (w x)]
+                         (".long":x:_) | isNumber (w x) -> [Long $ read (w x)]
+                                       | otherwise      -> [Ref  $ (w x)]
+                         (".space":x:_)| (w x) == "4"   -> [Long 0]
+                                       | (w x) == "8"   -> [Quad 0]
+                         (".ascii":x:_)             -> [Ascii $ read x]
+                         (".asciz":x:_)             -> [Ascii $ read x ++ "\0"]
+                         _                          -> []
+  where w = head . words
+preprocess ('.':'z':'e':'r':'o':'f':'i':'l':'l':' ':x) = case words' (==',') x of
+      (_seg:_sect:sym:size:_) | size == "4" -> [Ident sym, Long 0]
+                              | size == "8" -> [Ident sym, Quad 0]
+      _ -> []
+preprocess (c:cs) | not (isSpace c) = [Ident $ takeWhile (/= ':') (c:cs)]
+                  | otherwise       = []
+
+-- | turn the list of instructions into an associated list
+parseInsts :: [Inst] -> [(String, Inst)]
+parseInsts [] = []
+parseInsts (Ident name:xs) = case break isIdent xs of
+  ([], xs') -> parseInsts xs'
+  (is, xs') -> (name, combineInst is):parseInsts xs'
+parseInsts _ = error "Invalid instructions"
+
+-- | combine instructions (e.g. two long into a quad)
+combineInst :: [Inst] -> Inst
+combineInst [Quad i] = Quad i
+combineInst [Long i] = Quad (fromIntegral i)
+combineInst [Long h, Long l] = Quad $ (shiftL (fromIntegral h) 32) .|. fromIntegral l
+combineInst [Ref s]  = Ref s
+combineInst [Ascii s] = Ascii s
+combineInst is = error $ "Cannot combine instructions: " ++ show is
+
+-- | inline references
+inlineRef :: [(String, Inst)] -> [(String, Inst)]
+inlineRef xs = map go xs
+  where go (k, Ref name) = (k, fromMaybe (error $ "failed to find reference " ++ show name) $ lookup name xs)
+        go x = x
+
+fixWordOrder :: [(String, Inst)] -> [(String, Inst)]
+fixWordOrder xs = case lookupInteger "___hsc2hs_BOM___" xs of
+  Just 1 -> map go xs
+  _ -> xs
+  where go (k, Quad w) = (k, Quad $ shiftL w 32 .|. shiftR w 32)
+        go x = x
+
+parse :: FilePath -> IO [(String, Inst)]
+parse f = (fixWordOrder . inlineRef . parseInsts . concatMap preprocess . lines) `fmap` readFile f
+
+-- | lookup a symbol without or with underscore prefix
+lookup_ :: String -> [(String,b)] -> Maybe b
+lookup_ k l = lookup k l <|> lookup ("_" ++ k) l
+
+lookupString :: String -> [(String, Inst)] -> Maybe String
+lookupString k l = case (lookup_ k l) of
+  Just (Ascii s) -> Just s
+  _ -> Nothing
+
+lookupInteger :: String -> [(String, Inst)] -> Maybe Integer
+lookupInteger k l = case (lookup_ k l, lookup_ (k ++ "___hsc2hs_sign___") l) of
+  (Just (Quad i), Just (Quad 1)) -> Just (fromIntegral (fromIntegral i :: Int64))
+  (Just (Quad i), _) -> Just (fromIntegral i)
+  _ -> Nothing
diff --git a/CrossCodegen.hs b/CrossCodegen.hs
index 1312b917938ad3570c942d455be70fc56a5b7505..93f1e1859df2c3bff166fa5ad7834659881ce9b2 100644
--- a/CrossCodegen.hs
+++ b/CrossCodegen.hs
@@ -40,6 +40,8 @@ import Common
 import Flags
 import HSCParser
 
+import qualified ATTParser as ATT
+
 -- A monad over IO for performing tests; keeps the commandline flags
 -- and a state counter for unique filename generation.
 -- equivalent to ErrorT String (StateT Int (ReaderT TestMonadEnv IO))
@@ -219,8 +221,7 @@ outputSpecial output (z@ZCursor {zCursor=Special pos@(SourcePos file line _)  ke
        "const" -> outputConst value show >> return False
        "offset" -> outputConst ("offsetof(" ++ value ++ ")") (\i -> "(" ++ show i ++ ")") >> return False
        "size" -> outputConst ("sizeof(" ++ value ++ ")") (\i -> "(" ++ show i ++ ")") >> return False
-       "alignment" -> outputConst (alignment value)
-                                  (\i -> "(" ++ show i ++ ")") >> return False
+       "alignment" -> outputConst (alignment value) show >> return False
        "peek" -> outputConst ("offsetof(" ++ value ++ ")")
                              (\i -> "(\\hsc_ptr -> peekByteOff hsc_ptr " ++ show i ++ ")") >> return False
        "poke" -> outputConst ("offsetof(" ++ value ++ ")")
@@ -271,19 +272,21 @@ checkValidity input = do
     flags <- testGetFlags
     let test = outTemplateHeaderCProg (cTemplate config) ++
                concatMap outFlagHeaderCProg flags ++
-               concatMap (uncurry outValidityCheck) (zip input [0..])
+               concatMap (uncurry (outValidityCheck (cViaAsm config))) (zip input [0..])
     testLog ("checking for compilation errors") $ do
         success <- makeTest2 (".c",".o") $ \(cFile,oFile) -> do
             liftTestIO $ writeBinaryFile cFile test
             compiler <- testGetCompiler
             runCompiler compiler
-                        (["-c",cFile,"-o",oFile]++[f | CompFlag f <- flags])
+                        (["-S" | cViaAsm config ]++
+                         ["-c",cFile,"-o",oFile]++
+                         [f | CompFlag f <- flags])
                         Nothing
         when (not success) $ testFail' "compilation failed"
     testLog' "compilation is error-free"
 
-outValidityCheck :: Token -> Int -> String
-outValidityCheck s@(Special pos key value) uniq =
+outValidityCheck :: Bool -> Token -> Int -> String
+outValidityCheck viaAsm s@(Special pos key value) uniq =
     case key of
        "const" -> checkValidConst value
        "offset" -> checkValidConst ("offsetof(" ++ value ++ ")")
@@ -296,20 +299,26 @@ outValidityCheck s@(Special pos key value) uniq =
        "enum" -> checkValidEnum
        _ -> outHeaderCProg' s
     where
-    checkValidConst value' = "void _hsc2hs_test" ++ show uniq ++ "()\n{\n" ++ validConstTest value' ++ "}\n";
+    checkValidConst value' = if viaAsm
+                             then validConstTestViaAsm (show uniq) value' ++ "\n"
+                             else "void _hsc2hs_test" ++ show uniq ++ "()\n{\n" ++ validConstTest value' ++ "}\n"
     checkValidType = "void _hsc2hs_test" ++ show uniq ++ "()\n{\n" ++ outCLine pos ++ "    (void)(" ++ value ++ ")1;\n}\n";
     checkValidEnum =
         case parseEnum value of
             Nothing -> ""
+            Just (_,_,enums) | viaAsm ->
+                concatMap (\(hName,cName) -> validConstTestViaAsm (fromMaybe "noKey" (ATT.trim `fmap` hName) ++ show uniq) cName) enums
             Just (_,_,enums) ->
                 "void _hsc2hs_test" ++ show uniq ++ "()\n{\n" ++
                 concatMap (\(_,cName) -> validConstTest cName) enums ++
                 "}\n"
 
     -- we want this to fail if the value is syntactically invalid or isn't a constant
-    validConstTest value' = outCLine pos ++ "    {\n        static int test_array[(" ++ value' ++ ") > 0 ? 2 : 1];\n        (void)test_array;\n    }\n";
+    validConstTest value' = outCLine pos ++ "    {\n        static int test_array[(" ++ value' ++ ") > 0 ? 2 : 1];\n        (void)test_array;\n    }\n"
+    validConstTestViaAsm name value' = outCLine pos ++ "\nextern long long _hsc2hs_test_" ++ name ++";\n"
+                                                    ++ "long long _hsc2hs_test_" ++ name ++ " = (" ++ value' ++ ");\n"
 
-outValidityCheck (Text _ _) _ = ""
+outValidityCheck _ (Text _ _) _ = ""
 
 -- Skips over some #if or other conditional that we found to be false.
 -- I.e. the argument should be a zipper whose cursor is one past the #if,
@@ -365,13 +374,16 @@ cShowCmpTest (LessOrEqual x) = "<=" ++ cShowInteger x
 -- Determines the value of SOME_VALUE using binary search; this
 -- is a trick which is cribbed from autoconf's AC_COMPUTE_INT.
 computeConst :: ZCursor Token -> String -> TestMonad Integer
-computeConst zOrig@(ZCursor (Special pos _ _) _ _) value = do
+computeConst zOrig@(ZCursor (Special pos _ _) _ _) value =
     testLogAtPos pos ("computing " ++ value) $ do
-        nonNegative <- compareConst z (GreaterOrEqual (Signed 0))
-        integral <- checkValueIsIntegral z nonNegative
-        when (not integral) $ testFail pos $ value ++ " is not an integer"
-        (lower,upper) <- bracketBounds z nonNegative
-        int <- binarySearch z nonNegative lower upper
+        config <- testGetConfig
+        int <- case cViaAsm config of
+                 True -> runCompileAsmIntegerTest z
+                 False -> do nonNegative <- compareConst z (GreaterOrEqual (Signed 0))
+                             integral <- checkValueIsIntegral z nonNegative
+                             when (not integral) $ testFail pos $ value ++ " is not an integer"
+                             (lower,upper) <- bracketBounds z nonNegative
+                             binarySearch z nonNegative lower upper
         testLog' $ "result: " ++ show int
         return int
     where -- replace the Special's value with the provided value; e.g. the special
@@ -560,6 +572,39 @@ runCompileBooleanTest (ZCursor s above below) booleanTest = do
                (concatMap outHeaderCProg' below)
     runCompileTest test
 
+runCompileAsmIntegerTest :: ZCursor Token -> TestMonad Integer
+runCompileAsmIntegerTest (ZCursor s@(Special _ _ value) above below) = do
+    config <- testGetConfig
+    flags <- testGetFlags
+    let key = "___hsc2hs_int_test"
+    let test = -- all the surrounding code
+               outTemplateHeaderCProg (cTemplate config) ++
+               (concatMap outFlagHeaderCProg flags) ++
+               (concatMap outHeaderCProg' above) ++
+               outHeaderCProg' s ++
+               -- the test
+               "extern unsigned long long ___hsc2hs_BOM___;\n" ++
+               "unsigned long long ___hsc2hs_BOM___ = 0x100000000;\n" ++
+               "extern unsigned long long " ++ key ++ "___hsc2hs_sign___;\n" ++
+               "unsigned long long " ++ key ++ "___hsc2hs_sign___ = (" ++ value ++ ") < 0;\n" ++
+               "extern unsigned long long " ++ key ++ ";\n" ++
+               "unsigned long long " ++ key ++ " = (" ++ value ++ ");\n"++
+               (concatMap outHeaderCProg' below)
+    runCompileExtract key test
+runCompileAsmIntegerTest _ = error "runCompileAsmIntegerTestargument isn't a Special"
+
+runCompileExtract :: String -> String -> TestMonad Integer
+runCompileExtract k testStr = do
+    makeTest3 (".c", ".s", ".txt") $ \(cFile, sFile, stdout) -> do
+      liftTestIO $ writeBinaryFile cFile testStr
+      flags <- testGetFlags
+      compiler <- testGetCompiler
+      _ <- runCompiler compiler
+                  (["-S", "-c", cFile, "-o", sFile] ++ [f | CompFlag f <- flags])
+                  (Just stdout)
+      asm <- liftTestIO $ ATT.parse sFile
+      return $ fromMaybe (error "Failed to extract integer") (ATT.lookupInteger k asm)
+
 runCompileTest :: String -> TestMonad Bool
 runCompileTest testStr = do
     makeTest3 (".c", ".o",".txt") $ \(cFile,oFile,stdout) -> do
diff --git a/Flags.hs b/Flags.hs
index b4366729c287a5379a63dc98b292f04a4fc64535..d621fd13c661cce3f9bd371494b19ea708279a23 100644
--- a/Flags.hs
+++ b/Flags.hs
@@ -18,6 +18,7 @@ data ConfigM m = Config {
                      cKeepFiles :: Bool,
                      cNoCompile :: Bool,
                      cCrossCompile :: Bool,
+                     cViaAsm :: Bool,
                      cCrossSafe :: Bool,
                      cColumn :: Bool,
                      cVerbose :: Bool,
@@ -41,6 +42,7 @@ emptyMode = UseConfig $ Config {
                             cKeepFiles    = False,
                             cNoCompile    = False,
                             cCrossCompile = False,
+                            cViaAsm       = False,
                             cCrossSafe    = False,
                             cColumn       = False,
                             cVerbose      = False,
@@ -79,6 +81,8 @@ options = [
         "stop after writing *_hsc_make.c",
     Option ['x'] ["cross-compile"] (NoArg (withConfig $ setCrossCompile True))
         "activate cross-compilation mode",
+    Option [] ["via-asm"] (NoArg (withConfig $ setViaAsm True))
+        "use a crude asm parser to compute constants when cross compiling",
     Option [] ["cross-safe"] (NoArg (withConfig $ setCrossSafe True))
         "restrict .hsc directives to those supported by --cross-compile",
     Option ['k'] ["keep-files"] (NoArg (withConfig $ setKeepFiles True))
@@ -124,6 +128,9 @@ setNoCompile b c = c { cNoCompile = b }
 setCrossCompile :: Bool -> ConfigM Maybe -> ConfigM Maybe
 setCrossCompile b c = c { cCrossCompile = b }
 
+setViaAsm :: Bool -> ConfigM Maybe -> ConfigM Maybe
+setViaAsm b c = c { cViaAsm = b }
+
 setCrossSafe :: Bool -> ConfigM Maybe -> ConfigM Maybe
 setCrossSafe b c = c { cCrossSafe = b }
 
diff --git a/Main.hs b/Main.hs
index fad7aac5fa0c04971fe3352268fcaac3962ed40d..7f4eade2a643188e602fb98387d195998673fa8c 100644
--- a/Main.hs
+++ b/Main.hs
@@ -109,6 +109,7 @@ processFiles configM files usage = do
                      cKeepFiles    = cKeepFiles configM,
                      cNoCompile    = cNoCompile configM,
                      cCrossCompile = cCrossCompile configM,
+                     cViaAsm       = cViaAsm configM,
                      cCrossSafe    = cCrossSafe configM,
                      cColumn       = cColumn configM,
                      cVerbose      = cVerbose configM,
diff --git a/Spec.hs b/Spec.hs
new file mode 100644
index 0000000000000000000000000000000000000000..973e92c91434d655e5224274974264e8e8dfca08
--- /dev/null
+++ b/Spec.hs
@@ -0,0 +1,46 @@
+module Main where
+
+import Test.Tasty.Hspec
+import ATTParser
+import Control.Monad (forM_)
+
+main :: IO ()
+main = hspec $ do
+  describe "asm parser" $ do
+    forM_ [("x86_64 linux", "test/asm/x86_64-linux.s")
+          ,("x86_64 macos", "test/asm/x86_64-mac.s")
+          ,("x86_64 mingw", "test/asm/x86_64-mingw32.s")
+          ,("aarch64 ios",  "test/asm/aarch64-ios.s")
+          ,("aarch64 linux","test/asm/aarch64.s")]
+      $ \(d, f) ->do
+      context d $ do
+        x <- runIO $ parse f
+
+        it "x should be 1" $ do
+          lookupInteger "x" x `shouldBe` (Just 1)
+        it "z should be 0xffffffffffffffff" $ do
+          lookupInteger "y" x `shouldBe` (Just 0xffffffffffffffff)
+        it "z should be -1" $ do
+          lookupInteger "z" x `shouldBe` (Just (-1))
+
+        it "t should be \"Hello World\\\"\\n\\0\"" $ do
+          lookupString "t" x `shouldBe` (Just "Hello World\" 12345\0")
+
+    forM_ [("arm ios",      "test/asm/arm-ios.s")
+          ,("arm linux",    "test/asm/arm.s")
+          ,("x86 linux",    "test/asm/x86-linux.s")]
+      $ \(d, f) ->do
+      context d $ do
+        x <- runIO $ parse f
+
+        it "x should be 1" $ do
+          lookupInteger "x" x `shouldBe` (Just 1)
+        it "z should be 0xffffffff" $ do
+          lookupInteger "y" x `shouldBe` (Just 0xffffffff)
+        it "z should be -1" $ do
+          lookupInteger "z" x `shouldBe` (Just (-1))
+
+        it "t should be \"Hello World\\\"\\n\\0\"" $ do
+          lookupString "t" x `shouldBe` (Just "Hello World\" 12345\0")
+
+
diff --git a/hsc2hs.cabal b/hsc2hs.cabal
index 99d5072c953082d8fb49c6499771a0f5b640476d..804acf7fed98b7fed8b38e57d175218e833d228c 100644
--- a/hsc2hs.cabal
+++ b/hsc2hs.cabal
@@ -45,6 +45,7 @@ Executable hsc2hs
         DirectCodegen
         Flags
         HSCParser
+        ATTParser
         UtilsCodegen
         Paths_hsc2hs
 
@@ -58,3 +59,13 @@ Executable hsc2hs
     if flag(in-ghc-tree)
        cpp-options: -DIN_GHC_TREE
 
+test-suite spec
+  main-is:           Spec.hs
+  hs-source-dirs:    .
+  other-modules:     ATTParser
+  ghc-options:       -Wall -threaded
+  type:              exitcode-stdio-1.0
+  build-depends:       base
+                     , tasty
+                     , tasty-hspec
+  default-language: Haskell2010
\ No newline at end of file
diff --git a/test/asm/Makefile b/test/asm/Makefile
new file mode 100644
index 0000000000000000000000000000000000000000..91d2fcf50326447a42012c9633c31859ca6a23e4
--- /dev/null
+++ b/test/asm/Makefile
@@ -0,0 +1,10 @@
+all:
+	clang -target arm-linux-gnueabihf -S -c tmp.c -o arm.s
+	clang -target aarch64-linux-gnueabihf -S -c tmp.c -o aarch64.s
+	clang -target arm64-apple-ios -S -c tmp.c -o aarch64-ios.s
+	clang -target armv7-apple-ios -S -c tmp.c -o arm-ios.s 
+	x86_64-w64-mingw32-gcc -S -c tmp.c -o x86_64-mingw32.s
+	clang -target i386-unknown-linux -S -c tmp.c -o x86-linux.s
+	clang -target x86_64-apple-macos -S -c tmp.c -o x86_64-mac.s
+	clang -target i386-unknown-linux -S -c tmp.c -o x86-linux.s
+	clang -target x86_64-unknown-linux -S -c tmp.c -o x86_64-linux.s
diff --git a/test/asm/aarch64-ios.s b/test/asm/aarch64-ios.s
new file mode 100644
index 0000000000000000000000000000000000000000..2adeeef3ec86873bbca60a6c180e476f2ff8690d
--- /dev/null
+++ b/test/asm/aarch64-ios.s
@@ -0,0 +1,44 @@
+	.section	__TEXT,__text,regular,pure_instructions
+	.ios_version_min 7, 0
+	.section	__DATA,__data
+	.globl	____hsc2hs_BOM___       ; @___hsc2hs_BOM___
+	.p2align	3
+____hsc2hs_BOM___:
+	.quad	4294967296              ; 0x100000000
+
+	.globl	_x___hsc2hs_sign___     ; @x___hsc2hs_sign___
+.zerofill __DATA,__common,_x___hsc2hs_sign___,8,3
+	.globl	_x                      ; @x
+	.p2align	3
+_x:
+	.quad	1                       ; 0x1
+
+	.globl	_y___hsc2hs_sign___     ; @y___hsc2hs_sign___
+.zerofill __DATA,__common,_y___hsc2hs_sign___,8,3
+	.globl	_y                      ; @y
+	.p2align	3
+_y:
+	.quad	-1                      ; 0xffffffffffffffff
+
+	.globl	_z___hsc2hs_sign___     ; @z___hsc2hs_sign___
+	.p2align	3
+_z___hsc2hs_sign___:
+	.quad	1                       ; 0x1
+
+	.globl	_z                      ; @z
+	.p2align	3
+_z:
+	.quad	-1                      ; 0xffffffffffffffff
+
+	.section	__TEXT,__cstring,cstring_literals
+l_.str:                                 ; @.str
+	.asciz	"Hello World\" 12345"
+
+	.section	__DATA,__data
+	.globl	_t                      ; @t
+	.p2align	3
+_t:
+	.quad	l_.str
+
+
+.subsections_via_symbols
diff --git a/test/asm/aarch64.s b/test/asm/aarch64.s
new file mode 100644
index 0000000000000000000000000000000000000000..227c8339fbc95378d0ccc3433ea8b496fd7d7512
--- /dev/null
+++ b/test/asm/aarch64.s
@@ -0,0 +1,73 @@
+	.text
+	.file	"tmp.c"
+	.type	___hsc2hs_BOM___,@object // @___hsc2hs_BOM___
+	.data
+	.globl	___hsc2hs_BOM___
+	.p2align	3
+___hsc2hs_BOM___:
+	.xword	4294967296              // 0x100000000
+	.size	___hsc2hs_BOM___, 8
+
+	.type	x___hsc2hs_sign___,@object // @x___hsc2hs_sign___
+	.bss
+	.globl	x___hsc2hs_sign___
+	.p2align	3
+x___hsc2hs_sign___:
+	.xword	0                       // 0x0
+	.size	x___hsc2hs_sign___, 8
+
+	.type	x,@object               // @x
+	.data
+	.globl	x
+	.p2align	3
+x:
+	.xword	1                       // 0x1
+	.size	x, 8
+
+	.type	y___hsc2hs_sign___,@object // @y___hsc2hs_sign___
+	.bss
+	.globl	y___hsc2hs_sign___
+	.p2align	3
+y___hsc2hs_sign___:
+	.xword	0                       // 0x0
+	.size	y___hsc2hs_sign___, 8
+
+	.type	y,@object               // @y
+	.data
+	.globl	y
+	.p2align	3
+y:
+	.xword	-1                      // 0xffffffffffffffff
+	.size	y, 8
+
+	.type	z___hsc2hs_sign___,@object // @z___hsc2hs_sign___
+	.globl	z___hsc2hs_sign___
+	.p2align	3
+z___hsc2hs_sign___:
+	.xword	1                       // 0x1
+	.size	z___hsc2hs_sign___, 8
+
+	.type	z,@object               // @z
+	.globl	z
+	.p2align	3
+z:
+	.xword	-1                      // 0xffffffffffffffff
+	.size	z, 8
+
+	.type	.L.str,@object          // @.str
+	.section	.rodata.str1.1,"aMS",@progbits,1
+.L.str:
+	.asciz	"Hello World\" 12345"
+	.size	.L.str, 19
+
+	.type	t,@object               // @t
+	.data
+	.globl	t
+	.p2align	3
+t:
+	.xword	.L.str
+	.size	t, 8
+
+
+	.ident	"clang version 5.0.1 (tags/RELEASE_501/final)"
+	.section	".note.GNU-stack","",@progbits
diff --git a/test/asm/arm-ios.s b/test/asm/arm-ios.s
new file mode 100644
index 0000000000000000000000000000000000000000..56b18789c964ce5649223d18ed1a34033e85f6f9
--- /dev/null
+++ b/test/asm/arm-ios.s
@@ -0,0 +1,50 @@
+	.section	__TEXT,__text,regular,pure_instructions
+	.ios_version_min 5, 0
+	.syntax unified
+	.section	__DATA,__data
+	.globl	____hsc2hs_BOM___       @ @___hsc2hs_BOM___
+	.p2align	3
+____hsc2hs_BOM___:
+	.long	0                       @ 0x100000000
+	.long	1
+
+	.globl	_x___hsc2hs_sign___     @ @x___hsc2hs_sign___
+.zerofill __DATA,__common,_x___hsc2hs_sign___,8,3
+	.globl	_x                      @ @x
+	.p2align	3
+_x:
+	.long	1                       @ 0x1
+	.long	0
+
+	.globl	_y___hsc2hs_sign___     @ @y___hsc2hs_sign___
+.zerofill __DATA,__common,_y___hsc2hs_sign___,8,3
+	.globl	_y                      @ @y
+	.p2align	3
+_y:
+	.long	4294967295              @ 0xffffffff
+	.long	0
+
+	.globl	_z___hsc2hs_sign___     @ @z___hsc2hs_sign___
+	.p2align	3
+_z___hsc2hs_sign___:
+	.long	1                       @ 0x1
+	.long	0
+
+	.globl	_z                      @ @z
+	.p2align	3
+_z:
+	.long	4294967295              @ 0xffffffffffffffff
+	.long	4294967295
+
+	.section	__TEXT,__cstring,cstring_literals
+L_.str:                                 @ @.str
+	.asciz	"Hello World\" 12345"
+
+	.section	__DATA,__data
+	.globl	_t                      @ @t
+	.p2align	2
+_t:
+	.long	L_.str
+
+
+.subsections_via_symbols
diff --git a/test/asm/arm.s b/test/asm/arm.s
new file mode 100644
index 0000000000000000000000000000000000000000..936ef7c40c7d02594b6a33e03f840f2b6869720d
--- /dev/null
+++ b/test/asm/arm.s
@@ -0,0 +1,100 @@
+	.text
+	.syntax unified
+	.eabi_attribute	67, "2.09"	@ Tag_conformance
+	.cpu	arm1176jzf-s
+	.eabi_attribute	6, 6	@ Tag_CPU_arch
+	.eabi_attribute	8, 1	@ Tag_ARM_ISA_use
+	.eabi_attribute	9, 1	@ Tag_THUMB_ISA_use
+	.fpu	vfpv2
+	.eabi_attribute	34, 0	@ Tag_CPU_unaligned_access
+	.eabi_attribute	68, 1	@ Tag_Virtualization_use
+	.eabi_attribute	17, 1	@ Tag_ABI_PCS_GOT_use
+	.eabi_attribute	20, 2	@ Tag_ABI_FP_denormal
+	.eabi_attribute	21, 0	@ Tag_ABI_FP_exceptions
+	.eabi_attribute	23, 3	@ Tag_ABI_FP_number_model
+	.eabi_attribute	24, 1	@ Tag_ABI_align_needed
+	.eabi_attribute	25, 1	@ Tag_ABI_align_preserved
+	.eabi_attribute	28, 1	@ Tag_ABI_VFP_args
+	.eabi_attribute	38, 1	@ Tag_ABI_FP_16bit_format
+	.eabi_attribute	18, 4	@ Tag_ABI_PCS_wchar_t
+	.eabi_attribute	26, 2	@ Tag_ABI_enum_size
+	.eabi_attribute	14, 0	@ Tag_ABI_PCS_R9_use
+	.file	"tmp.c"
+	.type	___hsc2hs_BOM___,%object @ @___hsc2hs_BOM___
+	.data
+	.globl	___hsc2hs_BOM___
+	.p2align	3
+___hsc2hs_BOM___:
+	.long	0                       @ 0x100000000
+	.long	1
+	.size	___hsc2hs_BOM___, 8
+
+	.type	x___hsc2hs_sign___,%object @ @x___hsc2hs_sign___
+	.bss
+	.globl	x___hsc2hs_sign___
+	.p2align	3
+x___hsc2hs_sign___:
+	.long	0                       @ 0x0
+	.long	0
+	.size	x___hsc2hs_sign___, 8
+
+	.type	x,%object               @ @x
+	.data
+	.globl	x
+	.p2align	3
+x:
+	.long	1                       @ 0x1
+	.long	0
+	.size	x, 8
+
+	.type	y___hsc2hs_sign___,%object @ @y___hsc2hs_sign___
+	.bss
+	.globl	y___hsc2hs_sign___
+	.p2align	3
+y___hsc2hs_sign___:
+	.long	0                       @ 0x0
+	.long	0
+	.size	y___hsc2hs_sign___, 8
+
+	.type	y,%object               @ @y
+	.data
+	.globl	y
+	.p2align	3
+y:
+	.long	4294967295              @ 0xffffffff
+	.long	0
+	.size	y, 8
+
+	.type	z___hsc2hs_sign___,%object @ @z___hsc2hs_sign___
+	.globl	z___hsc2hs_sign___
+	.p2align	3
+z___hsc2hs_sign___:
+	.long	1                       @ 0x1
+	.long	0
+	.size	z___hsc2hs_sign___, 8
+
+	.type	z,%object               @ @z
+	.globl	z
+	.p2align	3
+z:
+	.long	4294967295              @ 0xffffffffffffffff
+	.long	4294967295
+	.size	z, 8
+
+	.type	.L.str,%object          @ @.str
+	.section	.rodata.str1.1,"aMS",%progbits,1
+.L.str:
+	.asciz	"Hello World\" 12345"
+	.size	.L.str, 19
+
+	.type	t,%object               @ @t
+	.data
+	.globl	t
+	.p2align	2
+t:
+	.long	.L.str
+	.size	t, 4
+
+
+	.ident	"clang version 5.0.1 (tags/RELEASE_501/final)"
+	.section	".note.GNU-stack","",%progbits
diff --git a/test/asm/tmp.c b/test/asm/tmp.c
new file mode 100644
index 0000000000000000000000000000000000000000..f08f67708e0f97608a1e7c3c4233836af3600e4e
--- /dev/null
+++ b/test/asm/tmp.c
@@ -0,0 +1,27 @@
+struct S { int unused; };
+
+#define X 1
+#define Y -1
+
+// if BOM is 1, we end up with two 32bit integers
+// where the upper 4 byte ended up in the lower 4.
+extern unsigned long long ___hsc2hs_BOM___;
+unsigned long long ___hsc2hs_BOM___ = 0x100000000;
+
+extern unsigned long long x___hsc2hs_sign___;
+extern unsigned long long x;
+unsigned long long x___hsc2hs_sign___ = ((struct S *)X) < 0;
+unsigned long long x = (unsigned long long)((struct S *)X);
+
+extern unsigned long long y___hsc2hs_sign___;
+extern unsigned long long y;
+unsigned long long y___hsc2hs_sign___ = ((struct S *)Y) < 0;
+unsigned long long y = (unsigned long long)((struct S *)Y);
+
+extern unsigned long long z___hsc2hs_sign___;
+extern unsigned long long z;
+unsigned long long z___hsc2hs_sign___ = Y < 0;
+unsigned long long z = (unsigned long long)Y;
+
+extern char * t;
+char * t = "Hello World\" 12345";
diff --git a/test/asm/x86-linux.s b/test/asm/x86-linux.s
new file mode 100644
index 0000000000000000000000000000000000000000..8808d41809eebb62b87b3fd92c1d3f6c3c19078a
--- /dev/null
+++ b/test/asm/x86-linux.s
@@ -0,0 +1,73 @@
+	.text
+	.file	"tmp.c"
+	.type	___hsc2hs_BOM___,@object # @___hsc2hs_BOM___
+	.data
+	.globl	___hsc2hs_BOM___
+	.p2align	3
+___hsc2hs_BOM___:
+	.quad	4294967296              # 0x100000000
+	.size	___hsc2hs_BOM___, 8
+
+	.type	x___hsc2hs_sign___,@object # @x___hsc2hs_sign___
+	.bss
+	.globl	x___hsc2hs_sign___
+	.p2align	3
+x___hsc2hs_sign___:
+	.quad	0                       # 0x0
+	.size	x___hsc2hs_sign___, 8
+
+	.type	x,@object               # @x
+	.data
+	.globl	x
+	.p2align	3
+x:
+	.quad	1                       # 0x1
+	.size	x, 8
+
+	.type	y___hsc2hs_sign___,@object # @y___hsc2hs_sign___
+	.bss
+	.globl	y___hsc2hs_sign___
+	.p2align	3
+y___hsc2hs_sign___:
+	.quad	0                       # 0x0
+	.size	y___hsc2hs_sign___, 8
+
+	.type	y,@object               # @y
+	.data
+	.globl	y
+	.p2align	3
+y:
+	.quad	4294967295              # 0xffffffff
+	.size	y, 8
+
+	.type	z___hsc2hs_sign___,@object # @z___hsc2hs_sign___
+	.globl	z___hsc2hs_sign___
+	.p2align	3
+z___hsc2hs_sign___:
+	.quad	1                       # 0x1
+	.size	z___hsc2hs_sign___, 8
+
+	.type	z,@object               # @z
+	.globl	z
+	.p2align	3
+z:
+	.quad	-1                      # 0xffffffffffffffff
+	.size	z, 8
+
+	.type	.L.str,@object          # @.str
+	.section	.rodata.str1.1,"aMS",@progbits,1
+.L.str:
+	.asciz	"Hello World\" 12345"
+	.size	.L.str, 19
+
+	.type	t,@object               # @t
+	.data
+	.globl	t
+	.p2align	2
+t:
+	.long	.L.str
+	.size	t, 4
+
+
+	.ident	"clang version 5.0.1 (tags/RELEASE_501/final)"
+	.section	".note.GNU-stack","",@progbits
diff --git a/test/asm/x86_64-linux.s b/test/asm/x86_64-linux.s
new file mode 100644
index 0000000000000000000000000000000000000000..351196ec59fe0d17f016545eec3c8b6d6ae36c0f
--- /dev/null
+++ b/test/asm/x86_64-linux.s
@@ -0,0 +1,73 @@
+	.text
+	.file	"tmp.c"
+	.type	___hsc2hs_BOM___,@object # @___hsc2hs_BOM___
+	.data
+	.globl	___hsc2hs_BOM___
+	.p2align	3
+___hsc2hs_BOM___:
+	.quad	4294967296              # 0x100000000
+	.size	___hsc2hs_BOM___, 8
+
+	.type	x___hsc2hs_sign___,@object # @x___hsc2hs_sign___
+	.bss
+	.globl	x___hsc2hs_sign___
+	.p2align	3
+x___hsc2hs_sign___:
+	.quad	0                       # 0x0
+	.size	x___hsc2hs_sign___, 8
+
+	.type	x,@object               # @x
+	.data
+	.globl	x
+	.p2align	3
+x:
+	.quad	1                       # 0x1
+	.size	x, 8
+
+	.type	y___hsc2hs_sign___,@object # @y___hsc2hs_sign___
+	.bss
+	.globl	y___hsc2hs_sign___
+	.p2align	3
+y___hsc2hs_sign___:
+	.quad	0                       # 0x0
+	.size	y___hsc2hs_sign___, 8
+
+	.type	y,@object               # @y
+	.data
+	.globl	y
+	.p2align	3
+y:
+	.quad	-1                      # 0xffffffffffffffff
+	.size	y, 8
+
+	.type	z___hsc2hs_sign___,@object # @z___hsc2hs_sign___
+	.globl	z___hsc2hs_sign___
+	.p2align	3
+z___hsc2hs_sign___:
+	.quad	1                       # 0x1
+	.size	z___hsc2hs_sign___, 8
+
+	.type	z,@object               # @z
+	.globl	z
+	.p2align	3
+z:
+	.quad	-1                      # 0xffffffffffffffff
+	.size	z, 8
+
+	.type	.L.str,@object          # @.str
+	.section	.rodata.str1.1,"aMS",@progbits,1
+.L.str:
+	.asciz	"Hello World\" 12345"
+	.size	.L.str, 19
+
+	.type	t,@object               # @t
+	.data
+	.globl	t
+	.p2align	3
+t:
+	.quad	.L.str
+	.size	t, 8
+
+
+	.ident	"clang version 5.0.1 (tags/RELEASE_501/final)"
+	.section	".note.GNU-stack","",@progbits
diff --git a/test/asm/x86_64-mac.s b/test/asm/x86_64-mac.s
new file mode 100644
index 0000000000000000000000000000000000000000..88a0e08080a8c00c4f1aca52c1dc44c596ba05e3
--- /dev/null
+++ b/test/asm/x86_64-mac.s
@@ -0,0 +1,44 @@
+	.section	__TEXT,__text,regular,pure_instructions
+	.macosx_version_min 10, 4
+	.section	__DATA,__data
+	.globl	____hsc2hs_BOM___       ## @___hsc2hs_BOM___
+	.p2align	3
+____hsc2hs_BOM___:
+	.quad	4294967296              ## 0x100000000
+
+	.globl	_x___hsc2hs_sign___     ## @x___hsc2hs_sign___
+.zerofill __DATA,__common,_x___hsc2hs_sign___,8,3
+	.globl	_x                      ## @x
+	.p2align	3
+_x:
+	.quad	1                       ## 0x1
+
+	.globl	_y___hsc2hs_sign___     ## @y___hsc2hs_sign___
+.zerofill __DATA,__common,_y___hsc2hs_sign___,8,3
+	.globl	_y                      ## @y
+	.p2align	3
+_y:
+	.quad	-1                      ## 0xffffffffffffffff
+
+	.globl	_z___hsc2hs_sign___     ## @z___hsc2hs_sign___
+	.p2align	3
+_z___hsc2hs_sign___:
+	.quad	1                       ## 0x1
+
+	.globl	_z                      ## @z
+	.p2align	3
+_z:
+	.quad	-1                      ## 0xffffffffffffffff
+
+	.section	__TEXT,__cstring,cstring_literals
+L_.str:                                 ## @.str
+	.asciz	"Hello World\" 12345"
+
+	.section	__DATA,__data
+	.globl	_t                      ## @t
+	.p2align	3
+_t:
+	.quad	L_.str
+
+
+.subsections_via_symbols
diff --git a/test/asm/x86_64-mingw32.s b/test/asm/x86_64-mingw32.s
new file mode 100644
index 0000000000000000000000000000000000000000..031061da36f1f7c17c415478126a16f2eecbbf85
--- /dev/null
+++ b/test/asm/x86_64-mingw32.s
@@ -0,0 +1,44 @@
+	.file	"tmp.c"
+	.text
+	.globl	___hsc2hs_BOM___
+	.data
+	.align 8
+___hsc2hs_BOM___:
+	.quad	4294967296
+	.globl	x___hsc2hs_sign___
+	.bss
+	.align 8
+x___hsc2hs_sign___:
+	.space 8
+	.globl	x
+	.data
+	.align 8
+x:
+	.quad	1
+	.globl	y___hsc2hs_sign___
+	.bss
+	.align 8
+y___hsc2hs_sign___:
+	.space 8
+	.globl	y
+	.data
+	.align 8
+y:
+	.quad	-1
+	.globl	z___hsc2hs_sign___
+	.align 8
+z___hsc2hs_sign___:
+	.quad	1
+	.globl	z
+	.align 8
+z:
+	.quad	-1
+	.globl	t
+	.section .rdata,"dr"
+.LC0:
+	.ascii "Hello World\" 12345\0"
+	.data
+	.align 8
+t:
+	.quad	.LC0
+	.ident	"GCC: (GNU) 7.3.0"