futhark-0.9.1: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.CodeGen.ImpCode.Kernels

Contents

Description

Variation of Futhark.CodeGen.ImpCode that contains the notion of a kernel invocation.

Synopsis

Documentation

data FunctionT a Source #

A imperative function, containing the body as well as its low-level inputs and outputs, as well as its high-level arguments and results. The latter are only used if the function is an entry point.

Instances
Functor FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> FunctionT a -> FunctionT b #

(<$) :: a -> FunctionT b -> FunctionT a #

Foldable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => FunctionT m -> m #

foldMap :: Monoid m => (a -> m) -> FunctionT a -> m #

foldr :: (a -> b -> b) -> b -> FunctionT a -> b #

foldr' :: (a -> b -> b) -> b -> FunctionT a -> b #

foldl :: (b -> a -> b) -> b -> FunctionT a -> b #

foldl' :: (b -> a -> b) -> b -> FunctionT a -> b #

foldr1 :: (a -> a -> a) -> FunctionT a -> a #

foldl1 :: (a -> a -> a) -> FunctionT a -> a #

toList :: FunctionT a -> [a] #

null :: FunctionT a -> Bool #

length :: FunctionT a -> Int #

elem :: Eq a => a -> FunctionT a -> Bool #

maximum :: Ord a => FunctionT a -> a #

minimum :: Ord a => FunctionT a -> a #

sum :: Num a => FunctionT a -> a #

product :: Num a => FunctionT a -> a #

Traversable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> FunctionT a -> f (FunctionT b) #

sequenceA :: Applicative f => FunctionT (f a) -> f (FunctionT a) #

mapM :: Monad m => (a -> m b) -> FunctionT a -> m (FunctionT b) #

sequence :: Monad m => FunctionT (m a) -> m (FunctionT a) #

Show a => Show (FunctionT a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty op => Pretty (FunctionT op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: FunctionT op -> Doc #

pprPrec :: Int -> FunctionT op -> Doc #

pprList :: [FunctionT op] -> Doc #

type Code = Code HostOp Source #

Host-level code that can call kernels.

type KernelCode = Code KernelOp Source #

Code inside a kernel.

type KernelConstExp = PrimExp KernelConst Source #

An expression whose variables are kernel constants.

data Kernel Source #

A generic kernel containing arbitrary kernel code.

In-kernel name and per-workgroup size in bytes.

Constructors

Kernel 

Fields

Instances
Show Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Pretty Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

ppr :: Kernel -> Doc #

pprPrec :: Int -> Kernel -> Doc #

pprList :: [Kernel] -> Doc #

FreeIn Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn :: Kernel -> Names Source #

data Int8 #

8-bit signed integer type

Instances
Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

(>=) :: Int8 -> Int8 -> Bool #

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Int8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int8 :: Nat #

PrimMemoryComparable Int8 
Instance details

Defined in Basement.PrimType

Subtractive Int8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int8 :: Type #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

Binary Int8 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int8 -> Put #

get :: Get Int8 #

putList :: [Int8] -> Put #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

ToConst Int8 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Int8 -> SrcLoc -> Const #

ToExp Int8 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Int8 -> SrcLoc -> Exp #

Pretty Int8 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int8 -> Doc #

pprPrec :: Int -> Int8 -> Doc #

pprList :: [Int8] -> Doc #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Random Int8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int8, Int8) -> g -> (Int8, g) #

random :: RandomGen g => g -> (Int8, g) #

randomRs :: RandomGen g => (Int8, Int8) -> g -> [Int8] #

randoms :: RandomGen g => g -> [Int8] #

randomRIO :: (Int8, Int8) -> IO Int8 #

randomIO :: IO Int8 #

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int8 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

Methods

value :: Int8 -> PrimValue Source #

IsPrimValue Int8 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Int8 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int8 -> (i, i) #

numElements :: Ix i => UArray i Int8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int8)] -> UArray i Int8

unsafeAt :: Ix i => UArray i Int8 -> Int -> Int8

unsafeReplace :: Ix i => UArray i Int8 -> [(Int, Int8)] -> UArray i Int8

unsafeAccum :: Ix i => (Int8 -> e' -> Int8) -> UArray i Int8 -> [(Int, e')] -> UArray i Int8

unsafeAccumArray :: Ix i => (Int8 -> e' -> Int8) -> Int8 -> (i, i) -> [(Int, e')] -> UArray i Int8

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Int8 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int8 -> ST s Int

newArray :: Ix i => (i, i) -> Int8 -> ST s (STUArray s i Int8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8)

unsafeRead :: Ix i => STUArray s i Int8 -> Int -> ST s Int8

unsafeWrite :: Ix i => STUArray s i Int8 -> Int -> Int8 -> ST s ()

type PrimSize Int8 
Instance details

Defined in Basement.PrimType

type PrimSize Int8 = 1
type Difference Int8 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int8 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int8 = 127
newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)

data Int16 #

16-bit signed integer type

Instances
Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

(>=) :: Int16 -> Int16 -> Bool #

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Int16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int16 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int16 :: Nat #

PrimMemoryComparable Int16 
Instance details

Defined in Basement.PrimType

Subtractive Int16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int16 :: Type #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

Binary Int16 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int16 -> Put #

get :: Get Int16 #

putList :: [Int16] -> Put #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

ToConst Int16 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Int16 -> SrcLoc -> Const #

ToExp Int16 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Int16 -> SrcLoc -> Exp #

Pretty Int16 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int16 -> Doc #

pprPrec :: Int -> Int16 -> Doc #

pprList :: [Int16] -> Doc #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Random Int16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int16, Int16) -> g -> (Int16, g) #

random :: RandomGen g => g -> (Int16, g) #

randomRs :: RandomGen g => (Int16, Int16) -> g -> [Int16] #

randoms :: RandomGen g => g -> [Int16] #

randomRIO :: (Int16, Int16) -> IO Int16 #

randomIO :: IO Int16 #

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int16 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int16 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Int16 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int16 -> (i, i) #

numElements :: Ix i => UArray i Int16 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int16)] -> UArray i Int16

unsafeAt :: Ix i => UArray i Int16 -> Int -> Int16

unsafeReplace :: Ix i => UArray i Int16 -> [(Int, Int16)] -> UArray i Int16

unsafeAccum :: Ix i => (Int16 -> e' -> Int16) -> UArray i Int16 -> [(Int, e')] -> UArray i Int16

unsafeAccumArray :: Ix i => (Int16 -> e' -> Int16) -> Int16 -> (i, i) -> [(Int, e')] -> UArray i Int16

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Int16 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int16 -> ST s Int

newArray :: Ix i => (i, i) -> Int16 -> ST s (STUArray s i Int16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16)

