| Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 QBayLogic Google Inc. 2020-2024 QBayLogic 2022 Google Inc. | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | QBayLogic B.V. <devops@qbaylogic.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Clash.Driver
Description
Module that connects all the parts of the Clash compiler library
Synopsis
- splitTopAnn :: TyConMap -> SrcSpan -> Type -> TopEntity -> TopEntity
- splitTopEntityT :: HasCallStack => TyConMap -> BindingMap -> TopEntityT -> TopEntityT
- removeForAll :: TopEntityT -> TopEntityT
- selectTopEntities :: [TopEntityT] -> Maybe (TopEntityT, [TopEntityT]) -> [TopEntityT]
- getClashModificationDate :: IO UTCTime
- hdlFromBackend :: forall backend. Backend backend => Proxy backend -> HDL
- replaceChar :: Char -> Char -> String -> String
- removeHistoryFile :: Maybe FilePath -> IO ()
- prefixModuleName :: HDL -> Maybe Text -> Maybe TopEntity -> String -> (String, Maybe String)
- generateHDL :: forall backend. Backend backend => ClashEnv -> ClashDesign -> Maybe backend -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> Maybe (TopEntityT, [TopEntityT]) -> UTCTime -> IO ()
- loadImportAndInterpret :: (MonadIO m, MonadMask m) => [String] -> [String] -> String -> ModuleName -> String -> String -> m (Either (NonEmpty InterpreterError) a)
- knownBlackBoxFunctions :: HashMap String BlackBoxFunction
- knownTemplateFunctions :: HashMap String TemplateFunction
- compilePrimitive :: [FilePath] -> [FilePath] -> FilePath -> ResolvedPrimitive -> IO CompiledPrimitive
- newtype HintError = HintError String
- processHintErrors :: (MonadThrow m, Monad m) => String -> Text -> Either (NonEmpty InterpreterError) t -> m t
- createHDL :: Backend backend => backend -> ClashOpts -> IdentifierText -> IdentifierSet -> ComponentMap -> HashMap Text VDomainConfiguration -> Component -> IdentifierText -> ([(String, Doc)], [(String, FilePath)], [(String, String)])
- writeVerilatorShim :: FilePath -> Identifier -> [(FilePath, ByteString)] -> IO [(FilePath, ByteString)]
- pprVerilatorShim :: Identifier -> Doc
- writeEdam :: FilePath -> (Identifier, Unique) -> HashMap Unique [Unique] -> HashMap Unique [EdamFile] -> [(FilePath, ByteString)] -> IO (HashMap Unique [EdamFile], [(FilePath, ByteString)])
- createEDAM :: (Identifier, Unique) -> HashMap Unique [Unique] -> HashMap Unique [EdamFile] -> [FilePath] -> (HashMap Unique [EdamFile], Edam)
- asEdamFile :: Identifier -> FilePath -> EdamFile
- prepareDir :: FilePath -> ClashOpts -> Maybe [UnexpectedModification] -> IO ()
- writeAndHash :: FilePath -> ByteString -> IO ByteString
- writeHDL :: FilePath -> (FilePath, Doc) -> IO ByteString
- writeMemoryDataFiles :: FilePath -> [(FilePath, String)] -> IO [ByteString]
- copyDataFiles :: [FilePath] -> FilePath -> [(FilePath, FilePath)] -> IO [ByteString]
- normalizeEntity :: ClashEnv -> BindingMap -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> [Id] -> Supply -> Id -> IO BindingMap
- sortTop :: BindingMap -> [TopEntityT] -> ([TopEntityT], HashMap Unique [Unique])
Documentation
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
splitTopEntityT :: HasCallStack => TyConMap -> BindingMap -> TopEntityT -> TopEntityT Source #
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 #
prefixModuleName :: HDL -> Maybe Text -> Maybe TopEntity -> String -> (String, Maybe String) Source #
Arguments
| :: forall backend. Backend backend | |
| => ClashEnv | |
| -> ClashDesign | |
| -> Maybe backend | |
| -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) | Hardcoded  | 
| -> Evaluator | Hardcoded evaluator for partial evaluation | 
| -> Evaluator | Hardcoded evaluator for WHNF (old evaluator) | 
| -> Maybe (TopEntityT, [TopEntityT]) | Main top entity to compile. If Nothing, all top entities in the
  | 
| -> 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 ( | 
| -> m (Either (NonEmpty 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.
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.
Instances
| Show HintError Source # | |
| Exception HintError Source # | |
| Defined in Clash.Driver Methods toException :: HintError -> SomeException Source # fromException :: SomeException -> Maybe HintError Source # displayException :: HintError -> String Source # | |
Arguments
| :: (MonadThrow m, Monad m) | |
| => String | Function to interpret | 
| -> Text | BlackBox function name | 
| -> Either (NonEmpty InterpreterError) t | Hint result | 
| -> m t | 
Arguments
| :: Backend backend | |
| => backend | Backend | 
| -> ClashOpts | Global Clash options | 
| -> 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
writeVerilatorShim :: FilePath -> Identifier -> [(FilePath, ByteString)] -> IO [(FilePath, ByteString)] Source #
pprVerilatorShim :: Identifier -> Doc Source #
Create a shim for using verilator, which loads the entity and steps through simulation until finished.
writeEdam :: FilePath -> (Identifier, Unique) -> HashMap Unique [Unique] -> HashMap Unique [EdamFile] -> [(FilePath, ByteString)] -> IO (HashMap Unique [EdamFile], [(FilePath, ByteString)]) 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
asEdamFile :: Identifier -> FilePath -> EdamFile Source #
Arguments
| :: FilePath | HDL directory to prepare | 
| -> ClashOpts | Relevant options:  | 
| -> Maybe [UnexpectedModification] | Did directory contain unexpected modifications? See  | 
| -> 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.
Arguments
| :: FilePath | Directory to copy files to | 
| -> [(FilePath, String)] | (filename, content) | 
| -> IO [ByteString] | 
Copy given files
Arguments
| :: [FilePath] | Import directories passed in with  | 
| -> FilePath | Directory to copy to | 
| -> [(FilePath, FilePath)] | 
 | 
| -> IO [ByteString] | SHA256 hashes of written files | 
Copy data files added with ~FILE
Arguments
| :: ClashEnv | |
| -> BindingMap | All bindings | 
| -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) | Hardcoded  | 
| -> Evaluator | Hardcoded evaluator for partial evaluation | 
| -> Evaluator | Hardcoded evaluator for WHNF (old evaluator) | 
| -> [Id] | TopEntities | 
| -> Supply | Unique supply | 
| -> Id | root of the hierarchy | 
| -> IO BindingMap | 
Normalize a complete hierarchy
sortTop :: BindingMap -> [TopEntityT] -> ([TopEntityT], HashMap Unique [Unique]) Source #
Reverse topologically sort given top entities. Also returns a mapping that maps a top entity to its reverse topologically sorted transitive dependencies.