futhark-0.15.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.SOACS

Description

A simple representation with SOACs and nested parallelism.

Synopsis

The Lore definition

data SOACS Source #

The lore for the basic representation.

Instances

Instances details
Annotations SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

PrettyLore SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Attributes SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Bindable SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

BinderOps SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Checkable SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

CheckableOp SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

LocalScope SOACS TryFusion Source # 
Instance details

Defined in Futhark.Optimise.Fusion.TryFusion

LocalScope SOACS InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

HasScope SOACS TryFusion Source # 
Instance details

Defined in Futhark.Optimise.Fusion.TryFusion

HasScope SOACS InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

HasScope SOACS (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

lookupType :: VName -> ImpM lore r op Type Source #

lookupInfo :: VName -> ImpM lore r op (NameInfo SOACS) Source #

askScope :: ImpM lore r op (Scope SOACS) Source #

asksScope :: (Scope SOACS -> a) -> ImpM lore r op a Source #

BinderOps (Wise SOACS) Source # 
Instance details

Defined in Futhark.Representation.SOACS.Simplify

type LetAttr SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type ExpAttr SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type ExpAttr SOACS = ()
type BodyAttr SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type BodyAttr SOACS = ()
type FParamAttr SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type LParamAttr SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type RetType SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type BranchType SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

type Op SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Syntax types

Module re-exports

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 #

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

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Pretty Int8 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int8 -> Doc

pprPrec :: Int -> Int8 -> Doc

pprList :: [Int8] -> Doc

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int

hash :: Int8 -> Int

IsValue Int8 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

Methods

value :: Int8 -> PrimValue Source #

IsPrimValue Int8 Source # 
Instance details

Defined in Language.Futhark.Syntax

FromJSON Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int8

parseJSONList :: Value -> Parser [Int8]

FromJSONKey Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Int8

fromJSONKeyList :: FromJSONKeyFunction [Int8]

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int8 -> Value

toEncoding :: Int8 -> Encoding

toJSONList :: [Int8] -> Value

toEncodingList :: [Int8] -> Encoding

ToJSONKey Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Int8

toJSONKeyList :: ToJSONKeyFunction [Int8]

Random Int8 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Int8

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Int8 -> m (Vector Int8)

basicUnsafeThaw :: PrimMonad m => Vector Int8 -> m (Mutable Vector (PrimState m) Int8)

basicLength :: Vector Int8 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Int8 -> Vector Int8

basicUnsafeIndexM :: Monad m => Vector Int8 -> Int -> m Int8

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Int8 -> Vector Int8 -> m ()

elemseq :: Vector Int8 -> Int8 -> b -> b

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Int8 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Int8 -> MVector s Int8

basicOverlaps :: MVector s Int8 -> MVector s Int8 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Int8)

basicInitialize :: PrimMonad m => MVector (PrimState m) Int8 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Int8 -> m (MVector (PrimState m) Int8)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Int8 -> Int -> m Int8

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Int8 -> Int -> Int8 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Int8 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Int8 -> Int8 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Int8 -> MVector (PrimState m) Int8 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Int8 -> MVector (PrimState m) Int8 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Int8 -> Int -> m (MVector (PrimState m) Int8)

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

newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int8 = V_Int8 (Vector Int8)
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

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

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Pretty Int16 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int16 -> Doc

pprPrec :: Int -> Int16 -> Doc

pprList :: [Int16] -> Doc

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int

hash :: Int16 -> Int

IsValue Int16 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int16 Source # 
Instance details

Defined in Language.Futhark.Syntax

FromJSON Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int16

parseJSONList :: Value -> Parser [Int16]

FromJSONKey Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Int16

fromJSONKeyList :: FromJSONKeyFunction [Int16]

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int16 -> Value

toEncoding :: Int16 -> Encoding

toJSONList :: [Int16] -> Value

toEncodingList :: [Int16] -> Encoding

ToJSONKey Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Int16

toJSONKeyList :: ToJSONKeyFunction [Int16]

Random Int16 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Int16

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Int16 -> m (Vector Int16)

basicUnsafeThaw :: PrimMonad m => Vector Int16 -> m (Mutable Vector (PrimState m) Int16)

basicLength :: Vector Int16 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Int16 -> Vector Int16

basicUnsafeIndexM :: Monad m => Vector Int16 -> Int -> m Int16

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Int16 -> Vector Int16 -> m ()

elemseq :: Vector Int16 -> Int16 -> b -> b

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Int16 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Int16 -> MVector s Int16

basicOverlaps :: MVector s Int16 -> MVector s Int16 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Int16)

basicInitialize :: PrimMonad m => MVector (PrimState m) Int16 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Int16 -> m (MVector (PrimState m) Int16)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Int16 -> Int -> m Int16

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Int16 -> Int -> Int16 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Int16 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Int16 -> Int16 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Int16 -> MVector (PrimState m) Int16 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Int16 -> MVector (PrimState m) Int16 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Int16 -> Int -> m (MVector (PrimState m) Int16)

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

newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 = V_Int16 (Vector Int16)
newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 = MV_Int16 (MVector s Int16)

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

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 #

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

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Pretty Int32 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int32 -> Doc

pprPrec :: Int -> Int32 -> Doc

pprList :: [Int32] -> Doc

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int

hash :: Int32 -> Int

IsValue Int32 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int32 Source # 
Instance details

Defined in Language.Futhark.Syntax

ToMarkup Int32 
Instance details

Defined in Text.Blaze

Methods

toMarkup :: Int32 -> Markup

preEscapedToMarkup :: Int32 -> Markup

ToValue Int32 
Instance details

Defined in Text.Blaze

Methods

toValue :: Int32 -> AttributeValue

preEscapedToValue :: Int32 -> AttributeValue

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int32

parseJSONList :: Value -> Parser [Int32]

FromJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Int32

fromJSONKeyList :: FromJSONKeyFunction [Int32]

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int32 -> Value

toEncoding :: Int32 -> Encoding

toJSONList :: [Int32] -> Value

toEncodingList :: [Int32] -> Encoding

ToJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Int32

toJSONKeyList :: ToJSONKeyFunction [Int32]

Random Int32 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Int32

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Int32 -> m (Vector Int32)

basicUnsafeThaw :: PrimMonad m => Vector Int32 -> m (Mutable Vector (PrimState m) Int32)

basicLength :: Vector Int32 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Int32 -> Vector Int32

basicUnsafeIndexM :: Monad m => Vector Int32 -> Int -> m Int32

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Int32 -> Vector Int32 -> m ()

elemseq :: Vector Int32 -> Int32 -> b -> b

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Int32 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Int32 -> MVector s Int32

basicOverlaps :: MVector s Int32 -> MVector s Int32 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Int32)

basicInitialize :: PrimMonad m => MVector (PrimState m) Int32 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Int32 -> m (MVector (PrimState m) Int32)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Int32 -> Int -> m Int32

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Int32 -> Int -> Int32 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Int32 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Int32 -> Int32 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Int32 -> MVector (PrimState m) Int32 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Int32 -> MVector (PrimState m) Int32 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Int32 -> Int -> m (MVector (PrimState m) Int32)

Pretty (ShapeDecl Int32) 
Instance details

Defined in Language.Futhark.Pretty

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

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 = V_Int32 (Vector Int32)
newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 = MV_Int32 (MVector s Int32)

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

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 #

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

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Pretty Int64 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int64 -> Doc

pprPrec :: Int -> Int64 -> Doc

pprList :: [Int64] -> Doc

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int

hash :: Int64 -> Int

IsValue Int64 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Int64 Source # 
Instance details

Defined in Language.Futhark.Syntax

ToMarkup Int64 
Instance details

Defined in Text.Blaze

Methods

toMarkup :: Int64 -> Markup

preEscapedToMarkup :: Int64 -> Markup

ToValue Int64 
Instance details

Defined in Text.Blaze

Methods

toValue :: Int64 -> AttributeValue

preEscapedToValue :: Int64 -> AttributeValue

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int64

parseJSONList :: Value -> Parser [Int64]

FromJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Int64

fromJSONKeyList :: FromJSONKeyFunction [Int64]

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int64 -> Value

toEncoding :: Int64 -> Encoding

toJSONList :: [Int64] -> Value

toEncodingList :: [Int64] -> Encoding

ToJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Int64

toJSONKeyList :: ToJSONKeyFunction [Int64]

Random Int64 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Int64

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

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Int64 -> m (Vector Int64)

basicUnsafeThaw :: PrimMonad m => Vector Int64 -> m (Mutable Vector (PrimState m) Int64)

basicLength :: Vector Int64 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Int64 -> Vector Int64

basicUnsafeIndexM :: Monad m => Vector Int64 -> Int -> m Int64

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Int64 -> Vector Int64 -> m ()

elemseq :: Vector Int64 -> Int64 -> b -> b

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Int64 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Int64 -> MVector s Int64

basicOverlaps :: MVector s Int64 -> MVector s Int64 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Int64)