unsafeRead :: Ix i => STUArray s i Int16 -> Int -> ST s Int16

unsafeWrite :: Ix i => STUArray s i Int16 -> Int -> Int16 -> ST s ()

type PrimSize Int16 
Instance details

Defined in Basement.PrimType

type PrimSize Int16 = 2
type Difference Int16 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int16 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int16 = 32767
newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int32 #

32-bit signed integer type

Instances
Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

(>=) :: Int32 -> Int32 -> Bool #

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Int32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int32 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int32 :: Nat #

PrimMemoryComparable Int32 
Instance details

Defined in Basement.PrimType

Subtractive Int32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int32 :: Type #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

Binary Int32 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int32 -> Put #

get :: Get Int32 #

putList :: [Int32] -> Put #

ToValue Int32 
Instance details

Defined in Text.Blaze

ToMarkup Int32 
Instance details

Defined in Text.Blaze

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

ToConst Int32 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Int32 -> SrcLoc -> Const #

ToExp Int32 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Int32 -> SrcLoc -> Exp #

Pretty Int32 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int32 -> Doc #

pprPrec :: Int -> Int32 -> Doc #

pprList :: [Int32] -> Doc #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Random Int32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int32, Int32) -> g -> (Int32, g) #

random :: RandomGen g => g -> (Int32, g) #

randomRs :: RandomGen g => (Int32, Int32) -> g -> [Int32] #

randoms :: RandomGen g => g -> [Int32] #

randomRIO :: (Int32, Int32) -> IO Int32 #

randomIO :: IO Int32 #

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int32 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int32 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Int32 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int32 -> (i, i) #

numElements :: Ix i => UArray i Int32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32

unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32

unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32

unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32

unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Int32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int32 -> ST s Int

newArray :: Ix i => (i, i) -> Int32 -> ST s (STUArray s i Int32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32)

unsafeRead :: Ix i => STUArray s i Int32 -> Int -> ST s Int32

unsafeWrite :: Ix i => STUArray s i Int32 -> Int -> Int32 -> ST s ()

type PrimSize Int32 
Instance details

Defined in Basement.PrimType

type PrimSize Int32 = 4
type Difference Int32 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int32 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int32 = 2147483647
newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int64 #

64-bit signed integer type

Instances
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Int64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int64 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int64 :: Nat #

PrimMemoryComparable Int64 
Instance details

Defined in Basement.PrimType

Subtractive Int64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int64 :: Type #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

Binary Int64 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int64 -> Put #

get :: Get Int64 #

putList :: [Int64] -> Put #

ToValue Int64 
Instance details

Defined in Text.Blaze

ToMarkup Int64 
Instance details

Defined in Text.Blaze

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

ToConst Int64 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Int64 -> SrcLoc -> Const #

ToExp Int64 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Int64 -> SrcLoc -> Exp #

Pretty Int64 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int64 -> Doc #

pprPrec :: Int -> Int64 -> Doc #

pprList :: [Int64] -> Doc #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Random Int64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int64, Int64) -> g -> (Int64, g) #

random :: RandomGen g => g -> (Int64, g) #

randomRs :: RandomGen g => (Int64, Int64) -> g -> [Int64] #

randoms :: RandomGen g => g -> [Int64] #

randomRIO :: (Int64, Int64) -> IO Int64 #

randomIO :: IO Int64 #

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int64 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int64 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Int64 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) #

numElements :: Ix i => UArray i Int64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64

UTF8Bytes ByteString Int64 
Instance details

Defined in Codec.Binary.UTF8.Generic

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Int64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

type PrimSize Int64 
Instance details

Defined in Basement.PrimType

type PrimSize Int64 = 8
type Difference Int64 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int64 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int64 = 9223372036854775807
newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word8 :: Nat #

PrimMemoryComparable Word8 
Instance details

Defined in Basement.PrimType

Subtractive Word8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word8 :: Type #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

Binary Word8 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word8 -> Put #

get :: Get Word8 #

putList :: [Word8] -> Put #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

ToConst Word8 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Word8 -> SrcLoc -> Const #

ToExp Word8 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Word8 -> SrcLoc -> Exp #

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word8 -> Doc #

pprPrec :: Int -> Word8 -> Doc #

pprList :: [Word8] -> Doc #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

ByteSource Word8 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word8 g -> Word8 -> g

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Word8 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word8 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Word8 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) #

numElements :: Ix i => UArray i Word8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

UTF8Bytes [Word8] Int 
Instance details

Defined in Codec.Binary.UTF8.Generic

Methods

bsplit :: Int -> [Word8] -> ([Word8], [Word8]) #

bdrop :: Int -> [Word8] -> [Word8] #

buncons :: [Word8] -> Maybe (Word8, [Word8]) #

elemIndex :: Word8 -> [Word8] -> Maybe Int #

empty :: [Word8] #

null :: [Word8] -> Bool #

pack :: [Word8] -> [Word8] #

tail :: [Word8] -> [Word8] #

MArray (STUArray s) Word8 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

type PrimSize Word8 
Instance details

Defined in Basement.PrimType

type PrimSize Word8 = 1
type Difference Word8 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word8 
Instance details

Defined in Basement.Nat

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word8 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word8 g = Takes1Byte g
newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word16 #

16-bit unsigned integer type

Instances
Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Word16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word16 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word16 :: Nat #

PrimMemoryComparable Word16 
Instance details

Defined in Basement.PrimType

Subtractive Word16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word16 :: Type #

Binary Word16 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word16 -> Put #

get :: Get Word16 #

putList :: [Word16] -> Put #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

ToConst Word16 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Word16 -> SrcLoc -> Const #

ToExp Word16 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Word16 -> SrcLoc -> Exp #

Pretty Word16 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word16 -> Doc #

pprPrec :: Int -> Word16 -> Doc #

pprList :: [Word16] -> Doc #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Random Word16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) #

random :: RandomGen g => g -> (Word16, g) #

randomRs :: RandomGen g => (Word16, Word16) -> g -> [Word16] #

randoms :: RandomGen g => g -> [Word16] #

randomRIO :: (Word16, Word16) -> IO Word16 #

randomIO :: IO Word16 #

ByteSource Word16 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word16 g -> Word16 -> g

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Word16 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word16 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Word16 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word16 -> (i, i) #

numElements :: Ix i => UArray i Word16 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word16)] -> UArray i Word16

unsafeAt :: Ix i => UArray i Word16 -> Int -> Word16

unsafeReplace :: Ix i => UArray i Word16 -> [(Int, Word16)] -> UArray i Word16

unsafeAccum :: Ix i => (Word16 -> e' -> Word16) -> UArray i Word16 -> [(Int, e')] -> UArray i Word16

