futhark-0.19.3: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.CodeGen.ImpCode.Sequential

Description

Sequential imperative code.

Synopsis

Documentation

type Program = Definitions Sequential Source #

An imperative program.

type Function = Function Sequential Source #

An imperative function.

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

Instances details
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 #

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 Sequential Source #

A piece of imperative code.

data Sequential Source #

Phantom type for identifying sequential imperative code.

Instances

Instances details
Pretty Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

FreeIn Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

data Int8 #

8-bit signed integer type

Instances

Instances details
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 #

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

FromJSON Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Int8 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int8 #

uniformR :: Generator g m => (Int8, Int8) -> g -> m Int8 #

uniformB :: Generator g m => Int8 -> g -> m Int8 #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Uniform Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int8 #

UniformRange Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int8, Int8) -> g -> m Int8 #

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int8 Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

Methods

value :: Int8 -> PrimValue Source #

IntExp Int8 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

NumExp Int8 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IsPrimValue Int8 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Int8 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

liftTyped :: Int8 -> Q (TExp Int8) #

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 Unsigned Int8 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Int16 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int16 #

uniformR :: Generator g m => (Int16, Int16) -> g -> m Int16 #

uniformB :: Generator g m => Int16 -> g -> m Int16 #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Uniform Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int16 #

UniformRange Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int16, Int16) -> g -> m Int16 #

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int16 Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

IntExp Int16 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

NumExp Int16 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IsPrimValue Int16 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Int16 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

liftTyped :: Int16 -> Q (TExp Int16) #

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 Unsigned Int16 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Int32 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int32 #

uniformR :: Generator g m => (Int32, Int32) -> g -> m Int32 #

uniformB :: Generator g m => Int32 -> g -> m Int32 #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Uniform Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int32 #

UniformRange Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int32, Int32) -> g -> m Int32 #

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int32 Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

IntExp Int32 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

NumExp Int32 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IsPrimValue Int32 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Int32 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

liftTyped :: Int32 -> Q (TExp Int32) #

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 Unsigned Int32 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Int64 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int64 #

uniformR :: Generator g m => (Int64, Int64) -> g -> m Int64 #

uniformB :: Generator g m => Int64 -> g -> m Int64 #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Uniform Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int64 #

UniformRange Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 #

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Int64 Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

IntExp Int64 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

NumExp Int64 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IsPrimValue Int64 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Int64 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

liftTyped :: Int64 -> Q (TExp Int64) #

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

Pretty (ShapeDecl Int64) Source # 
Instance details

Defined in Language.Futhark.Pretty

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 Unsigned Int64 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Word8 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word8 #

uniformR :: Generator g m => (Word8, Word8) -> g -> m Word8 #

uniformB :: Generator g m => Word8 -> g -> m Word8 #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Uniform Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word8 #

UniformRange Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word8, Word8) -> g -> m 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.IR.Prop.Constants

IsPrimValue Word8 Source # 
Instance details

Defined in Language.Futhark.Syntax

PutValue Word8 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Word8 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

liftTyped :: Word8 -> Q (TExp Word8) #

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 Unsigned Word8 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Word16 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word16 #

uniformR :: Generator g m => (Word16, Word16) -> g -> m Word16 #

uniformB :: Generator g m => Word16 -> g -> m Word16 #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Uniform Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word16 #

UniformRange Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word16, Word16) -> g -> m 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.IR.Prop.Constants

IsPrimValue Word16 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Word16 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

liftTyped :: Word16 -> Q (TExp Word16) #

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 Unsigned Word16 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Word32 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word32 #

uniformR :: Generator g m => (Word32, Word32) -> g -> m Word32 #

uniformB :: Generator g m => Word32 -> g -> m Word32 #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Uniform Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word32 #

UniformRange Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word32, Word32) -> g -> m 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.IR.Prop.Constants

IsPrimValue Word32 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Word32 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

liftTyped :: Word32 -> Q (TExp Word32) #

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 Unsigned Word32 
Instance details

Defined in System.Random.PCG.Class

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

Instances details
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

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

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

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 -> () #

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 #

Variate Word64 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word64 #

uniformR :: Generator g m => (Word64, Word64) -> g -> m Word64 #

uniformB :: Generator g m => Word64 -> g -> m Word64 #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Uniform Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word64 #

UniformRange Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word64, Word64) -> g -> m Word64 #

ByteSource Word64 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

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

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

IsValue Word64 Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

IsPrimValue Word64 Source # 
Instance details

Defined in Language.Futhark.Syntax

GetValue Word64 Source # 
Instance details

Defined in Futhark.Test.Values

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

liftTyped :: Word64 -> Q (TExp Word64) #

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 Unsigned Word64 
Instance details

Defined in System.Random.PCG.Class

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word64 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word64 g = Takes8Bytes g
newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

srclocOf :: Located a => a -> SrcLoc #

The SrcLoc of a Located value.

data Loc #

Location type, consisting of a beginning position and an end position.

Instances

Instances details
Eq Loc 
Instance details

Defined in Data.Loc

Methods

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

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

Data Loc 
Instance details

Defined in Data.Loc

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc #

toConstr :: Loc -> Constr #

dataTypeOf :: Loc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Loc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) #

gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

Read Loc 
Instance details

Defined in Data.Loc

Show Loc 
Instance details

Defined in Data.Loc

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Semigroup Loc 
Instance details

Defined in Data.Loc

Methods

(<>) :: Loc -> Loc -> Loc #

sconcat :: NonEmpty Loc -> Loc #

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

Monoid Loc 
Instance details

Defined in Data.Loc

Methods

mempty :: Loc #

mappend :: Loc -> Loc -> Loc #

mconcat :: [Loc] -> Loc #

Pretty Loc 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Loc -> Doc #

pprPrec :: Int -> Loc -> Doc #

pprList :: [Loc] -> Doc #

IsLocation Loc 
Instance details

Defined in Data.Loc

Methods

fromLoc :: Loc -> Loc #

fromPos :: Pos -> Loc #

Located Loc 
Instance details

Defined in Data.Loc

Methods

locOf :: Loc -> Loc #

locOfList :: [Loc] -> Loc #

data SrcLoc #

Source location type. Source location are all equal, which allows AST nodes to be compared modulo location information.

Instances

Instances details
Eq SrcLoc 
Instance details

Defined in Data.Loc

Methods

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

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

Data SrcLoc 
Instance details

Defined in Data.Loc

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcLoc -> c SrcLoc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcLoc #

toConstr :: SrcLoc -> Constr #

dataTypeOf :: SrcLoc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcLoc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc) #

gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcLoc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcLoc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc #

Ord SrcLoc 
Instance details