basicInitialize :: PrimMonad m => MVector (PrimState m) Int64 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Int64 -> m (MVector (PrimState m) Int64)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Int64 -> Int -> m Int64

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Int64 -> Int -> Int64 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Int64 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Int64 -> Int64 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Int64 -> MVector (PrimState m) Int64 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Int64 -> MVector (PrimState m) Int64 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Int64 -> Int -> m (MVector (PrimState m) Int64)

UTF8Bytes ByteString Int64 
Instance details

Defined in Codec.Binary.UTF8.Generic

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

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 = V_Int64 (Vector Int64)
newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 = MV_Int64 (MVector s Int64)

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

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

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word8 -> Doc

pprPrec :: Int -> Word8 -> Doc

pprList :: [Word8] -> Doc

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int

hash :: Word8 -> Int

IsValue Word8 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word8 Source # 
Instance details

Defined in Language.Futhark.Syntax

FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word8

parseJSONList :: Value -> Parser [Word8]

FromJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Word8

fromJSONKeyList :: FromJSONKeyFunction [Word8]

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word8 -> Value

toEncoding :: Word8 -> Encoding

toJSONList :: [Word8] -> Value

toEncodingList :: [Word8] -> Encoding

ToJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Word8

toJSONKeyList :: ToJSONKeyFunction [Word8]

ByteSource Word8 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

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

Random Word8 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Word8

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word8 -> m (Vector Word8)

basicUnsafeThaw :: PrimMonad m => Vector Word8 -> m (Mutable Vector (PrimState m) Word8)

basicLength :: Vector Word8 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word8 -> Vector Word8

basicUnsafeIndexM :: Monad m => Vector Word8 -> Int -> m Word8

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word8 -> Vector Word8 -> m ()

elemseq :: Vector Word8 -> Word8 -> b -> b

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Word8 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word8 -> MVector s Word8

basicOverlaps :: MVector s Word8 -> MVector s Word8 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word8)

basicInitialize :: PrimMonad m => MVector (PrimState m) Word8 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Word8 -> m (MVector (PrimState m) Word8)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word8 -> Int -> m Word8

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word8 -> Int -> Word8 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Word8 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Word8 -> Word8 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word8 -> MVector (PrimState m) Word8 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word8 -> MVector (PrimState m) Word8 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word8 -> Int -> m (MVector (PrimState m) Word8)

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

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 = V_Word8 (Vector Word8)
newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word8 = MV_Word8 (MVector s Word8)
type ByteSink Word8 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word8 g = Takes1Byte g

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

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

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Pretty Word16 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word16 -> Doc

pprPrec :: Int -> Word16 -> Doc

pprList :: [Word16] -> Doc

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int

hash :: Word16 -> Int

IsValue Word16 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word16 Source # 
Instance details

Defined in Language.Futhark.Syntax

FromJSON Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word16

parseJSONList :: Value -> Parser [Word16]

FromJSONKey Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Word16

fromJSONKeyList :: FromJSONKeyFunction [Word16]

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word16 -> Value

toEncoding :: Word16 -> Encoding

toJSONList :: [Word16] -> Value

toEncodingList :: [Word16] -> Encoding

ToJSONKey Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Word16

toJSONKeyList :: ToJSONKeyFunction [Word16]

ByteSource Word16 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

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

Random Word16 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Word16

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word16 -> m (Vector Word16)

basicUnsafeThaw :: PrimMonad m => Vector Word16 -> m (Mutable Vector (PrimState m) Word16)

basicLength :: Vector Word16 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word16 -> Vector Word16

basicUnsafeIndexM :: Monad m => Vector Word16 -> Int -> m Word16

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word16 -> Vector Word16 -> m ()

elemseq :: Vector Word16 -> Word16 -> b -> b

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Word16 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word16 -> MVector s Word16

basicOverlaps :: MVector s Word16 -> MVector s Word16 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word16)

basicInitialize :: PrimMonad m => MVector (PrimState m) Word16 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Word16 -> m (MVector (PrimState m) Word16)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word16 -> Int -> m Word16

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word16 -> Int -> Word16 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Word16 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Word16 -> Word16 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word16 -> MVector (PrimState m) Word16 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word16 -> MVector (PrimState m) Word16 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word16 -> Int -> m (MVector (PrimState m) Word16)

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

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 = V_Word16 (Vector Word16)
newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word16 = MV_Word16 (MVector s Word16)
type ByteSink Word16 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word16 g = Takes2Bytes g

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

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 #

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

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Pretty Word32 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word32 -> Doc

pprPrec :: Int -> Word32 -> Doc

pprList :: [Word32] -> Doc

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int

hash :: Word32 -> Int

IsValue Word32 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word32 Source # 
Instance details

Defined in Language.Futhark.Syntax

ToMarkup Word32 
Instance details

Defined in Text.Blaze

Methods

toMarkup :: Word32 -> Markup

preEscapedToMarkup :: Word32 -> Markup

ToValue Word32 
Instance details

Defined in Text.Blaze

Methods

toValue :: Word32 -> AttributeValue

preEscapedToValue :: Word32 -> AttributeValue

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word32

parseJSONList :: Value -> Parser [Word32]

FromJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Word32

fromJSONKeyList :: FromJSONKeyFunction [Word32]

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word32 -> Value

toEncoding :: Word32 -> Encoding

toJSONList :: [Word32] -> Value

toEncodingList :: [Word32] -> Encoding

ToJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Word32

toJSONKeyList :: ToJSONKeyFunction [Word32]

ByteSource Word32 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

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

Random Word32 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Word32

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word32 -> m (Vector Word32)

basicUnsafeThaw :: PrimMonad m => Vector Word32 -> m (Mutable Vector (PrimState m) Word32)

basicLength :: Vector Word32 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word32 -> Vector Word32

basicUnsafeIndexM :: Monad m => Vector Word32 -> Int -> m Word32

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word32 -> Vector Word32 -> m ()

elemseq :: Vector Word32 -> Word32 -> b -> b

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Word32 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word32 -> MVector s Word32

basicOverlaps :: MVector s Word32 -> MVector s Word32 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word32)

basicInitialize :: PrimMonad m => MVector (PrimState m) Word32 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Word32 -> m (MVector (PrimState m) Word32)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> m Word32

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> Word32 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Word32 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Word32 -> Word32 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word32 -> MVector (PrimState m) Word32 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word32 -> MVector (PrimState m) Word32 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> m (MVector (PrimState m) Word32)

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

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 = V_Word32 (Vector Word32)
newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 = MV_Word32 (MVector s Word32)
type ByteSink Word32 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word32 g = Takes4Bytes g

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

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 #

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

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Pretty Word64 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Word64 -> Doc

pprPrec :: Int -> Word64 -> Doc

pprList :: [Word64] -> Doc

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int

hash :: Word64 -> Int

IsValue Word64 Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

IsPrimValue Word64 Source # 
Instance details

Defined in Language.Futhark.Syntax

ToMarkup Word64 
Instance details

Defined in Text.Blaze

Methods

toMarkup :: Word64 -> Markup

preEscapedToMarkup :: Word64 -> Markup

ToValue Word64 
Instance details

Defined in Text.Blaze

Methods

toValue :: Word64 -> AttributeValue

preEscapedToValue :: Word64 -> AttributeValue

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word64

parseJSONList :: Value -> Parser [Word64]

FromJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Word64

fromJSONKeyList :: FromJSONKeyFunction [Word64]

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word64 -> Value

toEncoding :: Word64 -> Encoding

toJSONList :: [Word64] -> Value

toEncodingList :: [Word64] -> Encoding

ToJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Word64

toJSONKeyList :: ToJSONKeyFunction [Word64]

Random Word64 
Instance details

Defined in System.Random

Methods

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

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

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

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

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

randomIO :: IO Word64

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

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word64 -> m (Vector Word64)

basicUnsafeThaw :: PrimMonad m => Vector Word64 -> m (Mutable Vector (PrimState m) Word64)

basicLength :: Vector Word64 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word64 -> Vector Word64

basicUnsafeIndexM :: Monad m => Vector Word64 -> Int -> m Word64

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word64 -> Vector Word64 -> m ()

elemseq :: Vector Word64 -> Word64 -> b -> b

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Word64 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word64 -> MVector s Word64

basicOverlaps :: MVector s Word64 -> MVector s Word64 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word64)

basicInitialize :: PrimMonad m => MVector (PrimState m) Word64 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Word64 -> m (MVector (PrimState m) Word64)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word64 -> Int -> m Word64

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word64 -> Int -> Word64 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Word64 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Word64 -> Word64 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word64 -> MVector (PrimState m) Word64 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word64 -> MVector (PrimState m) Word64 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word64 -> Int -> m (MVector (PrimState m) Word64)

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

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word64 = V_Word64 (Vector Word64)
newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 = MV_Word64 (MVector s Word64)

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.Representation.Primitive

Methods

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

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

Ord ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: ConvOp -> Doc

pprPrec :: Int -> ConvOp -> Doc

pprList :: [ConvOp] -> Doc

data CmpOp Source #