unsafeAccumArray :: Ix i => (Word16 -> e' -> Word16) -> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Word16 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word16 -> ST s Int

newArray :: Ix i => (i, i) -> Word16 -> ST s (STUArray s i Word16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16)

unsafeRead :: Ix i => STUArray s i Word16 -> Int -> ST s Word16

unsafeWrite :: Ix i => STUArray s i Word16 -> Int -> Word16 -> ST s ()

type PrimSize Word16 
Instance details

Defined in Basement.PrimType

type PrimSize Word16 = 2
type Difference Word16 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word16 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word16 = 65535
newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word16 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word16 g = Takes2Bytes g
newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Word32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word32 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word32 :: Nat #

PrimMemoryComparable Word32 
Instance details

Defined in Basement.PrimType

Subtractive Word32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word32 :: Type #

Binary Word32 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word32 -> Put #

get :: Get Word32 #

putList :: [Word32] -> Put #

ToValue Word32 
Instance details

Defined in Text.Blaze

ToMarkup Word32 
Instance details

Defined in Text.Blaze

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

ToConst Word32 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Word32 -> SrcLoc -> Const #

ToExp Word32 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Word32 -> SrcLoc -> Exp #

Pretty Word32 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word32 -> Doc #

pprPrec :: Int -> Word32 -> Doc #

pprList :: [Word32] -> Doc #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Random Word32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) #

random :: RandomGen g => g -> (Word32, g) #

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32] #

randoms :: RandomGen g => g -> [Word32] #

randomRIO :: (Word32, Word32) -> IO Word32 #

randomIO :: IO Word32 #

ByteSource Word32 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word32 g -> Word32 -> g

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Word32 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word32 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Word32 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) #

numElements :: Ix i => UArray i Word32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Word32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

type PrimSize Word32 
Instance details

Defined in Basement.PrimType

type PrimSize Word32 = 4
type Difference Word32 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word32 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word32 = 4294967295
newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word32 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word32 g = Takes4Bytes g
newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word64 #

64-bit unsigned integer type

Instances
Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

PrintfArg Word64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word64 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word64 :: Nat #

PrimMemoryComparable Word64 
Instance details

Defined in Basement.PrimType

Subtractive Word64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word64 :: Type #

Binary Word64 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word64 -> Put #

get :: Get Word64 #

putList :: [Word64] -> Put #

ToValue Word64 
Instance details

Defined in Text.Blaze

ToMarkup Word64 
Instance details

Defined in Text.Blaze

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

ToConst Word64 
Instance details

Defined in Language.C.Quote.Base

Methods

toConst :: Word64 -> SrcLoc -> Const #

ToExp Word64 
Instance details

Defined in Language.C.Quote.Base

Methods

toExp :: Word64 -> SrcLoc -> Exp #

Pretty Word64 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word64 -> Doc #

pprPrec :: Int -> Word64 -> Doc #

pprList :: [Word64] -> Doc #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Random Word64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) #

random :: RandomGen g => g -> (Word64, g) #

randomRs :: RandomGen g => (Word64, Word64) -> g -> [Word64] #

randoms :: RandomGen g => g -> [Word64] #

randomRIO :: (Word64, Word64) -> IO Word64 #

randomIO :: IO Word64 #

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Word64 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word64 Source # 
Instance details

Defined in Language.Futhark.Syntax

IArray UArray Word64 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) #

numElements :: Ix i => UArray i Word64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Word64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

type PrimSize Word64 
Instance details

Defined in Basement.PrimType

type PrimSize Word64 = 8
type Difference Word64 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word64 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word64 = 18446744073709551615
newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

pretty :: Pretty a => a -> String Source #

Prettyprint a value, wrapped to 80 characters.

data ConvOp Source #

Conversion operators try to generalise the from t0 x to t1 instructions from LLVM.

Constructors

ZExt IntType IntType

Zero-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

SExt IntType IntType

Sign-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

FPConv FloatType FloatType

Convert value of the former floating-point type to the latter. If the new type is smaller, the result is a truncation.

FPToUI FloatType IntType

Convert a floating-point value to the nearest unsigned integer (rounding towards zero).

FPToSI FloatType IntType

Convert a floating-point value to the nearest signed integer (rounding towards zero).

UIToFP IntType FloatType

Convert an unsigned integer to a floating-point value.

SIToFP IntType FloatType

Convert a signed integer to a floating-point value.

IToB IntType

Convert an integer to a boolean value. Zero becomes false; anything else is true.

BToI IntType

Convert a boolean to an integer. True is converted to 1 and False to 0.

Instances
Eq ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: ConvOp -> ConvOp -> Bool #

(/=) :: ConvOp -> ConvOp -> Bool #

Ord ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: ConvOp -> Doc #

pprPrec :: Int -> ConvOp -> Doc #

pprList :: [ConvOp] -> Doc #

data CmpOp Source #

Comparison operators are like BinOps, but they return PrimTypes. The somewhat ugly constructor names are straight out of LLVM.

Constructors

CmpEq PrimType

All types equality.

CmpUlt IntType

Unsigned less than.

CmpUle IntType

Unsigned less than or equal.

CmpSlt IntType

Signed less than.

CmpSle IntType

Signed less than or equal.

FCmpLt FloatType

Floating-point less than.

FCmpLe FloatType

Floating-point less than or equal.

CmpLlt

Boolean less than.

CmpLle

Boolean less than or equal.

Instances
Eq CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: CmpOp -> CmpOp -> Bool #

(/=) :: CmpOp -> CmpOp -> Bool #

Ord CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: CmpOp -> CmpOp -> Ordering #

(<) :: CmpOp -> CmpOp -> Bool #

(<=) :: CmpOp -> CmpOp -> Bool #

(>) :: CmpOp -> CmpOp -> Bool #

(>=) :: CmpOp -> CmpOp -> Bool #

max :: CmpOp -> CmpOp -> CmpOp #

min :: CmpOp -> CmpOp -> CmpOp #

Show CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Pretty CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: CmpOp -> Doc #

pprPrec :: Int -> CmpOp -> Doc #

pprList :: [CmpOp] -> Doc #

data BinOp Source #

Binary operators. These correspond closely to the binary operators in LLVM. Most are parametrised by their expected input and output types.

Constructors

Add IntType

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType

Unsigned integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

SDiv IntType

Signed integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

FDiv FloatType

Floating-point division.

UMod IntType

Unsigned integer modulus; the countepart to UDiv.

SMod IntType

Signed integer modulus; the countepart to SDiv.

SQuot IntType

Signed integer division. Rounds towards zero. This corresponds to the sdiv instruction in LLVM.

SRem IntType

Signed integer division. Rounds towards zero. This corresponds to the srem instruction in LLVM.