Defined in Data.Loc

Read SrcLoc 
Instance details

Defined in Data.Loc

Show SrcLoc 
Instance details

Defined in Data.Loc

Semigroup SrcLoc 
Instance details

Defined in Data.Loc

Monoid SrcLoc 
Instance details

Defined in Data.Loc

IsLocation SrcLoc 
Instance details

Defined in Data.Loc

Methods

fromLoc :: Loc -> SrcLoc #

fromPos :: Pos -> SrcLoc #

Located SrcLoc 
Instance details

Defined in Data.Loc

Methods

locOf :: SrcLoc -> Loc #

locOfList :: [SrcLoc] -> Loc #

ToIdent (SrcLoc -> Id) 
Instance details

Defined in Language.C.Quote.Base

Methods

toIdent :: (SrcLoc -> Id) -> SrcLoc -> Id #

class Located a where #

Located values have a location.

Minimal complete definition

locOf

Methods

locOf :: a -> Loc #

locOfList :: [a] -> Loc #

Instances

Instances details
Located Id 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Id -> Loc #

locOfList :: [Id] -> Loc #

Located StringLit 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: StringLit -> Loc #

locOfList :: [StringLit] -> Loc #

Located Storage 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Storage -> Loc #

locOfList :: [Storage] -> Loc #

Located TypeQual 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: TypeQual -> Loc #

locOfList :: [TypeQual] -> Loc #

Located Sign 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Sign -> Loc #

locOfList :: [Sign] -> Loc #

Located TypeSpec 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: TypeSpec -> Loc #

locOfList :: [TypeSpec] -> Loc #

Located DeclSpec 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: DeclSpec -> Loc #

locOfList :: [DeclSpec] -> Loc #

Located ArraySize 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ArraySize -> Loc #

locOfList :: [ArraySize] -> Loc #

Located Decl 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Decl -> Loc #

locOfList :: [Decl] -> Loc #

Located Type 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Type -> Loc #

locOfList :: [Type] -> Loc #

Located Designator 
Instance details

Defined in Language.C.Syntax

Located Designation 
Instance details

Defined in Language.C.Syntax

Located Initializer 
Instance details

Defined in Language.C.Syntax

Located Init 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Init -> Loc #

locOfList :: [Init] -> Loc #

Located Typedef 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Typedef -> Loc #

locOfList :: [Typedef] -> Loc #

Located InitGroup 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: InitGroup -> Loc #

locOfList :: [InitGroup] -> Loc #

Located Field 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Field -> Loc #

locOfList :: [Field] -> Loc #

Located FieldGroup 
Instance details

Defined in Language.C.Syntax

Located CEnum 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: CEnum -> Loc #

locOfList :: [CEnum] -> Loc #

Located Attr 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Attr -> Loc #

locOfList :: [Attr] -> Loc #

Located Param 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Param -> Loc #

locOfList :: [Param] -> Loc #

Located Params 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Params -> Loc #

locOfList :: [Params] -> Loc #

Located Func 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Func -> Loc #

locOfList :: [Func] -> Loc #

Located Definition 
Instance details

Defined in Language.C.Syntax

Located Stm 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Stm -> Loc #

locOfList :: [Stm] -> Loc #

Located BlockItem 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: BlockItem -> Loc #

locOfList :: [BlockItem] -> Loc #

Located Const 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Const -> Loc #

locOfList :: [Const] -> Loc #

Located Exp 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: Exp -> Loc #

locOfList :: [Exp] -> Loc #

Located BlockType 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: BlockType -> Loc #

locOfList :: [BlockType] -> Loc #

Located ObjCIvarDecl 
Instance details

Defined in Language.C.Syntax

Located ObjCVisibilitySpec 
Instance details

Defined in Language.C.Syntax

Located ObjCIfaceDecl 
Instance details

Defined in Language.C.Syntax

Located ObjCPropAttr 
Instance details

Defined in Language.C.Syntax

Located ObjCMethodReq 
Instance details

Defined in Language.C.Syntax

Located ObjCParam 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ObjCParam -> Loc #

locOfList :: [ObjCParam] -> Loc #

Located ObjCMethodProto 
Instance details

Defined in Language.C.Syntax

Located ObjCCatch 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ObjCCatch -> Loc #

locOfList :: [ObjCCatch] -> Loc #

Located ObjCDictElem 
Instance details

Defined in Language.C.Syntax

Located ObjCRecv 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ObjCRecv -> Loc #

locOfList :: [ObjCRecv] -> Loc #

Located ObjCArg 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ObjCArg -> Loc #

locOfList :: [ObjCArg] -> Loc #

Located LambdaIntroducer 
Instance details

Defined in Language.C.Syntax

Located LambdaDeclarator 
Instance details

Defined in Language.C.Syntax

Located ExeConfig 
Instance details

Defined in Language.C.Syntax

Methods

locOf :: ExeConfig -> Loc #

locOfList :: [ExeConfig] -> Loc #

Located Pos 
Instance details

Defined in Data.Loc

Methods

locOf :: Pos -> Loc #

locOfList :: [Pos] -> Loc #

Located Loc 
Instance details

Defined in Data.Loc

Methods

locOf :: Loc -> Loc #

locOfList :: [Loc] -> Loc #

Located SrcLoc 
Instance details

Defined in Data.Loc

Methods

locOf :: SrcLoc -> Loc #

locOfList :: [SrcLoc] -> Loc #

Located DocComment Source # 
Instance details

Defined in Language.Futhark.Syntax

Located ImportName Source # 
Instance details

Defined in Language.Futhark.Semantic

Located StackFrame Source # 
Instance details

Defined in Language.Futhark.Interpreter

Located Constraint Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Unify

Located Usage Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Unify

Methods

locOf :: Usage -> Loc #

locOfList :: [Usage] -> Loc #

Located a => Located [a] 
Instance details

Defined in Data.Loc

Methods

locOf :: [a] -> Loc #

locOfList :: [[a]] -> Loc #

Located a => Located (Maybe a) 
Instance details

Defined in Data.Loc

Methods

locOf :: Maybe a -> Loc #

locOfList :: [Maybe a] -> Loc #

Located (L a) 
Instance details

Defined in Data.Loc

Methods

locOf :: L a -> Loc #

locOfList :: [L a] -> Loc #

