Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 QBayLogic Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Module that connects all the parts of the Clash compiler library
Synopsis
- splitTopAnn :: TyConMap -> SrcSpan -> Type -> TopEntity -> TopEntity
- splitTopEntityT :: HasCallStack => TyConMap -> BindingMap -> TopEntityT -> TopEntityT
- getClashModificationDate :: IO UTCTime
- generateHDL :: forall backend. Backend backend => CustomReprs -> BindingMap -> Maybe backend -> CompiledPrimMap -> TyConMap -> IntMap TyConName -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> (PrimStep, PrimUnwind) -> [TopEntityT] -> Maybe (TopEntityT, [TopEntityT]) -> ClashOpts -> (UTCTime, UTCTime) -> IO ()
- loadImportAndInterpret :: (MonadIO m, MonadMask m) => [String] -> [String] -> String -> ModuleName -> String -> String -> m (Either InterpreterError a)
- knownBlackBoxFunctions :: HashMap String BlackBoxFunction
- knownTemplateFunctions :: HashMap String TemplateFunction
- compilePrimitive :: [FilePath] -> [FilePath] -> FilePath -> ResolvedPrimitive -> IO CompiledPrimitive
- processHintError :: Monad m => String -> Text -> (t -> r) -> Either InterpreterError t -> m r
- createHDL :: Backend backend => backend -> Identifier -> HashMap Identifier Word -> [([Bool], SrcSpan, HashMap Identifier Word, Component)] -> Component -> (Identifier, Either Manifest Manifest) -> ([(String, Doc)], Manifest, [(String, FilePath)], [(String, String)])
- prepareDir :: Bool -> String -> String -> IO ()
- writeHDL :: FilePath -> (String, Doc) -> IO ()
- writeMemoryDataFiles :: FilePath -> [(String, String)] -> IO ()
- copyDataFiles :: [FilePath] -> FilePath -> [(String, FilePath)] -> IO ()
- callGraphBindings :: BindingMap -> Id -> [Term]
- normalizeEntity :: CustomReprs -> BindingMap -> CompiledPrimMap -> TyConMap -> IntMap TyConName -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> (PrimStep, PrimUnwind) -> [Id] -> ClashOpts -> Supply -> Id -> BindingMap
- sortTop :: BindingMap -> [TopEntityT] -> [TopEntityT]
Documentation
:: 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
splitTopEntityT :: HasCallStack => TyConMap -> BindingMap -> TopEntityT -> TopEntityT Source #
getClashModificationDate :: IO UTCTime Source #
Get modification data of current clash binary.
:: forall backend. Backend backend | |
=> CustomReprs | |
-> 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 |
-> (PrimStep, PrimUnwind) | Hardcoded evaluator (delta-reduction) |
-> [TopEntityT] | All topentities and associated testbench |
-> 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 #
:: (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:
- Interpret without explicitly loading the module. This will succeed if
the module was already loaded through a package database (set using
interpreterArgs
). - 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.
:: [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 #
:: Backend backend | |
=> backend | Backend |
-> Identifier | Module hierarchy root |
-> HashMap Identifier Word | Component names |
-> [([Bool], SrcSpan, HashMap Identifier Word, Component)] | List of components |
-> Component | Top component |
-> (Identifier, Either Manifest Manifest) | Name of the manifest file
+ Either:
* Left manifest: Only write/update the hashes of the |
-> ([(String, Doc)], Manifest, [(String, FilePath)], [(String, String)]) | The pretty-printed HDL documents + The update manifest file + The data files that need to be copied |
Pretty print Components to HDL Documents
Prepares the directory for writing HDL files. This means creating the dir if it does not exist and removing all existing .hdl files from it.
Copy given files
:: BindingMap | All bindings |
-> Id | Root of the call graph |
-> [Term] |
Get all the terms corresponding to a call graph
:: 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 |
-> (PrimStep, PrimUnwind) | Hardcoded evaluator (delta-reduction) |
-> [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] Source #
topologically sort the top entities