SMin IntType

Returns the smallest of two signed integers.

UMin IntType

Returns the smallest of two unsigned integers.

FMin FloatType

Returns the smallest of two floating-point numbers.

SMax IntType

Returns the greatest of two signed integers.

UMax IntType

Returns the greatest of two unsigned integers.

FMax FloatType

Returns the greatest of two floating-point numbers.

Shl IntType

Left-shift.

LShr IntType

Logical right-shift, zero-extended.

AShr IntType

Arithmetic right-shift, sign-extended.

And IntType

Bitwise and.

Or IntType

Bitwise or.

Xor IntType

Bitwise exclusive-or.

Pow IntType

Integer exponentiation.

FPow FloatType

Floating-point exponentiation.

LogAnd

Boolean and - not short-circuiting.

LogOr

Boolean or - not short-circuiting.

Instances
Eq BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Ord BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: BinOp -> BinOp -> Ordering #

(<) :: BinOp -> BinOp -> Bool #

(<=) :: BinOp -> BinOp -> Bool #

(>) :: BinOp -> BinOp -> Bool #

(>=) :: BinOp -> BinOp -> Bool #

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

Show BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: BinOp -> Doc #

pprPrec :: Int -> BinOp -> Doc #

pprList :: [BinOp] -> Doc #

data UnOp Source #

Various unary operators. It is a bit ad-hoc what is a unary operator and what is a built-in function. Perhaps these should all go away eventually.

Constructors

Not

E.g., ! True == False.

Complement IntType

E.g., ~(~1) = 1.

Abs IntType

abs(-2) = 2.

FAbs FloatType

fabs(-2.0) = 2.0.

SSignum IntType

Signed sign function: ssignum(-2) = -1.

USignum IntType

Unsigned sign function: usignum(2) = 1.

Instances
Eq UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: UnOp -> UnOp -> Bool #

(/=) :: UnOp -> UnOp -> Bool #

Ord UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: UnOp -> UnOp -> Ordering #

(<) :: UnOp -> UnOp -> Bool #

(<=) :: UnOp -> UnOp -> Bool #

(>) :: UnOp -> UnOp -> Bool #

(>=) :: UnOp -> UnOp -> Bool #

max :: UnOp -> UnOp -> UnOp #

min :: UnOp -> UnOp -> UnOp #

Show UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Pretty UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: UnOp -> Doc #

pprPrec :: Int -> UnOp -> Doc #

pprList :: [UnOp] -> Doc #

data PrimType Source #

Low-level primitive types.

data FloatType Source #

A floating point type.

Constructors

Float32 
Float64 
Instances
Bounded FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Enum FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Eq FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Ord FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: FloatType -> Doc #

pprPrec :: Int -> FloatType -> Doc #

pprList :: [FloatType] -> Doc #

data IntType Source #

An integer type, ordered by size. Note that signedness is not a property of the type, but a property of the operations performed on values of these types.

Constructors

Int8 
Int16 
Int32 
Int64 

allIntTypes :: [IntType] Source #

A list of all integer types.

allFloatTypes :: [FloatType] Source #

A list of all floating-point types.

allPrimTypes :: [PrimType] Source #

A list of all primitive types.

intValue :: Integral int => IntType -> int -> IntValue Source #

Create an IntValue from a type and an Integer.

valueIntegral :: Integral int => IntValue -> int Source #

Convert an IntValue to any Integral type.

floatValue :: Real num => FloatType -> num -> FloatValue Source #

Create a FloatValue from a type and a Rational.

primValueType :: PrimValue -> PrimType Source #

The type of a basic value.

blankPrimValue :: PrimType -> PrimValue Source #

A "blank" value of the given primitive type - this is zero, or whatever is close to it. Don't depend on this value, but use it for e.g. creating arrays to be populated by do-loops.

allUnOps :: [UnOp] Source #

A list of all unary operators for all types.

allBinOps :: [BinOp] Source #

A list of all binary operators for all types.

allCmpOps :: [CmpOp] Source #

A list of all comparison operators for all types.

allConvOps :: [ConvOp] Source #

A list of all conversion operators for all types.

doComplement :: IntValue -> IntValue Source #

E.g., ~(~1) = 1.

doAbs :: IntValue -> IntValue Source #

abs(-2) = 2.

doFAbs :: FloatValue -> FloatValue Source #

abs(-2.0) = 2.0.

doSSignum :: IntValue -> IntValue Source #

ssignum(-2) = -1.

doUSignum :: IntValue -> IntValue Source #

usignum(-2) = -1.

doAdd :: IntValue -> IntValue -> IntValue Source #

Integer addition.

doMul :: IntValue -> IntValue -> IntValue Source #

Integer multiplication.

doSDiv :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

doSMod :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer modulus; the countepart to SDiv.

doPow :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer exponentatation.

doZExt :: IntValue -> IntType -> IntValue Source #

Zero-extend the given integer value to the size of the given type. If the type is smaller than the given value, the result is a truncation.

doSExt :: IntValue -> IntType -> IntValue Source #

Sign-extend the given integer value to the size of the given type. If the type is smaller than the given value, the result is a truncation.

doFPConv :: FloatValue -> FloatType -> FloatValue Source #

Convert the former floating-point type to the latter.

doFPToUI :: FloatValue -> IntType -> IntValue Source #

Convert a floating-point value to the nearest unsigned integer (rounding towards zero).

doFPToSI :: FloatValue -> IntType -> IntValue Source #

Convert a floating-point value to the nearest signed integer (rounding towards zero).

doUIToFP :: IntValue -> FloatType -> FloatValue Source #

Convert an unsigned integer to a floating-point value.

doSIToFP :: IntValue -> FloatType -> FloatValue Source #

Convert a signed integer to a floating-point value.

doCmpEq :: PrimValue -> PrimValue -> Bool Source #

Compare any two primtive values for exact equality.

doCmpUlt :: IntValue -> IntValue -> Bool Source #

Unsigned less than.

doCmpUle :: IntValue -> IntValue -> Bool Source #

Unsigned less than or equal.

doCmpSlt :: IntValue -> IntValue -> Bool Source #

Signed less than.

doCmpSle :: IntValue -> IntValue -> Bool Source #

Signed less than or equal.

doFCmpLt :: FloatValue -> FloatValue -> Bool Source #

Floating-point less than.

doFCmpLe :: FloatValue -> FloatValue -> Bool Source #

Floating-point less than or equal.

intToWord64 :: IntValue -> Word64 Source #

Translate an IntValue to Word64. This is guaranteed to fit.

intToInt64 :: IntValue -> Int64 Source #

Translate an IntValue to IntType. This is guaranteed to fit.

binOpType :: BinOp -> PrimType Source #