Located (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeParamBase vn -> Loc #

locOfList :: [TypeParamBase vn] -> Loc #

Located a => Located (Inclusiveness a) Source # 
Instance details

Defined in Language.Futhark.Syntax

Located (TypeArgExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeArgExp vn -> Loc #

locOfList :: [TypeArgExp vn] -> Loc #

Located (TypeExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeExp vn -> Loc #

locOfList :: [TypeExp vn] -> Loc #

Located (L a) Source # 
Instance details

Defined in Language.Futhark.Parser.Lexer

Methods

locOf :: L a -> Loc #

locOfList :: [L a] -> Loc #

Located (DecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: DecBase f vn -> Loc #

locOfList :: [DecBase f vn] -> Loc #

Located (ModParamBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModParamBase f vn -> Loc #

locOfList :: [ModParamBase f vn] -> Loc #

Located (ModBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModBindBase f vn -> Loc #

locOfList :: [ModBindBase f vn] -> Loc #

Located (ModExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModExpBase f vn -> Loc #

locOfList :: [ModExpBase f vn] -> Loc #

Located (SigBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SigBindBase f vn -> Loc #

locOfList :: [SigBindBase f vn] -> Loc #

Located (TypeRefBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeRefBase f vn -> Loc #

locOfList :: [TypeRefBase f vn] -> Loc #

Located (SigExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SigExpBase f vn -> Loc #

locOfList :: [SigExpBase f vn] -> Loc #

Located (SpecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SpecBase f vn -> Loc #

locOfList :: [SpecBase f vn] -> Loc #

Located (TypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeBindBase f vn -> Loc #

locOfList :: [TypeBindBase f vn] -> Loc #

Located (ValBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ValBindBase f vn -> Loc #

locOfList :: [ValBindBase f vn] -> Loc #

Located (PatternBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: PatternBase f vn -> Loc #

locOfList :: [PatternBase f vn] -> Loc #

Located (CaseBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: CaseBase f vn -> Loc #

locOfList :: [CaseBase f vn] -> Loc #

Located (FieldBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: FieldBase f vn -> Loc #

locOfList :: [FieldBase f vn] -> Loc #

Located (ExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ExpBase f vn -> Loc #

locOfList :: [ExpBase f vn] -> Loc #

Located (IdentBase ty vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: IdentBase ty vn -> Loc #

locOfList :: [IdentBase ty vn] -> Loc #

Located (TypeDeclBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeDeclBase f vn -> Loc #

locOfList :: [TypeDeclBase f vn] -> Loc #

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

Instances details
Eq ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Show ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: ConvOp -> Doc #

pprPrec :: Int -> ConvOp -> Doc #

pprList :: [ConvOp] -> Doc #

data CmpOp Source #

Comparison operators are like BinOps, but they always return a boolean value. 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

Instances details
Eq CmpOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord CmpOp Source # 
Instance details

Defined in Futhark.IR.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.IR.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Pretty CmpOp Source # 
Instance details

Defined in Futhark.IR.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 Overflow

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType Overflow

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType Overflow

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType Safety

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

UDivUp IntType Safety

Unsigned integer division. Rounds towards positive infinity.

SDiv IntType Safety

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

SDivUp IntType Safety

Signed integer division. Rounds towards positive infinity.

FDiv FloatType

Floating-point division.

FMod FloatType

Floating-point modulus.

UMod IntType Safety

Unsigned integer modulus; the countepart to UDiv.

SMod IntType Safety

Signed integer modulus; the countepart to SDiv.

SQuot IntType Safety

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

SRem IntType Safety

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

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

Instances details
Eq BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord BinOp Source # 
Instance details

Defined in Futhark.IR.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.IR.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: BinOp -> Doc #

pprPrec :: Int -> BinOp -> Doc #

pprList :: [BinOp] -> Doc #

data Safety Source #

Whether something is safe or unsafe (mostly function calls, and in the context of whether operations are dynamically checked). When we inline an Unsafe function, we remove all safety checks in its body. The Ord instance picks Unsafe as being less than Safe.

For operations like integer division, a safe division will not explode the computer in case of division by zero, but instead return some unspecified value. This always involves a run-time check, so generally the unsafe variant is what the compiler will insert, but guarded by an explicit assertion elsewhere. Safe operations are useful when the optimiser wants to move e.g. a division to a location where the divisor may be zero, but where the result will only be used when it is non-zero (so it doesn't matter what result is provided with a zero divisor, as long as the program keeps running).

Constructors

Unsafe 
Safe 

Instances

Instances details
Eq Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

Show Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

data Overflow Source #

What to do in case of arithmetic overflow. Futhark's semantics are that overflow does wraparound, but for generated code (like address arithmetic), it can be beneficial for overflow to be undefined behaviour, as it allows better optimisation of things such as GPU kernels.

Note that all values of this type are considered equal for Eq and Ord.

Instances

Instances details
Eq Overflow Source # 
Instance details

Defined in Futhark.IR.Primitive

Ord Overflow Source # 
Instance details

Defined in Futhark.IR.Primitive

Show Overflow Source # 
Instance details

Defined in Futhark.IR.Primitive

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.

FSignum FloatType

Floating-point sign function.

Instances

Instances details
Eq UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord UnOp Source # 
Instance details

Defined in Futhark.IR.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.IR.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Pretty UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: UnOp -> Doc #

pprPrec :: Int -> UnOp -> Doc #

pprList :: [UnOp] -> Doc #

data PrimValue Source #

Non-array values.

Constructors

IntValue !IntValue 
FloatValue !FloatValue 
BoolValue !Bool 
Checked

The only value of type cert.

Instances

Instances details
Eq PrimValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Ord PrimValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Show PrimValue Source # 
Instance details

Defined in Futhark.IR.Primitive

ToExp PrimValue Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: PrimValue -> SrcLoc -> Exp #

Pretty PrimValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: PrimValue -> Doc #

pprPrec :: Int -> PrimValue -> Doc #

pprList :: [PrimValue] -> Doc #

IsValue PrimValue Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

data FloatValue Source #

A floating-point value.

data IntValue Source #

An integer value.

Instances

Instances details
Eq IntValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Ord IntValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Show IntValue Source # 
Instance details

Defined in Futhark.IR.Primitive

ToExp IntValue Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: IntValue -> SrcLoc -> Exp #

Pretty IntValue Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: IntValue -> Doc #

pprPrec :: Int -> IntValue -> Doc #

pprList :: [IntValue] -> Doc #

IsValue IntValue Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

data PrimType Source #

Low-level primitive types.

data FloatType Source #

A floating point type.

Constructors

Float32 
Float64 

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 

Instances

Instances details
Bounded IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Enum IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Eq IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Show IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Pretty IntType Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: IntType -> Doc #

pprPrec :: Int -> IntType -> Doc #

pprList :: [IntType] -> Doc #

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.

intValueType :: IntValue -> IntType Source #

The type of an integer value.

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.

floatValueType :: FloatValue -> FloatType Source #

The type of a floating-point value.

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.

doUnOp :: UnOp -> PrimValue -> Maybe PrimValue Source #

Apply an UnOp to an operand. Returns Nothing if the application is mistyped.

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.

doBinOp :: BinOp -> PrimValue -> PrimValue -> Maybe PrimValue Source #

Apply a BinOp to an operand. Returns Nothing if the application is mistyped, or outside the domain (e.g. division by zero).

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.

doConvOp :: ConvOp -> PrimValue -> Maybe PrimValue Source #

Apply a ConvOp to an operand. Returns Nothing if the application is mistyped.

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.

doCmpOp :: CmpOp -> PrimValue -> PrimValue -> Maybe Bool Source #

Apply a CmpOp to an operand. Returns Nothing if the application is mistyped.

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 Int64. 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?

zeroIshInt :: IntValue -> Bool Source #

Is the given integer value kind of zero?

oneIshInt :: IntValue -> Bool Source #

Is the given integer value kind of one?

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.

convOpFun :: ConvOp -> String Source #

The human-readable name for a ConvOp. This is used to expose the ConvOp in the intrinsics module of a Futhark program.

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

Instances details
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.SimpleRep

Methods

toIdent :: VName -> SrcLoc -> Id #

ToExp VName Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: VName -> SrcLoc -> Exp #

Pretty VName Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: VName -> Doc #

pprPrec :: Int -> VName -> Doc #

pprList :: [VName] -> Doc #

FreeIn VName Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: VName -> FV Source #

Substitute VName Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename VName Source # 
Instance details

Defined in Futhark.Transform.Rename

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

Substitutable Pattern Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

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

Defined in Futhark.IR.Prop.Scope

Methods

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

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

Defined in Futhark.IR.Prop.Scope

Methods

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

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

Defined in Futhark.IR.Prop.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, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.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, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.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, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.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, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.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 #

Eq (QualName VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (TypeArgExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (TypeExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (DimExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (QualName VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (TypeArgExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (TypeExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (DimExp VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

ArrayDim (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

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 (DimExp VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> DimExp VName -> m (DimExp 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 #

Substitutable (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

ToExp (PrimExp VName) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

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

Defined in Futhark.IR.Prop.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 #

Eq (PatternBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (LoopFormBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (CaseBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (FieldBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (ExpBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (DimIndexBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (TypeDeclBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (PatternBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (LoopFormBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (CaseBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (FieldBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (ExpBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (DimIndexBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (TypeDeclBase NoInfo VName) Source # 
Instance details

Defined in Language.Futhark.Syntax

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

Instances details
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.SimpleRep

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 #

Eq (QualName Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (TypeArgExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (TypeExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (DimExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq (DimDecl Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (QualName Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (TypeArgExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (TypeExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (DimExp Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord (DimDecl Name) Source # 
Instance details

Defined in Language.Futhark.Syntax

data Commutativity Source #

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

Instances

Instances details
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.IR.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

Instances details
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.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

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 :: Located a => a -> 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).

locStrRel :: (Located a, Located b) => a -> b -> String Source #

Like locStr, but locStrRel prev now prints the location now with the file name left out if the same as prev. This is useful when printing messages that are all in the context of some initially printed location (e.g. the first mention contains the file name; the rest just line and column name).

prettyStacktrace :: Int -> [String] -> String Source #

Given a list of strings representing entries in the stack trace and the index of the frame to highlight, produce a final newline-terminated string for showing to the user. This string should also be preceded by a newline. The most recent stack frame must come first in the list.

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.

quote :: String -> String Source #

Enclose a string in the prefered quotes used in error messages. These are picked to not collide with characters permitted in identifiers.

pquote :: Doc -> Doc Source #

As quote, but works on prettyprinted representation.

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString String

A literal string.

ErrorInt32 a

A run-time integer value.

ErrorInt64 a

A bigger run-time integer value.

Instances

Instances details
Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

foldMap :: Monoid m => (a -> m) -> ErrorMsgPart a -> 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.IR.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.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.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

Instances details
Functor ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

foldMap :: Monoid m => (a -> m) -> ErrorMsg a -> 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.IR.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.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.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.IR.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.IR.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

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

Defined in Futhark.IR.Pretty

Methods

ppr :: ErrorMsg a -> Doc #

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

pprList :: [ErrorMsg a] -> Doc #

data SubExp Source #

A subexpression is either a scalar constant or a variable. One important property is that evaluation of a subexpression is guaranteed to complete in constant time.

Constructors

Constant PrimValue 
Var VName 

Instances

Instances details
Eq SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Show SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: SubExp -> SrcLoc -> Exp #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: SubExp -> Doc #

pprPrec :: Int -> SubExp -> Doc #

pprList :: [SubExp] -> Doc #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Shape -> Doc #

pprPrec :: Int -> Shape -> Doc #

pprList :: [Shape] -> Doc #

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

fixExt :: Int -> SubExp -> ExtSize -> ExtSize Source #

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

setType :: Type -> Type -> Type Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

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

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Pretty u => Pretty (TypeBase ExtShape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Pretty u => Pretty (TypeBase Shape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: TypeBase Shape u -> Doc #

pprPrec :: Int -> TypeBase Shape u -> Doc #

pprList :: [TypeBase Shape u] -> Doc #

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

Defined in Futhark.IR.Mem

Methods

fixExt :: Int -> SubExp -> MemInfo ExtSize u ret -> MemInfo ExtSize u ret Source #

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

Defined in Futhark.IR.Mem

FixExt ret => ExtTyped (MemInfo ExtSize NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

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 
ScalarSpace [SubExp] PrimType

A special kind of memory that is a statically sized array of some primitive type. Used for private memory on GPUs.

Instances

Instances details
Eq Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.IR.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.IR.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Space -> Doc #

pprPrec :: Int -> Space -> Doc #

pprList :: [Space] -> Doc #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

Simplifiable Space Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

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

errorMsgArgTypes :: ErrorMsg a -> [PrimType] Source #

How many non-constant parts does the error message have, and what is their type?

class FreeIn dec => FreeDec dec where Source #

Either return precomputed free names stored in the attribute, or the freshly computed names. Relies on lazy evaluation to avoid the work.

Minimal complete definition

Nothing

Methods

precomputed :: dec -> FV -> FV Source #

Instances

Instances details
FreeDec () Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: () -> FV -> FV Source #

FreeDec Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: Names -> FV -> FV Source #

FreeDec AliasDec Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

precomputed :: AliasDec -> FV -> FV Source #

FreeDec ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

precomputed :: ExpWisdom -> FV -> FV Source #

FreeDec a => FreeDec [a] Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: [a] -> FV -> FV Source #

FreeDec a => FreeDec (Maybe a) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: Maybe a -> FV -> FV Source #

(FreeDec a, FreeIn b) => FreeDec (a, b) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: (a, b) -> FV -> FV Source #

class FreeIn a where Source #

A class indicating that we can obtain free variable information from values of this type.

Minimal complete definition

Nothing

Methods

freeIn' :: a -> FV Source #

Instances

Instances details
FreeIn Bool Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Bool -> FV Source #

FreeIn Int Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Int -> FV Source #

FreeIn () Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: () -> FV Source #

FreeIn VName Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: VName -> FV Source #

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

FreeIn Certificates Source # 
Instance details

Defined in Futhark.IR.Prop.Names

FreeIn Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ident -> FV Source #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

FreeIn Attrs Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Attrs -> FV Source #

FreeIn FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FV -> FV Source #

FreeIn Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Names -> FV Source #

FreeIn AliasDec Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

freeIn' :: AliasDec -> FV Source #

FreeIn ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

freeIn' :: ExpWisdom -> FV Source #

FreeIn VarWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

freeIn' :: VarWisdom -> FV Source #

FreeIn Indexed Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

freeIn' :: Indexed -> FV Source #

FreeIn MemReturn Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemReturn -> FV Source #

FreeIn MemBind Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemBind -> FV Source #

FreeIn KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

FreeIn SplitOrdering Source # 
Instance details

Defined in Futhark.IR.SegOp

FreeIn LoopNesting Source # 
Instance details

Defined in Futhark.Pass.ExtractKernels.Distribution

FreeIn SizeOp Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: SizeOp -> FV Source #

FreeIn SegLevel Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: SegLevel -> FV Source #

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Arg -> FV Source #

FreeIn ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ExpLeaf -> FV Source #

FreeIn ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

FreeIn ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ValueDesc -> FV Source #

FreeIn Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

FreeIn ParallelTask Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

FreeIn SchedulerInfo Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

FreeIn AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

freeIn' :: AtomicOp -> FV Source #

FreeIn Multicore Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

freeIn' :: Multicore -> FV Source #

FreeIn AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: AtomicOp -> FV Source #

FreeIn KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: KernelOp -> FV Source #

FreeIn Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: Kernel -> FV Source #

FreeIn HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: HostOp -> FV Source #

FreeIn a => FreeIn [a] Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: [a] -> FV Source #

FreeIn a => FreeIn (Maybe a) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Maybe a -> FV Source #

FreeIn dec => FreeIn (PatElemT dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElemT dec -> FV Source #

FreeIn d => FreeIn (DimIndex d) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimIndex d -> FV Source #

FreeIn dec => FreeIn (Param dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Param dec -> FV Source #

FreeIn d => FreeIn (Ext d) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ext d -> FV Source #

FreeIn d => FreeIn (ShapeBase d) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: ShapeBase d -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (RetType lore), FreeIn (Op lore)) => FreeIn (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FunDef lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Lambda lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Lambda lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Exp lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Exp lore -> FV Source #

FreeIn a => FreeIn (IfDec a) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: IfDec a -> FV Source #

FreeIn (LParamInfo lore) => FreeIn (LoopForm lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: LoopForm lore -> FV Source #

FreeIn d => FreeIn (DimChange d) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimChange d -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Body lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Body lore -> FV Source #

FreeIn (Stm lore) => FreeIn (Stms lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stms lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stm lore -> FV Source #

FreeIn dec => FreeIn (StmAux dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: StmAux dec -> FV Source #

FreeIn dec => FreeIn (PatternT dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatternT dec -> FV Source #

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

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: PrimExp v -> FV Source #

FreeIn num => FreeIn (IxFun num) Source # 
Instance details

Defined in Futhark.IR.Mem.IxFun

Methods

freeIn' :: IxFun num -> FV Source #

FreeIn num => FreeIn (LMAD num) Source # 
Instance details

Defined in Futhark.IR.Mem.IxFun

Methods

freeIn' :: LMAD num -> FV Source #

ASTLore lore => FreeIn (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

freeIn' :: SOAC lore -> FV Source #

FreeIn inner => FreeIn (MemOp inner) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemOp inner -> FV Source #

ASTLore lore => FreeIn (KernelBody lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

freeIn' :: KernelBody lore -> FV Source #

FreeIn a => FreeIn (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Code a -> FV Source #

FreeIn a => FreeIn (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Functions a -> FV Source #

(FreeIn a, FreeIn b) => FreeIn (a, b) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: (a, b) -> FV Source #

FreeIn shape => FreeIn (TypeBase shape u) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: TypeBase shape u -> FV Source #

FreeIn v => FreeIn (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: TPrimExp t v -> FV Source #

FreeIn e => FreeIn (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

freeIn' :: Count u e -> FV Source #

(ASTLore lore, FreeIn (LParamInfo lore), FreeIn lvl) => FreeIn (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

freeIn' :: SegOp lvl lore -> FV Source #

(ASTLore lore, FreeIn op) => FreeIn (MCOp lore op) Source # 
Instance details

Defined in Futhark.IR.MC.Op

Methods

freeIn' :: MCOp lore op -> FV Source #

(ASTLore lore, FreeIn op) => FreeIn (HostOp lore op) Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: HostOp lore op -> FV Source #

(FreeIn a, FreeIn b, FreeIn c) => FreeIn (a, b, c) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: (a, b, c) -> FV Source #

(FreeIn d, FreeIn ret) => FreeIn (MemInfo d u ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemInfo d u ret -> FV Source #

data FV Source #

A computation to build a free variable set.

Instances

Instances details
Semigroup FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

(<>) :: FV -> FV -> FV #

sconcat :: NonEmpty FV -> FV #

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

Monoid FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

mempty :: FV #

mappend :: FV -> FV -> FV #

mconcat :: [FV] -> FV #

FreeIn FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FV -> FV Source #

Substitute FV Source # 
Instance details

Defined in Futhark.Transform.Substitute

data Names Source #

A set of names. Note that the Ord instance is a dummy that treats everything as EQ if ==, and otherwise LT.

Instances

Instances details
Eq Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

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

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

Ord Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

compare :: Names -> Names -> Ordering #

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

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

(>) :: Names -> Names -> Bool #

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

max :: Names -> Names -> Names #

min :: Names -> Names -> Names #

Show Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

showsPrec :: Int -> Names -> ShowS #

show :: Names -> String #

showList :: [Names] -> ShowS #

Semigroup Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

(<>) :: Names -> Names -> Names #

sconcat :: NonEmpty Names -> Names #

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

Monoid Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

mempty :: Names #

mappend :: Names -> Names -> Names #

mconcat :: [Names] -> Names #

Pretty Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

ppr :: Names -> Doc #

pprPrec :: Int -> Names -> Doc #

pprList :: [Names] -> Doc #

FreeDec Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

precomputed :: Names -> FV -> FV Source #

FreeIn Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Names -> FV Source #

Substitute Names Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Names Source # 
Instance details

Defined in Futhark.Transform.Rename

AliasesOf Names Source # 
Instance details

Defined in Futhark.IR.Prop.Aliases

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 #

namesIntMap :: Names -> IntMap VName Source #

Retrieve the data structure underlying the names representation.

nameIn :: VName -> Names -> Bool Source #

Does the set of names contain this name?

namesFromList :: [VName] -> Names Source #

Construct a name set from a list. Slow.

namesToList :: Names -> [VName] Source #

Turn a name set into a list of names. Slow.

oneName :: VName -> Names Source #

Construct a name set from a single name.

namesIntersection :: Names -> Names -> Names Source #

The intersection of two name sets.

namesIntersect :: Names -> Names -> Bool Source #

Do the two name sets intersect?

namesSubtract :: Names -> Names -> Names Source #

Subtract the latter name set from the former.

mapNames :: (VName -> VName) -> Names -> Names Source #

Map over the names in a set.

fvBind :: Names -> FV -> FV Source #

Consider a variable to be bound in the given FV computation.

fvName :: VName -> FV Source #

Take note of a variable reference.

fvNames :: Names -> FV Source #

Take note of a set of variable references.

freeInStmsAndRes :: (FreeIn (Op lore), FreeIn (LetDec lore), FreeIn (LParamInfo lore), FreeIn (FParamInfo lore), FreeDec (BodyDec lore), FreeDec (ExpDec lore)) => Stms lore -> Result -> FV Source #

Return the set of variable names that are free in the given statements and result. Filters away the names that are bound by the statements.

freeIn :: FreeIn a => a -> Names Source #

The free variables of some syntactic construct.

boundInBody :: Body lore -> Names Source #

The names bound by the bindings immediately in a Body.

boundByStm :: Stm lore -> Names Source #

The names bound by a binding.

boundByStms :: Stms lore -> Names Source #

The names bound by the bindings.

boundByLambda :: Lambda lore -> [VName] Source #

The names of the lambda parameters plus the index parameter.

class NumExp t => FloatExp t where Source #

The class of floating-point types that can be used for constructing TPrimExps.

Methods

fromRational' :: Rational -> TPrimExp t v Source #

Construct a typed expression from a rational.

Instances

Instances details
FloatExp Double Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

FloatExp Float Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

class NumExp t => IntExp t Source #

The class of integer types that can be used for constructing TPrimExps.

Instances

Instances details
IntExp Int8 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IntExp Int16 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IntExp Int32 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

IntExp Int64 Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

class NumExp t where Source #

The class of numeric types that can be used for constructing TPrimExps.

Methods

fromInteger' :: Integer -> TPrimExp t v Source #

Construct a typed expression from an integer.

fromBoolExp :: TPrimExp Bool v -> TPrimExp t v Source #

Construct a numeric expression from a boolean expression. This can be used to encode arithmetic control flow.

newtype TPrimExp t v Source #

A PrimExp tagged with a phantom type used to provide type-safe construction. Does not guarantee that the underlying expression is actually type correct.

Constructors

TPrimExp 

Fields

Instances

Instances details
Functor (TPrimExp t) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

fmap :: (a -> b) -> TPrimExp t a -> TPrimExp t b #

(<$) :: a -> TPrimExp t b -> TPrimExp t a #

Foldable (TPrimExp t) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

fold :: Monoid m => TPrimExp t m -> m #

foldMap :: Monoid m => (a -> m) -> TPrimExp t a -> m #

foldMap' :: Monoid m => (a -> m) -> TPrimExp t a -> m #

foldr :: (a -> b -> b) -> b -> TPrimExp t a -> b #

foldr' :: (a -> b -> b) -> b -> TPrimExp t a -> b #

foldl :: (b -> a -> b) -> b -> TPrimExp t a -> b #

foldl' :: (b -> a -> b) -> b -> TPrimExp t a -> b #

foldr1 :: (a -> a -> a) -> TPrimExp t a -> a #

foldl1 :: (a -> a -> a) -> TPrimExp t a -> a #

toList :: TPrimExp t a -> [a] #

null :: TPrimExp t a -> Bool #

length :: TPrimExp t a -> Int #

elem :: Eq a => a -> TPrimExp t a -> Bool #

maximum :: Ord a => TPrimExp t a -> a #

minimum :: Ord a => TPrimExp t a -> a #

sum :: Num a => TPrimExp t a -> a #

product :: Num a => TPrimExp t a -> a #

Traversable (TPrimExp t) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

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

sequenceA :: Applicative f => TPrimExp t (f a) -> f (TPrimExp t a) #

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

sequence :: Monad m => TPrimExp t (m a) -> m (TPrimExp t a) #

Eq v => Eq (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(==) :: TPrimExp t v -> TPrimExp t v -> Bool #

(/=) :: TPrimExp t v -> TPrimExp t v -> Bool #

Pretty v => Floating (TPrimExp Double v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Pretty v => Floating (TPrimExp Float v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

(FloatExp t, Pretty v) => Fractional (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(/) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

recip :: TPrimExp t v -> TPrimExp t v #

fromRational :: Rational -> TPrimExp t v #

(NumExp t, Pretty v) => Num (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(+) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

(-) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

(*) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

negate :: TPrimExp t v -> TPrimExp t v #

abs :: TPrimExp t v -> TPrimExp t v #

signum :: TPrimExp t v -> TPrimExp t v #

fromInteger :: Integer -> TPrimExp t v #

Ord v => Ord (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

compare :: TPrimExp t v -> TPrimExp t v -> Ordering #

(<) :: TPrimExp t v -> TPrimExp t v -> Bool #

(<=) :: TPrimExp t v -> TPrimExp t v -> Bool #

(>) :: TPrimExp t v -> TPrimExp t v -> Bool #

(>=) :: TPrimExp t v -> TPrimExp t v -> Bool #

max :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

min :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v #

Show v => Show (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

showsPrec :: Int -> TPrimExp t v -> ShowS #

show :: TPrimExp t v -> String #

showList :: [TPrimExp t v] -> ShowS #

Pretty v => Pretty (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

ppr :: TPrimExp t v -> Doc #

pprPrec :: Int -> TPrimExp t v -> Doc #

pprList :: [TPrimExp t v] -> Doc #

(IntExp t, Pretty v) => IntegralExp (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

quot :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

rem :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

div :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

mod :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

sgn :: TPrimExp t v -> Maybe Int Source #

divUp :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

FreeIn v => FreeIn (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: TPrimExp t v -> FV Source #

Substitute v => Substitute (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Transform.Substitute

ToExp v => ToExp (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp.Convert

Methods

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

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.

Note also that the Num instance assumes OverflowUndef semantics!

Instances

Instances details
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 #

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 #

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 #

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

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: PrimExp v -> FV 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 #

ToExp (PrimExp VName) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

isInt8 :: PrimExp v -> TPrimExp Int8 v Source #

This expression is of type Int8.

isInt16 :: PrimExp v -> TPrimExp Int16 v Source #

This expression is of type Int16.

isInt32 :: PrimExp v -> TPrimExp Int32 v Source #

This expression is of type Int32.

isInt64 :: PrimExp v -> TPrimExp Int64 v Source #

This expression is of type Int64.

isBool :: PrimExp v -> TPrimExp Bool v Source #

This is a boolean expression.

isF32 :: PrimExp v -> TPrimExp Float v Source #

This expression is of type Float.

isF64 :: PrimExp v -> TPrimExp Double v Source #

This expression is of type Double.

primExpSizeAtLeast :: Int -> PrimExp v -> Bool Source #

True if the PrimExp has at least this many nodes. This can be much more efficient than comparing with length for large PrimExps, as this function is lazy.

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.

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

Lifted logical conjunction.

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

Lifted logical conjunction.

(.<.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp Bool v infix 4 Source #

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

(.<=.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp Bool v infix 4 Source #

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

(.==.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp Bool v infix 4 Source #

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

(.>.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp Bool v infix 4 Source #

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

(.>=.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp Bool v infix 4 Source #

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

(.&.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

Lifted bitwise operators. The right-shift is logical, *not* arithmetic.

(.|.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

Lifted bitwise operators. The right-shift is logical, *not* arithmetic.

(.^.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

Lifted bitwise operators. The right-shift is logical, *not* arithmetic.

(.>>.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

Lifted bitwise operators. The right-shift is logical, *not* arithmetic.

(.<<.) :: TPrimExp t v -> TPrimExp t v -> TPrimExp t v Source #

Lifted bitwise operators. The right-shift is logical, *not* arithmetic.

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

Untyped smart constructor for sign extension that does a bit of constant folding.

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

Untyped smart constructor for zero extension that does a bit of constant folding.

evalPrimExp :: (Pretty v, MonadFail 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 :: TPrimExp Bool v Source #

Boolean-valued PrimExps.

false :: TPrimExp Bool v Source #

Boolean-valued PrimExps.

bNot :: TPrimExp Bool v -> TPrimExp Bool v Source #

Boolean negation smart constructor.

sMax32 :: TPrimExp Int32 v -> TPrimExp Int32 v -> TPrimExp Int32 v Source #

SMax on 32-bit integers.

sMin32 :: TPrimExp Int32 v -> TPrimExp Int32 v -> TPrimExp Int32 v Source #

SMin on 32-bit integers.

sMax64 :: TPrimExp Int64 v -> TPrimExp Int64 v -> TPrimExp Int64 v Source #

SMax on 64-bit integers.

sMin64 :: TPrimExp Int64 v -> TPrimExp Int64 v -> TPrimExp Int64 v Source #

SMin on 64-bit integers.

sExt32 :: IntExp t => TPrimExp t v -> TPrimExp Int32 v Source #

Sign-extend to 32 bit integer.

sExt64 :: IntExp t => TPrimExp t v -> TPrimExp Int64 v Source #

Sign-extend to 64 bit integer.

zExt32 :: IntExp t => TPrimExp t v -> TPrimExp Int32 v Source #

Zero-extend to 32 bit integer.

zExt64 :: IntExp t => TPrimExp t v -> TPrimExp Int64 v Source #

Zero-extend to 64 bit integer.

fMin64 :: TPrimExp Double v -> TPrimExp Double v -> TPrimExp Double v Source #

64-bit float minimum.

fMax64 :: TPrimExp Double v -> TPrimExp Double v -> TPrimExp Double v Source #

64-bit float maximum.

leafExpTypes :: Ord a => PrimExp a -> Set (a, PrimType) Source #

Produce a mapping from the leaves of the PrimExp to their designated types.

newtype Count u e Source #

A wrapper supporting a phantom type for indicating what we are counting.

Constructors

Count 

Fields

Instances

Instances details
Functor (Count u) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

fmap :: (a -> b) -> Count u a -> Count u b #

(<$) :: a -> Count u b -> Count u a #

Foldable (Count u) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

fold :: Monoid m => Count u m -> m #

foldMap :: Monoid m => (a -> m) -> Count u a -> m #

foldMap' :: Monoid m => (a -> m) -> Count u a -> m #

foldr :: (a -> b -> b) -> b -> Count u a -> b #

foldr' :: (a -> b -> b) -> b -> Count u a -> b #

foldl :: (b -> a -> b) -> b -> Count u a -> b #

foldl' :: (b -> a -> b) -> b -> Count u a -> b #

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

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

toList :: Count u a -> [a] #

null :: Count u a -> Bool #

length :: Count u a -> Int #

elem :: Eq a => a -> Count u a -> Bool #

maximum :: Ord a => Count u a -> a #

minimum :: Ord a => Count u a -> a #

sum :: Num a => Count u a -> a #

product :: Num a => Count u a -> a #

Traversable (Count u) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

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

sequenceA :: Applicative f => Count u (f a) -> f (Count u a) #

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

sequence :: Monad m => Count u (m a) -> m (Count u a) #

Eq e => Eq (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

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

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

Num e => Num (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

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

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

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

negate :: Count u e -> Count u e #

abs :: Count u e -> Count u e #

signum :: Count u e -> Count u e #

fromInteger :: Integer -> Count u e #

Ord e => Ord (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

compare :: Count u e -> Count u e -> Ordering #

(<) :: Count u e -> Count u e -> Bool #

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

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

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

max :: Count u e -> Count u e -> Count u e #

min :: Count u e -> Count u e -> Count u e #

Show e => Show (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

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

show :: Count u e -> String #

showList :: [Count u e] -> ShowS #

Pretty e => Pretty (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

ppr :: Count u e -> Doc #

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

pprList :: [Count u e] -> Doc #

IntegralExp e => IntegralExp (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

quot :: Count u e -> Count u e -> Count u e Source #

rem :: Count u e -> Count u e -> Count u e Source #

div :: Count u e -> Count u e -> Count u e Source #

mod :: Count u e -> Count u e -> Count u e Source #

sgn :: Count u e -> Maybe Int Source #

divUp :: Count u e -> Count u e -> Count u e Source #

FreeIn e => FreeIn (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

freeIn' :: Count u e -> FV Source #

Substitute e => Substitute (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

substituteNames :: Map VName VName -> Count u e -> Count u e Source #

data Bytes Source #

Phantom type for a count of bytes.

data Elements Source #

Phantom type for a count of elements.

data Arg Source #

A function call argument.

Constructors

ExpArg Exp 
MemArg VName 

Instances

Instances details
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 -> FV Source #

type TExp t = TPrimExp t ExpLeaf Source #

Like Exp, but with a required/known type.

type Exp = PrimExp ExpLeaf Source #

A side-effect free expression whose execution will produce a single primitive value.

data ExpLeaf Source #

The leaves of an Exp.

Constructors

ScalarVar VName

A scalar variable. The type is stored in the LeafExp constructor itself.

SizeOf PrimType

The size of a primitive type.

Index VName (Count Elements (TExp Int64)) PrimType Space Volatility

Reading a value from memory. The arguments have the same meaning as with Write.

Instances

Instances details
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 -> FV Source #

data Volatility Source #

The volatility of a memory access or variable. Feel free to ignore this for backends where it makes no sense (anything but C and similar low-level things)

Constructors

Volatile 
Nonvolatile 

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

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

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

Function call. The results are written to the provided VName variables.

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

Must be in same space.

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

Set a scalar variable.

pattern DeclareArray :: VName -> Space -> PrimType -> ArrayContents -> 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 DeclareScalar :: VName -> Volatility -> PrimType -> Code a Source #

Declare a scalar variable with an initially undefined value.

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

Declare a memory block variable that will point to memory in the given memory space. Note that this is distinct from allocation. The memory block must be the target of either an Allocate or a SetMem before it can be used for reading or writing.

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

Statement composition. Crucial for the Semigroup instance.

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

Assert that something must be true. Should it turn out not to be true, then report a failure along with the given error message.

pattern Copy :: VName -> Count Bytes (TExp Int64) -> Space -> VName -> Count Bytes (TExp Int64) -> Space -> Count Bytes (TExp Int64) -> Code a Source #

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

pattern Allocate :: VName -> Count Bytes (TExp Int64) -> Space -> Code a Source #

Memory space must match the corresponding DeclareMem.

pattern Skip :: Code a Source #

No-op. Crucial for the Monoid instance.

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

A for-loop iterating the given number of times. The loop parameter starts counting from zero and will have the same (integer) type as the bound. The bound is evaluated just once, before the loop is entered.

pattern While :: TExp Bool -> Code a -> Code a Source #

While loop. The conditional is (of course) re-evaluated before every iteration of the loop.

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 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 Write :: VName -> Count Elements (TExp Int64) -> PrimType -> Space -> Volatility -> Exp -> Code a Source #

Write mem i t space vol v writes the value v to mem offset by i elements of type t. The Space argument is the memory space of mem (technically redundant, but convenient). Note that reading is done with an Exp (Index).

pattern If :: TExp Bool -> Code a -> Code a -> Code a Source #

Conditional execution.

pattern Op :: a -> Code a Source #

Perform an extensible operation.

data ArrayContents Source #

The contents of a statically declared constant array. Such arrays are always unidimensional, and reshaped if necessary in the code that uses them.

Constructors

ArrayValues [PrimValue]

Precisely these values.

ArrayZeros Int

This many zeroes.

Instances

Instances details
Show ArrayContents Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ArrayContents Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

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

Instances details
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 #

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 

Instances

Instances details
Show ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

FreeIn ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

data ValueDesc Source #

A description of an externally meaningful value.

Constructors

ArrayValue VName Space PrimType Signedness [DimSize]

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

ScalarValue PrimType Signedness VName

A scalar value with signedness if applicable.

Instances

Instances details
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 #

FreeIn ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ValueDesc -> FV Source #

data Signedness Source #

Since the core language does not care for signedness, but the source language does, entry point input/output information has metadata for integer types (and arrays containing these) that indicate whether they are really unsigned integers.

Constructors

TypeUnsigned 
TypeDirect 

Instances

Instances details
Eq Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Show Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

data Constants a Source #

A collection of imperative constants.

Constructors

Constants 

Fields

  • constsDecl :: [Param]

    The constants that are made available to the functions.

  • constsInit :: Code a

    Setting the value of the constants. Note that this must not contain declarations of the names defined in constsDecl.

Instances

Instances details
Pretty op => Pretty (Constants op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Constants op -> Doc #

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

pprList :: [Constants op] -> Doc #

newtype Functions a Source #

A collection of imperative functions.

Constructors

Functions [(Name, Function a)] 

Instances

Instances details
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 #

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 #

FreeIn a => FreeIn (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Functions a -> FV Source #

data Definitions a Source #

A collection of imperative functions and constants.

Constructors

Definitions 

Instances

Instances details
Pretty op => Pretty (Definitions op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Definitions op -> Doc #

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

pprList :: [Definitions op] -> Doc #

data Param Source #

An ImpCode function parameter.

Instances

Instances details
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 #

type DimSize = SubExp Source #

The size of an array.

type MemSize = SubExp Source #

The size of a memory block.

paramName :: Param -> VName Source #

The name of a parameter.

lexicalMemoryUsage :: Function a -> Map VName Space Source #

Find those memory blocks that are used only lexically. That is, are not used as the source or target of a SetMem, or are the result of the function, nor passed as arguments to other functions. This is interesting because such memory blocks do not need reference counting, but can be managed in a purely stack-like fashion.

We do not look inside any Ops. We assume that no Op is going to SetMem a memory block declared outside it.

calledFuncs :: Code a -> Set Name Source #

The set of functions that are called by this code. Assumes there are no function calls in Ops.

elements :: a -> Count Elements a Source #

This expression counts elements.

bytes :: a -> Count Bytes a Source #

This expression counts bytes.

withElemType :: Count Elements (TExp Int64) -> PrimType -> Count Bytes (TExp Int64) Source #

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

var :: VName -> PrimType -> Exp Source #

Turn a VName into a ScalarVar.

index :: VName -> Count Elements (TExp Int64) -> PrimType -> Space -> Volatility -> Exp Source #

Concise wrapper for using Index.

declaredIn :: Code a -> Names Source #

The names declared with DeclareMem, DeclareScalar, and DeclareArray in the given code.