Comparison operators are like BinOps, but they return Bools. 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.Representation.Primitive

Methods

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

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

Ord CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: CmpOp -> CmpOp -> Ordering #

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

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

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

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

max :: CmpOp -> CmpOp -> CmpOp #

min :: CmpOp -> CmpOp -> CmpOp #

Show CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Pretty CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: CmpOp -> Doc

pprPrec :: Int -> CmpOp -> Doc

pprList :: [CmpOp] -> Doc

data BinOp Source #

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

Constructors

Add IntType

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType

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

SDiv IntType

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

FDiv FloatType

Floating-point division.

FMod FloatType

Floating-point modulus.

UMod IntType

Unsigned integer modulus; the countepart to UDiv.

SMod IntType

Signed integer modulus; the countepart to SDiv.

SQuot IntType

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

SRem IntType

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

SMin IntType

Returns the smallest of two signed integers.

UMin IntType

Returns the smallest of two unsigned integers.

FMin FloatType

Returns the smallest of two floating-point numbers.

SMax IntType

Returns the greatest of two signed integers.

UMax IntType

Returns the greatest of two unsigned integers.

FMax FloatType

Returns the greatest of two floating-point numbers.

Shl IntType

Left-shift.

LShr IntType

Logical right-shift, zero-extended.

AShr IntType

Arithmetic right-shift, sign-extended.

And IntType

Bitwise and.

Or IntType

Bitwise or.

Xor IntType

Bitwise exclusive-or.

Pow IntType

Integer exponentiation.

FPow FloatType

Floating-point exponentiation.

LogAnd

Boolean and - not short-circuiting.

LogOr

Boolean or - not short-circuiting.

Instances

Instances details
Eq BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

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

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

Ord BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: BinOp -> BinOp -> Ordering #

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

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

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

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

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

Show BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: BinOp -> Doc

pprPrec :: Int -> BinOp -> Doc

pprList :: [BinOp] -> Doc

data UnOp Source #

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

Constructors

Not

E.g., ! True == False.

Complement IntType

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

Abs IntType

abs(-2) = 2.

FAbs FloatType

fabs(-2.0) = 2.0.

SSignum IntType

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

USignum IntType

Unsigned sign function: usignum(2) = 1.

Instances

Instances details
Eq UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

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

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

Ord UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: UnOp -> UnOp -> Ordering #

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

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

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

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

max :: UnOp -> UnOp -> UnOp #

min :: UnOp -> UnOp -> UnOp #

Show UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Pretty UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: UnOp -> Doc

pprPrec :: Int -> UnOp -> Doc

pprList :: [UnOp] -> Doc

data PrimValue Source #

Non-array values.

Constructors

IntValue !IntValue 
FloatValue !FloatValue 
BoolValue !Bool 
Checked

The only value of type cert.

data IntValue Source #

An integer value.

Instances

Instances details
Eq IntValue Source # 
Instance details

Defined in Futhark.Representation.Primitive

Ord IntValue Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show IntValue Source # 
Instance details

Defined in Futhark.Representation.Primitive

ToExp IntValue 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toExp :: IntValue -> SrcLoc -> Exp

Pretty IntValue Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: IntValue -> Doc

pprPrec :: Int -> IntValue -> Doc

pprList :: [IntValue] -> Doc

IsValue IntValue Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Constants

data PrimType Source #

Low-level primitive types.

data FloatType Source #

A floating point type.

Constructors

Float32 
Float64 

Instances

Instances details
Bounded FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Enum FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Eq FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Ord FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

data IntType Source #

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

Constructors

Int8 
Int16 
Int32 
Int64 

allIntTypes :: [IntType] Source #

A list of all integer types.

allFloatTypes :: [FloatType] Source #

A list of all floating-point types.

allPrimTypes :: [PrimType] Source #

A list of all primitive types.

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

Create an IntValue from a type and an Integer.

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

Convert an IntValue to any Integral type.

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

Create a FloatValue from a type and a Rational.

primValueType :: PrimValue -> PrimType Source #

The type of a basic value.

blankPrimValue :: PrimType -> PrimValue Source #

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

allUnOps :: [UnOp] Source #

A list of all unary operators for all types.

allBinOps :: [BinOp] Source #

A list of all binary operators for all types.

allCmpOps :: [CmpOp] Source #

A list of all comparison operators for all types.

allConvOps :: [ConvOp] Source #

A list of all conversion operators for all types.

doComplement :: IntValue -> IntValue Source #

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

doAbs :: IntValue -> IntValue Source #

abs(-2) = 2.

doFAbs :: FloatValue -> FloatValue Source #

abs(-2.0) = 2.0.

doSSignum :: IntValue -> IntValue Source #

ssignum(-2) = -1.

doUSignum :: IntValue -> IntValue Source #

usignum(-2) = -1.

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

Integer addition.

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

Integer multiplication.

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

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

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

Signed integer modulus; the countepart to SDiv.

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

Signed integer exponentatation.

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

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

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

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

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

Convert the former floating-point type to the latter.

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

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

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

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

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

Convert an unsigned integer to a floating-point value.

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

Convert a signed integer to a floating-point value.

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

Compare any two primtive values for exact equality.

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

Unsigned less than.

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

Unsigned less than or equal.

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

Signed less than.

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

Signed less than or equal.

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

Floating-point less than.

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

Floating-point less than or equal.

intToWord64 :: IntValue -> Word64 Source #

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

intToInt64 :: IntValue -> Int64 Source #

Translate an IntValue to 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.

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 #

ToExp VName 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toExp :: VName -> SrcLoc -> Exp

ToIdent VName 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toIdent :: VName -> SrcLoc -> Id

Pretty VName 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: VName -> Doc

pprPrec :: Int -> VName -> Doc

pprList :: [VName] -> Doc

FreeIn VName Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: VName -> 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.Representation.AST.Attributes.Scope

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

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

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

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

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

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

ToExp (PrimExp VName) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

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

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

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

ask :: ExtendedScope lore m (Scope lore) #

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

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

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

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toIdent :: Name -> SrcLoc -> Id

Pretty Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

ppr :: Name -> Doc

pprPrec :: Int -> Name -> Doc

pprList :: [Name] -> Doc

IsName Name Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pprName :: Name -> Doc Source #

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

Defined in Futhark.Representation.AST.Pretty

data StreamOrd Source #

Constructors

InOrder 
Disorder 

Instances

Instances details
Eq StreamOrd Source # 
Instance details

Defined in Language.Futhark.Core

Ord StreamOrd Source # 
Instance details

Defined in Language.Futhark.Core

Show StreamOrd Source # 
Instance details

Defined in Language.Futhark.Core

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.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.ExplicitMemory

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

defaultEntryPoint :: Name Source #

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

nameToString :: Name -> String Source #

Convert a name to the corresponding list of characters.

nameFromString :: String -> Name Source #

Convert a list of characters to the corresponding name.

nameToText :: Name -> Text Source #

Convert a name to the corresponding Text.

nameFromText :: Text -> Name Source #

Convert a Text to the corresponding name.

locStr :: 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.

Instances

Instances details
Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: ErrorMsgPart a -> [a] #

null :: ErrorMsgPart a -> Bool #

length :: ErrorMsgPart a -> Int #

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

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

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

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

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

Traversable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

newtype ErrorMsg a Source #

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

Constructors

ErrorMsg [ErrorMsgPart a] 

Instances

Instances details
Functor ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: ErrorMsg a -> [a] #

null :: ErrorMsg a -> Bool #

length :: ErrorMsg a -> Int #

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

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

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

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

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

Traversable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

Pretty a => Pretty (ErrorMsg a) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ErrorMsg a -> Doc

pprPrec :: Int -> ErrorMsg a -> Doc

pprList :: [ErrorMsg a] -> Doc

data PatElemT attr Source #

An element of a pattern - consisting of a name (essentially a pair of the name and type) and an addditional parametric attribute. This attribute is what is expected to contain the type of the resulting variable.

Instances