The result type of a binary operator.

cmpOpType :: CmpOp -> PrimType Source #

The operand types of a comparison operator.

unOpType :: UnOp -> PrimType Source #

The operand and result type of a unary operator.

convOpType :: ConvOp -> (PrimType, PrimType) Source #

The input and output types of a conversion operator.

primFuns :: Map String ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue) Source #

A mapping from names of primitive functions to their parameter types, their result type, and a function for evaluating them.

zeroIsh :: PrimValue -> Bool Source #

Is the given value kind of zero?

oneIsh :: PrimValue -> Bool Source #

Is the given value kind of one?

negativeIsh :: PrimValue -> Bool Source #

Is the given value kind of negative?

primBitSize :: PrimType -> Int Source #

The size of a value of a given primitive type in bites.

primByteSize :: Num a => PrimType -> a Source #

The size of a value of a given primitive type in eight-bit bytes.

intByteSize :: Num a => IntType -> a Source #

The size of a value of a given integer type in eight-bit bytes.

floatByteSize :: Num a => FloatType -> a Source #

The size of a value of a given floating-point type in eight-bit bytes.

commutativeBinOp :: BinOp -> Bool Source #

True if the given binary operator is commutative.

prettySigned :: Bool -> PrimType -> String Source #

True if signed. Only makes a difference for integer types.

data VName Source #

A name tagged with some integer. Only the integer is used in comparisons, no matter the type of vn.

Constructors

VName !Name !Int 
Instances
Eq VName Source # 
Instance details

Defined in Language.Futhark.Core

Methods

(==) :: VName -> VName -> Bool #

(/=) :: VName -> VName -> Bool #

Ord VName Source # 
Instance details

Defined in Language.Futhark.Core

Methods

compare :: VName -> VName -> Ordering #

(<) :: VName -> VName -> Bool #

(<=) :: VName -> VName -> Bool #

(>) :: VName -> VName -> Bool #

(>=) :: VName -> VName -> Bool #

max :: VName -> VName -> VName #

min :: VName -> VName -> VName #

Show VName Source # 
Instance details

Defined in Language.Futhark.Core

Methods

showsPrec :: Int -> VName -> ShowS #

show :: VName -> String #

showList :: [VName] -> ShowS #

ToIdent VName Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toIdent :: VName -> SrcLoc -> Id #

ToExp VName Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toExp :: VName -> SrcLoc -> Exp #

Pretty VName Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: VName -> Doc #

pprPrec :: Int -> VName -> Doc #

pprList :: [VName] -> Doc #

FreeIn VName Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: VName -> Names Source #

FreeIn Names Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Names -> Names Source #

Substitute VName Source # 
Instance details

Defined in Futhark.Transform.Substitute

Substitute Names Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename VName Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename Names Source # 
Instance details

Defined in Futhark.Transform.Rename

AliasesOf Names Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Aliases

ToExp VName Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBinder m => VName -> m (Exp (Lore m)) Source #

Simplifiable VName Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => VName -> SimpleM lore VName Source #

IsName VName Source #

Depending on the environment variable FUTHARK_COMPILER_DEBUGGING, VNames are printed as either the name with an internal tag, or just the base name.

Instance details

Defined in Language.Futhark.Pretty

Methods

pprName :: VName -> Doc Source #

ASTMappable StructType Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable PatternType Source # 
Instance details

Defined in Language.Futhark.Traversals

