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

Futhark.IR.Syntax

Description

Definition of the Futhark core language IR

For actually constructing ASTs, see Futhark.Construct.

Types and values

The core language type system is much more restricted than the core language. This is a theme that repeats often. The only types that are supported in the core language are various primitive types PrimType which can be combined in arrays (ignore Mem and Acc for now). Types are represented as TypeBase, which is parameterised by the shape of the array and whether we keep uniqueness information. The Type alias, which is the most commonly used, uses Shape and NoUniqueness.

This means that the records, tuples, and sum types of the source language are represented merely as collections of primitives and arrays. This is implemented in Futhark.Internalise, but the specifics are not important for writing passes on the core language. What is important is that many constructs that conceptually return tuples instead return multiple values. This is not merely syntactic sugar for a tuple: each of those values are eventually bound to distinct variables. The prettyprinter for the IR will typically print such collections of values or types in curly braces.

The system of primitive types is interesting in itself. See Language.Futhark.Primitive.

Overall AST design

Internally, the Futhark compiler core intermediate representation resembles a traditional compiler for an imperative language more than it resembles, say, a Haskell or ML compiler. All functions are monomorphic (except for sizes), first-order, and defined at the top level. Notably, the IR does not use continuation-passing style (CPS) at any time. Instead it uses Administrative Normal Form (ANF), where all subexpressions SubExp are either constants PrimValue or variables VName. Variables are represented as a human-readable Name (which doesn't matter to the compiler) as well as a numeric tag, which is what the compiler actually looks at. All variable names when prettyprinted are of the form foo_123. Function names are just Names, though.

The body of a function (FunDef) is a Body, which consists of a sequence of statements (Stms) and a Result. Execution of a Body consists of executing all of the statements, then returning the values of the variables indicated by the result.

A statement (Stm) consists of a Pat alongside an expression Exp. A pattern is a sequence of name/type pairs.

For example, the source language expression let z = x + y - 1 in z would in the core language be represented (in prettyprinted form) as something like:

let {a_12} = x_10 + y_11
let {b_13} = a_12 - 1
in {b_13}

Representations

Most AST types (Stm, Exp, Prog, etc) are parameterised by a type parameter rep. The representation specifies how to fill out various polymorphic parts of the AST. For example, Exp has a constructor Op whose payload depends on rep, via the use of a type family called Op (a kind of type-level function) which is applied to the rep. The SOACS representation (Futhark.IR.SOACS) thus uses a rep called SOACS, and defines that Op SOACS is a SOAC, while the Kernels representation (Futhark.IR.Kernels) defines Op Kernels as some kind of kernel construct. Similarly, various other decorations (e.g. what information we store in a PatElem) are also type families.

The full list of possible decorations is defined as part of the type class RepTypes (although other type families are also used elsewhere in the compiler on an ad hoc basis).

Essentially, the rep type parameter functions as a kind of proxy, saving us from having to parameterise the AST type with all the different forms of decorations that we desire (it would easily become a type with a dozen type parameters).

Some AST elements (such as Pat) do not take a rep type parameter, but instead immediately the single type of decoration that they contain. We only use the more complicated machinery when needed.

Defining a new representation (or rep) thus requires you to define an empty datatype and implement a handful of type class instances for it. See the source of Futhark.IR.Seq for what is likely the simplest example.

Synopsis

Documentation

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

Prettyprint a value to a String, appropriately wrapped.

prettyText :: Pretty a => a -> Text Source #

Prettyprint a value to a Text, appropriately wrapped.

class Pretty a #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Instances

Instances details
Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty CallGraph Source # 
Instance details

Defined in Futhark.Analysis.CallGraph

Methods

pretty :: CallGraph -> Doc ann #

prettyList :: [CallGraph] -> Doc ann #

Pretty ArrayTransform Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

pretty :: ArrayTransform -> Doc ann #

prettyList :: [ArrayTransform] -> Doc ann #

Pretty Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

pretty :: Input -> Doc ann #

prettyList :: [Input] -> Doc ann #

Pretty MemAliases Source # 
Instance details

Defined in Futhark.Analysis.MemAlias

Methods

pretty :: MemAliases -> Doc ann #

prettyList :: [MemAliases] -> Doc ann #

Pretty PyArg Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyArg -> Doc ann #

prettyList :: [PyArg] -> Doc ann #

Pretty PyClassDef Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyClassDef -> Doc ann #

prettyList :: [PyClassDef] -> Doc ann #

Pretty PyExcept Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyExcept -> Doc ann #

prettyList :: [PyExcept] -> Doc ann #

Pretty PyExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyExp -> Doc ann #

prettyList :: [PyExp] -> Doc ann #

Pretty PyFunDef Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyFunDef -> Doc ann #

prettyList :: [PyFunDef] -> Doc ann #

Pretty PyIdx Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyIdx -> Doc ann #

prettyList :: [PyIdx] -> Doc ann #

Pretty PyProg Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyProg -> Doc ann #

prettyList :: [PyProg] -> Doc ann #

Pretty PyStmt Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericPython.AST

Methods

pretty :: PyStmt -> Doc ann #

prettyList :: [PyStmt] -> Doc ann #

Pretty Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Arg -> Doc ann #

prettyList :: [Arg] -> Doc ann #

Pretty ArrayContents Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: ArrayContents -> Doc ann #

prettyList :: [ArrayContents] -> Doc ann #

Pretty EntryPoint Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: EntryPoint -> Doc ann #

prettyList :: [EntryPoint] -> Doc ann #

Pretty ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: ExternalValue -> Doc ann #

prettyList :: [ExternalValue] -> Doc ann #

Pretty Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Param -> Doc ann #

prettyList :: [Param] -> Doc ann #

Pretty ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: ValueDesc -> Doc ann #

prettyList :: [ValueDesc] -> Doc ann #

Pretty HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: HostOp -> Doc ann #

prettyList :: [HostOp] -> Doc ann #

Pretty Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: Kernel -> Doc ann #

prettyList :: [Kernel] -> Doc ann #

Pretty KernelConst Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: KernelConst -> Doc ann #

prettyList :: [KernelConst] -> Doc ann #

Pretty KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: KernelOp -> Doc ann #

prettyList :: [KernelOp] -> Doc ann #

Pretty KernelUse Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: KernelUse -> Doc ann #

prettyList :: [KernelUse] -> Doc ann #

Pretty Multicore Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

pretty :: Multicore -> Doc ann #

prettyList :: [Multicore] -> Doc ann #

Pretty ParallelTask Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

pretty :: ParallelTask -> Doc ann #

prettyList :: [ParallelTask] -> Doc ann #

Pretty SchedulerInfo Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

pretty :: SchedulerInfo -> Doc ann #

prettyList :: [SchedulerInfo] -> Doc ann #

Pretty Scheduling Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Multicore

Methods

pretty :: Scheduling -> Doc ann #

prettyList :: [Scheduling] -> Doc ann #

Pretty OpenCL Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.OpenCL

Methods

pretty :: OpenCL -> Doc ann #

prettyList :: [OpenCL] -> Doc ann #

Pretty Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

Methods

pretty :: Sequential -> Doc ann #

prettyList :: [Sequential] -> Doc ann #

Pretty DeviceInfo Source # 
Instance details

Defined in Futhark.CodeGen.OpenCL.Heuristics

Methods

pretty :: DeviceInfo -> Doc ann #

prettyList :: [DeviceInfo] -> Doc ann #

Pretty AliasDec Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

pretty :: AliasDec -> Doc ann #

prettyList :: [AliasDec] -> Doc ann #

Pretty KernelGrid Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

pretty :: KernelGrid -> Doc ann #

prettyList :: [KernelGrid] -> Doc ann #

Pretty SegLevel Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

pretty :: SegLevel -> Doc ann #

prettyList :: [SegLevel] -> Doc ann #

Pretty SegVirt Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

pretty :: SegVirt -> Doc ann #

prettyList :: [SegVirt] -> Doc ann #

Pretty SizeOp Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

pretty :: SizeOp -> Doc ann #

prettyList :: [SizeOp] -> Doc ann #

Pretty SizeClass Source # 
Instance details

Defined in Futhark.IR.GPU.Sizes

Methods

pretty :: SizeClass -> Doc ann #

prettyList :: [SizeClass] -> Doc ann #

Pretty MemBind Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

pretty :: MemBind -> Doc ann #

prettyList :: [MemBind] -> Doc ann #

Pretty MemReturn Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

pretty :: MemReturn -> Doc ann #

prettyList :: [MemReturn] -> Doc ann #

Pretty Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

pretty :: Names -> Doc ann #

prettyList :: [Names] -> Doc ann #

Pretty KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

pretty :: KernelResult -> Doc ann #

prettyList :: [KernelResult] -> Doc ann #

Pretty SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

pretty :: SegSpace -> Doc ann #

prettyList :: [SegSpace] -> Doc ann #

Pretty BasicOp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: BasicOp -> Doc ann #

prettyList :: [BasicOp] -> Doc ann #

Pretty EntryParam Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: EntryParam -> Doc ann #

prettyList :: [EntryParam] -> Doc ann #

Pretty EntryResult Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: EntryResult -> Doc ann #

prettyList :: [EntryResult] -> Doc ann #

Pretty SubExpRes Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: SubExpRes -> Doc ann #

prettyList :: [SubExpRes] -> Doc ann #

Pretty Attr Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Attr -> Doc ann #

prettyList :: [Attr] -> Doc ann #

Pretty Attrs Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Attrs -> Doc ann #

prettyList :: [Attrs] -> Doc ann #

Pretty Certs Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Certs -> Doc ann #

prettyList :: [Certs] -> Doc ann #

Pretty Commutativity Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Commutativity -> Doc ann #

prettyList :: [Commutativity] -> Doc ann #

Pretty EntryPointType Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: EntryPointType -> Doc ann #

prettyList :: [EntryPointType] -> Doc ann #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Pretty Ident Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Ident -> Doc ann #

prettyList :: [Ident] -> Doc ann #

Pretty OpaqueType Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: OpaqueType -> Doc ann #

prettyList :: [OpaqueType] -> Doc ann #

Pretty OpaqueTypes Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: OpaqueTypes -> Doc ann #

prettyList :: [OpaqueTypes] -> Doc ann #

Pretty Rank Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Rank -> Doc ann #

prettyList :: [Rank] -> Doc ann #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Shape -> Doc ann #

prettyList :: [Shape] -> Doc ann #

Pretty Signedness Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Signedness -> Doc ann #

prettyList :: [Signedness] -> Doc ann #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Space -> Doc ann #

prettyList :: [Space] -> Doc ann #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: SubExp -> Doc ann #

prettyList :: [SubExp] -> Doc ann #

Pretty ValueType Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ValueType -> Doc ann #

prettyList :: [ValueType] -> Doc ann #

Pretty AccessSummary Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: AccessSummary -> Doc ann #

prettyList :: [AccessSummary] -> Doc ann #

Pretty ArrayMemBound Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: ArrayMemBound -> Doc ann #

prettyList :: [ArrayMemBound] -> Doc ann #

Pretty Coalesced Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: Coalesced -> Doc ann #

prettyList :: [Coalesced] -> Doc ann #

Pretty CoalescedKind Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalescedKind -> Doc ann #

prettyList :: [CoalescedKind] -> Doc ann #

Pretty CoalsEntry Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalsEntry -> Doc ann #

prettyList :: [CoalsEntry] -> Doc ann #

Pretty CoalsTab Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalsTab -> Doc ann #

prettyList :: [CoalsTab] -> Doc ann #

Pretty MemRefs Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: MemRefs -> Doc ann #

prettyList :: [MemRefs] -> Doc ann #

Pretty VarWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rep

Methods

pretty :: VarWisdom -> Doc ann #

prettyList :: [VarWisdom] -> Doc ann #

Pretty Exp Source # 
Instance details

Defined in Futhark.Script

Methods

pretty :: Exp -> Doc ann #

prettyList :: [Exp] -> Doc ann #

Pretty Func Source # 
Instance details

Defined in Futhark.Script

Methods

pretty :: Func -> Doc ann #

prettyList :: [Func] -> Doc ann #

Pretty ScriptValueType Source # 
Instance details

Defined in Futhark.Script

Pretty Name Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: Name -> Doc ann #

prettyList :: [Name] -> Doc ann #

Pretty NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: NoUniqueness -> Doc ann #

prettyList :: [NoUniqueness] -> Doc ann #

Pretty Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: Uniqueness -> Doc ann #

prettyList :: [Uniqueness] -> Doc ann #

Pretty VName Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: VName -> Doc ann #

prettyList :: [VName] -> Doc ann #

Pretty BinOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: BinOp -> Doc ann #

prettyList :: [BinOp] -> Doc ann #

Pretty CmpOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: CmpOp -> Doc ann #

prettyList :: [CmpOp] -> Doc ann #

Pretty ConvOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: ConvOp -> Doc ann #

prettyList :: [ConvOp] -> Doc ann #

Pretty FloatType Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: FloatType -> Doc ann #

prettyList :: [FloatType] -> Doc ann #

Pretty FloatValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: FloatValue -> Doc ann #

prettyList :: [FloatValue] -> Doc ann #

Pretty IntType Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: IntType -> Doc ann #

prettyList :: [IntType] -> Doc ann #

Pretty IntValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: IntValue -> Doc ann #

prettyList :: [IntValue] -> Doc ann #

Pretty PrimType Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: PrimType -> Doc ann #

prettyList :: [PrimType] -> Doc ann #

Pretty PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: PrimValue -> Doc ann #

prettyList :: [PrimValue] -> Doc ann #

Pretty UnOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: UnOp -> Doc ann #

prettyList :: [UnOp] -> Doc ann #

Pretty Env Source # 
Instance details

Defined in Language.Futhark.Semantic

Methods

pretty :: Env -> Doc ann #

prettyList :: [Env] -> Doc ann #

Pretty MTy Source # 
Instance details

Defined in Language.Futhark.Semantic

Methods

pretty :: MTy -> Doc ann #

prettyList :: [MTy] -> Doc ann #

Pretty Mod Source # 
Instance details

Defined in Language.Futhark.Semantic

Methods

pretty :: Mod -> Doc ann #

prettyList :: [Mod] -> Doc ann #

Pretty Namespace Source # 
Instance details

Defined in Language.Futhark.Semantic

Methods

pretty :: Namespace -> Doc ann #

prettyList :: [Namespace] -> Doc ann #

Pretty BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

pretty :: BinOp -> Doc ann #

prettyList :: [BinOp] -> Doc ann #

Pretty Diet Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Diet -> Doc ann #

prettyList :: [Diet] -> Doc ann #

Pretty Liftedness Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Liftedness -> Doc ann #

prettyList :: [Liftedness] -> Doc ann #

Pretty PatLit Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: PatLit -> Doc ann #

prettyList :: [PatLit] -> Doc ann #

Pretty PrimType Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

pretty :: PrimType -> Doc ann #

prettyList :: [PrimType] -> Doc ann #

Pretty PrimValue Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: PrimValue -> Doc ann #

prettyList :: [PrimValue] -> Doc ann #

Pretty Notes Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Monad

Methods

pretty :: Notes -> Doc ann #

prettyList :: [Notes] -> Doc ann #

Pretty Checking Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Terms.Monad

Methods

pretty :: Checking -> Doc ann #

prettyList :: [Checking] -> Doc ann #

Pretty BreadCrumbs Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Unify

Methods

pretty :: BreadCrumbs -> Doc ann #

prettyList :: [BreadCrumbs] -> Doc ann #

Pretty Usage Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Unify

Methods

pretty :: Usage -> Doc ann #

prettyList :: [Usage] -> Doc ann #

Pretty Value Source # 
Instance details

Defined in Futhark.Test.Values

Methods

pretty :: Value -> Doc ann #

prettyList :: [Value] -> Doc ann #

Pretty ValueType Source # 
Instance details

Defined in Futhark.Test.Values

Methods

pretty :: ValueType -> Doc ann #

prettyList :: [ValueType] -> Doc ann #

Pretty Half Source # 
Instance details

Defined in Futhark.Util.Pretty

Methods

pretty :: Half -> Doc ann #

prettyList :: [Half] -> Doc ann #

Pretty LspServerLog 
Instance details

Defined in Language.LSP.Server.Control

Methods

pretty :: LspServerLog -> Doc ann #

prettyList :: [LspServerLog] -> Doc ann #

Pretty LspCoreLog 
Instance details

Defined in Language.LSP.Server.Core

Methods

pretty :: LspCoreLog -> Doc ann #

prettyList :: [LspCoreLog] -> Doc ann #

Pretty VfsLog 
Instance details

Defined in Language.LSP.VFS

Methods

pretty :: VfsLog -> Doc ann #

prettyList :: [VfsLog] -> Doc ann #

Pretty AnnotatedTextEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.AnnotatedTextEdit

Pretty ApplyWorkspaceEditParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ApplyWorkspaceEditParams

Pretty ApplyWorkspaceEditResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ApplyWorkspaceEditResult

Pretty BaseSymbolInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.BaseSymbolInformation

Pretty CallHierarchyClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyClientCapabilities

Pretty CallHierarchyIncomingCall 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyIncomingCall

Pretty CallHierarchyIncomingCallsParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyIncomingCallsParams

Pretty CallHierarchyItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyItem

Pretty CallHierarchyOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyOptions

Pretty CallHierarchyOutgoingCall 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyOutgoingCall

Pretty CallHierarchyOutgoingCallsParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyOutgoingCallsParams

Pretty CallHierarchyPrepareParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyPrepareParams

Pretty CallHierarchyRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CallHierarchyRegistrationOptions

Pretty CancelParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CancelParams

Methods

pretty :: CancelParams -> Doc ann #

prettyList :: [CancelParams] -> Doc ann #

Pretty ChangeAnnotation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ChangeAnnotation

Pretty ChangeAnnotationIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ChangeAnnotationIdentifier

Pretty ClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ClientCapabilities

Pretty CodeAction 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeAction

Methods

pretty :: CodeAction -> Doc ann #

prettyList :: [CodeAction] -> Doc ann #

Pretty CodeActionClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionClientCapabilities

Pretty CodeActionContext 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionContext

Pretty CodeActionKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionKind

Methods

pretty :: CodeActionKind -> Doc ann #

prettyList :: [CodeActionKind] -> Doc ann #

Pretty CodeActionOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionOptions

Pretty CodeActionParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionParams

Pretty CodeActionRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionRegistrationOptions

Pretty CodeActionTriggerKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeActionTriggerKind

Pretty CodeDescription 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeDescription

Pretty CodeLens 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLens

Methods

pretty :: CodeLens -> Doc ann #

prettyList :: [CodeLens] -> Doc ann #

Pretty CodeLensClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLensClientCapabilities

Pretty CodeLensOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLensOptions

Pretty CodeLensParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLensParams

Methods

pretty :: CodeLensParams -> Doc ann #

prettyList :: [CodeLensParams] -> Doc ann #

Pretty CodeLensRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLensRegistrationOptions

Pretty CodeLensWorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CodeLensWorkspaceClientCapabilities

Pretty Color 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Color

Methods

pretty :: Color -> Doc ann #

prettyList :: [Color] -> Doc ann #

Pretty ColorInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ColorInformation

Pretty ColorPresentation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ColorPresentation

Pretty ColorPresentationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ColorPresentationParams

Pretty Command 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Command

Methods

pretty :: Command -> Doc ann #

prettyList :: [Command] -> Doc ann #

Pretty CompletionClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionClientCapabilities

Pretty CompletionContext 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionContext

Pretty CompletionItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionItem

Methods

pretty :: CompletionItem -> Doc ann #

prettyList :: [CompletionItem] -> Doc ann #

Pretty CompletionItemKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionItemKind

Pretty CompletionItemLabelDetails 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionItemLabelDetails

Pretty CompletionItemTag 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionItemTag

Pretty CompletionList 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionList

Methods

pretty :: CompletionList -> Doc ann #

prettyList :: [CompletionList] -> Doc ann #

Pretty CompletionOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionOptions

Pretty CompletionParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionParams

Pretty CompletionRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionRegistrationOptions

Pretty CompletionTriggerKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CompletionTriggerKind

Pretty ConfigurationItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ConfigurationItem

Pretty ConfigurationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ConfigurationParams

Pretty CreateFile 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CreateFile

Methods

pretty :: CreateFile -> Doc ann #

prettyList :: [CreateFile] -> Doc ann #

Pretty CreateFileOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CreateFileOptions

Pretty CreateFilesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.CreateFilesParams

Pretty Declaration 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Declaration

Methods

pretty :: Declaration -> Doc ann #

prettyList :: [Declaration] -> Doc ann #

Pretty DeclarationClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeclarationClientCapabilities

Pretty DeclarationLink 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeclarationLink

Pretty DeclarationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeclarationOptions

Pretty DeclarationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeclarationParams

Pretty DeclarationRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeclarationRegistrationOptions

Pretty Definition 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Definition

Methods

pretty :: Definition -> Doc ann #

prettyList :: [Definition] -> Doc ann #

Pretty DefinitionClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DefinitionClientCapabilities

Pretty DefinitionLink 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DefinitionLink

Methods

pretty :: DefinitionLink -> Doc ann #

prettyList :: [DefinitionLink] -> Doc ann #

Pretty DefinitionOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DefinitionOptions

Pretty DefinitionParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DefinitionParams

Pretty DefinitionRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DefinitionRegistrationOptions

Pretty DeleteFile 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeleteFile

Methods

pretty :: DeleteFile -> Doc ann #

prettyList :: [DeleteFile] -> Doc ann #

Pretty DeleteFileOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeleteFileOptions

Pretty DeleteFilesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DeleteFilesParams

Pretty Diagnostic 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Diagnostic

Methods

pretty :: Diagnostic -> Doc ann #

prettyList :: [Diagnostic] -> Doc ann #

Pretty DiagnosticClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticClientCapabilities

Pretty DiagnosticOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticOptions

Pretty DiagnosticRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticRegistrationOptions

Pretty DiagnosticRelatedInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticRelatedInformation

Pretty DiagnosticServerCancellationData 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticServerCancellationData

Pretty DiagnosticSeverity 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity

Pretty DiagnosticTag 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticTag

Methods

pretty :: DiagnosticTag -> Doc ann #

prettyList :: [DiagnosticTag] -> Doc ann #

Pretty DiagnosticWorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DiagnosticWorkspaceClientCapabilities

Pretty DidChangeConfigurationClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeConfigurationClientCapabilities

Pretty DidChangeConfigurationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeConfigurationParams

Pretty DidChangeConfigurationRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeConfigurationRegistrationOptions

Pretty DidChangeNotebookDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeNotebookDocumentParams

Pretty DidChangeTextDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeTextDocumentParams

Pretty DidChangeWatchedFilesClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeWatchedFilesClientCapabilities

Pretty DidChangeWatchedFilesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeWatchedFilesParams

Pretty DidChangeWatchedFilesRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeWatchedFilesRegistrationOptions

Pretty DidChangeWorkspaceFoldersParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidChangeWorkspaceFoldersParams

Pretty DidCloseNotebookDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidCloseNotebookDocumentParams

Pretty DidCloseTextDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidCloseTextDocumentParams

Pretty DidOpenNotebookDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidOpenNotebookDocumentParams

Pretty DidOpenTextDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidOpenTextDocumentParams

Pretty DidSaveNotebookDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidSaveNotebookDocumentParams

Pretty DidSaveTextDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DidSaveTextDocumentParams

Pretty DocumentColorClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentColorClientCapabilities

Pretty DocumentColorOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentColorOptions

Pretty DocumentColorParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentColorParams

Pretty DocumentColorRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentColorRegistrationOptions

Pretty DocumentDiagnosticParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentDiagnosticParams

Pretty DocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentDiagnosticReport

Pretty DocumentDiagnosticReportKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentDiagnosticReportKind

Pretty DocumentDiagnosticReportPartialResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentDiagnosticReportPartialResult

Pretty DocumentFilter 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentFilter

Methods

pretty :: DocumentFilter -> Doc ann #

prettyList :: [DocumentFilter] -> Doc ann #

Pretty DocumentFormattingClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentFormattingClientCapabilities

Pretty DocumentFormattingOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentFormattingOptions

Pretty DocumentFormattingParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentFormattingParams

Pretty DocumentFormattingRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentFormattingRegistrationOptions

Pretty DocumentHighlight 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlight

Pretty DocumentHighlightClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlightClientCapabilities

Pretty DocumentHighlightKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlightKind

Pretty DocumentHighlightOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlightOptions

Pretty DocumentHighlightParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlightParams

Pretty DocumentHighlightRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentHighlightRegistrationOptions

Pretty DocumentLink 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentLink

Methods

pretty :: DocumentLink -> Doc ann #

prettyList :: [DocumentLink] -> Doc ann #

Pretty DocumentLinkClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentLinkClientCapabilities

Pretty DocumentLinkOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentLinkOptions

Pretty DocumentLinkParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentLinkParams

Pretty DocumentLinkRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentLinkRegistrationOptions

Pretty DocumentOnTypeFormattingClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentOnTypeFormattingClientCapabilities

Pretty DocumentOnTypeFormattingOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentOnTypeFormattingOptions

Pretty DocumentOnTypeFormattingParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentOnTypeFormattingParams

Pretty DocumentOnTypeFormattingRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentOnTypeFormattingRegistrationOptions

Pretty DocumentRangeFormattingClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentRangeFormattingClientCapabilities

Pretty DocumentRangeFormattingOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentRangeFormattingOptions

Pretty DocumentRangeFormattingParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentRangeFormattingParams

Pretty DocumentRangeFormattingRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentRangeFormattingRegistrationOptions

Pretty DocumentSelector 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSelector

Pretty DocumentSymbol 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSymbol

Methods

pretty :: DocumentSymbol -> Doc ann #

prettyList :: [DocumentSymbol] -> Doc ann #

Pretty DocumentSymbolClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSymbolClientCapabilities

Pretty DocumentSymbolOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSymbolOptions

Pretty DocumentSymbolParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSymbolParams

Pretty DocumentSymbolRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.DocumentSymbolRegistrationOptions

Pretty ErrorCodes 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ErrorCodes

Methods

pretty :: ErrorCodes -> Doc ann #

prettyList :: [ErrorCodes] -> Doc ann #

Pretty ExecuteCommandClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ExecuteCommandClientCapabilities

Pretty ExecuteCommandOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ExecuteCommandOptions

Pretty ExecuteCommandParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ExecuteCommandParams

Pretty ExecuteCommandRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ExecuteCommandRegistrationOptions

Pretty ExecutionSummary 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ExecutionSummary

Pretty FailureHandlingKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FailureHandlingKind

Pretty FileChangeType 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileChangeType

Methods

pretty :: FileChangeType -> Doc ann #

prettyList :: [FileChangeType] -> Doc ann #

Pretty FileCreate 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileCreate

Methods

pretty :: FileCreate -> Doc ann #

prettyList :: [FileCreate] -> Doc ann #

Pretty FileDelete 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileDelete

Methods

pretty :: FileDelete -> Doc ann #

prettyList :: [FileDelete] -> Doc ann #

Pretty FileEvent 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileEvent

Methods

pretty :: FileEvent -> Doc ann #

prettyList :: [FileEvent] -> Doc ann #

Pretty FileOperationClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationClientCapabilities

Pretty FileOperationFilter 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationFilter

Pretty FileOperationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationOptions

Pretty FileOperationPattern 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationPattern

Pretty FileOperationPatternKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationPatternKind

Pretty FileOperationPatternOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationPatternOptions

Pretty FileOperationRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileOperationRegistrationOptions

Pretty FileRename 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileRename

Methods

pretty :: FileRename -> Doc ann #

prettyList :: [FileRename] -> Doc ann #

Pretty FileSystemWatcher 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FileSystemWatcher

Pretty FoldingRange 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRange

Methods

pretty :: FoldingRange -> Doc ann #

prettyList :: [FoldingRange] -> Doc ann #

Pretty FoldingRangeClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRangeClientCapabilities

Pretty FoldingRangeKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRangeKind

Pretty FoldingRangeOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRangeOptions

Pretty FoldingRangeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRangeParams

Pretty FoldingRangeRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FoldingRangeRegistrationOptions

Pretty FormattingOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FormattingOptions

Pretty FullDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.FullDocumentDiagnosticReport

Pretty GeneralClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.GeneralClientCapabilities

Pretty GlobPattern 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.GlobPattern

Methods

pretty :: GlobPattern -> Doc ann #

prettyList :: [GlobPattern] -> Doc ann #

Pretty Hover 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Hover

Methods

pretty :: Hover -> Doc ann #

prettyList :: [Hover] -> Doc ann #

Pretty HoverClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.HoverClientCapabilities

Pretty HoverOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.HoverOptions

Methods

pretty :: HoverOptions -> Doc ann #

prettyList :: [HoverOptions] -> Doc ann #

Pretty HoverParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.HoverParams

Methods

pretty :: HoverParams -> Doc ann #

prettyList :: [HoverParams] -> Doc ann #

Pretty HoverRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.HoverRegistrationOptions

Pretty ImplementationClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ImplementationClientCapabilities

Pretty ImplementationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ImplementationOptions

Pretty ImplementationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ImplementationParams

Pretty ImplementationRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ImplementationRegistrationOptions

Pretty InitializeError 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InitializeError

Pretty InitializeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InitializeParams

Pretty InitializeResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InitializeResult

Pretty InitializedParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InitializedParams

Pretty InlayHint 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHint

Methods

pretty :: InlayHint -> Doc ann #

prettyList :: [InlayHint] -> Doc ann #

Pretty InlayHintClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintClientCapabilities

Pretty InlayHintKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintKind

Methods

pretty :: InlayHintKind -> Doc ann #

prettyList :: [InlayHintKind] -> Doc ann #

Pretty InlayHintLabelPart 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintLabelPart

Pretty InlayHintOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintOptions

Pretty InlayHintParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintParams

Pretty InlayHintRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintRegistrationOptions

Pretty InlayHintWorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlayHintWorkspaceClientCapabilities

Pretty InlineValue 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValue

Methods

pretty :: InlineValue -> Doc ann #

prettyList :: [InlineValue] -> Doc ann #

Pretty InlineValueClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueClientCapabilities

Pretty InlineValueContext 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueContext

Pretty InlineValueEvaluatableExpression 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueEvaluatableExpression

Pretty InlineValueOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueOptions

Pretty InlineValueParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueParams

Pretty InlineValueRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueRegistrationOptions

Pretty InlineValueText 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueText

Pretty InlineValueVariableLookup 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueVariableLookup

Pretty InlineValueWorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InlineValueWorkspaceClientCapabilities

Pretty InsertReplaceEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InsertReplaceEdit

Pretty InsertTextFormat 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InsertTextFormat

Pretty InsertTextMode 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.InsertTextMode

Methods

pretty :: InsertTextMode -> Doc ann #

prettyList :: [InsertTextMode] -> Doc ann #

Pretty LSPErrorCodes 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LSPErrorCodes

Methods

pretty :: LSPErrorCodes -> Doc ann #

prettyList :: [LSPErrorCodes] -> Doc ann #

Pretty LinkedEditingRangeClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LinkedEditingRangeClientCapabilities

Pretty LinkedEditingRangeOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LinkedEditingRangeOptions

Pretty LinkedEditingRangeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LinkedEditingRangeParams

Pretty LinkedEditingRangeRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LinkedEditingRangeRegistrationOptions

Pretty LinkedEditingRanges 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LinkedEditingRanges

Pretty Location 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Location

Methods

pretty :: Location -> Doc ann #

prettyList :: [Location] -> Doc ann #

Pretty LocationLink 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LocationLink

Methods

pretty :: LocationLink -> Doc ann #

prettyList :: [LocationLink] -> Doc ann #

Pretty LogMessageParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LogMessageParams

Pretty LogTraceParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.LogTraceParams

Methods

pretty :: LogTraceParams -> Doc ann #

prettyList :: [LogTraceParams] -> Doc ann #

Pretty MarkdownClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MarkdownClientCapabilities

Pretty MarkedString 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MarkedString

Methods

pretty :: MarkedString -> Doc ann #

prettyList :: [MarkedString] -> Doc ann #

Pretty MarkupContent 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MarkupContent

Methods

pretty :: MarkupContent -> Doc ann #

prettyList :: [MarkupContent] -> Doc ann #

Pretty MarkupKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MarkupKind

Methods

pretty :: MarkupKind -> Doc ann #

prettyList :: [MarkupKind] -> Doc ann #

Pretty MessageActionItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MessageActionItem

Pretty MessageType 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MessageType

Methods

pretty :: MessageType -> Doc ann #

prettyList :: [MessageType] -> Doc ann #

Pretty Moniker 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Moniker

Methods

pretty :: Moniker -> Doc ann #

prettyList :: [Moniker] -> Doc ann #

Pretty MonikerClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MonikerClientCapabilities

Pretty MonikerKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MonikerKind

Methods

pretty :: MonikerKind -> Doc ann #

prettyList :: [MonikerKind] -> Doc ann #

Pretty MonikerOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MonikerOptions

Methods

pretty :: MonikerOptions -> Doc ann #

prettyList :: [MonikerOptions] -> Doc ann #

Pretty MonikerParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MonikerParams

Methods

pretty :: MonikerParams -> Doc ann #

prettyList :: [MonikerParams] -> Doc ann #

Pretty MonikerRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.MonikerRegistrationOptions

Pretty NotebookCell 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookCell

Methods

pretty :: NotebookCell -> Doc ann #

prettyList :: [NotebookCell] -> Doc ann #

Pretty NotebookCellArrayChange 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookCellArrayChange

Pretty NotebookCellKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookCellKind

Pretty NotebookCellTextDocumentFilter 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookCellTextDocumentFilter

Pretty NotebookDocument 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocument

Pretty NotebookDocumentChangeEvent 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentChangeEvent

Pretty NotebookDocumentClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentClientCapabilities

Pretty NotebookDocumentFilter 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentFilter

Pretty NotebookDocumentIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentIdentifier

Pretty NotebookDocumentSyncClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentSyncClientCapabilities

Pretty NotebookDocumentSyncOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentSyncOptions

Pretty NotebookDocumentSyncRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.NotebookDocumentSyncRegistrationOptions

Pretty OptionalVersionedTextDocumentIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.OptionalVersionedTextDocumentIdentifier

Pretty ParameterInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ParameterInformation

Pretty PartialResultParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PartialResultParams

Pretty Pattern 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Pattern

Methods

pretty :: Pattern -> Doc ann #

prettyList :: [Pattern] -> Doc ann #

Pretty Position 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Position

Methods

pretty :: Position -> Doc ann #

prettyList :: [Position] -> Doc ann #

Pretty PositionEncodingKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PositionEncodingKind

Pretty PrepareRenameParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PrepareRenameParams

Pretty PrepareRenameResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PrepareRenameResult

Pretty PrepareSupportDefaultBehavior 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PrepareSupportDefaultBehavior

Pretty PreviousResultId 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PreviousResultId

Pretty ProgressParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ProgressParams

Methods

pretty :: ProgressParams -> Doc ann #

prettyList :: [ProgressParams] -> Doc ann #

Pretty ProgressToken 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ProgressToken

Methods

pretty :: ProgressToken -> Doc ann #

prettyList :: [ProgressToken] -> Doc ann #

Pretty PublishDiagnosticsClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PublishDiagnosticsClientCapabilities

Pretty PublishDiagnosticsParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.PublishDiagnosticsParams

Pretty Range 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Range

Methods

pretty :: Range -> Doc ann #

prettyList :: [Range] -> Doc ann #

Pretty ReferenceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ReferenceClientCapabilities

Pretty ReferenceContext 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ReferenceContext

Pretty ReferenceOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ReferenceOptions

Pretty ReferenceParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ReferenceParams

Pretty ReferenceRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ReferenceRegistrationOptions

Pretty Registration 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Registration

Methods

pretty :: Registration -> Doc ann #

prettyList :: [Registration] -> Doc ann #

Pretty RegistrationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RegistrationParams

Pretty RegularExpressionsClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RegularExpressionsClientCapabilities

Pretty RelatedFullDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RelatedFullDocumentDiagnosticReport

Pretty RelatedUnchangedDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RelatedUnchangedDocumentDiagnosticReport

Pretty RelativePattern 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RelativePattern

Pretty RenameClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameClientCapabilities

Pretty RenameFile 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameFile

Methods

pretty :: RenameFile -> Doc ann #

prettyList :: [RenameFile] -> Doc ann #

Pretty RenameFileOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameFileOptions

Pretty RenameFilesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameFilesParams

Pretty RenameOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameOptions

Methods

pretty :: RenameOptions -> Doc ann #

prettyList :: [RenameOptions] -> Doc ann #

Pretty RenameParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameParams

Methods

pretty :: RenameParams -> Doc ann #

prettyList :: [RenameParams] -> Doc ann #

Pretty RenameRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.RenameRegistrationOptions

Pretty ResourceOperation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ResourceOperation

Pretty ResourceOperationKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ResourceOperationKind

Pretty SaveOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SaveOptions

Methods

pretty :: SaveOptions -> Doc ann #

prettyList :: [SaveOptions] -> Doc ann #

Pretty SelectionRange 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SelectionRange

Methods

pretty :: SelectionRange -> Doc ann #

prettyList :: [SelectionRange] -> Doc ann #

Pretty SelectionRangeClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SelectionRangeClientCapabilities

Pretty SelectionRangeOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SelectionRangeOptions

Pretty SelectionRangeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SelectionRangeParams

Pretty SelectionRangeRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SelectionRangeRegistrationOptions

Pretty SemanticTokenModifiers 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokenModifiers

Pretty SemanticTokenTypes 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokenTypes

Pretty SemanticTokens 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokens

Methods

pretty :: SemanticTokens -> Doc ann #

prettyList :: [SemanticTokens] -> Doc ann #

Pretty SemanticTokensClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensClientCapabilities

Pretty SemanticTokensDelta 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensDelta

Pretty SemanticTokensDeltaParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensDeltaParams

Pretty SemanticTokensDeltaPartialResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensDeltaPartialResult

Pretty SemanticTokensEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensEdit

Pretty SemanticTokensLegend 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensLegend

Pretty SemanticTokensOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensOptions

Pretty SemanticTokensParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensParams

Pretty SemanticTokensPartialResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensPartialResult

Pretty SemanticTokensRangeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensRangeParams

Pretty SemanticTokensRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensRegistrationOptions

Pretty SemanticTokensWorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SemanticTokensWorkspaceClientCapabilities

Pretty ServerCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ServerCapabilities

Pretty SetTraceParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SetTraceParams

Methods

pretty :: SetTraceParams -> Doc ann #

prettyList :: [SetTraceParams] -> Doc ann #

Pretty ShowDocumentClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowDocumentClientCapabilities

Pretty ShowDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowDocumentParams

Pretty ShowDocumentResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowDocumentResult

Pretty ShowMessageParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowMessageParams

Pretty ShowMessageRequestClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowMessageRequestClientCapabilities

Pretty ShowMessageRequestParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.ShowMessageRequestParams

Pretty SignatureHelp 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelp

Methods

pretty :: SignatureHelp -> Doc ann #

prettyList :: [SignatureHelp] -> Doc ann #

Pretty SignatureHelpClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpClientCapabilities

Pretty SignatureHelpContext 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpContext

Pretty SignatureHelpOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpOptions

Pretty SignatureHelpParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpParams

Pretty SignatureHelpRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpRegistrationOptions

Pretty SignatureHelpTriggerKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureHelpTriggerKind

Pretty SignatureInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SignatureInformation

Pretty StaticRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.StaticRegistrationOptions

Pretty SymbolInformation 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SymbolInformation

Pretty SymbolKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SymbolKind

Methods

pretty :: SymbolKind -> Doc ann #

prettyList :: [SymbolKind] -> Doc ann #

Pretty SymbolTag 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.SymbolTag

Methods

pretty :: SymbolTag -> Doc ann #

prettyList :: [SymbolTag] -> Doc ann #

Pretty TextDocumentChangeRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentChangeRegistrationOptions

Pretty TextDocumentClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentClientCapabilities

Pretty TextDocumentContentChangeEvent 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentContentChangeEvent

Pretty TextDocumentEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentEdit

Pretty TextDocumentFilter 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentFilter

Pretty TextDocumentIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentIdentifier

Pretty TextDocumentItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentItem

Pretty TextDocumentPositionParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentPositionParams

Pretty TextDocumentRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentRegistrationOptions

Pretty TextDocumentSaveReason 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentSaveReason

Pretty TextDocumentSaveRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentSaveRegistrationOptions

Pretty TextDocumentSyncClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentSyncClientCapabilities

Pretty TextDocumentSyncKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentSyncKind

Pretty TextDocumentSyncOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextDocumentSyncOptions

Pretty TextEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TextEdit

Methods

pretty :: TextEdit -> Doc ann #

prettyList :: [TextEdit] -> Doc ann #

Pretty TokenFormat 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TokenFormat

Methods

pretty :: TokenFormat -> Doc ann #

prettyList :: [TokenFormat] -> Doc ann #

Pretty TraceValues 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TraceValues

Methods

pretty :: TraceValues -> Doc ann #

prettyList :: [TraceValues] -> Doc ann #

Pretty TypeDefinitionClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeDefinitionClientCapabilities

Pretty TypeDefinitionOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeDefinitionOptions

Pretty TypeDefinitionParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeDefinitionParams

Pretty TypeDefinitionRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeDefinitionRegistrationOptions

Pretty TypeHierarchyClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchyClientCapabilities

Pretty TypeHierarchyItem 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchyItem

Pretty TypeHierarchyOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchyOptions

Pretty TypeHierarchyPrepareParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchyPrepareParams

Pretty TypeHierarchyRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchyRegistrationOptions

Pretty TypeHierarchySubtypesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchySubtypesParams

Pretty TypeHierarchySupertypesParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.TypeHierarchySupertypesParams

Pretty UInitializeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.UInitializeParams

Pretty UnchangedDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.UnchangedDocumentDiagnosticReport

Pretty UniquenessLevel 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.UniquenessLevel

Pretty Unregistration 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.Unregistration

Methods

pretty :: Unregistration -> Doc ann #

prettyList :: [Unregistration] -> Doc ann #

Pretty UnregistrationParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.UnregistrationParams

Pretty VersionedNotebookDocumentIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.VersionedNotebookDocumentIdentifier

Pretty VersionedTextDocumentIdentifier 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.VersionedTextDocumentIdentifier

Pretty WatchKind 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WatchKind

Methods

pretty :: WatchKind -> Doc ann #

prettyList :: [WatchKind] -> Doc ann #

Pretty WillSaveTextDocumentParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WillSaveTextDocumentParams

Pretty WindowClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WindowClientCapabilities

Pretty WorkDoneProgressBegin 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressBegin

Pretty WorkDoneProgressCancelParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressCancelParams

Pretty WorkDoneProgressCreateParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressCreateParams

Pretty WorkDoneProgressEnd 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressEnd

Pretty WorkDoneProgressOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressOptions

Pretty WorkDoneProgressParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressParams

Pretty WorkDoneProgressReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkDoneProgressReport

Pretty WorkspaceClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceClientCapabilities

Pretty WorkspaceDiagnosticParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceDiagnosticParams

Pretty WorkspaceDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceDiagnosticReport

Pretty WorkspaceDiagnosticReportPartialResult 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceDiagnosticReportPartialResult

Pretty WorkspaceDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceDocumentDiagnosticReport

Pretty WorkspaceEdit 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceEdit

Methods

pretty :: WorkspaceEdit -> Doc ann #

prettyList :: [WorkspaceEdit] -> Doc ann #

Pretty WorkspaceEditClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceEditClientCapabilities

Pretty WorkspaceFolder 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceFolder

Pretty WorkspaceFoldersChangeEvent 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceFoldersChangeEvent

Pretty WorkspaceFoldersInitializeParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceFoldersInitializeParams

Pretty WorkspaceFoldersServerCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceFoldersServerCapabilities

Pretty WorkspaceFullDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceFullDocumentDiagnosticReport

Pretty WorkspaceSymbol 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceSymbol

Pretty WorkspaceSymbolClientCapabilities 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceSymbolClientCapabilities

Pretty WorkspaceSymbolOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceSymbolOptions

Pretty WorkspaceSymbolParams 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceSymbolParams

Pretty WorkspaceSymbolRegistrationOptions 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceSymbolRegistrationOptions

Pretty WorkspaceUnchangedDocumentDiagnosticReport 
Instance details

Defined in Language.LSP.Protocol.Internal.Types.WorkspaceUnchangedDocumentDiagnosticReport

Pretty SomeClientMethod 
Instance details

Defined in Language.LSP.Protocol.Message.Method

Pretty SomeServerMethod 
Instance details

Defined in Language.LSP.Protocol.Message.Method

Pretty SomeRegistration 
Instance details

Defined in Language.LSP.Protocol.Message.Registration

Pretty SomeUnregistration 
Instance details

Defined in Language.LSP.Protocol.Message.Registration

Pretty NotificationMessage 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Pretty RequestMessage 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: RequestMessage -> Doc ann #

prettyList :: [RequestMessage] -> Doc ann #

Pretty ResponseError 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: ResponseError -> Doc ann #

prettyList :: [ResponseError] -> Doc ann #

Pretty ResponseMessage 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Pretty Null 
Instance details

Defined in Language.LSP.Protocol.Types.Common

Methods

pretty :: Null -> Doc ann #

prettyList :: [Null] -> Doc ann #

Pretty UInt 
Instance details

Defined in Language.LSP.Protocol.Types.Common

Methods

pretty :: UInt -> Doc ann #

prettyList :: [UInt] -> Doc ann #

Pretty NormalizedUri 
Instance details

Defined in Language.LSP.Protocol.Types.Uri

Methods

pretty :: NormalizedUri -> Doc ann #

prettyList :: [NormalizedUri] -> Doc ann #

Pretty Uri 
Instance details

Defined in Language.LSP.Protocol.Types.Uri

Methods

pretty :: Uri -> Doc ann #

prettyList :: [Uri] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

(lazy Doc instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

PrettyRep rep => Pretty (SOAC rep) Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

pretty :: SOAC rep -> Doc ann #

prettyList :: [SOAC rep] -> Doc ann #

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

Defined in Futhark.Analysis.PrimExp

Methods

pretty :: PrimExp v -> Doc ann #

prettyList :: [PrimExp v] -> Doc ann #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Code op -> Doc ann #

prettyList :: [Code op] -> Doc ann #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Constants op -> Doc ann #

prettyList :: [Constants op] -> Doc ann #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Definitions op -> Doc ann #

prettyList :: [Definitions op] -> Doc ann #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: FunctionT op -> Doc ann #

prettyList :: [FunctionT op] -> Doc ann #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Functions op -> Doc ann #

prettyList :: [Functions op] -> Doc ann #

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

Defined in Futhark.IR.Mem.LMAD

Methods

pretty :: LMAD num -> Doc ann #

prettyList :: [LMAD num] -> Doc ann #

PrettyRep rep => Pretty (Reduce rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

pretty :: Reduce rep -> Doc ann #

prettyList :: [Reduce rep] -> Doc ann #

PrettyRep rep => Pretty (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

pretty :: SOAC rep -> Doc ann #

prettyList :: [SOAC rep] -> Doc ann #

PrettyRep rep => Pretty (Scan rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

pretty :: Scan rep -> Doc ann #

prettyList :: [Scan rep] -> Doc ann #

PrettyRep rep => Pretty (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

pretty :: KernelBody rep -> Doc ann #

prettyList :: [KernelBody rep] -> Doc ann #

PrettyRep rep => Pretty (SegBinOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

pretty :: SegBinOp rep -> Doc ann #

prettyList :: [SegBinOp rep] -> Doc ann #

PrettyRep rep => Pretty (Body rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Body rep -> Doc ann #

prettyList :: [Body rep] -> Doc ann #

PrettyRep rep => Pretty (Case (Body rep)) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Case (Body rep) -> Doc ann #

prettyList :: [Case (Body rep)] -> Doc ann #

PrettyRep rep => Pretty (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Exp rep -> Doc ann #

prettyList :: [Exp rep] -> Doc ann #

PrettyRep rep => Pretty (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: FunDef rep -> Doc ann #

prettyList :: [FunDef rep] -> Doc ann #

PrettyRep rep => Pretty (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Lambda rep -> Doc ann #

prettyList :: [Lambda rep] -> Doc ann #

Pretty t => Pretty (Pat t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Pat t -> Doc ann #

prettyList :: [Pat t] -> Doc ann #

PrettyRep rep => Pretty (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Prog rep -> Doc ann #

prettyList :: [Prog rep] -> Doc ann #

PrettyRep rep => Pretty (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Stm rep -> Doc ann #

prettyList :: [Stm rep] -> Doc ann #

PrettyRep rep => Pretty (Stms rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Stms rep -> Doc ann #

prettyList :: [Stms rep] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: DimIndex d -> Doc ann #

prettyList :: [DimIndex d] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: ErrorMsg a -> Doc ann #

prettyList :: [ErrorMsg a] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: Ext a -> Doc ann #

prettyList :: [Ext a] -> Doc ann #

Pretty d => Pretty (FlatDimIndex d) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: FlatDimIndex d -> Doc ann #

prettyList :: [FlatDimIndex d] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: FlatSlice a -> Doc ann #

prettyList :: [FlatSlice a] -> Doc ann #

Pretty t => Pretty (Param t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Param t -> Doc ann #

prettyList :: [Param t] -> Doc ann #

Pretty t => Pretty (PatElem t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: PatElem t -> Doc ann #

prettyList :: [PatElem t] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: Slice a -> Doc ann #

prettyList :: [Slice a] -> Doc ann #

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

Defined in Futhark.Test.Values

Methods

pretty :: Compound v -> Doc ann #

prettyList :: [Compound v] -> Doc ann #

Pretty d => Pretty (Shape d) Source # 
Instance details

Defined in Language.Futhark.Interpreter.Values

Methods

pretty :: Shape d -> Doc ann #

prettyList :: [Shape d] -> Doc ann #

IsName vn => Pretty (QualName vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: QualName vn -> Doc ann #

prettyList :: [QualName vn] -> Doc ann #

Pretty (Shape Int64) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Shape Int64 -> Doc ann #

prettyList :: [Shape Int64] -> Doc ann #

Pretty (Shape Size) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Shape Size -> Doc ann #

prettyList :: [Shape Size] -> Doc ann #

Pretty (Shape ()) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Shape () -> Doc ann #

prettyList :: [Shape ()] -> Doc ann #

Pretty (Shape Bool) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: Shape Bool -> Doc ann #

prettyList :: [Shape Bool] -> Doc ann #

IsName vn => Pretty (SizeBinder vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: SizeBinder vn -> Doc ann #

prettyList :: [SizeBinder vn] -> Doc ann #

Pretty d => Pretty (SizeExp d) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: SizeExp d -> Doc ann #

prettyList :: [SizeExp d] -> Doc ann #

Pretty (TypeArg Size) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeArg Size -> Doc ann #

prettyList :: [TypeArg Size] -> Doc ann #

(Eq vn, IsName vn) => Pretty (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeParamBase vn -> Doc ann #

prettyList :: [TypeParamBase vn] -> Doc ann #

Pretty (Match t) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Match

Methods

pretty :: Match t -> Doc ann #

prettyList :: [Match t] -> Doc ann #

Pretty t => Pretty (Subst t) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Methods

pretty :: Subst t -> Doc ann #

prettyList :: [Subst t] -> Doc ann #

Pretty (AString s) 
Instance details

Defined in Language.LSP.Protocol.Types.Singletons

Methods

pretty :: AString s -> Doc ann #

prettyList :: [AString s] -> Doc ann #

Pretty (AnInteger n) 
Instance details

Defined in Language.LSP.Protocol.Types.Singletons

Methods

pretty :: AnInteger n -> Doc ann #

prettyList :: [AnInteger n] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

(PrettyRep rep, Pretty (op rep)) => Pretty (HostOp op rep) Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

pretty :: HostOp op rep -> Doc ann #

prettyList :: [HostOp op rep] -> Doc ann #

(PrettyRep rep, Pretty (op rep)) => Pretty (MCOp op rep) Source # 
Instance details

Defined in Futhark.IR.MC.Op

Methods

pretty :: MCOp op rep -> Doc ann #

prettyList :: [MCOp op rep] -> Doc ann #

Pretty (inner rep) => Pretty (MemOp inner rep) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

pretty :: MemOp inner rep -> Doc ann #

prettyList :: [MemOp inner rep] -> Doc ann #

Pretty (NoOp rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: NoOp rep -> Doc ann #

prettyList :: [NoOp rep] -> Doc ann #

(PrettyRep rep, Pretty lvl) => Pretty (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

pretty :: SegOp lvl rep -> Doc ann #

prettyList :: [SegOp lvl rep] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (AppExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: AppExpBase f vn -> Doc ann #

prettyList :: [AppExpBase f vn] -> Doc ann #

IsName vn => Pretty (AttrAtom vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: AttrAtom vn -> Doc ann #

prettyList :: [AttrAtom vn] -> Doc ann #

IsName vn => Pretty (AttrInfo vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: AttrInfo vn -> Doc ann #

prettyList :: [AttrInfo vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (CaseBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: CaseBase f vn -> Doc ann #

prettyList :: [CaseBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (DecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: DecBase f vn -> Doc ann #

prettyList :: [DecBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (DimIndexBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: DimIndexBase f vn -> Doc ann #

prettyList :: [DimIndexBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ExpBase f vn -> Doc ann #

prettyList :: [ExpBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (FieldBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: FieldBase f vn -> Doc ann #

prettyList :: [FieldBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (LoopFormBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: LoopFormBase f vn -> Doc ann #

prettyList :: [LoopFormBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ModBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ModBindBase f vn -> Doc ann #

prettyList :: [ModBindBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ModExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ModExpBase f vn -> Doc ann #

prettyList :: [ModExpBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ModParamBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ModParamBase f vn -> Doc ann #

prettyList :: [ModParamBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ModTypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ModTypeBindBase f vn -> Doc ann #

prettyList :: [ModTypeBindBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ModTypeExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ModTypeExpBase f vn -> Doc ann #

prettyList :: [ModTypeExpBase f vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ProgBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ProgBase f vn -> Doc ann #

prettyList :: [ProgBase f vn] -> Doc ann #

(Pretty (Shape dim), Pretty u) => Pretty (RetTypeBase dim u) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: RetTypeBase dim u -> Doc ann #

prettyList :: [RetTypeBase dim u] -> Doc ann #

(Pretty (Shape dim), Pretty u) => Pretty (ScalarTypeBase dim u) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ScalarTypeBase dim u -> Doc ann #

prettyList :: [ScalarTypeBase dim u] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (SpecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: SpecBase f vn -> Doc ann #

prettyList :: [SpecBase f vn] -> Doc ann #

(Pretty d, IsName vn) => Pretty (TypeArgExp d vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeArgExp d vn -> Doc ann #

prettyList :: [TypeArgExp d vn] -> Doc ann #

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

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeBase dim u -> Doc ann #

prettyList :: [TypeBase dim u] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (TypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeBindBase f vn -> Doc ann #

prettyList :: [TypeBindBase f vn] -> Doc ann #

(IsName vn, Pretty d) => Pretty (TypeExp d vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: TypeExp d vn -> Doc ann #

prettyList :: [TypeExp d vn] -> Doc ann #

(Eq vn, IsName vn, Annot f) => Pretty (ValBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: ValBindBase f vn -> Doc ann #

prettyList :: [ValBindBase f vn] -> Doc ann #

Pretty (LspId m) 
Instance details

Defined in Language.LSP.Protocol.Message.LspId

Methods

pretty :: LspId m -> Doc ann #

prettyList :: [LspId m] -> Doc ann #

Pretty (TRegistration m) 
Instance details

Defined in Language.LSP.Protocol.Message.Registration

Methods

pretty :: TRegistration m -> Doc ann #

prettyList :: [TRegistration m] -> Doc ann #

Pretty (TUnregistration m) 
Instance details

Defined in Language.LSP.Protocol.Message.Registration

Methods

pretty :: TUnregistration m -> Doc ann #

prettyList :: [TUnregistration m] -> Doc ann #

ToJSON (MessageParams m) => Pretty (TNotificationMessage m) 
Instance details

Defined in Language.LSP.Protocol.Message.Types

ToJSON (MessageParams m) => Pretty (TRequestMessage m) 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: TRequestMessage m -> Doc ann #

prettyList :: [TRequestMessage m] -> Doc ann #

ToJSON (ErrorData m) => Pretty (TResponseError m) 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: TResponseError m -> Doc ann #

prettyList :: [TResponseError m] -> Doc ann #

(ToJSON (MessageResult m), ToJSON (ErrorData m)) => Pretty (TResponseMessage m) 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: TResponseMessage m -> Doc ann #

prettyList :: [TResponseMessage m] -> Doc ann #

(ToJSON a, ToJSON b) => Pretty (a |? b) 
Instance details

Defined in Language.LSP.Protocol.Types.Common

Methods

pretty :: (a |? b) -> Doc ann #

prettyList :: [a |? b] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

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

Defined in Futhark.Analysis.PrimExp

Methods

pretty :: TPrimExp t v -> Doc ann #

prettyList :: [TPrimExp t v] -> Doc ann #

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

Defined in Futhark.IR.GPU.Sizes

Methods

pretty :: Count u e -> Doc ann #

prettyList :: [Count u e] -> Doc ann #

(Pretty (ShapeBase d), Pretty (TypeBase (ShapeBase d) u), Pretty d, Pretty u, Pretty ret) => Pretty (MemInfo d u ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

pretty :: MemInfo d u ret -> Doc ann #

prettyList :: [MemInfo d u ret] -> Doc ann #

(Eq vn, IsName vn, Annot f, Pretty t) => Pretty (PatBase f vn t) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: PatBase f vn t -> Doc ann #

prettyList :: [PatBase f vn t] -> Doc ann #

KnownSymbol s => Pretty (TCustomMessage s f t) 
Instance details

Defined in Language.LSP.Protocol.Message.Types

Methods

pretty :: TCustomMessage s f t -> Doc ann #

prettyList :: [TCustomMessage s f t] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

IsName vn => Pretty (IdentBase f vn t) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

pretty :: IdentBase f vn t -> Doc ann #

prettyList :: [IdentBase f vn t] -> Doc ann #

Types

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
Monoid Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Show Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

ASTMappable ResRetType Source # 
Instance details

Defined in Language.Futhark.Traversals

Eq Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Ord Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Pretty Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: Uniqueness -> Doc ann #

prettyList :: [Uniqueness] -> Doc ann #

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

ASTMappable (TypeBase Size Uniqueness) Source # 
Instance details

Defined in Language.Futhark.Traversals

Substitutable (RetTypeBase Size Uniqueness) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase Size Uniqueness) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

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

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

data NoUniqueness Source #

A fancier name for () - encodes no uniqueness information. Also has a different prettyprinting instance.

Constructors

NoUniqueness 

Instances

Instances details
Monoid NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Show NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

ASTMappable StructType Source # 
Instance details

Defined in Language.Futhark.Traversals

Substitutable StructType Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Eq NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Ord NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Pretty NoUniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: NoUniqueness -> Doc ann #

prettyList :: [NoUniqueness] -> Doc ann #

Substitutable (Pat StructType) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (RetTypeBase Size NoUniqueness) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

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

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

ASTMappable (PatBase Info VName StructType) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (IdentBase Info VName StructType) Source # 
Instance details

Defined in Language.Futhark.Traversals

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
Monoid Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

Semigroup Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

sconcat :: NonEmpty Rank -> Rank #

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

Show Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Rename Rank Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Rank Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Rank Source # 
Instance details

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

Pretty Rank Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Rank -> Doc ann #

prettyList :: [Rank] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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.

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

Check whether one shape if a subset of another shape.

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
Show Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

Simplifiable Space Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Eq Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Space -> Space -> Ordering #

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

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

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

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

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Space -> Doc ann #

prettyList :: [Space] -> Doc ann #

data TypeBase shape u Source #

The type of a value. When comparing types for equality with ==, shapes must match.

Constructors

Prim PrimType 
Acc VName Shape [Type] u

Token, index space, element type, and uniqueness.

Array PrimType shape u 
Mem Space 

Instances

Instances details
Bifoldable TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bifold :: Monoid m => TypeBase m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> TypeBase a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> TypeBase a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> TypeBase a b -> c #

Bifunctor TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bimap :: (a -> b) -> (c -> d) -> TypeBase a c -> TypeBase b d #

first :: (a -> b) -> TypeBase a c -> TypeBase b c #

second :: (b -> c) -> TypeBase a b -> TypeBase a c #

Bitraversable TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> TypeBase a b -> f (TypeBase c d) #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Foldable (TypeBase shape) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fold :: Monoid m => TypeBase shape m -> m #

foldMap :: Monoid m => (a -> m) -> TypeBase shape a -> m #

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

foldr :: (a -> b -> b) -> b -> TypeBase shape a -> b #

foldr' :: (a -> b -> b) -> b -> TypeBase shape a -> b #

foldl :: (b -> a -> b) -> b -> TypeBase shape a -> b #

foldl' :: (b -> a -> b) -> b -> TypeBase shape a -> b #

foldr1 :: (a -> a -> a) -> TypeBase shape a -> a #

foldl1 :: (a -> a -> a) -> TypeBase shape a -> a #

toList :: TypeBase shape a -> [a] #

null :: TypeBase shape a -> Bool #

length :: TypeBase shape a -> Int #

elem :: Eq a => a -> TypeBase shape a -> Bool #

maximum :: Ord a => TypeBase shape a -> a #

minimum :: Ord a => TypeBase shape a -> a #

sum :: Num a => TypeBase shape a -> a #

product :: Num a => TypeBase shape a -> a #

Traversable (TypeBase shape) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

sequenceA :: Applicative f => TypeBase shape (f a) -> f (TypeBase shape a) #

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

sequence :: Monad m => TypeBase shape (m a) -> m (TypeBase shape a) #

Functor (TypeBase shape) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fmap :: (a -> b) -> TypeBase shape a -> TypeBase shape b #

(<$) :: a -> TypeBase shape b -> TypeBase shape a #

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

Defined in Futhark.IR.Syntax.Core

Methods

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

show :: TypeBase shape u -> String #

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

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

Defined in Futhark.IR.Prop.Types

Methods

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

mapExt :: (Int -> Int) -> TypeBase shape u -> TypeBase shape u Source #

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableRep rep => TypeBase shape u -> SimpleM rep (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 #

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 #

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

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

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

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
Show Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

Eq Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Diet Source # 
Instance details

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

Abstract syntax tree

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
Show Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

FreeIn Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ident -> FV Source #

Typed Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Ident -> Type Source #

Rename Ident Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Ident Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Ident Source # 
Instance details

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

Pretty Ident Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Ident -> Doc ann #

prettyList :: [Ident] -> Doc ann #

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
Show SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

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

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

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBuilder m => SubExp -> m (Exp (Rep m)) Source #

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: SubExp -> SrcLoc -> Exp #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Shape -> Doc ann #

prettyList :: [Shape] -> Doc ann #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: SubExp -> Doc ann #

prettyList :: [SubExp] -> Doc ann #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

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

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

Methods

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

mapExt :: (Int -> Int) -> MemInfo ExtSize u ret -> MemInfo ExtSize u ret Source #

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

data PatElem dec Source #

An element of a pattern - consisting of a name and an addditional parametric decoration. This decoration is what is expected to contain the type of the resulting variable.

Constructors

PatElem 

Fields

Instances

Instances details
Foldable PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: PatElem a -> [a] #

null :: PatElem a -> Bool #

length :: PatElem a -> Int #

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

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

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

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

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

Traversable PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Show dec => Show (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> PatElem dec -> ShowS #

show :: PatElem dec -> String #

showList :: [PatElem dec] -> ShowS #

AliasesOf dec => AliasesOf (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Aliases

Methods

aliasesOf :: PatElem dec -> Names Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElem dec -> FV Source #

Typed dec => Typed (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: PatElem dec -> Type Source #

Rename dec => Rename (PatElem dec) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatElem dec -> RenameM (PatElem dec) Source #

Substitute dec => Substitute (PatElem dec) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq dec => Eq (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: PatElem dec -> PatElem dec -> Bool #

(/=) :: PatElem dec -> PatElem dec -> Bool #

Ord dec => Ord (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: PatElem dec -> PatElem dec -> Ordering #

(<) :: PatElem dec -> PatElem dec -> Bool #

(<=) :: PatElem dec -> PatElem dec -> Bool #

(>) :: PatElem dec -> PatElem dec -> Bool #

(>=) :: PatElem dec -> PatElem dec -> Bool #

max :: PatElem dec -> PatElem dec -> PatElem dec #

min :: PatElem dec -> PatElem dec -> PatElem dec #

Pretty t => Pretty (PatElem t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: PatElem t -> Doc ann #

prettyList :: [PatElem t] -> Doc ann #

newtype Pat dec Source #

A pattern is conceptually just a list of names and their types.

Constructors

Pat 

Fields

Instances

Instances details
Foldable Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

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

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

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

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

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

toList :: Pat a -> [a] #

null :: Pat a -> Bool #

length :: Pat a -> Int #

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

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

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

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

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

Traversable Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

Functor Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Monoid (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

mempty :: Pat dec #

mappend :: Pat dec -> Pat dec -> Pat dec #

mconcat :: [Pat dec] -> Pat dec #

Semigroup (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(<>) :: Pat dec -> Pat dec -> Pat dec #

sconcat :: NonEmpty (Pat dec) -> Pat dec #

stimes :: Integral b => b -> Pat dec -> Pat dec #

Show dec => Show (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Pat dec -> ShowS #

show :: Pat dec -> String #

showList :: [Pat dec] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Pat dec -> FV Source #

Rename dec => Rename (Pat dec) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Pat dec -> RenameM (Pat dec) Source #

Substitute dec => Substitute (Pat dec) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Pat dec -> Pat dec Source #

Eq dec => Eq (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Pat dec -> Pat dec -> Bool #

(/=) :: Pat dec -> Pat dec -> Bool #

Ord dec => Ord (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Pat dec -> Pat dec -> Ordering #

(<) :: Pat dec -> Pat dec -> Bool #

(<=) :: Pat dec -> Pat dec -> Bool #

(>) :: Pat dec -> Pat dec -> Bool #

(>=) :: Pat dec -> Pat dec -> Bool #

max :: Pat dec -> Pat dec -> Pat dec #

min :: Pat dec -> Pat dec -> Pat dec #

Pretty t => Pretty (Pat t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Pat t -> Doc ann #

prettyList :: [Pat t] -> Doc ann #

data StmAux dec Source #

Auxilliary Information associated with a statement.

Constructors

StmAux 

Fields

Instances

Instances details
Semigroup dec => Semigroup (StmAux dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(<>) :: StmAux dec -> StmAux dec -> StmAux dec #

sconcat :: NonEmpty (StmAux dec) -> StmAux dec #

stimes :: Integral b => b -> StmAux dec -> StmAux dec #

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

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> StmAux dec -> ShowS #

show :: StmAux dec -> String #

showList :: [StmAux dec] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: StmAux dec -> FV Source #

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

Defined in Futhark.Transform.Rename

Methods

rename :: StmAux dec -> RenameM (StmAux dec) Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax

Methods

(==) :: StmAux dec -> StmAux dec -> Bool #

(/=) :: StmAux dec -> StmAux dec -> Bool #

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

Defined in Futhark.IR.Syntax

Methods

compare :: StmAux dec -> StmAux dec -> Ordering #

(<) :: StmAux dec -> StmAux dec -> Bool #

(<=) :: StmAux dec -> StmAux dec -> Bool #

(>) :: StmAux dec -> StmAux dec -> Bool #

(>=) :: StmAux dec -> StmAux dec -> Bool #

max :: StmAux dec -> StmAux dec -> StmAux dec #

min :: StmAux dec -> StmAux dec -> StmAux dec #

data Stm rep Source #

A local variable binding.

Constructors

Let 

Fields

Instances

Instances details
Scoped rep (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stm rep -> Scope rep Source #

Scoped rep (Stms rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stms rep -> Scope rep Source #

RepTypes rep => Show (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Stm rep -> ShowS #

show :: Stm rep -> String #

showList :: [Stm rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stm rep -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stms rep -> FV Source #

Renameable rep => Rename (Stm rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Stm rep -> RenameM (Stm rep) Source #

Substitutable rep => Substitute (Stm rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Stm rep -> Stm rep Source #

Substitute (Stm rep) => Substitute (Stms rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Stms rep -> Stms rep Source #

RepTypes rep => Eq (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Stm rep -> Stm rep -> Bool #

(/=) :: Stm rep -> Stm rep -> Bool #

RepTypes rep => Ord (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Stm rep -> Stm rep -> Ordering #

(<) :: Stm rep -> Stm rep -> Bool #

(<=) :: Stm rep -> Stm rep -> Bool #

(>) :: Stm rep -> Stm rep -> Bool #

(>=) :: Stm rep -> Stm rep -> Bool #

max :: Stm rep -> Stm rep -> Stm rep #

min :: Stm rep -> Stm rep -> Stm rep #

PrettyRep rep => Pretty (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Stm rep -> Doc ann #

prettyList :: [Stm rep] -> Doc ann #

PrettyRep rep => Pretty (Stms rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Stms rep -> Doc ann #

prettyList :: [Stms rep] -> Doc ann #

type Stms rep = Seq (Stm rep) Source #

A sequence of statements.

data SubExpRes Source #

A pairing of a subexpression and some certificates.

Constructors

SubExpRes 

type Result = [SubExpRes] Source #

The result of a body is a sequence of subexpressions.

data Body rep Source #

A body consists of a sequence of statements, terminating in a list of result values.

Constructors

Body 

Fields

Instances

Instances details
RepTypes rep => Show (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Body rep -> ShowS #

show :: Body rep -> String #

showList :: [Body rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Body rep -> FV Source #

Renameable rep => Rename (Body rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Body rep -> RenameM (Body rep) Source #

Substitutable rep => Substitute (Body rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Body rep -> Body rep Source #

RepTypes rep => Eq (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Body rep -> Body rep -> Bool #

(/=) :: Body rep -> Body rep -> Bool #

RepTypes rep => Ord (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Body rep -> Body rep -> Ordering #

(<) :: Body rep -> Body rep -> Bool #

(<=) :: Body rep -> Body rep -> Bool #

(>) :: Body rep -> Body rep -> Bool #

(>=) :: Body rep -> Body rep -> Bool #

max :: Body rep -> Body rep -> Body rep #

min :: Body rep -> Body rep -> Body rep #

PrettyRep rep => Pretty (Body rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Body rep -> Doc ann #

prettyList :: [Body rep] -> Doc ann #

PrettyRep rep => Pretty (Case (Body rep)) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Case (Body rep) -> Doc ann #

prettyList :: [Case (Body rep)] -> Doc ann #

data BasicOp Source #

A primitive operation that returns something of known size and does not itself contain any bindings.

Constructors

SubExp SubExp

A variable or constant.

Opaque OpaqueOp SubExp

Semantically and operationally just identity, but is invisible/impenetrable to optimisations (hopefully). This partially a hack to avoid optimisation (so, to work around compiler limitations), but is also used to implement tracing and other operations that are semantically invisible, but have some sort of effect (brrr).

ArrayLit [SubExp] Type

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

UnOp UnOp SubExp

Unary operation.

BinOp BinOp SubExp SubExp

Binary operation.

CmpOp CmpOp SubExp SubExp

Comparison - result type is always boolean.

ConvOp ConvOp SubExp

Conversion "casting".

Assert SubExp (ErrorMsg SubExp) (SrcLoc, [SrcLoc])

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

Index VName (Slice SubExp)

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

Update Safety VName (Slice SubExp) SubExp

An in-place update of the given array at the given position. Consumes the array. If Safe, perform a run-time bounds check and ignore the write if out of bounds (like Scatter).

FlatIndex VName (FlatSlice SubExp) 
FlatUpdate VName (FlatSlice SubExp) VName 
Concat Int (NonEmpty VName) SubExp
concat(0, [1] :| [[2, 3, 4], [5, 6]], 6) = [1, 2, 3, 4, 5, 6]

Concatenates the non-empty list of VName resulting in an array of length SubExp. The Int argument is used to specify the dimension along which the arrays are concatenated. For instance:

concat(1, [[1,2], [3, 4]] :| [[[5,6]], [[7, 8]]], 4) = [[1, 2, 5, 6], [3, 4, 7, 8]]
Manifest [Int] VName

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

Iota SubExp SubExp SubExp IntType

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.

Replicate Shape SubExp

replicate([3][2],1) = [[1,1], [1,1], [1,1]]. The result has no aliases. Copy a value by passing an empty shape.

Scratch PrimType [SubExp]

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

Reshape ReshapeKind Shape VName

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

Rearrange [Int] VName

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.

UpdateAcc VName [SubExp] [SubExp]

Update an accumulator at the given index with the given value. Consumes the accumulator and produces a new one.

Instances

Instances details
Show BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Eq BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Pretty BasicOp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: BasicOp -> Doc ann #

prettyList :: [BasicOp] -> Doc ann #

data UnOp Source #

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

Constructors

Not

E.g., ! True == False.

Complement IntType

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

Abs IntType

abs(-2) = 2.

FAbs FloatType

fabs(-2.0) = 2.0.

SSignum IntType

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

USignum IntType

Unsigned sign function: usignum(2) = 1.

FSignum FloatType

Floating-point sign function.

Instances

Instances details
Show UnOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Eq UnOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

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

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

Ord UnOp Source # 
Instance details

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

Pretty UnOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: UnOp -> Doc ann #

prettyList :: [UnOp] -> Doc ann #

data BinOp Source #

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

Constructors

Add IntType Overflow

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType Overflow

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType Overflow

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType Safety

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

UDivUp IntType Safety

Unsigned integer division. Rounds towards positive infinity.

SDiv IntType Safety

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

SDivUp IntType Safety

Signed integer division. Rounds towards positive infinity.

FDiv FloatType

Floating-point division.

FMod FloatType

Floating-point modulus.

UMod IntType Safety

Unsigned integer modulus; the countepart to UDiv.

SMod IntType Safety

Signed integer modulus; the countepart to SDiv.

SQuot IntType Safety

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

SRem IntType Safety

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

SMin IntType

Returns the smallest of two signed integers.

UMin IntType

Returns the smallest of two unsigned integers.

FMin FloatType

Returns the smallest of two floating-point numbers.

SMax IntType

Returns the greatest of two signed integers.

UMax IntType

Returns the greatest of two unsigned integers.

FMax FloatType

Returns the greatest of two floating-point numbers.

Shl IntType

Left-shift.

LShr IntType

Logical right-shift, zero-extended.

AShr IntType

Arithmetic right-shift, sign-extended.

And IntType

Bitwise and.

Or IntType

Bitwise or.

Xor IntType

Bitwise exclusive-or.

Pow IntType

Integer exponentiation.

FPow FloatType

Floating-point exponentiation.

LogAnd

Boolean and - not short-circuiting.

LogOr

Boolean or - not short-circuiting.

Instances

Instances details
Show BinOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Eq BinOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

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

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

Ord BinOp Source # 
Instance details

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

Pretty BinOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: BinOp -> Doc ann #

prettyList :: [BinOp] -> Doc ann #

data CmpOp Source #

Comparison operators are like BinOps, but they always return a boolean value. The somewhat ugly constructor names are straight out of LLVM.

Constructors

CmpEq PrimType

All types equality.

CmpUlt IntType

Unsigned less than.

CmpUle IntType

Unsigned less than or equal.

CmpSlt IntType

Signed less than.

CmpSle IntType

Signed less than or equal.

FCmpLt FloatType

Floating-point less than.

FCmpLe FloatType

Floating-point less than or equal.

CmpLlt

Boolean less than.

CmpLle

Boolean less than or equal.

Instances

Instances details
Show CmpOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Eq CmpOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

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

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

Ord CmpOp Source # 
Instance details

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

Pretty CmpOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: CmpOp -> Doc ann #

prettyList :: [CmpOp] -> Doc ann #

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.

FToB FloatType

Convert a float to a boolean value. Zero becomes false; | anything else is true.

BToF FloatType

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

Instances

Instances details
Show ConvOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Eq ConvOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

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

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

Ord ConvOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: ConvOp -> Doc ann #

prettyList :: [ConvOp] -> Doc ann #

data OpaqueOp Source #

Apart from being Opaque, what else is going on here?

Constructors

OpaqueNil

No special operation.

OpaqueTrace Text

Print the argument, prefixed by this string.

Instances

Instances details
Show OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Eq OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

data ReshapeKind Source #

Which kind of reshape is this?

Constructors

ReshapeCoerce

New shape is dynamically same as original.

ReshapeArbitrary

Any kind of reshaping.

type WithAccInput rep = (Shape, [VName], Maybe (Lambda rep, [SubExp])) Source #

The input to a WithAcc construct. Comprises the index space of the accumulator, the underlying arrays, and possibly a combining function.

data Exp rep Source #

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

Constructors

BasicOp BasicOp

A simple (non-recursive) operation.

Apply Name [(SubExp, Diet)] [(RetType rep, RetAls)] (Safety, SrcLoc, [SrcLoc]) 
Match [SubExp] [Case (Body rep)] (Body rep) (MatchDec (BranchType rep))

A match statement picks a branch by comparing the given subexpressions (called the scrutinee) with the pattern in each of the cases. If none of the cases match, the /default body/ is picked.

Loop [(FParam rep, SubExp)] LoopForm (Body rep)

loop {a} = {v} (for i < n|while b) do b.

WithAcc [WithAccInput rep] (Lambda rep)

Create accumulators backed by the given arrays (which are consumed) and pass them to the lambda, which must return the updated accumulators and possibly some extra values. The accumulators are turned back into arrays. The Shape is the write index space. The corresponding arrays must all have this shape outermost. This construct is not part of BasicOp because we need the rep parameter.

Op (Op rep) 

Instances

Instances details
RepTypes rep => Show (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Exp rep -> ShowS #

show :: Exp rep -> String #

showList :: [Exp rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Exp rep -> FV Source #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

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

RepTypes rep => Eq (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Exp rep -> Exp rep -> Bool #

(/=) :: Exp rep -> Exp rep -> Bool #

RepTypes rep => Ord (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Exp rep -> Exp rep -> Ordering #

(<) :: Exp rep -> Exp rep -> Bool #

(<=) :: Exp rep -> Exp rep -> Bool #

(>) :: Exp rep -> Exp rep -> Bool #

(>=) :: Exp rep -> Exp rep -> Bool #

max :: Exp rep -> Exp rep -> Exp rep #

min :: Exp rep -> Exp rep -> Exp rep #

PrettyRep rep => Pretty (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Exp rep -> Doc ann #

prettyList :: [Exp rep] -> Doc ann #

data Case body Source #

A non-default case in a Match statement. The number of elements in the pattern must match the number of scrutinees. A Nothing value indicates that we don't care about it (i.e. a wildcard).

Constructors

Case 

Fields

Instances

Instances details
Foldable Case Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

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

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

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

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

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

toList :: Case a -> [a] #

null :: Case a -> Bool #

length :: Case a -> Int #

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

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

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

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

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

Traversable Case Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

Functor Case Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Show body => Show (Case body) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Case body -> ShowS #

show :: Case body -> String #

showList :: [Case body] -> ShowS #

FreeIn body => FreeIn (Case body) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Case body -> FV Source #

Eq body => Eq (Case body) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Case body -> Case body -> Bool #

(/=) :: Case body -> Case body -> Bool #

Ord body => Ord (Case body) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Case body -> Case body -> Ordering #

(<) :: Case body -> Case body -> Bool #

(<=) :: Case body -> Case body -> Bool #

(>) :: Case body -> Case body -> Bool #

(>=) :: Case body -> Case body -> Bool #

max :: Case body -> Case body -> Case body #

min :: Case body -> Case body -> Case body #

PrettyRep rep => Pretty (Case (Body rep)) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Case (Body rep) -> Doc ann #

prettyList :: [Case (Body rep)] -> Doc ann #

data LoopForm Source #

For-loop or while-loop?

Constructors

ForLoop 

Fields

  • VName

    The loop iterator var

  • IntType

    The type of the loop iterator var

  • SubExp

    The number of iterations.

WhileLoop VName 

Instances

Instances details
Show LoopForm Source # 
Instance details

Defined in Futhark.IR.Syntax

FreeIn LoopForm Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: LoopForm -> FV Source #

Eq LoopForm Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord LoopForm Source # 
Instance details

Defined in Futhark.IR.Syntax

data MatchDec rt Source #

Data associated with a branch.

Constructors

MatchDec 

Fields

Instances

Instances details
Show rt => Show (MatchDec rt) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: MatchDec rt -> String #

showList :: [MatchDec rt] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: MatchDec a -> FV Source #

Eq rt => Eq (MatchDec rt) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

Defined in Futhark.IR.Syntax

Methods

compare :: MatchDec rt -> MatchDec rt -> Ordering #

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

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

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

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

max :: MatchDec rt -> MatchDec rt -> MatchDec rt #

min :: MatchDec rt -> MatchDec rt -> MatchDec rt #

data MatchSort Source #

What kind of branch is this? This has no semantic meaning, but provides hints to simplifications.

Constructors

MatchNormal

An ordinary branch.

MatchFallback

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.

MatchEquiv

Both of these branches are semantically equivalent, and it is fine to eliminate one if it turns out to have problems (e.g. contain things we cannot generate code for).

Instances

Instances details
Show MatchSort Source # 
Instance details

Defined in Futhark.IR.Syntax

Eq MatchSort Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord MatchSort Source # 
Instance details

Defined in Futhark.IR.Syntax

data Safety Source #

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

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

Constructors

Unsafe 
Safe 

Instances

Instances details
Show Safety Source # 
Instance details

Defined in Language.Futhark.Primitive

Eq Safety Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

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

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

Ord Safety Source # 
Instance details

Defined in Language.Futhark.Primitive

data Lambda rep Source #

Anonymous function for use in a SOAC.

Constructors

Lambda 

Fields

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Lambda rep -> Scope rep Source #

RepTypes rep => Show (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Lambda rep -> ShowS #

show :: Lambda rep -> String #

showList :: [Lambda rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Lambda rep -> FV Source #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Transform.Substitute

RepTypes rep => Eq (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Lambda rep -> Lambda rep -> Bool #

(/=) :: Lambda rep -> Lambda rep -> Bool #

RepTypes rep => Ord (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Lambda rep -> Lambda rep -> Ordering #

(<) :: Lambda rep -> Lambda rep -> Bool #

(<=) :: Lambda rep -> Lambda rep -> Bool #

(>) :: Lambda rep -> Lambda rep -> Bool #

(>=) :: Lambda rep -> Lambda rep -> Bool #

max :: Lambda rep -> Lambda rep -> Lambda rep #

min :: Lambda rep -> Lambda rep -> Lambda rep #

PrettyRep rep => Pretty (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Lambda rep -> Doc ann #

prettyList :: [Lambda rep] -> Doc ann #

data RetAls Source #

Information about the possible aliases of a function result.

Constructors

RetAls 

Fields

  • paramAls :: [Int]

    Which of the parameters may be aliased, numbered from zero.

  • otherAls :: [Int]

    Which of the other results may be aliased, numbered from zero. This must be a reflexive relation.

Instances

Instances details
Monoid RetAls Source # 
Instance details

Defined in Futhark.IR.Syntax

Semigroup RetAls Source # 
Instance details

Defined in Futhark.IR.Syntax

Show RetAls Source # 
Instance details

Defined in Futhark.IR.Syntax

Eq RetAls Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord RetAls Source # 
Instance details

Defined in Futhark.IR.Syntax

Definitions

data Param dec Source #

A function or lambda parameter.

Constructors

Param 

Fields

Instances

Instances details
Foldable Param Source # 
Instance details

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

Functor Param Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

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

show :: Param dec -> String #

showList :: [Param dec] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Param dec -> FV Source #

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

Defined in Futhark.IR.Prop.Types

Methods

declTypeOf :: Param dec -> DeclType Source #

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

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Param dec -> Type Source #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

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

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Param dec -> Param dec -> Ordering #

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

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

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

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

max :: Param dec -> Param dec -> Param dec #

min :: Param dec -> Param dec -> Param dec #

Pretty t => Pretty (Param t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Param t -> Doc ann #

prettyList :: [Param t] -> Doc ann #

type FParam rep = Param (FParamInfo rep) Source #

A function and loop parameter.

type LParam rep = Param (LParamInfo rep) Source #

A lambda parameter.

data FunDef rep Source #

Function definitions.

Constructors

FunDef 

Fields

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: FunDef rep -> Scope rep Source #

RepTypes rep => Show (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: FunDef rep -> String #

showList :: [FunDef rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FunDef rep -> FV Source #

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

Defined in Futhark.Transform.Rename

Methods

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

RepTypes rep => Eq (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

RepTypes rep => Ord (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: FunDef rep -> FunDef rep -> Ordering #

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

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

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

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

max :: FunDef rep -> FunDef rep -> FunDef rep #

min :: FunDef rep -> FunDef rep -> FunDef rep #

PrettyRep rep => Pretty (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: FunDef rep -> Doc ann #

prettyList :: [FunDef rep] -> Doc ann #

data EntryParam Source #

An entry point parameter, comprising its name and original type.

Instances

Instances details
Show EntryParam Source # 
Instance details

Defined in Futhark.IR.Syntax

Eq EntryParam Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord EntryParam Source # 
Instance details

Defined in Futhark.IR.Syntax

Pretty EntryParam Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: EntryParam -> Doc ann #

prettyList :: [EntryParam] -> Doc ann #

type EntryPoint = (Name, [EntryParam], [EntryResult]) Source #

Information about the inputs and outputs (return value) of an entry point.

data Prog rep Source #

An entire Futhark program.

Constructors

Prog 

Fields

  • progTypes :: OpaqueTypes

    The opaque types used in entry points. This information is used to generate extra API functions for construction and deconstruction of values of these types.

  • progConsts :: Stms rep

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

  • progFuns :: [FunDef rep]

    The functions comprising the program. All functions 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
RepTypes rep => Show (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: Prog rep -> String #

showList :: [Prog rep] -> ShowS #

RepTypes rep => Eq (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

RepTypes rep => Ord (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Prog rep -> Prog rep -> Ordering #

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

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

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

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

max :: Prog rep -> Prog rep -> Prog rep #

min :: Prog rep -> Prog rep -> Prog rep #

PrettyRep rep => Pretty (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Prog rep -> Doc ann #

prettyList :: [Prog rep] -> Doc ann #

Utils

oneStm :: Stm rep -> Stms rep Source #

A single statement.

stmsFromList :: [Stm rep] -> Stms rep Source #

Convert a statement list to a statement sequence.

stmsToList :: Stms rep -> [Stm rep] Source #

Convert a statement sequence to a statement list.

stmsHead :: Stms rep -> Maybe (Stm rep, Stms rep) Source #

The first statement in the sequence, if any.

stmsLast :: Stms lore -> Maybe (Stms lore, Stm lore) Source #

The last statement in the sequence, if any.

subExpRes :: SubExp -> SubExpRes Source #

Construct a SubExpRes with no certificates.

subExpsRes :: [SubExp] -> Result Source #

Construct a Result from subexpressions.

varRes :: VName -> SubExpRes Source #

Construct a SubExpRes from a variable name.

varsRes :: [VName] -> Result Source #

Construct a Result from variable names.

subExpResVName :: SubExpRes -> Maybe VName Source #

The VName of a SubExpRes, if it exists.