clash-lib-1.7.0: Clash: a functional hardware description language - As a library
Copyright(C) 2021-2023 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Driver.Manifest

Description

Functions to read, write, and handle manifest files.

Synopsis

Documentation

data PortDirection Source #

Constructors

In 
Out 
InOut 

Instances

Instances details
Eq PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

Read PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

Show PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

Generic PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

Associated Types

type Rep PortDirection :: Type -> Type #

ToJSON PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

FromJSON PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

type Rep PortDirection Source # 
Instance details

Defined in Clash.Driver.Manifest

type Rep PortDirection = D1 ('MetaData "PortDirection" "Clash.Driver.Manifest" "clash-lib-1.7.0-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Out" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InOut" 'PrefixI 'False) (U1 :: Type -> Type)))

data ManifestPort Source #

Constructors

ManifestPort 

Fields

newtype FilesManifest Source #

Just the fileNames part of Manifest

Constructors

FilesManifest [(FilePath, ByteString)] 

Instances

Instances details
FromJSON FilesManifest Source # 
Instance details

Defined in Clash.Driver.Manifest

data Manifest Source #

Information about the generated HDL between (sub)runs of the compiler

Constructors

Manifest 

Fields

  • manifestHash :: ByteString

    Hash digest of the TopEntity and all its dependencies.

  • successFlags :: (Int, Int)

    Compiler flags used to achieve successful compilation:

    • opt_inlineLimit
    • opt_specLimit
  • ports :: [ManifestPort]

    Ports in the generated TopEntity.

  • componentNames :: [Text]

    Names of all the generated components for the TopEntity (does not include the names of the components of the TestBench accompanying the TopEntity).

    This list is reverse topologically sorted. I.e., a component might depend on any component listed before it, but not after it.

  • topComponent :: Text

    Design entry point. This is usually the component annotated with a TopEntity annotation.

  • fileNames :: [(FilePath, ByteString)]

    Names and hashes of all the generated files for the TopEntity. Hashes are SHA256.

    This list is reverse topologically sorted. I.e., a component might depend on any component listed before it, but not after it.

  • domains :: HashMap Text VDomainConfiguration

    Domains encountered in design

  • transitiveDependencies :: [Text]

    Dependencies of this design (fully qualified binder names). Is a transitive closure of all dependencies.

    This list is reverse topologically sorted. I.e., a component might depend on any component listed before it, but not after it.

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 #

Constructors

Modified FilePath

Clash generated file was modified

Added FilePath

Non-clash generated file was added

Removed FilePath

Clash generated file was removed

mkManifestPort Source #

Arguments

:: 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

mkManifest Source #

Arguments

:: 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 readFreshManifest

-> 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.

readFreshManifest Source #

Arguments

:: [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.

writeManifest :: FilePath -> Manifest -> IO () Source #

Write manifest file to disk

serializeManifest :: Manifest -> Text Source #

Serialize a manifest.

TODO: This should really yield a ByteString.