Copyright | (C) 2021-2023 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Functions to read, write, and handle manifest files.
Synopsis
- data PortDirection
- data ManifestPort = ManifestPort {
- mpName :: Text
- mpTypeName :: Text
- mpDirection :: PortDirection
- mpWidth :: Int
- mpIsClock :: Bool
- mpDomain :: Maybe Text
- newtype FilesManifest = FilesManifest [(FilePath, ByteString)]
- data Manifest = Manifest {
- manifestHash :: ByteString
- successFlags :: (Int, Int)
- ports :: [ManifestPort]
- componentNames :: [Text]
- topComponent :: Text
- fileNames :: [(FilePath, ByteString)]
- domains :: HashMap Text VDomainConfiguration
- transitiveDependencies :: [Text]
- unsafeFromHexDigest :: Text -> ByteString
- toHexDigest :: ByteString -> Text
- parseFiles :: Object -> Parser [(FilePath, ByteString)]
- data UnexpectedModification
- mkManifestPort :: Backend backend => backend -> Identifier -> HWType -> PortDirection -> ManifestPort
- manifestFilename :: IsString a => a
- mkManifest :: Backend backend => backend -> HashMap Text VDomainConfiguration -> ClashOpts -> Component -> [Component] -> [Id] -> [(FilePath, ByteString)] -> ByteString -> Manifest
- pprintUnexpectedModification :: UnexpectedModification -> String
- pprintUnexpectedModifications :: Int -> [UnexpectedModification] -> String
- readFreshManifest :: [TopEntityT] -> (BindingMap, Id) -> CompiledPrimMap -> ClashOpts -> UTCTime -> FilePath -> IO (Maybe [UnexpectedModification], Maybe Manifest, ByteString)
- isUserModified :: FilePath -> FilesManifest -> IO [UnexpectedModification]
- readManifest :: FromJSON a => FilePath -> IO (Maybe a)
- writeManifest :: FilePath -> Manifest -> IO ()
- serializeManifest :: Manifest -> Text
Documentation
data PortDirection Source #
Instances
data ManifestPort Source #
ManifestPort | |
|
Instances
Eq ManifestPort Source # | |
Defined in Clash.Driver.Manifest (==) :: ManifestPort -> ManifestPort -> Bool # (/=) :: ManifestPort -> ManifestPort -> Bool # | |
Read ManifestPort Source # | |
Defined in Clash.Driver.Manifest readsPrec :: Int -> ReadS ManifestPort # readList :: ReadS [ManifestPort] # | |
Show ManifestPort Source # | |
Defined in Clash.Driver.Manifest showsPrec :: Int -> ManifestPort -> ShowS # show :: ManifestPort -> String # showList :: [ManifestPort] -> ShowS # | |
ToJSON ManifestPort Source # | |
Defined in Clash.Driver.Manifest toJSON :: ManifestPort -> Value # toEncoding :: ManifestPort -> Encoding # toJSONList :: [ManifestPort] -> Value # toEncodingList :: [ManifestPort] -> Encoding # | |
FromJSON ManifestPort Source # | |
Defined in Clash.Driver.Manifest parseJSON :: Value -> Parser ManifestPort # parseJSONList :: Value -> Parser [ManifestPort] # |
newtype FilesManifest Source #
Instances
FromJSON FilesManifest Source # | |
Defined in Clash.Driver.Manifest parseJSON :: Value -> Parser FilesManifest # parseJSONList :: Value -> Parser [FilesManifest] # |
Information about the generated HDL between (sub)runs of the compiler
Manifest | |
|
unsafeFromHexDigest :: Text -> ByteString Source #
Decode a hex digest to a ByteString. Returns a broken digest if the decode fails - hence it being marked as unsafe.
toHexDigest :: ByteString -> Text Source #
Encode a ByteString to a hex digest.
parseFiles :: Object -> Parser [(FilePath, ByteString)] Source #
Parse files
part of a Manifest file
data UnexpectedModification Source #
Modified FilePath | Clash generated file was modified |
Added FilePath | Non-clash generated file was added |
Removed FilePath | Clash generated file was removed |
Instances
Show UnexpectedModification Source # | |
Defined in Clash.Driver.Manifest showsPrec :: Int -> UnexpectedModification -> ShowS # show :: UnexpectedModification -> String # showList :: [UnexpectedModification] -> ShowS # |
:: Backend backend | |
=> backend | Backend used to lookup port type names |
-> Identifier | Port name |
-> HWType | Port type |
-> PortDirection | |
-> ManifestPort |
manifestFilename :: IsString a => a Source #
Filename manifest file should be written to and read from
:: Backend backend | |
=> backend | Backend used to lookup port type names |
-> HashMap Text VDomainConfiguration | Domains encountered in design |
-> ClashOpts | Options Clash was run with |
-> Component | Component of top entity |
-> [Component] | All other entities |
-> [Id] | Names of dependencies (transitive closure) |
-> [(FilePath, ByteString)] | Files and their hashes |
-> ByteString | Hash returned by |
-> Manifest | New manifest |
pprintUnexpectedModification :: UnexpectedModification -> String Source #
Pretty print an unexpected modification as a list item.
pprintUnexpectedModifications :: Int -> [UnexpectedModification] -> String Source #
Pretty print a list of unexpected modifications. Print a maximum of n modifications.
:: [TopEntityT] | This top entity plus all that depend on it. |
-> (BindingMap, Id) | Core expressions and entry point. Any changes in the call graph will trigger a recompile. |
-> CompiledPrimMap | Any changes in any primitive will trigger a recompile. |
-> ClashOpts | Certain options will trigger recompiles if changed |
-> UTCTime | Clash modification date |
-> FilePath | Path to manifest file. |
-> IO (Maybe [UnexpectedModification], Maybe Manifest, ByteString) | ( Nothing if no manifest file was found , Nothing on stale cache, disabled cache, or not manifest file found ) |
Reads a manifest file. Does not return manifest file if:
- Caching is disabled through
-fclash-no-cache
. - Manifest could not be found.
- Cache is stale. This could be triggered by any of the given arguments.
Raises an exception if the manifest file or any of the files it is referring to was inaccessible.
isUserModified :: FilePath -> FilesManifest -> IO [UnexpectedModification] Source #
Determines whether the HDL directory the given LocatedManifest
was found
in contains any user made modifications. This is used by Clash to protect the
user against lost work.
readManifest :: FromJSON a => FilePath -> IO (Maybe a) Source #
Read a manifest file from disk. Returns Nothing
if file does not exist.
Any other IO exception is re-raised.
serializeManifest :: Manifest -> Text Source #
Serialize a manifest.
TODO: This should really yield a ByteString
.