Instances details
Functor PatElemT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Eq attr => Eq (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: PatElemT attr -> PatElemT attr -> Bool #

(/=) :: PatElemT attr -> PatElemT attr -> Bool #

Ord attr => Ord (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: PatElemT attr -> PatElemT attr -> Ordering #

(<) :: PatElemT attr -> PatElemT attr -> Bool #

(<=) :: PatElemT attr -> PatElemT attr -> Bool #

(>) :: PatElemT attr -> PatElemT attr -> Bool #

(>=) :: PatElemT attr -> PatElemT attr -> Bool #

max :: PatElemT attr -> PatElemT attr -> PatElemT attr #

min :: PatElemT attr -> PatElemT attr -> PatElemT attr #

Show attr => Show (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> PatElemT attr -> ShowS #

show :: PatElemT attr -> String #

showList :: [PatElemT attr] -> ShowS #

Pretty (PatElemT b) => Pretty (PatElemT (a, b)) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: PatElemT (a, b) -> Doc

pprPrec :: Int -> PatElemT (a, b) -> Doc

pprList :: [PatElemT (a, b)] -> Doc

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

SetType attr => SetType (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

setType :: PatElemT attr -> Type -> PatElemT attr Source #

Typed attr => Typed (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: PatElemT attr -> Type Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (Range, attr)) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

ppAnnot :: PatElemT (Range, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (VarAliases, attr)) Source # 
Instance details

Defined in Futhark.Representation.Aliases

Methods

ppAnnot :: PatElemT (VarAliases, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (VarWisdom, attr)) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

ppAnnot :: PatElemT (VarWisdom, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: PatElemT (TypeBase shape u) -> Maybe Doc Source #

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: PatElemT attr -> FV Source #

Substitute attr => Substitute (PatElemT attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename attr => Rename (PatElemT attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatElemT attr -> RenameM (PatElemT attr) Source #

AliasesOf attr => AliasesOf (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Aliases

Methods

aliasesOf :: PatElemT attr -> Names Source #

RangeOf attr => RangeOf (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: PatElemT attr -> Range Source #

type Slice d = [DimIndex d] Source #

A list of DimFixs, indicating how an array should be sliced. Whenever a function accepts a Slice, that slice should be total, i.e, cover all dimensions of the array. Deviators should be indicated by taking a list of DimIndexes instead.

data DimIndex d Source #

How to index a single dimension of an array.

Constructors

DimFix d

Fix index in this dimension.

DimSlice d d d

DimSlice start_offset num_elems stride.

Instances

Instances details
Functor DimIndex Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable DimIndex Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: DimIndex a -> [a] #

null :: DimIndex a -> Bool #

length :: DimIndex a -> Int #

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

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

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

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

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

Traversable DimIndex Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: DimIndex d -> DimIndex d -> Bool #

(/=) :: DimIndex d -> DimIndex d -> Bool #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: DimIndex d -> DimIndex d -> Ordering #

(<) :: DimIndex d -> DimIndex d -> Bool #

(<=) :: DimIndex d -> DimIndex d -> Bool #

(>) :: DimIndex d -> DimIndex d -> Bool #

(>=) :: DimIndex d -> DimIndex d -> Bool #

max :: DimIndex d -> DimIndex d -> DimIndex d #

min :: DimIndex d -> DimIndex d -> DimIndex d #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> DimIndex d -> ShowS #

show :: DimIndex d -> String #

showList :: [DimIndex d] -> ShowS #

Pretty d => Pretty (DimIndex d) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: DimIndex d -> Doc

pprPrec :: Int -> DimIndex d -> Doc

pprList :: [DimIndex d] -> Doc

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: DimIndex d -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

rename :: DimIndex d -> RenameM (DimIndex d) Source #

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => DimIndex d -> SimpleM lore (DimIndex d) Source #

data Param attr Source #

A function or lambda parameter.

Constructors

Param 

Fields

Instances

Instances details
Functor Param Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable Param Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: Param a -> [a] #

null :: Param a -> Bool #

length :: Param a -> Int #

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

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

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

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

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

Traversable Param Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

Eq attr => Eq (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: Param attr -> Param attr -> Bool #

(/=) :: Param attr -> Param attr -> Bool #

Ord attr => Ord (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Param attr -> Param attr -> Ordering #

(<) :: Param attr -> Param attr -> Bool #

(<=) :: Param attr -> Param attr -> Bool #

(>) :: Param attr -> Param attr -> Bool #

(>=) :: Param attr -> Param attr -> Bool #

max :: Param attr -> Param attr -> Param attr #

min :: Param attr -> Param attr -> Param attr #

Show attr => Show (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Param attr -> ShowS #

show :: Param attr -> String #

showList :: [Param attr] -> ShowS #

Pretty (Param b) => Pretty (Param (a, b)) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param (a, b) -> Doc

pprPrec :: Int -> Param (a, b) -> Doc

pprList :: [Param (a, b)] -> Doc

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

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

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

DeclTyped attr => DeclTyped (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

declTypeOf :: Param attr -> DeclType Source #

Typed attr => Typed (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Param attr -> Type Source #

PrettyAnnot (Param (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: Param (TypeBase shape u) -> Maybe Doc Source #

(Pretty u, Pretty r) => PrettyAnnot (Param (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Param attr -> FV Source #

Substitute attr => Substitute (Param attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Param attr -> Param attr Source #

Rename attr => Rename (Param attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Param attr -> RenameM (Param attr) Source #

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.Representation.AST.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ToExp SubExp 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toExp :: SubExp -> SrcLoc -> Exp

Pretty SubExp 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: SubExp -> Doc

pprPrec :: Int -> SubExp -> Doc

pprList :: [SubExp] -> Doc

Pretty ExtShape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc

pprPrec :: Int -> ExtShape -> Doc

pprList :: [ExtShape] -> Doc

Pretty Shape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Shape -> Doc

pprPrec :: Int -> Shape -> Doc

pprList :: [Shape] -> Doc

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FreeIn SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.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

RangeOf SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: SubExp -> Range Source #

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

Methods

toExp :: SubExp -> ImpM lore r op Exp Source #

toExp' :: PrimType -> SubExp -> Exp Source #

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

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

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

(Pretty u, Pretty r) => PrettyAnnot (Param (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.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.Representation.ExplicitMemory

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.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

newtype Certificates Source #

A list of names used for certificates in some expressions.

Constructors

Certificates 

Fields

Instances

Instances details
Eq Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Semigroup Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Monoid Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty Certificates 
Instance details

Defined in Futhark.Representation.AST.Pretty

FreeIn Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Substitute Certificates Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Certificates Source # 
Instance details

Defined in Futhark.Transform.Rename

Simplifiable Certificates Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

MonadState (VNameSource, Bool, Certificates) (SimpleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

data Ident Source #

An identifier consists of its name and the type of the value bound to the identifier.

Constructors

Ident 

Fields

Instances

Instances details
Eq Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pretty Ident 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Ident -> Doc

pprPrec :: Int -> Ident -> Doc

pprList :: [Ident] -> Doc

Typed Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Ident -> Type Source #

FreeIn Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Ident -> FV Source #

Substitute Ident Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Ident Source # 
Instance details

Defined in Futhark.Transform.Rename

data Diet Source #

Information about which parts of a value/type are consumed. For example, we might say that a function taking three arguments of types ([int], *[int], [int]) has diet [Observe, Consume, Observe].

Constructors

Consume

Consumes this value.

Observe

Only observes value in this position, does not consume. A result may alias this.

ObservePrim

As Observe, but the result will not alias, because the parameter does not carry aliases.

Instances

Instances details
Eq Diet Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Diet Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Diet -> Diet -> Ordering #

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

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

(>) :: Diet -> Diet -> Bool #

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

max :: Diet -> Diet -> Diet #

min :: Diet -> Diet -> Diet #

Show Diet Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

type DeclExtType = TypeBase ExtShape Uniqueness Source #

An ExtType with uniqueness information, used for function return types.

type DeclType = TypeBase Shape Uniqueness Source #

A type with shape and uniqueness information, used declaring return- and parameters types.

type ExtType = TypeBase ExtShape NoUniqueness Source #

A type with existentially quantified shapes - used as part of function (and function-like) return types. Generally only makes sense when used in a list.

type Type = TypeBase Shape NoUniqueness Source #

A type with shape information, used for describing the type of variables.

data TypeBase shape u Source #

An Futhark type is either an array or an element type. When comparing types for equality with ==, shapes must match.

Constructors

Prim PrimType 
Array PrimType shape u 
Mem Space 

Instances

Instances details
SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

PrettyAnnot (PatElemT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: PatElemT (TypeBase shape u) -> Maybe Doc Source #

PrettyAnnot (Param (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: Param (TypeBase shape u) -> Maybe Doc Source #

(Eq shape, Eq u) => Eq (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: TypeBase shape u -> TypeBase shape u -> Bool #

(/=) :: TypeBase shape u -> TypeBase shape u -> Bool #

(Ord shape, Ord u) => Ord (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: TypeBase shape u -> TypeBase shape u -> Ordering #

(<) :: TypeBase shape u -> TypeBase shape u -> Bool #

(<=) :: TypeBase shape u -> TypeBase shape u -> Bool #

(>) :: TypeBase shape u -> TypeBase shape u -> Bool #

(>=) :: TypeBase shape u -> TypeBase shape u -> Bool #

max :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u #

min :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u #

(Show shape, Show u) => Show (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> TypeBase shape u -> ShowS #

show :: TypeBase shape u -> String #

showList :: [TypeBase shape u] -> ShowS #

Pretty u => Pretty (TypeBase Rank u) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Rank u -> Doc

pprPrec :: Int -> TypeBase Rank u -> Doc

pprList :: [TypeBase Rank u] -> Doc

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Shape u -> Doc

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

pprList :: [TypeBase Shape u] -> Doc

(FixExt shape, ArrayShape shape) => FixExt (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> TypeBase shape u -> TypeBase shape u Source #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> TypeBase shape u -> TypeBase shape u Source #

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

Defined in Futhark.Transform.Rename

Methods

rename :: TypeBase shape u -> RenameM (TypeBase shape u) Source #

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => TypeBase shape u -> SimpleM lore (TypeBase shape u) Source #

data NoUniqueness Source #

A fancier name for () - encodes no uniqueness information.

Constructors

NoUniqueness 

Instances

Instances details
Eq NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty NoUniqueness 
Instance details

Defined in Futhark.Representation.AST.Pretty

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

Pretty (Param (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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.Representation.AST.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Space -> Space -> Ordering #

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

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

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

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

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Show Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Space -> Doc

pprPrec :: Int -> Space -> Doc

pprList :: [Space] -> Doc

FreeIn Space Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.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 #

class (Monoid a, Eq a, Ord a) => ArrayShape a where Source #

A class encompassing types containing array shape information.

Methods

shapeRank :: a -> Int Source #

Return the rank of an array with the given size.

stripDims :: Int -> a -> a Source #

stripDims n shape strips the outer n dimensions from shape.

subShapeOf :: a -> a -> Bool Source #

Check whether one shape if a subset of another shape.

newtype Rank Source #

The size of an array type as merely the number of dimensions, with no further information.

Constructors

Rank Int 

Instances

Instances details
Eq Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Rank -> Rank -> Ordering #

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

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

(>) :: Rank -> Rank -> Bool #

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

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Show Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Semigroup Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(<>) :: Rank -> Rank -> Rank #

sconcat :: NonEmpty Rank -> Rank #

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

Monoid Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Substitute Rank Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Rank Source # 
Instance details

Defined in Futhark.Transform.Rename

Pretty u => Pretty (TypeBase Rank u) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Rank u -> Doc

pprPrec :: Int -> TypeBase Rank u -> Doc

pprList :: [TypeBase Rank u] -> Doc

type ExtShape = ShapeBase ExtSize Source #

Like Shape but some of its elements may be bound in a local environment instead. These are denoted with integral indices.

type ExtSize = Ext SubExp Source #

The size of this dimension.

data Ext a Source #

Something that may be existential.

Constructors

Ext Int 
Free a 

Instances

Instances details
Pretty ExtShape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc

pprPrec :: Int -> ExtShape -> Doc

pprList :: [ExtShape] -> Doc

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Ext a -> Ext a -> Ordering #

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

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

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

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

max :: Ext a -> Ext a -> Ext a #

min :: Ext a -> Ext a -> Ext a #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: Ext a -> String #

showList :: [Ext a] -> ShowS #

Pretty a => Pretty (Ext a) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Ext a -> Doc

pprPrec :: Int -> Ext a -> Doc

pprList :: [Ext a] -> Doc

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Ext d -> FV Source #

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

Defined in Futhark.Transform.Substitute

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.ExplicitMemory

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.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

type Shape = ShapeBase SubExp Source #

The size of an array as a list of subexpressions. If a variable, that variable must be in scope where this array is used.

newtype ShapeBase d Source #

The size of an array type as a list of its dimension sizes, with the type of sizes being parametric.

Constructors

Shape 

Fields

Instances

Instances details
Functor ShapeBase Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Pretty ExtShape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc

pprPrec :: Int -> ExtShape -> Doc

pprList :: [ExtShape] -> Doc

Pretty Shape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Shape -> Doc

pprPrec :: Int -> Shape -> Doc

pprList :: [Shape] -> Doc

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: ShapeBase d -> ShapeBase d -> Bool #

(/=) :: ShapeBase d -> ShapeBase d -> Bool #

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

Semigroup (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(<>) :: ShapeBase d -> ShapeBase d -> ShapeBase d #

sconcat :: NonEmpty (ShapeBase d) -> ShapeBase d #

stimes :: Integral b => b -> ShapeBase d -> ShapeBase d #

Monoid (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> ShapeBase d -> ShapeBase d Source #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: ShapeBase d -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => ShapeBase d -> SimpleM lore (ShapeBase d) Source #

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Shape u -> Doc

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

pprList :: [TypeBase Shape u] -> Doc

dimFix :: DimIndex d -> Maybe d Source #

If the argument is a DimFix, return its component.

sliceIndices :: Slice d -> Maybe [d] Source #

If the slice is all DimFixs, return the components.

sliceDims :: Slice d -> [d] Source #

The dimensions of the array produced by this slice.

unitSlice :: Num d => d -> d -> DimIndex d Source #

A slice with a stride of one.

fixSlice :: Num d => Slice d -> [d] -> [d] Source #

Fix the DimSlices of a slice. The number of indexes must equal the length of sliceDims for the slice.

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

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

class (Show rt, Eq rt, Ord rt, DeclExtTyped rt) => IsRetType rt where Source #

A type representing the return type of a function. In practice, a list of these will be used. It should contain at least the information contained in an ExtType, but may have more, notably an existential context.

Methods

primRetType :: PrimType -> rt Source #

Contruct a return type from a primitive type.

applyRetType :: Typed attr => [rt] -> [Param attr] -> [(SubExp, Type)] -> Maybe [rt] Source #

Given a function return type, the parameters of the function, and the arguments for a concrete call, return the instantiated return type for the concrete call, if valid.

Instances

Instances details
IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

class (Show rt, Eq rt, Ord rt, ExtTyped rt) => IsBodyType rt where Source #

A type representing the return type of a body. It should contain at least the information contained in a list of ExtTypes, but may have more, notably an existential context.

Methods

primBodyType :: PrimType -> rt Source #

Construct a body type from a primitive type.

expectedTypes :: Typed t => [VName] -> [t] -> [SubExp] -> [Type] Source #

Given shape parameter names and value parameter types, produce the types of arguments accepted.

class (Show (LetAttr l), Show (ExpAttr l), Show (BodyAttr l), Show (FParamAttr l), Show (LParamAttr l), Show (RetType l), Show (BranchType l), Show (Op l), Eq (LetAttr l), Eq (ExpAttr l), Eq (BodyAttr l), Eq (FParamAttr l), Eq (LParamAttr l), Eq (RetType l), Eq (BranchType l), Eq (Op l), Ord (LetAttr l), Ord (ExpAttr l), Ord (BodyAttr l), Ord (FParamAttr l), Ord (LParamAttr l), Ord (RetType l), Ord (BranchType l), Ord (Op l), IsRetType (RetType l), IsBodyType (BranchType l), Typed (FParamAttr l), Typed (LParamAttr l), Typed (LetAttr l), DeclTyped (FParamAttr l)) => Annotations l Source #

Associated Types

type LetAttr l :: Type Source #

Annotation for every let-pattern element.

type LetAttr l = Type

type ExpAttr l :: Type Source #

Annotation for every expression.

type ExpAttr l = ()

type BodyAttr l :: Type Source #

Annotation for every body.

type BodyAttr l = ()

type FParamAttr l :: Type Source #

Annotation for every (non-lambda) function parameter.

type LParamAttr l :: Type Source #

Annotation for every lambda function parameter.

type LParamAttr l = Type

type BranchType l :: Type Source #

The return type annotation of branches.

type Op l :: Type Source #

Extensible operation.

type Op l = ()

Instances

Instances details
Annotations SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Annotations Kernels Source # 
Instance details

Defined in Futhark.Representation.Kernels

Annotations ExplicitMemory Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

(Annotations lore, CanBeRanged (Op lore)) => Annotations (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Associated Types

type LetAttr (Ranges lore) Source #

type ExpAttr (Ranges lore) Source #

type BodyAttr (Ranges lore) Source #

type FParamAttr (Ranges lore) Source #

type LParamAttr (Ranges lore) Source #

type RetType (Ranges lore) Source #

type BranchType (Ranges lore) Source #

type Op (Ranges lore) Source #

(Annotations lore, CanBeAliased (Op lore)) => Annotations (Aliases lore) Source # 
Instance details

Defined in Futhark.Representation.Aliases

Associated Types

type LetAttr (Aliases lore) Source #

type ExpAttr (Aliases lore) Source #

type BodyAttr (Aliases lore) Source #

type FParamAttr (Aliases lore) Source #

type LParamAttr (Aliases lore) Source #

type RetType (Aliases lore) Source #

type BranchType (Aliases lore) Source #

type Op (Aliases lore) Source #

(Annotations lore, CanBeWise (Op lore)) => Annotations (Wise lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Associated Types

type LetAttr (Wise lore) Source #

type ExpAttr (Wise lore) Source #

type BodyAttr (Wise lore) Source #

type FParamAttr (Wise lore) Source #

type LParamAttr (Wise lore) Source #

type RetType (Wise lore) Source #

type BranchType (Wise lore) Source #

type Op (Wise lore) Source #

data Prog lore Source #

An entire Futhark program.

Constructors

Prog 

Fields

  • progConsts :: Stms lore

    Top-level constants that are computed at program startup, and which are in scope inside all functions.

  • progFuns :: [FunDef lore]

    The functions comprising the program. All funtions are also available in scope in the definitions of the constants, so be careful not to introduce circular dependencies (not currently checked).

Instances

Instances details
Annotations lore => Eq (Prog lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: Prog lore -> Prog lore -> Bool #

(/=) :: Prog lore -> Prog lore -> Bool #

Annotations lore => Ord (Prog lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: Prog lore -> Prog lore -> Ordering #

(<) :: Prog lore -> Prog lore -> Bool #

(<=) :: Prog lore -> Prog lore -> Bool #

(>) :: Prog lore -> Prog lore -> Bool #

(>=) :: Prog lore -> Prog lore -> Bool #

max :: Prog lore -> Prog lore -> Prog lore #

min :: Prog lore -> Prog lore -> Prog lore #

Annotations lore => Show (Prog lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> Prog lore -> ShowS #

show :: Prog lore -> String #

showList :: [Prog lore] -> ShowS #

PrettyLore lore => Pretty (Prog lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Prog lore -> Doc

pprPrec :: Int -> Prog lore -> Doc

pprList :: [Prog lore] -> Doc

data EntryPointType Source #

Every entry point argument and return value has an annotation indicating how it maps to the original source program type.

Constructors

TypeUnsigned

Is an unsigned integer or array of unsigned integers.

TypeOpaque String Int

A black box type comprising this many core values. The string is a human-readable description with no other semantics.

TypeDirect

Maps directly.

type EntryPoint = ([EntryPointType], [EntryPointType]) Source #

Information about the parameters and return value of an entry point. The first element is for parameters, the second for return value.

data FunDef lore Source #

Function Declarations

Constructors

FunDef 

Fields

Instances

Instances details
Scoped lore (FunDef lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

scopeOf :: FunDef lore -> Scope lore Source #

Annotations lore => Eq (FunDef lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: FunDef lore -> FunDef lore -> Bool #

(/=) :: FunDef lore -> FunDef lore -> Bool #

Annotations lore => Ord (FunDef lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: FunDef lore -> FunDef lore -> Ordering #

(<) :: FunDef lore -> FunDef lore -> Bool #

(<=) :: FunDef lore -> FunDef lore -> Bool #

(>) :: FunDef lore -> FunDef lore -> Bool #

(>=) :: FunDef lore -> FunDef lore -> Bool #

max :: FunDef lore -> FunDef lore -> FunDef lore #

min :: FunDef lore -> FunDef lore -> FunDef lore #

Annotations lore => Show (FunDef lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> FunDef lore -> ShowS #

show :: FunDef lore -> String #

showList :: [FunDef lore] -> ShowS #

PrettyLore lore => Pretty (FunDef lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: FunDef lore -> Doc

pprPrec :: Int -> FunDef lore -> Doc

pprList :: [FunDef lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (RetType lore), FreeIn (Op lore)) => FreeIn (FunDef lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: FunDef lore -> FV Source #

Renameable lore => Rename (FunDef lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: FunDef lore -> RenameM (FunDef lore) Source #

data LambdaT lore Source #

Anonymous function for use in a SOAC.

Instances

Instances details
Scoped lore (Lambda lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

scopeOf :: Lambda lore -> Scope lore Source #

Annotations lore => Eq (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: LambdaT lore -> LambdaT lore -> Bool #

(/=) :: LambdaT lore -> LambdaT lore -> Bool #

Annotations lore => Ord (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: LambdaT lore -> LambdaT lore -> Ordering #

(<) :: LambdaT lore -> LambdaT lore -> Bool #

(<=) :: LambdaT lore -> LambdaT lore -> Bool #

(>) :: LambdaT lore -> LambdaT lore -> Bool #

(>=) :: LambdaT lore -> LambdaT lore -> Bool #

max :: LambdaT lore -> LambdaT lore -> LambdaT lore #

min :: LambdaT lore -> LambdaT lore -> LambdaT lore #

Annotations lore => Show (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> LambdaT lore -> ShowS #

show :: LambdaT lore -> String #

showList :: [LambdaT lore] -> ShowS #

PrettyLore lore => Pretty (Lambda lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Lambda lore -> Doc

pprPrec :: Int -> Lambda lore -> Doc

pprList :: [Lambda lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Lambda lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Lambda lore -> FV Source #

Substitutable lore => Substitute (Lambda lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Lambda lore -> Lambda lore Source #

Renameable lore => Rename (Lambda lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Lambda lore -> RenameM (Lambda lore) Source #

data IfSort Source #

Constructors

IfNormal

An ordinary branch.

IfFallback

A branch where the "true" case is what we are actually interested in, and the "false" case is only present as a fallback for when the true case cannot be safely evaluated. the compiler is permitted to optimise away the branch if the true case contains only safe statements.

Instances

Instances details
Eq IfSort Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

Ord IfSort Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Show IfSort Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

data IfAttr rt Source #

Data associated with a branch.

Constructors

IfAttr 

Fields

Instances

Instances details
Eq rt => Eq (IfAttr rt) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: IfAttr rt -> IfAttr rt -> Bool #

(/=) :: IfAttr rt -> IfAttr rt -> Bool #

Ord rt => Ord (IfAttr rt) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: IfAttr rt -> IfAttr rt -> Ordering #

(<) :: IfAttr rt -> IfAttr rt -> Bool #

(<=) :: IfAttr rt -> IfAttr rt -> Bool #

(>) :: IfAttr rt -> IfAttr rt -> Bool #

(>=) :: IfAttr rt -> IfAttr rt -> Bool #

max :: IfAttr rt -> IfAttr rt -> IfAttr rt #

min :: IfAttr rt -> IfAttr rt -> IfAttr rt #

Show rt => Show (IfAttr rt) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> IfAttr rt -> ShowS #

show :: IfAttr rt -> String #

showList :: [IfAttr rt] -> ShowS #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: IfAttr a -> FV Source #

data LoopForm lore Source #

For-loop or while-loop?

Instances

Instances details
Scoped lore (LoopForm lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

scopeOf :: LoopForm lore -> Scope lore Source #

Annotations lore => Eq (LoopForm lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: LoopForm lore -> LoopForm lore -> Bool #

(/=) :: LoopForm lore -> LoopForm lore -> Bool #

Annotations lore => Ord (LoopForm lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: LoopForm lore -> LoopForm lore -> Ordering #

(<) :: LoopForm lore -> LoopForm lore -> Bool #

(<=) :: LoopForm lore -> LoopForm lore -> Bool #

(>) :: LoopForm lore -> LoopForm lore -> Bool #

(>=) :: LoopForm lore -> LoopForm lore -> Bool #

max :: LoopForm lore -> LoopForm lore -> LoopForm lore #

min :: LoopForm lore -> LoopForm lore -> LoopForm lore #

Annotations lore => Show (LoopForm lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> LoopForm lore -> ShowS #

show :: LoopForm lore -> String #

showList :: [LoopForm lore] -> ShowS #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: LoopForm lore -> FV Source #

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.

Constructors

Unsafe 
Safe 

Instances

Instances details
Eq Safety Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

Ord Safety Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Show Safety Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

data ExpT lore Source #

The root Futhark expression type. The Op constructor contains a lore-specific operation. Do-loops, branches and function calls are special. Everything else is a simple BasicOp.

Constructors

Apply Name [(SubExp, Diet)] [RetType lore] (Safety, SrcLoc, [SrcLoc]) 
If SubExp (BodyT lore) (BodyT lore) (IfAttr (BranchType lore)) 
DoLoop [(FParam lore, SubExp)] [(FParam lore, SubExp)] (LoopForm lore) (BodyT lore)

loop {a} = {v} (for i < n|while b) do b. The merge parameters are divided into context and value part.

Op (Op lore) 

Instances

Instances details
Annotations lore => Eq (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: ExpT lore -> ExpT lore -> Bool #

(/=) :: ExpT lore -> ExpT lore -> Bool #

Annotations lore => Ord (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: ExpT lore -> ExpT lore -> Ordering #

(<) :: ExpT lore -> ExpT lore -> Bool #

(<=) :: ExpT lore -> ExpT lore -> Bool #

(>) :: ExpT lore -> ExpT lore -> Bool #

(>=) :: ExpT lore -> ExpT lore -> Bool #

max :: ExpT lore -> ExpT lore -> ExpT lore #

min :: ExpT lore -> ExpT lore -> ExpT lore #

Annotations lore => Show (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> ExpT lore -> ShowS #

show :: ExpT lore -> String #

showList :: [ExpT lore] -> ShowS #

PrettyLore lore => Pretty (Exp lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Exp lore -> Doc

pprPrec :: Int -> Exp lore -> Doc

pprList :: [Exp lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Exp lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Exp lore -> FV Source #

Substitutable lore => Substitute (Exp lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Exp lore -> Exp lore Source #

Renameable lore => Rename (Exp lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Exp lore -> RenameM (Exp lore) Source #

pattern Rotate :: [SubExp] -> VName -> BasicOp lore Source #

Rotate the dimensions of the input array. The list of subexpressions specify how much each dimension is rotated. The length of this list must be equal to the rank of the array.

pattern Scratch :: PrimType -> [SubExp] -> BasicOp lore Source #

Create array of given type and shape, with undefined elements.

pattern Repeat :: [Shape] -> Shape -> VName -> BasicOp lore Source #

Repeat each dimension of the input array some number of times, given by the corresponding shape. For an array of rank k, the list must contain k shapes. A shape may be empty (in which case the dimension is not repeated, but it is still present). The last shape indicates the amount of extra innermost dimensions. All other extra dimensions are added *before* the original dimension.

pattern Manifest :: [Int] -> VName -> BasicOp lore Source #

Manifest an array with dimensions represented in the given order. The result will not alias anything.

pattern Concat :: Int -> VName -> [VName] -> SubExp -> BasicOp lore Source #

concat0([1],[2, 3, 4]) = [1, 2, 3, 4]@.

pattern Update :: VName -> Slice SubExp -> SubExp -> BasicOp lore Source #

An in-place update of the given array at the given position. Consumes the array.

pattern Assert :: SubExp -> ErrorMsg SubExp -> (SrcLoc, [SrcLoc]) -> BasicOp lore Source #

Turn a boolean into a certificate, halting the program with the given error message if the boolean is false.

pattern ArrayLit :: [SubExp] -> Type -> BasicOp lore Source #

Array literals, e.g., [ [1+x, 3], [2, 1+4] ]. Second arg is the element type of the rows of the array. Scalar operations

pattern ConvOp :: ConvOp -> SubExp -> BasicOp lore Source #

Conversion "casting".

pattern CmpOp :: CmpOp -> SubExp -> SubExp -> BasicOp lore Source #

Comparison - result type is always boolean.

pattern BinOp :: BinOp -> SubExp -> SubExp -> BasicOp lore Source #

Binary operation.

pattern UnOp :: UnOp -> SubExp -> BasicOp lore Source #

Unary operation.

pattern Copy :: VName -> BasicOp lore Source #

Copy the given array. The result will not alias anything.

pattern SubExp :: SubExp -> BasicOp lore Source #

A variable or constant.

pattern Index :: VName -> Slice SubExp -> BasicOp lore Source #

The certificates for bounds-checking are part of the Stm.

pattern Replicate :: Shape -> SubExp -> BasicOp lore Source #

replicate([3][2],1) = [[1,1], [1,1], [1,1]]

pattern Reshape :: ShapeChange SubExp -> VName -> BasicOp lore Source #

1st arg is the new shape, 2nd arg is the input array *)

pattern Rearrange :: [Int] -> VName -> BasicOp lore Source #

Permute the dimensions of the input array. The list of integers is a list of dimensions (0-indexed), which must be a permutation of [0,n-1], where n is the number of dimensions in the input array.

pattern Opaque :: SubExp -> BasicOp lore Source #

Semantically and operationally just identity, but is invisible/impenetrable to optimisations (hopefully). This is just a hack to avoid optimisation (so, to work around compiler limitations).

pattern Iota :: SubExp -> SubExp -> SubExp -> IntType -> BasicOp lore Source #

iota(n, x, s) = [x,x+s,..,x+(n-1)*s].

The IntType indicates the type of the array returned and the offset/stride arguments, but not the length argument.

type ShapeChange d = [DimChange d] Source #

A list of DimChanges, indicating the new dimensions of an array.

data DimChange d Source #

The new dimension in a Reshape-like operation. This allows us to disambiguate "real" reshapes, that change the actual shape of the array, from type coercions that are just present to make the types work out. The two constructors are considered equal for purposes of Eq.

Constructors

DimCoercion d

The new dimension is guaranteed to be numerically equal to the old one.

DimNew d

The new dimension is not necessarily numerically equal to the old one.

Instances

Instances details
Functor DimChange Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

Foldable DimChange Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

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

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

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

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

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

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

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

toList :: DimChange a -> [a] #

null :: DimChange a -> Bool #

length :: DimChange a -> Int #

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

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

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

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

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

Traversable DimChange Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

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

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

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

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: DimChange d -> DimChange d -> Bool #

(/=) :: DimChange d -> DimChange d -> Bool #

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

Defined in Futhark.Representation.AST.Syntax

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

Defined in Futhark.Representation.AST.Syntax

Pretty d => Pretty (DimChange d) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: DimChange d -> Doc

pprPrec :: Int -> DimChange d -> Doc

pprList :: [DimChange d] -> Doc

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: DimChange d -> FV Source #

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

Defined in Futhark.Transform.Substitute

data BodyT lore Source #

A body consists of a number of bindings, terminating in a result (essentially a tuple literal).

Instances

Instances details
Annotations lore => Eq (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: BodyT lore -> BodyT lore -> Bool #

(/=) :: BodyT lore -> BodyT lore -> Bool #

Annotations lore => Ord (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: BodyT lore -> BodyT lore -> Ordering #

(<) :: BodyT lore -> BodyT lore -> Bool #

(<=) :: BodyT lore -> BodyT lore -> Bool #

(>) :: BodyT lore -> BodyT lore -> Bool #

(>=) :: BodyT lore -> BodyT lore -> Bool #

max :: BodyT lore -> BodyT lore -> BodyT lore #

min :: BodyT lore -> BodyT lore -> BodyT lore #

Annotations lore => Show (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> BodyT lore -> ShowS #

show :: BodyT lore -> String #

showList :: [BodyT lore] -> ShowS #

PrettyLore lore => Pretty (Body lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Body lore -> Doc

pprPrec :: Int -> Body lore -> Doc

pprList :: [Body lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Body lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Body lore -> FV Source #

Substitutable lore => Substitute (Body lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Body lore -> Body lore Source #

Renameable lore => Rename (Body lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Body lore -> RenameM (Body lore) Source #

Ranged lore => RangesOf (Body lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: Body lore -> [Range] Source #

type Result = [SubExp] Source #

The result of a body is a sequence of subexpressions.

type Stms lore = Seq (Stm lore) Source #

A sequence of statements.

pattern Let :: Pattern lore -> StmAux (ExpAttr lore) -> Exp lore -> Stm lore Source #

stmExp :: Stm lore -> Exp lore Source #

stmPattern :: Stm lore -> Pattern lore Source #

stmAux :: Stm lore -> StmAux (ExpAttr lore) Source #

data StmAux attr Source #

Auxilliary Information associated with a statement.

Constructors

StmAux 

Fields

Instances

Instances details
Eq attr => Eq (StmAux attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: StmAux attr -> StmAux attr -> Bool #

(/=) :: StmAux attr -> StmAux attr -> Bool #

Ord attr => Ord (StmAux attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: StmAux attr -> StmAux attr -> Ordering #

(<) :: StmAux attr -> StmAux attr -> Bool #

(<=) :: StmAux attr -> StmAux attr -> Bool #

(>) :: StmAux attr -> StmAux attr -> Bool #

(>=) :: StmAux attr -> StmAux attr -> Bool #

max :: StmAux attr -> StmAux attr -> StmAux attr #

min :: StmAux attr -> StmAux attr -> StmAux attr #

Show attr => Show (StmAux attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> StmAux attr -> ShowS #

show :: StmAux attr -> String #

showList :: [StmAux attr] -> ShowS #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: StmAux attr -> FV Source #

Substitute attr => Substitute (StmAux attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> StmAux attr -> StmAux attr Source #

Rename attr => Rename (StmAux attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: StmAux attr -> RenameM (StmAux attr) Source #

data PatternT attr Source #

A pattern is conceptually just a list of names and their types.

Instances

Instances details
Functor PatternT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

Eq attr => Eq (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: PatternT attr -> PatternT attr -> Bool #

(/=) :: PatternT attr -> PatternT attr -> Bool #

Ord attr => Ord (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: PatternT attr -> PatternT attr -> Ordering #

(<) :: PatternT attr -> PatternT attr -> Bool #

(<=) :: PatternT attr -> PatternT attr -> Bool #

(>) :: PatternT attr -> PatternT attr -> Bool #

(>=) :: PatternT attr -> PatternT attr -> Bool #

max :: PatternT attr -> PatternT attr -> PatternT attr #

min :: PatternT attr -> PatternT attr -> PatternT attr #

Show attr => Show (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> PatternT attr -> ShowS #

show :: PatternT attr -> String #

showList :: [PatternT attr] -> ShowS #

Semigroup (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(<>) :: PatternT attr -> PatternT attr -> PatternT attr #

sconcat :: NonEmpty (PatternT attr) -> PatternT attr #

stimes :: Integral b => b -> PatternT attr -> PatternT attr #

Monoid (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

mempty :: PatternT attr #

mappend :: PatternT attr -> PatternT attr -> PatternT attr #

mconcat :: [PatternT attr] -> PatternT attr #

Pretty (PatElemT attr) => Pretty (PatternT attr) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: PatternT attr -> Doc

pprPrec :: Int -> PatternT attr -> Doc

pprList :: [PatternT attr] -> Doc

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: PatternT attr -> FV Source #

Substitute attr => Substitute (PatternT attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename attr => Rename (PatternT attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatternT attr -> RenameM (PatternT attr) Source #

RangeOf attr => RangesOf (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: PatternT attr -> [Range] Source #

oneStm :: Stm lore -> Stms lore Source #

stmsFromList :: [Stm lore] -> Stms lore Source #

stmsToList :: Stms lore -> [Stm lore] Source #

stmsHead :: Stms lore -> Maybe (Stm lore, Stms lore) Source #

data LambdaT lore Source #

Anonymous function for use in a SOAC.

Constructors

Lambda [LParam lore] (BodyT lore) [Type] 

Instances

Instances details
Scoped lore (Lambda lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

scopeOf :: Lambda lore -> Scope lore Source #

Annotations lore => Eq (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: LambdaT lore -> LambdaT lore -> Bool #

(/=) :: LambdaT lore -> LambdaT lore -> Bool #

Annotations lore => Ord (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: LambdaT lore -> LambdaT lore -> Ordering #

(<) :: LambdaT lore -> LambdaT lore -> Bool #

(<=) :: LambdaT lore -> LambdaT lore -> Bool #

(>) :: LambdaT lore -> LambdaT lore -> Bool #

(>=) :: LambdaT lore -> LambdaT lore -> Bool #

max :: LambdaT lore -> LambdaT lore -> LambdaT lore #

min :: LambdaT lore -> LambdaT lore -> LambdaT lore #

Annotations lore => Show (LambdaT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> LambdaT lore -> ShowS #

show :: LambdaT lore -> String #

showList :: [LambdaT lore] -> ShowS #

PrettyLore lore => Pretty (Lambda lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Lambda lore -> Doc

pprPrec :: Int -> Lambda lore -> Doc

pprList :: [Lambda lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Lambda lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Lambda lore -> FV Source #

Substitutable lore => Substitute (Lambda lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Lambda lore -> Lambda lore Source #

Renameable lore => Rename (Lambda lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Lambda lore -> RenameM (Lambda lore) Source #

data BodyT lore Source #

A body consists of a number of bindings, terminating in a result (essentially a tuple literal).

Constructors

Body (BodyAttr lore) (Stms lore) Result 

Instances

Instances details
Annotations lore => Eq (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: BodyT lore -> BodyT lore -> Bool #

(/=) :: BodyT lore -> BodyT lore -> Bool #

Annotations lore => Ord (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: BodyT lore -> BodyT lore -> Ordering #

(<) :: BodyT lore -> BodyT lore -> Bool #

(<=) :: BodyT lore -> BodyT lore -> Bool #

(>) :: BodyT lore -> BodyT lore -> Bool #

(>=) :: BodyT lore -> BodyT lore -> Bool #

max :: BodyT lore -> BodyT lore -> BodyT lore #

min :: BodyT lore -> BodyT lore -> BodyT lore #

Annotations lore => Show (BodyT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> BodyT lore -> ShowS #

show :: BodyT lore -> String #

showList :: [BodyT lore] -> ShowS #

PrettyLore lore => Pretty (Body lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Body lore -> Doc

pprPrec :: Int -> Body lore -> Doc

pprList :: [Body lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Body lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Body lore -> FV Source #

Substitutable lore => Substitute (Body lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Body lore -> Body lore Source #

Renameable lore => Rename (Body lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Body lore -> RenameM (Body lore) Source #

Ranged lore => RangesOf (Body lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: Body lore -> [Range] Source #

data PatternT attr Source #

A pattern is conceptually just a list of names and their types.

Constructors

Pattern [PatElemT attr] [PatElemT attr] 

Instances

Instances details
Functor PatternT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

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

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

Eq attr => Eq (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: PatternT attr -> PatternT attr -> Bool #

(/=) :: PatternT attr -> PatternT attr -> Bool #

Ord attr => Ord (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: PatternT attr -> PatternT attr -> Ordering #

(<) :: PatternT attr -> PatternT attr -> Bool #

(<=) :: PatternT attr -> PatternT attr -> Bool #

(>) :: PatternT attr -> PatternT attr -> Bool #

(>=) :: PatternT attr -> PatternT attr -> Bool #

max :: PatternT attr -> PatternT attr -> PatternT attr #

min :: PatternT attr -> PatternT attr -> PatternT attr #

Show attr => Show (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> PatternT attr -> ShowS #

show :: PatternT attr -> String #

showList :: [PatternT attr] -> ShowS #

Semigroup (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(<>) :: PatternT attr -> PatternT attr -> PatternT attr #

sconcat :: NonEmpty (PatternT attr) -> PatternT attr #

stimes :: Integral b => b -> PatternT attr -> PatternT attr #

Monoid (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

mempty :: PatternT attr #

mappend :: PatternT attr -> PatternT attr -> PatternT attr #

mconcat :: [PatternT attr] -> PatternT attr #

Pretty (PatElemT attr) => Pretty (PatternT attr) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: PatternT attr -> Doc

pprPrec :: Int -> PatternT attr -> Doc

pprList :: [PatternT attr] -> Doc

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: PatternT attr -> FV Source #

Substitute attr => Substitute (PatternT attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename attr => Rename (PatternT attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatternT attr -> RenameM (PatternT attr) Source #

RangeOf attr => RangesOf (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: PatternT attr -> [Range] Source #

data PatElemT attr Source #

An element of a pattern - consisting of a name (essentially a pair of the name and type) and an addditional parametric attribute. This attribute is what is expected to contain the type of the resulting variable.

Constructors

PatElem VName attr 

Instances

Instances details
Functor PatElemT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Eq attr => Eq (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: PatElemT attr -> PatElemT attr -> Bool #

(/=) :: PatElemT attr -> PatElemT attr -> Bool #

Ord attr => Ord (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: PatElemT attr -> PatElemT attr -> Ordering #

(<) :: PatElemT attr -> PatElemT attr -> Bool #

(<=) :: PatElemT attr -> PatElemT attr -> Bool #

(>) :: PatElemT attr -> PatElemT attr -> Bool #

(>=) :: PatElemT attr -> PatElemT attr -> Bool #

max :: PatElemT attr -> PatElemT attr -> PatElemT attr #

min :: PatElemT attr -> PatElemT attr -> PatElemT attr #

Show attr => Show (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> PatElemT attr -> ShowS #

show :: PatElemT attr -> String #

showList :: [PatElemT attr] -> ShowS #

Pretty (PatElemT b) => Pretty (PatElemT (a, b)) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: PatElemT (a, b) -> Doc

pprPrec :: Int -> PatElemT (a, b) -> Doc

pprList :: [PatElemT (a, b)] -> Doc

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

SetType attr => SetType (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

setType :: PatElemT attr -> Type -> PatElemT attr Source #

Typed attr => Typed (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: PatElemT attr -> Type Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (Range, attr)) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

ppAnnot :: PatElemT (Range, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (VarAliases, attr)) Source # 
Instance details

Defined in Futhark.Representation.Aliases

Methods

ppAnnot :: PatElemT (VarAliases, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (VarWisdom, attr)) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

ppAnnot :: PatElemT (VarWisdom, attr) -> Maybe Doc Source #

PrettyAnnot (PatElemT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: PatElemT (TypeBase shape u) -> Maybe Doc Source #

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: PatElemT attr -> FV Source #

Substitute attr => Substitute (PatElemT attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename attr => Rename (PatElemT attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatElemT attr -> RenameM (PatElemT attr) Source #

AliasesOf attr => AliasesOf (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Aliases

Methods

aliasesOf :: PatElemT attr -> Names Source #

RangeOf attr => RangeOf (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: PatElemT attr -> Range Source #

data ExpT lore Source #

The root Futhark expression type. The Op constructor contains a lore-specific operation. Do-loops, branches and function calls are special. Everything else is a simple BasicOp.

Constructors

BasicOp (BasicOp lore)

A simple (non-recursive) operation.

Instances

Instances details
Annotations lore => Eq (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

(==) :: ExpT lore -> ExpT lore -> Bool #

(/=) :: ExpT lore -> ExpT lore -> Bool #

Annotations lore => Ord (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

compare :: ExpT lore -> ExpT lore -> Ordering #

(<) :: ExpT lore -> ExpT lore -> Bool #

(<=) :: ExpT lore -> ExpT lore -> Bool #

(>) :: ExpT lore -> ExpT lore -> Bool #

(>=) :: ExpT lore -> ExpT lore -> Bool #

max :: ExpT lore -> ExpT lore -> ExpT lore #

min :: ExpT lore -> ExpT lore -> ExpT lore #

Annotations lore => Show (ExpT lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax

Methods

showsPrec :: Int -> ExpT lore -> ShowS #

show :: ExpT lore -> String #

showList :: [ExpT lore] -> ShowS #

PrettyLore lore => Pretty (Exp lore) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Exp lore -> Doc

pprPrec :: Int -> Exp lore -> Doc

pprList :: [Exp lore] -> Doc

(FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => FreeIn (Exp lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Exp lore -> FV Source #

Substitutable lore => Substitute (Exp lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Exp lore -> Exp lore Source #

Renameable lore => Rename (Exp lore) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Exp lore -> RenameM (Exp lore) Source #