clash-lib-1.4.6: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
2016-2017 Myrtle Software Ltd
2017 QBayLogic Google Inc.
2020 QBayLogic
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Driver

Description

Module that connects all the parts of the Clash compiler library

Synopsis

Documentation

splitTopAnn Source #

Arguments

:: TyConMap 
-> SrcSpan

Source location of top entity (for error reporting)

-> Type

Top entity body

-> TopEntity

Port annotations for top entity

-> TopEntity

New top entity with split ports (or the old one if not applicable)

Worker function of splitTopEntityT

removeForAll :: TopEntityT -> TopEntityT Source #

Remove constraints such as 'a ~ 3'.

selectTopEntities :: [TopEntityT] -> Maybe (TopEntityT, [TopEntityT]) -> [TopEntityT] Source #

Given a list of all found top entities and _maybe_ a top entity (+dependencies) passed in by '-main-is', return the list of top entities Clash needs to compile.

getClashModificationDate :: IO UTCTime Source #

Get modification data of current clash binary.

hdlFromBackend :: forall backend. Backend backend => Proxy backend -> HDL Source #

generateHDL Source #

Arguments

:: forall backend. Backend backend 
=> CustomReprs 
-> HashMap Text VDomainConfiguration

Known domains to configurations

-> BindingMap

Set of functions

-> Maybe backend 
-> CompiledPrimMap

Primitive / BlackBox Definitions

-> TyConMap

TyCon cache

-> IntMap TyConName

Tuple TyCon cache

-> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)))

Hardcoded Type -> HWType translator

-> Evaluator

Hardcoded evaluator for partial evaluation

-> [TopEntityT]

All topentities

-> Maybe (TopEntityT, [TopEntityT])

Main top entity to compile. If Nothing, all top entities in previous argument will be compiled.

-> ClashOpts

Debug information level for the normalization process

-> (UTCTime, UTCTime) 
-> IO () 

Create a set of target HDL files for a set of functions

loadImportAndInterpret Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> [String]

Extra search path (usually passed as -i)

-> [String]

Interpreter args

-> String

The folder in which the GHC bootstrap libraries (base, containers, etc.) can be found

-> ModuleName

Module function lives in

-> String

Function name

-> String

Type name (BlackBoxFunction or TemplateFunction)

-> m (Either InterpreterError a) 

Interpret a specific function from a specific module. This action tries two things:

  1. Interpret without explicitly loading the module. This will succeed if the module was already loaded through a package database (set using interpreterArgs).
  2. If (1) fails, it does try to load it explicitly. If this also fails, an error is returned.

knownBlackBoxFunctions :: HashMap String BlackBoxFunction Source #

List of known BlackBoxFunctions used to prevent Hint from firing. This improves Clash startup times.

knownTemplateFunctions :: HashMap String TemplateFunction Source #

List of known TemplateFunctions used to prevent Hint from firing. This improves Clash startup times.

compilePrimitive Source #

Arguments

:: [FilePath]

Import directories (-i flag)

-> [FilePath]

Package databases

-> FilePath

The folder in which the GHC bootstrap libraries (base, containers, etc.) can be found

-> ResolvedPrimitive

Primitive to compile

-> IO CompiledPrimitive 

Compiles blackbox functions and parses blackbox templates.

processHintError :: Monad m => String -> Text -> (t -> r) -> Either InterpreterError t -> m r Source #

createHDL Source #

Arguments

:: Backend backend 
=> backend

Backend

-> IdentifierText

Module hierarchy root

-> IdentifierSet

Component names

-> ComponentMap

List of components

-> HashMap Text VDomainConfiguration

Known domains to configurations

-> Component

Top component

-> IdentifierText

Name of the manifest file

-> ([(String, Doc)], [(String, FilePath)], [(String, String)])

The pretty-printed HDL documents + The data files that need to be copied

Pretty print Components to HDL Documents

createEDAM Source #

Arguments

:: (Identifier, Unique) 
-> HashMap Unique [Unique]

Top entity dependency map

-> HashMap Unique [EdamFile]

Edam files of each top entity

-> [FilePath]

Files to include in Edam file

-> (HashMap Unique [EdamFile], Edam)

(updated map, edam)

Create an Edalize metadata file for using Edalize to build the project.

TODO: Handle libraries. Also see: https://github.com/olofk/edalize/issues/220

prepareDir Source #

Arguments

:: FilePath

HDL directory to prepare

-> ClashOpts

Relevant options: -fclash-no-clean

-> Maybe [UnexpectedModification]

Did directory contain unexpected modifications? See readFreshManifest

-> IO () 

Prepares directory for writing HDL files.

writeAndHash :: FilePath -> ByteString -> IO ByteString Source #

Write a file to disk in chunks. Returns SHA256 sum of file contents.

writeHDL :: FilePath -> (FilePath, Doc) -> IO ByteString Source #

Writes a HDL file to the given directory. Returns SHA256 hash of written file.

writeMemoryDataFiles Source #

Arguments

:: FilePath

Directory to copy files to

-> [(FilePath, String)]

(filename, content)

-> IO [ByteString] 

Copy given files

copyDataFiles Source #

Arguments

:: [FilePath]

Import directories passed in with -i

-> FilePath

Directory to copy to

-> [(FilePath, FilePath)]
(name of newly made file in HDL output dir, file to copy)
-> IO [ByteString]

SHA256 hashes of written files

Copy data files added with ~FILEPATH

normalizeEntity Source #

Arguments

:: CustomReprs 
-> BindingMap

All bindings

-> CompiledPrimMap

BlackBox HDL templates

-> TyConMap

TyCon cache

-> IntMap TyConName

Tuple TyCon cache

-> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)))

Hardcoded Type -> HWType translator

-> Evaluator

Hardcoded evaluator for partial evaluation

-> [Id]

TopEntities

-> ClashOpts

Debug information level for the normalization process

-> Supply

Unique supply

-> Id

root of the hierarchy

-> BindingMap 

Normalize a complete hierarchy

sortTop :: BindingMap -> [TopEntityT] -> ([TopEntityT], HashMap Unique [Unique]) Source #

topologically sort the top entities