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

[ futhark, library, program ] [ Propose Tags ]

Futhark is a small programming language designed to be compiled to efficient parallel code. It is a statically typed, data-parallel, and purely functional array language in the ML family, and comes with a heavily optimising ahead-of-time compiler that presently generates GPU code via CUDA and OpenCL, although the language itself is hardware-agnostic.

For more information, see the website at https://futhark-lang.org

For introductionary information about hacking on the Futhark compiler, see the hacking guide. Regarding the internal design of the compiler, the following modules make good starting points:

  • Futhark contains a basic architectural overview of the compiler.

  • Futhark.IR.Syntax explains the basic design of the intermediate representation (IR).

  • Futhark.Construct explains how to write code that manipulates and creates AST fragments.

Modules

[Last Documentation]

  • Futhark
    • AD
      • Futhark.AD.Derivatives
      • Futhark.AD.Fwd
      • Futhark.AD.Rev
        • Futhark.AD.Rev.Loop
        • Futhark.AD.Rev.Map
        • Futhark.AD.Rev.Monad
        • Futhark.AD.Rev.Reduce
        • Futhark.AD.Rev.SOAC
        • Futhark.AD.Rev.Scan
        • Futhark.AD.Rev.Scatter
    • Futhark.Actions
    • Analysis
      • Futhark.Analysis.Alias
      • Futhark.Analysis.CallGraph
      • Futhark.Analysis.DataDependencies
      • HORep
        • Futhark.Analysis.HORep.MapNest
        • Futhark.Analysis.HORep.SOAC
      • Futhark.Analysis.Interference
      • Futhark.Analysis.LastUse
      • Futhark.Analysis.MemAlias
      • Futhark.Analysis.Metrics
        • Futhark.Analysis.Metrics.Type
      • Futhark.Analysis.PrimExp
        • Futhark.Analysis.PrimExp.Convert
        • Futhark.Analysis.PrimExp.Parse
        • Futhark.Analysis.PrimExp.Simplify
      • Futhark.Analysis.Rephrase
      • Futhark.Analysis.SymbolTable
      • Futhark.Analysis.UsageTable
    • Futhark.Bench
    • Futhark.Builder
      • Futhark.Builder.Class
    • CLI
      • Futhark.CLI.Autotune
      • Futhark.CLI.Bench
      • Futhark.CLI.C
      • Futhark.CLI.CUDA
      • Futhark.CLI.Check
      • Futhark.CLI.Datacmp
      • Futhark.CLI.Dataset
      • Futhark.CLI.Defs
      • Futhark.CLI.Dev
      • Futhark.CLI.Doc
      • Futhark.CLI.LSP
      • Futhark.CLI.Literate
      • Futhark.CLI.Main
      • Futhark.CLI.Misc
      • Futhark.CLI.Multicore
      • Futhark.CLI.MulticoreISPC
      • Futhark.CLI.MulticoreWASM
      • Futhark.CLI.OpenCL
      • Futhark.CLI.Pkg
      • Futhark.CLI.PyOpenCL
      • Futhark.CLI.Python
      • Futhark.CLI.Query
      • Futhark.CLI.REPL
      • Futhark.CLI.Run
      • Futhark.CLI.Test
      • Futhark.CLI.WASM
    • CodeGen
      • Backends
        • Futhark.CodeGen.Backends.CCUDA
          • Futhark.CodeGen.Backends.CCUDA.Boilerplate
        • Futhark.CodeGen.Backends.COpenCL
          • Futhark.CodeGen.Backends.COpenCL.Boilerplate
        • Futhark.CodeGen.Backends.GenericC
          • Futhark.CodeGen.Backends.GenericC.CLI
          • Futhark.CodeGen.Backends.GenericC.Code
          • Futhark.CodeGen.Backends.GenericC.EntryPoints
          • Futhark.CodeGen.Backends.GenericC.Monad
          • Futhark.CodeGen.Backends.GenericC.Options
          • Futhark.CodeGen.Backends.GenericC.Server
          • Futhark.CodeGen.Backends.GenericC.Types
        • Futhark.CodeGen.Backends.GenericPython
          • Futhark.CodeGen.Backends.GenericPython.AST
          • Futhark.CodeGen.Backends.GenericPython.Options
        • Futhark.CodeGen.Backends.GenericWASM
        • Futhark.CodeGen.Backends.MulticoreC
        • Futhark.CodeGen.Backends.MulticoreISPC
        • Futhark.CodeGen.Backends.MulticoreWASM
        • Futhark.CodeGen.Backends.PyOpenCL
          • Futhark.CodeGen.Backends.PyOpenCL.Boilerplate
        • Futhark.CodeGen.Backends.SequentialC
          • Futhark.CodeGen.Backends.SequentialC.Boilerplate
        • Futhark.CodeGen.Backends.SequentialPython
        • Futhark.CodeGen.Backends.SequentialWASM
        • Futhark.CodeGen.Backends.SimpleRep
      • Futhark.CodeGen.ImpCode
        • Futhark.CodeGen.ImpCode.GPU
        • Futhark.CodeGen.ImpCode.Multicore
        • Futhark.CodeGen.ImpCode.OpenCL
        • Futhark.CodeGen.ImpCode.Sequential
      • Futhark.CodeGen.ImpGen
        • Futhark.CodeGen.ImpGen.CUDA
        • Futhark.CodeGen.ImpGen.GPU
          • Futhark.CodeGen.ImpGen.GPU.Base
          • Futhark.CodeGen.ImpGen.GPU.SegHist
          • Futhark.CodeGen.ImpGen.GPU.SegMap
          • Futhark.CodeGen.ImpGen.GPU.SegRed
          • Futhark.CodeGen.ImpGen.GPU.SegScan
            • Futhark.CodeGen.ImpGen.GPU.SegScan.SinglePass
            • Futhark.CodeGen.ImpGen.GPU.SegScan.TwoPass
          • Futhark.CodeGen.ImpGen.GPU.ToOpenCL
          • Futhark.CodeGen.ImpGen.GPU.Transpose
        • Futhark.CodeGen.ImpGen.Multicore
          • Futhark.CodeGen.ImpGen.Multicore.Base
          • Futhark.CodeGen.ImpGen.Multicore.SegHist
          • Futhark.CodeGen.ImpGen.Multicore.SegMap
          • Futhark.CodeGen.ImpGen.Multicore.SegRed
          • Futhark.CodeGen.ImpGen.Multicore.SegScan
        • Futhark.CodeGen.ImpGen.OpenCL
        • Futhark.CodeGen.ImpGen.Sequential
        • Futhark.CodeGen.ImpGen.Transpose
      • OpenCL
        • Futhark.CodeGen.OpenCL.Heuristics
      • RTS
        • Futhark.CodeGen.RTS.C
        • Futhark.CodeGen.RTS.JavaScript
        • Futhark.CodeGen.RTS.Python
      • Futhark.CodeGen.SetDefaultSpace
    • Futhark.Compiler
      • Futhark.Compiler.CLI
      • Futhark.Compiler.Config
      • Futhark.Compiler.Program
    • Futhark.Construct
    • Doc
      • Futhark.Doc.Generator
    • Futhark.Error
    • Futhark.FreshNames
    • Futhark.IR
      • Futhark.IR.Aliases
      • Futhark.IR.GPU
        • Futhark.IR.GPU.Op
        • Futhark.IR.GPU.Simplify
        • Futhark.IR.GPU.Sizes
      • Futhark.IR.GPUMem
      • Futhark.IR.MC
        • Futhark.IR.MC.Op
      • Futhark.IR.MCMem
      • Futhark.IR.Mem
        • Futhark.IR.Mem.IxFun
        • Futhark.IR.Mem.Simplify
      • Futhark.IR.Parse
      • Futhark.IR.Pretty
      • Futhark.IR.Prop
        • Futhark.IR.Prop.Aliases
        • Futhark.IR.Prop.Constants
        • Futhark.IR.Prop.Names
        • Futhark.IR.Prop.Patterns
        • Futhark.IR.Prop.Rearrange
        • Futhark.IR.Prop.Reshape
        • Futhark.IR.Prop.Scope
        • Futhark.IR.Prop.TypeOf
        • Futhark.IR.Prop.Types
      • Futhark.IR.Rep
      • Futhark.IR.RetType
      • Futhark.IR.SOACS
        • Futhark.IR.SOACS.SOAC
        • Futhark.IR.SOACS.Simplify
      • Futhark.IR.SegOp
      • Futhark.IR.Seq
      • Futhark.IR.SeqMem
      • Futhark.IR.Syntax
        • Futhark.IR.Syntax.Core
      • Futhark.IR.Traversals
      • Futhark.IR.TypeCheck
    • Futhark.Internalise
      • Futhark.Internalise.AccurateSizes
      • Futhark.Internalise.Bindings
      • Futhark.Internalise.Defunctionalise
      • Futhark.Internalise.Defunctorise
      • Futhark.Internalise.Entry
      • Futhark.Internalise.Exps
      • Futhark.Internalise.Lambdas
      • Futhark.Internalise.LiftLambdas
      • Futhark.Internalise.Monad
      • Futhark.Internalise.Monomorphise
      • Futhark.Internalise.TypesValues
    • LSP
      • Futhark.LSP.Compile
      • Futhark.LSP.Diagnostic
      • Futhark.LSP.Handlers
      • Futhark.LSP.PositionMapping
      • Futhark.LSP.State
      • Futhark.LSP.Tool
    • Futhark.MonadFreshNames
    • Optimise
      • Futhark.Optimise.BlkRegTiling
      • Futhark.Optimise.CSE
      • Futhark.Optimise.DoubleBuffer
      • Futhark.Optimise.EntryPointMem
      • Futhark.Optimise.Fusion
        • Futhark.Optimise.Fusion.Composing
        • Futhark.Optimise.Fusion.GraphRep
        • Futhark.Optimise.Fusion.TryFusion
      • Futhark.Optimise.GenRedOpt
      • Futhark.Optimise.HistAccs
      • Futhark.Optimise.InPlaceLowering
        • Futhark.Optimise.InPlaceLowering.LowerIntoStm
        • Futhark.Optimise.InPlaceLowering.SubstituteIndices
      • Futhark.Optimise.InliningDeadFun
      • Futhark.Optimise.MemoryBlockMerging
        • Futhark.Optimise.MemoryBlockMerging.GreedyColoring
      • Futhark.Optimise.MergeGPUBodies
      • Futhark.Optimise.ReduceDeviceSyncs
        • Futhark.Optimise.ReduceDeviceSyncs.MigrationTable
          • Futhark.Optimise.ReduceDeviceSyncs.MigrationTable.Graph
      • Futhark.Optimise.Simplify
        • Futhark.Optimise.Simplify.Engine
        • Futhark.Optimise.Simplify.Rep
        • Futhark.Optimise.Simplify.Rule
        • Futhark.Optimise.Simplify.Rules
          • Futhark.Optimise.Simplify.Rules.BasicOp
          • Futhark.Optimise.Simplify.Rules.ClosedForm
          • Futhark.Optimise.Simplify.Rules.Index
          • Futhark.Optimise.Simplify.Rules.Loop
          • Futhark.Optimise.Simplify.Rules.Match
          • Futhark.Optimise.Simplify.Rules.Simple
      • Futhark.Optimise.Sink
      • Futhark.Optimise.TileLoops
        • Futhark.Optimise.TileLoops.Shared
      • Futhark.Optimise.Unstream
    • Futhark.Pass
      • Futhark.Pass.AD
      • Futhark.Pass.ExpandAllocations
      • Futhark.Pass.ExplicitAllocations
        • Futhark.Pass.ExplicitAllocations.GPU
        • Futhark.Pass.ExplicitAllocations.MC
        • Futhark.Pass.ExplicitAllocations.SegOp
        • Futhark.Pass.ExplicitAllocations.Seq
      • Futhark.Pass.ExtractKernels
        • Futhark.Pass.ExtractKernels.BlockedKernel
        • Futhark.Pass.ExtractKernels.DistributeNests
        • Futhark.Pass.ExtractKernels.Distribution
        • Futhark.Pass.ExtractKernels.ISRWIM
        • Futhark.Pass.ExtractKernels.Interchange
        • Futhark.Pass.ExtractKernels.Intragroup
        • Futhark.Pass.ExtractKernels.StreamKernel
        • Futhark.Pass.ExtractKernels.ToGPU
      • Futhark.Pass.ExtractMulticore
      • Futhark.Pass.FirstOrderTransform
      • Futhark.Pass.KernelBabysitting
      • Futhark.Pass.Simplify
    • Futhark.Passes
    • Futhark.Pipeline
    • Pkg
      • Futhark.Pkg.Info
      • Futhark.Pkg.Solve
      • Futhark.Pkg.Types
    • Futhark.Script
    • Futhark.Test
      • Futhark.Test.Spec
      • Futhark.Test.Values
    • Futhark.Tools
    • Transform
      • Futhark.Transform.CopyPropagate
      • Futhark.Transform.FirstOrderTransform
      • Futhark.Transform.Rename
      • Futhark.Transform.Substitute
    • Futhark.Util
      • Futhark.Util.Console
      • Futhark.Util.IntegralExp
      • Futhark.Util.Loc
      • Futhark.Util.Log
      • Futhark.Util.Options
      • Futhark.Util.Pretty
      • Futhark.Util.ProgressBar
      • Futhark.Util.Table
    • Futhark.Version
  • Language
    • Language.Futhark
      • Language.Futhark.Core
      • Language.Futhark.FreeVars
      • Language.Futhark.Interpreter
      • Language.Futhark.Parser
        • Lexer
          • Language.Futhark.Parser.Lexer.Tokens
          • Language.Futhark.Parser.Lexer.Wrapper
        • Language.Futhark.Parser.Monad
      • Language.Futhark.Prelude
      • Language.Futhark.Pretty
      • Language.Futhark.Primitive
        • Language.Futhark.Primitive.Parse
      • Language.Futhark.Prop
      • Language.Futhark.Query
      • Language.Futhark.Semantic
      • Language.Futhark.Syntax
      • Language.Futhark.Traversals
      • Language.Futhark.Tuple
      • Language.Futhark.TypeChecker
        • Language.Futhark.TypeChecker.Match
        • Language.Futhark.TypeChecker.Modules
        • Language.Futhark.TypeChecker.Monad
        • Language.Futhark.TypeChecker.Terms
          • Language.Futhark.TypeChecker.Terms.DoLoop
          • Language.Futhark.TypeChecker.Terms.Monad
          • Language.Futhark.TypeChecker.Terms.Pat
        • Language.Futhark.TypeChecker.Types
        • Language.Futhark.TypeChecker.Unify
      • Language.Futhark.Warnings

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.7.3, 0.7.4, 0.8.1, 0.9.1, 0.10.1, 0.10.2, 0.11.1, 0.11.2, 0.12.1, 0.12.2, 0.12.3, 0.13.1, 0.13.2, 0.14.1, 0.15.1, 0.15.2, 0.15.3, 0.15.4, 0.15.5, 0.15.6, 0.15.7, 0.15.8, 0.16.1, 0.16.2, 0.16.3, 0.16.4, 0.17.1, 0.17.2, 0.17.3, 0.18.1, 0.18.2, 0.18.3, 0.18.4, 0.18.5, 0.18.6, 0.19.1, 0.19.2, 0.19.3, 0.19.4, 0.19.5, 0.19.6, 0.19.7, 0.20.1, 0.20.2, 0.20.3, 0.20.4, 0.20.5, 0.20.6, 0.20.7, 0.20.8, 0.21.1, 0.21.2, 0.21.3, 0.21.4, 0.21.5, 0.21.6, 0.21.7, 0.21.8, 0.21.9, 0.21.10, 0.21.11, 0.21.12, 0.21.13, 0.21.14, 0.21.15, 0.22.1, 0.22.2, 0.22.3, 0.22.4, 0.22.5, 0.22.6, 0.22.7, 0.23.1, 0.24.1, 0.24.2, 0.24.3, 0.25.1, 0.25.2, 0.25.3, 0.25.4, 0.25.5, 0.25.6, 0.25.7, 0.25.8, 0.25.9, 0.25.10, 0.25.11, 0.25.12, 0.25.13, 0.25.14, 0.25.15
Dependencies aeson (>=2.0.0.0), ansi-terminal (>=0.6.3.1), array (>=0.4), base (>=4.15 && <5), base16-bytestring, binary (>=0.8.3), blaze-html (>=0.9.0.1), bmp (>=1.2.6.3), bytestring (>=0.10.8), bytestring-to-vector (>=0.3.0.1), cmark-gfm (>=0.2.1), co-log-core, containers (>=0.6.2.1), cryptohash-md5, Diff (>=0.4.1), directory (>=1.3.0.0), directory-tree (>=0.12.1), dlist (>=0.6.0.1), fgl, fgl-visualize, file-embed (>=0.0.14.0), filepath (>=1.4.1.1), free (>=4.12.4), futhark, futhark-data (>=1.1.0.0), futhark-manifest (>=1.1.0.0), futhark-server (>=1.2.1.0), githash (>=0.1.6.1), half (>=0.3), haskeline, language-c-quote (>=0.12), lens, lsp (>=1.5 && <1.6), mainland-pretty (>=0.7.1), megaparsec (>=9.0.0), mtl (>=2.2.1), mwc-random, neat-interpolation (>=0.3), parallel (>=3.2.1.0), process (>=1.4.3.0), process-extras (>=0.7.2), random (>=1.2.0), regex-tdfa (>=1.2), srcloc (>=0.4), statistics, template-haskell (>=2.11.1), temporary, terminal-size (>=0.3), text (>=1.2.2.2), time (>=1.6.0.1), transformers (>=0.3), vector (>=0.12), versions (>=5.0.0), zip-archive (>=0.3.1.1), zlib (>=0.6.1.2) [details]
License ISC
Author
Maintainer Troels Henriksen athas@sigkill.dk
Category Futhark
Home page https://futhark-lang.org
Bug tracker https://github.com/diku-dk/futhark/issues
Source repo head: git clone https://github.com/diku-dk/futhark
Uploaded by TroelsHenriksen at 2022-07-30T08:29:31Z
Distributions NixOS:0.25.15
Reverse Dependencies 1 direct, 0 indirect [details]
Executables futhark
Downloads 26482 total (301 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2022-07-30 [all 2 reports]