{-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances, StandaloneDeriving #-}
module Futhark.Representation.AST.Syntax
(
module Language.Futhark.Core
, module Futhark.Representation.AST.Annotations
, module Futhark.Representation.AST.Syntax.Core
, Uniqueness(..)
, NoUniqueness(..)
, Rank(..)
, ArrayShape(..)
, Space (..)
, TypeBase(..)
, Diet(..)
, Ident (..)
, SubExp(..)
, PatElem
, PatElemT (..)
, PatternT (..)
, Pattern
, StmAux(..)
, Stm(..)
, Stms
, Result
, BodyT(..)
, Body
, BasicOp (..)
, UnOp (..)
, BinOp (..)
, CmpOp (..)
, ConvOp (..)
, DimChange (..)
, ShapeChange
, ExpT(..)
, Exp
, LoopForm (..)
, IfAttr (..)
, IfSort (..)
, Safety (..)
, LambdaT(..)
, Lambda
, ParamT (..)
, FParam
, LParam
, FunDefT (..)
, FunDef
, EntryPoint
, EntryPointType(..)
, ProgT(..)
, Prog
, oneStm
, stmsFromList
, stmsToList
, stmsHead
)
where
import Data.Foldable
import Data.Loc
import qualified Data.Sequence as Seq
import Language.Futhark.Core
import Futhark.Representation.AST.Annotations
import Futhark.Representation.AST.Syntax.Core
type PatElem lore = PatElemT (LetAttr lore)
data PatternT attr =
Pattern { patternContextElements :: [PatElemT attr]
, patternValueElements :: [PatElemT attr]
}
deriving (Ord, Show, Eq)
instance Functor PatternT where
fmap f (Pattern ctx val) = Pattern (map (fmap f) ctx) (map (fmap f) val)
instance Semigroup (PatternT attr) where
Pattern cs1 vs1 <> Pattern cs2 vs2 = Pattern (cs1++cs2) (vs1++vs2)
instance Monoid (PatternT attr) where
mempty = Pattern [] []
type Pattern lore = PatternT (LetAttr lore)
data StmAux attr = StmAux { stmAuxCerts :: !Certificates
, stmAuxAttr :: attr
}
deriving (Ord, Show, Eq)
data Stm lore = Let { stmPattern :: Pattern lore
, stmAux :: StmAux (ExpAttr lore)
, stmExp :: Exp lore
}
deriving instance Annotations lore => Ord (Stm lore)
deriving instance Annotations lore => Show (Stm lore)
deriving instance Annotations lore => Eq (Stm lore)
type Stms lore = Seq.Seq (Stm lore)
oneStm :: Stm lore -> Stms lore
oneStm = Seq.singleton
stmsFromList :: [Stm lore] -> Stms lore
stmsFromList = Seq.fromList
stmsToList :: Stms lore -> [Stm lore]
stmsToList = toList
stmsHead :: Stms lore -> Maybe (Stm lore, Stms lore)
stmsHead stms = case Seq.viewl stms of stm Seq.:< stms' -> Just (stm, stms')
Seq.EmptyL -> Nothing
type Result = [SubExp]
data BodyT lore = Body { bodyAttr :: BodyAttr lore
, bodyStms :: Stms lore
, bodyResult :: Result
}
deriving instance Annotations lore => Ord (BodyT lore)
deriving instance Annotations lore => Show (BodyT lore)
deriving instance Annotations lore => Eq (BodyT lore)
type Body = BodyT
data DimChange d = DimCoercion d
| DimNew d
deriving (Ord, Show)
instance Eq d => Eq (DimChange d) where
DimCoercion x == DimNew y = x == y
DimCoercion x == DimCoercion y = x == y
DimNew x == DimCoercion y = x == y
DimNew x == DimNew y = x == y
instance Functor DimChange where
fmap f (DimCoercion d) = DimCoercion $ f d
fmap f (DimNew d) = DimNew $ f d
instance Foldable DimChange where
foldMap f (DimCoercion d) = f d
foldMap f (DimNew d) = f d
instance Traversable DimChange where
traverse f (DimCoercion d) = DimCoercion <$> f d
traverse f (DimNew d) = DimNew <$> f d
type ShapeChange d = [DimChange d]
data BasicOp lore
= SubExp SubExp
| Opaque SubExp
| ArrayLit [SubExp] Type
| UnOp UnOp SubExp
| BinOp BinOp SubExp SubExp
| CmpOp CmpOp SubExp SubExp
| ConvOp ConvOp SubExp
| Assert SubExp (ErrorMsg SubExp) (SrcLoc, [SrcLoc])
| Index VName (Slice SubExp)
| Update VName (Slice SubExp) SubExp
| Concat Int VName [VName] SubExp
| Copy VName
| Manifest [Int] VName
| Iota SubExp SubExp SubExp IntType
| Replicate Shape SubExp
| Repeat [Shape] Shape VName
| Scratch PrimType [SubExp]
| Reshape (ShapeChange SubExp) VName
| Rearrange [Int] VName
| Rotate [SubExp] VName
deriving (Eq, Ord, Show)
data ExpT lore
= BasicOp (BasicOp lore)
| 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)
| Op (Op lore)
deriving instance Annotations lore => Eq (ExpT lore)
deriving instance Annotations lore => Show (ExpT lore)
deriving instance Annotations lore => Ord (ExpT lore)
data Safety = Unsafe | Safe deriving (Eq, Ord, Show)
data LoopForm lore = ForLoop VName IntType SubExp [(LParam lore,VName)]
| WhileLoop VName
deriving instance Annotations lore => Eq (LoopForm lore)
deriving instance Annotations lore => Show (LoopForm lore)
deriving instance Annotations lore => Ord (LoopForm lore)
data IfAttr rt = IfAttr { ifReturns :: [rt]
, ifSort :: IfSort
}
deriving (Eq, Show, Ord)
data IfSort = IfNormal
| IfFallback
deriving (Eq, Show, Ord)
type Exp = ExpT
data LambdaT lore = Lambda { lambdaParams :: [LParam lore]
, lambdaBody :: BodyT lore
, lambdaReturnType :: [Type]
}
deriving instance Annotations lore => Eq (LambdaT lore)
deriving instance Annotations lore => Show (LambdaT lore)
deriving instance Annotations lore => Ord (LambdaT lore)
type Lambda = LambdaT
type FParam lore = ParamT (FParamAttr lore)
type LParam lore = ParamT (LParamAttr lore)
data FunDefT lore = FunDef { funDefEntryPoint :: Maybe EntryPoint
, funDefName :: Name
, funDefRetType :: [RetType lore]
, funDefParams :: [FParam lore]
, funDefBody :: BodyT lore
}
deriving instance Annotations lore => Eq (FunDefT lore)
deriving instance Annotations lore => Show (FunDefT lore)
deriving instance Annotations lore => Ord (FunDefT lore)
type EntryPoint = ([EntryPointType], [EntryPointType])
data EntryPointType = TypeUnsigned
| TypeOpaque String Int
| TypeDirect
deriving (Eq, Show, Ord)
type FunDef = FunDefT
newtype ProgT lore = Prog { progFunctions :: [FunDef lore] }
deriving (Eq, Ord, Show)
type Prog = ProgT