MonadState Names (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

get :: TypeM lore Names #

put :: Names -> TypeM lore () #

state :: (Names -> (a, Names)) -> TypeM lore a #

Scoped lore (VName, NameInfo lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

scopeOf :: (VName, NameInfo lore) -> Scope lore Source #

(Applicative m, Monad m, Annotations lore) => LocalScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

localScope :: Scope lore -> ReaderT (Scope lore) m a -> ReaderT (Scope lore) m a Source #

(Applicative m, Monad m, Annotations lore) => HasScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

lookupType :: VName -> ReaderT (Scope lore) m Type Source #

lookupInfo :: VName -> ReaderT (Scope lore) m (NameInfo lore) Source #

askScope :: ReaderT (Scope lore) m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ReaderT (Scope lore) m a Source #

(Applicative m, Monad m, Monoid w, Annotations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Annotations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Annotations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Annotations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

ASTMappable (TypeParamBase VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (TypeArgExp VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (TypeExp VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> TypeExp VName -> m (TypeExp VName) Source #

ASTMappable (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> DimDecl VName -> m (DimDecl VName) Source #

Monad m => MonadReader (Scope lore) (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

ask :: ExtendedScope lore m (Scope lore) #

local :: (Scope lore -> Scope lore) -> ExtendedScope lore m a -> ExtendedScope lore m a #

reader :: (Scope lore -> a) -> ExtendedScope lore m a #

ASTMappable (PatternBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (LoopFormBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (CaseBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (FieldBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (ExpBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (DimIndexBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (IdentBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (TypeDeclBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Substitutable (TypeBase (DimDecl VName) ()) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase (DimDecl VName) Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

data Name Source #

The abstract (not really) type representing names in the Futhark compiler. Strings, being lists of characters, are very slow, while Texts are based on byte-arrays.

Instances
Eq Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

fromString :: String -> Name #

Semigroup Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

(<>) :: Name -> Name -> Name #

sconcat :: NonEmpty Name -> Name #

stimes :: Integral b => b -> Name -> Name #

ToIdent Name Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toIdent :: Name -> SrcLoc -> Id #

Pretty Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

ppr :: Name -> Doc #

pprPrec :: Int -> Name -> Doc #

pprList :: [Name] -> Doc #

IsName Name Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pprName :: Name -> Doc Source #

data Commutativity Source #

Whether some operator is commutative or not. The Monoid instance returns the least commutative of its arguments.

Instances
Eq Commutativity Source # 
Instance details

Defined in Language.Futhark.Core

Ord Commutativity Source # 
Instance details

Defined in Language.Futhark.Core

Show Commutativity Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup Commutativity Source # 
Instance details

Defined in Language.Futhark.Core

Monoid Commutativity Source # 
Instance details

Defined in Language.Futhark.Core

Pretty Commutativity Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

data Uniqueness Source #

The uniqueness attribute of a type. This essentially indicates whether or not in-place modifications are acceptable. With respect to ordering, Unique is greater than Nonunique.

Constructors

Nonunique

May have references outside current function.

Unique

No references outside current function.

Instances
Eq Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Ord Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Show Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Monoid Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Pretty Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp Uniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FixExt ret => DeclExtTyped (MemInfo ExtSize Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

defaultEntryPoint :: Name Source #

The name of the default program entry point (main).

nameToString :: Name -> String Source #

Convert a name to the corresponding list of characters.

nameFromString :: String -> Name Source #

Convert a list of characters to the corresponding name.

nameToText :: Name -> Text Source #

Convert a name to the corresponding Text.

nameFromText :: Text -> Name Source #

Convert a Text to the corresponding name.

locStr :: SrcLoc -> String Source #

A human-readable location string, of the form filename:lineno:columnno. This follows the GNU coding standards for error messages: https://www.gnu.org/prep/standards/html_node/Errors.html

This function assumes that both start and end position is in the same file (it is not clear what the alternative would even mean).

baseTag :: VName -> Int Source #

Return the tag contained in the VName.

baseName :: VName -> Name Source #

Return the name contained in the VName.

baseString :: VName -> String Source #

Return the base Name converted to a string.

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString String

A literal string.

ErrorInt32 a

A run-time integer value.

Instances
Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fmap :: (a -> b) -> ErrorMsgPart a -> ErrorMsgPart b #

(<$) :: a -> ErrorMsgPart b -> ErrorMsgPart a #

Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => ErrorMsgPart m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorMsgPart a -> m #

foldr :: (a -> b -> b) -> b -> ErrorMsgPart a -> b #

foldr' :: (a -> b -> b) -> b -> ErrorMsgPart a -> b #

foldl :: (b -> a -> b) -> b -> ErrorMsgPart a -> b #

foldl' :: (b -> a -> b) -> b -> ErrorMsgPart a -> b #

foldr1 :: (a -> a -> a) -> ErrorMsgPart a -> a #

foldl1 :: (a -> a -> a) -> ErrorMsgPart a -> a #

toList :: ErrorMsgPart a -> [a] #

null :: ErrorMsgPart a -> Bool #

length :: ErrorMsgPart a -> Int #

elem :: Eq a => a -> ErrorMsgPart a -> Bool #

maximum :: Ord a => ErrorMsgPart a -> a #

minimum :: Ord a => ErrorMsgPart a -> a #

sum :: Num a => ErrorMsgPart a -> a #

product :: Num a => ErrorMsgPart a -> a #

Traversable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> ErrorMsgPart a -> f (ErrorMsgPart b) #

sequenceA :: Applicative f => ErrorMsgPart (f a) -> f (ErrorMsgPart a) #

mapM :: Monad m => (a -> m b) -> ErrorMsgPart a -> m (ErrorMsgPart b) #

sequence :: Monad m => ErrorMsgPart (m a) -> m (ErrorMsgPart a) #

Eq a => Eq (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord a => Ord (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show a => Show (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

newtype ErrorMsg a Source #

An error message is a list of error parts, which are concatenated to form the final message.

Constructors

ErrorMsg [ErrorMsgPart a] 
Instances
Functor ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fmap :: (a -> b) -> ErrorMsg a -> ErrorMsg b #

(<$) :: a -> ErrorMsg b -> ErrorMsg a #

Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => ErrorMsg m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorMsg a -> m #

foldr :: (a -> b -> b) -> b -> ErrorMsg a -> b #

foldr' :: (a -> b -> b) -> b -> ErrorMsg a -> b #

foldl :: (b -> a -> b) -> b -> ErrorMsg a -> b #

foldl' :: (b -> a -> b) -> b -> ErrorMsg a -> b #

foldr1 :: (a -> a -> a) -> ErrorMsg a -> a #

foldl1 :: (a -> a -> a) -> ErrorMsg a -> a #

toList :: ErrorMsg a -> [a] #

null :: ErrorMsg a -> Bool #

length :: ErrorMsg a -> Int #

elem :: Eq a => a -> ErrorMsg a -> Bool #

maximum :: Ord a => ErrorMsg a -> a #

minimum :: Ord a => ErrorMsg a -> a #

sum :: Num a => ErrorMsg a -> a #

product :: Num a => ErrorMsg a -> a #

Traversable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> ErrorMsg a -> f (ErrorMsg b) #

sequenceA :: Applicative f => ErrorMsg (f a) -> f (ErrorMsg a) #

mapM :: Monad m => (a -> m b) -> ErrorMsg a -> m (ErrorMsg b) #

sequence :: Monad m => ErrorMsg (m a) -> m (ErrorMsg a) #

Eq a => Eq (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: ErrorMsg a -> ErrorMsg a -> Bool #

(/=) :: ErrorMsg a -> ErrorMsg a -> Bool #

Ord a => Ord (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: ErrorMsg a -> ErrorMsg a -> Ordering #

(<) :: ErrorMsg a -> ErrorMsg a -> Bool #

(<=) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>=) :: ErrorMsg a -> ErrorMsg a -> Bool #

max :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

min :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

Show a => Show (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> ErrorMsg a -> ShowS #

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

Pretty a => Pretty (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ErrorMsg a -> Doc #

pprPrec :: Int -> ErrorMsg a -> Doc #

pprList :: [ErrorMsg a] -> Doc #

type SpaceId = String Source #

A string representing a specific non-default memory space.

data Space Source #

The memory space of a block. If DefaultSpace, this is the "default" space, whatever that is. The exact meaning of the SpaceID depends on the backend used. In GPU kernels, for example, this is used to distinguish between constant, global and shared memory spaces. In GPU-enabled host code, it is used to distinguish between host memory (DefaultSpace) and GPU space.

Constructors

DefaultSpace 
Space SpaceId 
Instances
Eq Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: Space -> Space -> Bool #

(/=) :: Space -> Space -> Bool #

Ord Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Space -> Space -> Ordering #

(<) :: Space -> Space -> Bool #

(<=) :: Space -> Space -> Bool #

(>) :: Space -> Space -> Bool #

(>=) :: Space -> Space -> Bool #

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Show Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Space -> Doc #

pprPrec :: Int -> Space -> Doc #

pprList :: [Space] -> Doc #

data PrimExp v Source #

A primitive expression parametrised over the representation of free variables. Note that the Functor, Traversable, and Num instances perform automatic (but simple) constant folding.

Instances
Functor PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

fmap :: (a -> b) -> PrimExp a -> PrimExp b #

(<$) :: a -> PrimExp b -> PrimExp a #

Foldable PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

fold :: Monoid m => PrimExp m -> m #

foldMap :: Monoid m => (a -> m) -> PrimExp a -> m #

foldr :: (a -> b -> b) -> b -> PrimExp a -> b #

foldr' :: (a -> b -> b) -> b -> PrimExp a -> b #

foldl :: (b -> a -> b) -> b -> PrimExp a -> b #

foldl' :: (b -> a -> b) -> b -> PrimExp a -> b #

foldr1 :: (a -> a -> a) -> PrimExp a -> a #

foldl1 :: (a -> a -> a) -> PrimExp a -> a #

toList :: PrimExp a -> [a] #

null :: PrimExp a -> Bool #

length :: PrimExp a -> Int #

elem :: Eq a => a -> PrimExp a -> Bool #

maximum :: Ord a => PrimExp a -> a #

minimum :: Ord a => PrimExp a -> a #

sum :: Num a => PrimExp a -> a #

product :: Num a => PrimExp a -> a #

Traversable PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

traverse :: Applicative f => (a -> f b) -> PrimExp a -> f (PrimExp b) #

sequenceA :: Applicative f => PrimExp (f a) -> f (PrimExp a) #

mapM :: Monad m => (a -> m b) -> PrimExp a -> m (PrimExp b) #

sequence :: Monad m => PrimExp (m a) -> m (PrimExp a) #

Eq v => Eq (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(==) :: PrimExp v -> PrimExp v -> Bool #

(/=) :: PrimExp v -> PrimExp v -> Bool #

Pretty v => Num (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(+) :: PrimExp v -> PrimExp v -> PrimExp v #

(-) :: PrimExp v -> PrimExp v -> PrimExp v #

(*) :: PrimExp v -> PrimExp v -> PrimExp v #

negate :: PrimExp v -> PrimExp v #

abs :: PrimExp v -> PrimExp v #

signum :: PrimExp v -> PrimExp v #

fromInteger :: Integer -> PrimExp v #

Ord v => Ord (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

compare :: PrimExp v -> PrimExp v -> Ordering #

(<) :: PrimExp v -> PrimExp v -> Bool #

(<=) :: PrimExp v -> PrimExp v -> Bool #

(>) :: PrimExp v -> PrimExp v -> Bool #

(>=) :: PrimExp v -> PrimExp v -> Bool #

max :: PrimExp v -> PrimExp v -> PrimExp v #

min :: PrimExp v -> PrimExp v -> PrimExp v #

Show v => Show (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

showsPrec :: Int -> PrimExp v -> ShowS #

show :: PrimExp v -> String #

showList :: [PrimExp v] -> ShowS #

Pretty v => Pretty (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

ppr :: PrimExp v -> Doc #

pprPrec :: Int -> PrimExp v -> Doc #

pprList :: [PrimExp v] -> Doc #

Pretty v => IntegralExp (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

FreeIn v => FreeIn (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

freeIn :: PrimExp v -> Names Source #

Substitute v => Substitute (PrimExp v) Source # 
Instance details

Defined in Futhark.Transform.Substitute

ToExp v => ToExp (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBinder m => PrimExp v -> m (Exp (Lore m)) Source #

constFoldPrimExp :: PrimExp v -> PrimExp v Source #

Perform quick and dirty constant folding on the top level of a PrimExp. This is necessary because we want to consider e.g. equality modulo constant folding.

(.&&.) :: PrimExp v -> PrimExp v -> PrimExp v infixr 3 Source #

Lifted logical conjunction.

(.||.) :: PrimExp v -> PrimExp v -> PrimExp v infixr 2 Source #

Lifted logical conjunction.

(.<.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #

Lifted relational operators; assuming signed numbers in case of integers.

(.<=.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #

Lifted relational operators; assuming signed numbers in case of integers.

(.==.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #

Lifted relational operators; assuming signed numbers in case of integers.

(.>.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #

Lifted relational operators; assuming signed numbers in case of integers.

(.>=.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #

Lifted relational operators; assuming signed numbers in case of integers.

(.&.) :: PrimExp v -> PrimExp v -> PrimExp v Source #

Lifted bitwise operators.

(.|.) :: PrimExp v -> PrimExp v -> PrimExp v Source #

Lifted bitwise operators.

(.^.) :: PrimExp v -> PrimExp v -> PrimExp v Source #

Lifted bitwise operators.

evalPrimExp :: (Pretty v, Monad m) => (v -> m PrimValue) -> PrimExp v -> m PrimValue Source #

Evaluate a PrimExp in the given monad. Invokes fail on type errors.

primExpType :: PrimExp v -> PrimType Source #

The type of values returned by a PrimExp. This function returning does not imply that the PrimExp is type-correct.

coerceIntPrimExp :: IntType -> PrimExp v -> PrimExp v Source #

If the given PrimExp is a constant of the wrong integer type, coerce it to the given integer type. This is a workaround for an issue in the Num instance.

true :: PrimExp v Source #

Boolean-valued PrimExps.

false :: PrimExp v Source #

Boolean-valued PrimExps.

data Bytes Source #

Phantom type for a count of bytes.

data Elements Source #

Phantom type for a count of elements.

newtype Count u Source #

A wrapper around Exp that maintains a unit as a phantom type.

Constructors

Count 

Fields

Instances
Eq (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(==) :: Count u -> Count u -> Bool #

(/=) :: Count u -> Count u -> Bool #

Num (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(+) :: Count u -> Count u -> Count u #

(-) :: Count u -> Count u -> Count u #

(*) :: Count u -> Count u -> Count u #

negate :: Count u -> Count u #

abs :: Count u -> Count u #

signum :: Count u -> Count u #

fromInteger :: Integer -> Count u #

Show (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Count u -> ShowS #

show :: Count u -> String #

showList :: [Count u] -> ShowS #

Pretty (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Count u -> Doc #

pprPrec :: Int -> Count u -> Doc #

pprList :: [Count u] -> Doc #

IntegralExp (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

FreeIn (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Count u -> Names Source #

data Arg Source #

A function call argument.

Constructors

ExpArg Exp 
MemArg VName 
Instances
Show Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

Pretty Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Arg -> Doc #

pprPrec :: Int -> Arg -> Doc #

pprList :: [Arg] -> Doc #

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Arg -> Names Source #

data ExpLeaf Source #

Instances
Eq ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(==) :: ExpLeaf -> ExpLeaf -> Bool #

(/=) :: ExpLeaf -> ExpLeaf -> Bool #

Show ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: ExpLeaf -> Doc #

pprPrec :: Int -> ExpLeaf -> Doc #

pprList :: [ExpLeaf] -> Doc #

FreeIn ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: ExpLeaf -> Names Source #

pattern If :: Exp -> Code a -> Code a -> Code a Source #

pattern Op :: a -> Code a Source #

pattern Write :: VName -> Count Bytes -> PrimType -> Space -> Volatility -> Exp -> Code a Source #

pattern Comment :: String -> Code a -> Code a Source #

Has the same semantics as the contained code, but the comment should show up in generated code for ease of inspection.

pattern Skip :: Code a Source #

pattern Free :: VName -> Space -> Code a Source #

Indicate that some memory block will never again be referenced via the indicated variable. However, it may still be accessed through aliases. It is only safe to actually deallocate the memory block if this is the last reference. There is no guarantee that all memory blocks will be freed with this statement. Backends are free to ignore it entirely.

pattern While :: Exp -> Code a -> Code a Source #

pattern For :: VName -> IntType -> Exp -> Code a -> Code a Source #

pattern Allocate :: VName -> Count Bytes -> Space -> Code a Source #

Memory space must match the corresponding DeclareMem.

pattern Copy :: VName -> Count Bytes -> Space -> VName -> Count Bytes -> Space -> Count Bytes -> Code a Source #

Destination, offset in destination, destination space, source, offset in source, offset space, number of bytes.

pattern Assert :: Exp -> ErrorMsg Exp -> (SrcLoc, [SrcLoc]) -> Code a Source #

pattern (:>>:) :: Code a -> Code a -> Code a Source #

pattern DeclareMem :: VName -> Space -> Code a Source #

pattern DeclareArray :: VName -> Space -> PrimType -> [PrimValue] -> Code a Source #

Create an array containing the given values. The lifetime of the array will be the entire application. This is mostly used for constant arrays, but also for some bookkeeping data, like the synchronisation counts used to implement reduction.

pattern SetScalar :: VName -> Exp -> Code a Source #

pattern SetMem :: VName -> VName -> Space -> Code a Source #

Must be in same space.

pattern Call :: [VName] -> Name -> [Arg] -> Code a Source #

pattern DebugPrint :: String -> PrimType -> Exp -> Code a Source #

Print the given value (of the given type) to the screen, somehow annotated with the given string as a description. This has no semantic meaning, but is used entirely for debugging. Code generators are free to ignore this statement.

data FunctionT a Source #

A imperative function, containing the body as well as its low-level inputs and outputs, as well as its high-level arguments and results. The latter are only used if the function is an entry point.

Instances
Functor FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> FunctionT a -> FunctionT b #

(<$) :: a -> FunctionT b -> FunctionT a #

Foldable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => FunctionT m -> m #

foldMap :: Monoid m => (a -> m) -> FunctionT a -> m #

foldr :: (a -> b -> b) -> b -> FunctionT a -> b #

foldr' :: (a -> b -> b) -> b -> FunctionT a -> b #

foldl :: (b -> a -> b) -> b -> FunctionT a -> b #

foldl' :: (b -> a -> b) -> b -> FunctionT a -> b #

foldr1 :: (a -> a -> a) -> FunctionT a -> a #

foldl1 :: (a -> a -> a) -> FunctionT a -> a #

toList :: FunctionT a -> [a] #

null :: FunctionT a -> Bool #

length :: FunctionT a -> Int #

elem :: Eq a => a -> FunctionT a -> Bool #

maximum :: Ord a => FunctionT a -> a #

minimum :: Ord a => FunctionT a -> a #

sum :: Num a => FunctionT a -> a #

product :: Num a => FunctionT a -> a #

Traversable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> FunctionT a -> f (FunctionT b) #

sequenceA :: Applicative f => FunctionT (f a) -> f (FunctionT a) #

mapM :: Monad m => (a -> m b) -> FunctionT a -> m (FunctionT b) #

sequence :: Monad m => FunctionT (m a) -> m (FunctionT a) #

Show a => Show (FunctionT a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty op => Pretty (FunctionT op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: FunctionT op -> Doc #

pprPrec :: Int -> FunctionT op -> Doc #

pprList :: [FunctionT op] -> Doc #

data ExternalValue Source #

^ An externally visible value. This can be an opaque value (covering several physical internal values), or a single value that can be used externally.

Constructors

OpaqueValue String [ValueDesc]

The string is a human-readable description with no other semantics.

TransparentValue ValueDesc 

data ValueDesc Source #

A description of an externally meaningful value.

Constructors

ArrayValue VName MemSize Space PrimType Signedness [DimSize]

An array with memory block, memory block size, memory space, element type, signedness of element type (if applicable), and shape.

ScalarValue PrimType Signedness VName

A scalar value with signedness if applicable.

Instances
Eq ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Show ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: ValueDesc -> Doc #

pprPrec :: Int -> ValueDesc -> Doc #

pprList :: [ValueDesc] -> Doc #

data Signedness Source #

Constructors

TypeUnsigned 
TypeDirect 
Instances
Eq Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Show Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

newtype Functions a Source #

A collection of imperative functions.

Constructors

Functions [(Name, Function a)] 
Instances
Functor Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> Functions a -> Functions b #

(<$) :: a -> Functions b -> Functions a #

Foldable Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => Functions m -> m #

foldMap :: Monoid m => (a -> m) -> Functions a -> m #

foldr :: (a -> b -> b) -> b -> Functions a -> b #

foldr' :: (a -> b -> b) -> b -> Functions a -> b #

foldl :: (b -> a -> b) -> b -> Functions a -> b #

foldl' :: (b -> a -> b) -> b -> Functions a -> b #

foldr1 :: (a -> a -> a) -> Functions a -> a #

foldl1 :: (a -> a -> a) -> Functions a -> a #

toList :: Functions a -> [a] #

null :: Functions a -> Bool #

length :: Functions a -> Int #

elem :: Eq a => a -> Functions a -> Bool #

maximum :: Ord a => Functions a -> a #

minimum :: Ord a => Functions a -> a #

sum :: Num a => Functions a -> a #

product :: Num a => Functions a -> a #

Traversable Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> Functions a -> f (Functions b) #

sequenceA :: Applicative f => Functions (f a) -> f (Functions a) #

mapM :: Monad m => (a -> m b) -> Functions a -> m (Functions b) #

sequence :: Monad m => Functions (m a) -> m (Functions a) #

Semigroup (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(<>) :: Functions a -> Functions a -> Functions a #

sconcat :: NonEmpty (Functions a) -> Functions a #

stimes :: Integral b => b -> Functions a -> Functions a #

Monoid (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty op => Pretty (Functions op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Functions op -> Doc #

pprPrec :: Int -> Functions op -> Doc #

pprList :: [Functions op] -> Doc #

data Param Source #

Instances
Show Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

Pretty Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Param -> Doc #

pprPrec :: Int -> Param -> Doc #

pprList :: [Param] -> Doc #

data Size Source #

Constructors

ConstSize Int64 
VarSize VName 
Instances
Eq Size Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Show Size Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Pretty Size Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Size -> Doc #

pprPrec :: Int -> Size -> Doc #

pprList :: [Size] -> Doc #

FreeIn Size Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Size -> Names Source #

withElemType :: Count Elements -> PrimType -> Count Bytes Source #

Convert a count of elements into a count of bytes, given the per-element size.

Utility functions

atomicBinOp :: BinOp -> Maybe (VName -> VName -> Count Bytes -> Exp -> AtomicOp) Source #

Get an atomic operator corresponding to a binary operator.