compiler: check arch-dependent implementation

Array lengths and indices are kept 32-bit no matter what arch is chosen;
pointer types and word sizes are in accordance with the arch chosen.
[skip bamboo]
diff --git a/cogent/src/Cogent/Common/Syntax.hs b/cogent/src/Cogent/Common/Syntax.hs
index e00183d..11118e8 100644
--- a/cogent/src/Cogent/Common/Syntax.hs
+++ b/cogent/src/Cogent/Common/Syntax.hs
@@ -43,7 +43,7 @@
 unsafeCoreFunName = CoreFunName
 
 type FieldIndex = Int
-type ArrayIndex = Word32
+type ArrayIndex = Word32  -- It actually can be large on 64-bit machines, but for now we just leave them Word32 for simplicity / zilinc
 type ArraySize  = Word32
 
 type Size = Integer -- Not sure why quickcheck tests infinite loop if Size = Word32.
diff --git a/cogent/src/Cogent/Common/Types.hs b/cogent/src/Cogent/Common/Types.hs
index 58025fb..1a344e9 100644
--- a/cogent/src/Cogent/Common/Types.hs
+++ b/cogent/src/Cogent/Common/Types.hs
@@ -19,6 +19,7 @@
 module Cogent.Common.Types where
 
 import Cogent.Common.Syntax
+import Cogent.Compiler
 import Data.Binary (Binary)
 import Data.Data
 import Data.Map as M
@@ -67,6 +68,20 @@
 
 instance Binary PrimInt
 
+machineWordType :: PrimInt
+machineWordType = case __cogent_arch of
+                    ARM32  -> U32
+                    X86_32 -> U32
+                    X86_64 -> U64
+
+primIntSizeBits :: PrimInt -> Size
+primIntSizeBits U8      = 8
+primIntSizeBits U16     = 16
+primIntSizeBits U32     = 32
+primIntSizeBits U64     = 64
+primIntSizeBits Boolean = 8
+
+
 isSubtypePrim :: PrimInt -> PrimInt -> Bool
 isSubtypePrim U8  U8  = True
 isSubtypePrim U8  U16 = True
diff --git a/cogent/src/Cogent/Dargent/CodeGen.hs b/cogent/src/Cogent/Dargent/CodeGen.hs
index ea89658..c3d5f3f 100644
--- a/cogent/src/Cogent/Dargent/CodeGen.hs
+++ b/cogent/src/Cogent/Dargent/CodeGen.hs
@@ -26,6 +26,7 @@
   , __todo
   , __assert_
   , Architecture (..)
+  , __cogent_arch
   )
 import Cogent.Core (Type (..))
 import Cogent.Dargent.Allocation
@@ -883,7 +884,7 @@
 
 type CogentType = Type 'Zero VarName
 
-intTypeForPointer = case architecture of
+intTypeForPointer = case __cogent_arch of
   X86_64 -> unsignedLongType
   X86_32 -> unsignedIntType
   ARM32  -> unsignedIntType
diff --git a/cogent/src/Cogent/Dargent/Util.hs b/cogent/src/Cogent/Dargent/Util.hs
index 4138dd8..fae2b31 100644
--- a/cogent/src/Cogent/Dargent/Util.hs
+++ b/cogent/src/Cogent/Dargent/Util.hs
@@ -18,27 +18,12 @@
 
 import Text.Parsec.Pos (SourcePos)
 
-wordSizeBits :: Size
-wordSizeBits = case architecture of
-                 X86_32 -> 32
-                 X86_64 -> 64
-                 ARM32  -> 32
-
 byteSizeBits :: Size
 byteSizeBits = 8
 
-architecture :: Architecture
-architecture = __cogent_arch
-
-pointerSizeBits :: Size
-pointerSizeBits = wordSizeBits
-
-primIntSizeBits :: PrimInt -> Size
-primIntSizeBits U8      = 8
-primIntSizeBits U16     = 16
-primIntSizeBits U32     = 32
-primIntSizeBits U64     = 64
-primIntSizeBits Boolean = 8
+pointerSizeBits, wordSizeBits :: Size
+pointerSizeBits = primIntSizeBits machineWordType
+wordSizeBits    = primIntSizeBits machineWordType
 
 
 -- When transforming (Offset repExpr offsetSize),
diff --git a/cogent/src/Cogent/Inference.hs b/cogent/src/Cogent/Inference.hs
index cf115c9..59a75fa 100644
--- a/cogent/src/Cogent/Inference.hs
+++ b/cogent/src/Cogent/Inference.hs
@@ -67,7 +67,6 @@
 #if __GLASGOW_HASKELL__ < 709
 import Data.Traversable(traverse)
 #endif
-import Data.Word (Word32)
 import Lens.Micro (_2)
 import Lens.Micro.Mtl (view)
 import Text.PrettyPrint.ANSI.Leijen (Pretty, pretty)
diff --git a/cogent/src/Cogent/LLVM/Compile.hs b/cogent/src/Cogent/LLVM/Compile.hs
index 4a757cd..087dedd 100644
--- a/cogent/src/Cogent/LLVM/Compile.hs
+++ b/cogent/src/Cogent/LLVM/Compile.hs
@@ -1,3 +1,15 @@
+--
+-- Copyright 2020, Data61
+-- Commonwealth Scientific and Industrial Research Organisation (CSIRO)
+-- ABN 41 687 119 230.
+--
+-- This software may be distributed and modified according to the terms of
+-- the GNU General Public License version 2. Note that NO WARRANTY is provided.
+-- See "LICENSE_GPLv2.txt" for details.
+--
+-- @TAG(DATA61_GPL)
+--
+
 {-# LANGUAGE DisambiguateRecordFields #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE OverloadedStrings          #-}
@@ -125,7 +137,7 @@
                        U32 -> 32
                        U64 -> 64
 typeSize (TUnit) = 0
-typeSize _ = 32 -- assuming 32 bit machine
+typeSize _ = fromIntegral $ primIntSizeBits machineWordType
 
 
 -- Name
diff --git a/cogent/src/Cogent/TypeCheck/Solver/Simplify.hs b/cogent/src/Cogent/TypeCheck/Solver/Simplify.hs
index 3d16c16..8ee2d1e 100644
--- a/cogent/src/Cogent/TypeCheck/Solver/Simplify.hs
+++ b/cogent/src/Cogent/TypeCheck/Solver/Simplify.hs
@@ -44,7 +44,6 @@
 import qualified Data.Map as M
 import           Data.Maybe
 import qualified Data.Set as S
-import           Data.Word (Word32)
 import           Lens.Micro
 
 import           Debug.Trace
diff --git a/cogent/src/Cogent/Util.hs b/cogent/src/Cogent/Util.hs
index 49778ba..8b12e1a 100644
--- a/cogent/src/Cogent/Util.hs
+++ b/cogent/src/Cogent/Util.hs
@@ -450,6 +450,7 @@
 u16MAX = 65535
 u32MAX = 4294967296
 
+
 data Bound = GLB | LUB deriving (Eq, Ord)
 
 instance Show Bound where