Skip to content

Commit

Permalink
Use 64-bit arithmetic for computing array offsets.
Browse files Browse the repository at this point in the history
This is not a complete solution to #134, because individual array
dimensions must still fit in a signed 32-bit integer.  However, it
does allow the product of dimensions to be large.
  • Loading branch information
athas committed Jul 31, 2020
1 parent 372e644 commit 1ec4675
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 9 deletions.
2 changes: 1 addition & 1 deletion src/Futhark/CodeGen/Backends/GenericC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1873,7 +1873,7 @@ compileExp = compilePrimExp compileLeaf
return [C.cexp|$id:src[$exp:iexp']|]

compileLeaf (SizeOf t) =
return [C.cexp|(typename int32_t)sizeof($ty:t')|]
return [C.cexp|(typename int64_t)sizeof($ty:t')|]
where t' = primTypeToCType t

-- | Tell me how to compile a @v@, and I'll Compile any @PrimExp v@ for you.
Expand Down
25 changes: 17 additions & 8 deletions src/Futhark/CodeGen/ImpGen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ import Data.Either
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import Data.Maybe
import Data.List (find, sortOn, genericLength)
import Data.List (find, foldl', sortOn, genericLength)

import qualified Futhark.CodeGen.ImpCode as Imp
import Futhark.CodeGen.ImpCode
Expand Down Expand Up @@ -1053,8 +1053,10 @@ fullyIndexArray' (MemLocation mem _ ixfun) indices = do
let (zero_is, is) = splitFromEnd (length ds) indices
in map (const 0) zero_is ++ is
_ -> indices
ixfun64 = fmap (sExt Int64) ixfun
indices64 = fmap (sExt Int64) indices'
return (mem, space,
elements $ IxFun.index ixfun indices')
elements $ IxFun.index ixfun64 indices64)

-- More complicated read/write operations that use index functions.

Expand All @@ -1067,9 +1069,9 @@ copy bt dest destslice src srcslice = do
defaultCopy :: CopyCompiler lore r op
defaultCopy bt dest destslice src srcslice
| Just destoffset <-
IxFun.linearWithOffset (IxFun.slice destIxFun destslice) bt_size,
IxFun.linearWithOffset (IxFun.slice dest_ixfun64 destslice64) bt_size,
Just srcoffset <-
IxFun.linearWithOffset (IxFun.slice srcIxFun srcslice) bt_size = do
IxFun.linearWithOffset (IxFun.slice src_ixfun64 srcslice64) bt_size = do
srcspace <- entryMemSpace <$> lookupMemory srcmem
destspace <- entryMemSpace <$> lookupMemory destmem
if isScalarSpace srcspace || isScalarSpace destspace
Expand All @@ -1082,8 +1084,15 @@ defaultCopy bt dest destslice src srcslice
copyElementWise bt dest destslice src srcslice
where bt_size = primByteSize bt
num_elems = Imp.elements $ product $ sliceDims srcslice
MemLocation destmem _ destIxFun = dest
MemLocation srcmem _ srcIxFun = src

MemLocation destmem _ dest_ixfun = dest
MemLocation srcmem _ src_ixfun = src

dest_ixfun64 = fmap (sExt Int64) dest_ixfun
destslice64 = map (fmap (sExt Int64)) destslice
src_ixfun64 = fmap (sExt Int64) src_ixfun
srcslice64 = map (fmap (sExt Int64)) srcslice

isScalarSpace ScalarSpace{} = True
isScalarSpace _ = False

Expand Down Expand Up @@ -1271,8 +1280,8 @@ compileAlloc pat _ _ =
-- straightforward contiguous format, as an 'Int64' expression.
typeSize :: Type -> Count Bytes Imp.Exp
typeSize t =
Imp.bytes $ sExt Int64 (Imp.LeafExp (Imp.SizeOf $ elemType t) int32) *
product (map (sExt Int64 . toExp' int32) (arrayDims t))
Imp.bytes $ foldl' (*) (Imp.LeafExp (Imp.SizeOf $ elemType t) int64) $
map (sExt Int64 . toExp' int32) (arrayDims t)

--- Building blocks for constructing code.

Expand Down
9 changes: 9 additions & 0 deletions tests/big.fut
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
-- Testing big arrays.
-- ==
-- no_opencl compiled input { 2 1100000000 1 1073741823 } output { 255u8 }
-- no_opencl compiled input { 3 1073741824 2 1073741823 } output { 255u8 }
-- structure { Replicate 1 Iota 1 }

let main (n: i32) (m: i32) (i: i32) (j: i32) =
-- The opaque is just to force manifestation.
(opaque (replicate n (tabulate m (\i -> u8.i32 i))))[i,j]

0 comments on commit 1ec4675

Please sign in to comment.