Copyright | (C) 2019 Myrtle Software Ltd |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type Outro = (((((("" :$$$: "------") :$$$: "") :$$$: "You tried to apply an explicitly routed clock, reset, or enable line") :$$$: "to a construct with, possibly, an implicitly routed one. Clash failed to") :$$$: "unambigously link the given domain (by passing in a 'Clock', 'Reset', or") :$$$: "'Enable') to the component passed in.") :$$$: ""
- type NotFoundError (dom :: Domain) (t :: Type) = (((((((((((("Could not find domain '" :<<>>: 'ShowType dom) :<<>>: "' in the following type:") :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: "If that type contains that domain anyway, you might need to provide an") :$$$: "additional type instance of HasDomain. Example implementations:") :$$$: "") :$$$: " * type instance HasDomain dom (MyVector n a) = HasDomain dom a") :$$$: " * type instance HasDomain dom1 (MyCircuit dom2 a) = DomEq dom1 dom2") :$$$: " * type instance HasDomain dom1 (MyTuple a b) = Merge dom a b") :$$$: "") :$$$: Outro
- type WithSpecificDomain dom r = (HasSpecificDomain dom r, dom ~ GetDomain dom r)
- data HasDomainWrapperResult
- type family MergeWorker (n :: HasDomainWrapperResult) (m :: HasDomainWrapperResult) :: HasDomainWrapperResult where ...
- type Merge (dom :: Domain) (n :: Type) (m :: Type) = MergeWorker (HasDomainWrapper dom n) (HasDomainWrapper dom m)
- type family DomEqWorker (n :: Domain) (m :: Domain) :: HasDomainWrapperResult where ...
- type DomEq (n :: Domain) (m :: Domain) = IfStuck (DomEqWorker n m) 'NotFound (Pure (DomEqWorker n m))
- type family HasDomain (dom :: Domain) (n :: Type) :: HasDomainWrapperResult
- type family ErrOnNotFound (dom :: Domain) (n :: HasDomainWrapperResult) (t :: Type) :: Domain where ...
- type family HasDomainWrapper (dom :: Domain) (n :: Type) :: HasDomainWrapperResult where ...
- type family ResolveOrErr (dom :: Domain) (t :: Type) :: Domain where ...
- class HasSpecificDomain (dom :: Domain) (r :: Type) where
Documentation
type Outro = (((((("" :$$$: "------") :$$$: "") :$$$: "You tried to apply an explicitly routed clock, reset, or enable line") :$$$: "to a construct with, possibly, an implicitly routed one. Clash failed to") :$$$: "unambigously link the given domain (by passing in a 'Clock', 'Reset', or") :$$$: "'Enable') to the component passed in.") :$$$: "" Source #
type NotFoundError (dom :: Domain) (t :: Type) = (((((((((((("Could not find domain '" :<<>>: 'ShowType dom) :<<>>: "' in the following type:") :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: "If that type contains that domain anyway, you might need to provide an") :$$$: "additional type instance of HasDomain. Example implementations:") :$$$: "") :$$$: " * type instance HasDomain dom (MyVector n a) = HasDomain dom a") :$$$: " * type instance HasDomain dom1 (MyCircuit dom2 a) = DomEq dom1 dom2") :$$$: " * type instance HasDomain dom1 (MyTuple a b) = Merge dom a b") :$$$: "") :$$$: Outro Source #
type WithSpecificDomain dom r = (HasSpecificDomain dom r, dom ~ GetDomain dom r) Source #
Type that forces dom to be present in r at least once. Will resolve to a type error if it doesn't. It will always fail if given dom is completely polymorphic and can't be tied to r in any way.
type family MergeWorker (n :: HasDomainWrapperResult) (m :: HasDomainWrapperResult) :: HasDomainWrapperResult where ... Source #
Merge two HasDomainWrapperResult
s according to the semantics of 'HasDomain.
MergeWorker 'Found b = 'Found | |
MergeWorker a 'Found = 'Found | |
MergeWorker 'NotFound 'NotFound = 'NotFound |
type Merge (dom :: Domain) (n :: Type) (m :: Type) = MergeWorker (HasDomainWrapper dom n) (HasDomainWrapper dom m) Source #
type family DomEqWorker (n :: Domain) (m :: Domain) :: HasDomainWrapperResult where ... Source #
DomEqWorker n n = 'Found | |
DomEqWorker n m = 'NotFound |
type DomEq (n :: Domain) (m :: Domain) = IfStuck (DomEqWorker n m) 'NotFound (Pure (DomEqWorker n m)) Source #
Check domain for equality. Return 'Found if so, return 'NotFound if not. The reason d'etre for this type family is that _open_ type families don't allow overlapping types. We therefore defer equality checking to a closed type family.
type family HasDomain (dom :: Domain) (n :: Type) :: HasDomainWrapperResult Source #
Type family that searches a type and checks whether a specific domain is present. Will result in either "domain not found, and no others either", "domain not found, but found another", or "found domain".
Instances
type family ErrOnNotFound (dom :: Domain) (n :: HasDomainWrapperResult) (t :: Type) :: Domain where ... Source #
ErrOnNotFound dom 'NotFound t = DelayError (NotFoundError dom t) | |
ErrOnNotFound dom 'Found t = dom |
type family HasDomainWrapper (dom :: Domain) (n :: Type) :: HasDomainWrapperResult where ... Source #
Wrapper that checks for stuckness and returns NotFound if so
type family ResolveOrErr (dom :: Domain) (t :: Type) :: Domain where ... Source #
Helper function for HasSpecificDomain class (I don't really understand why this one is necessary. HasDomainWrapper _should_ check for stuckness and does so according to tests..
ResolveOrErr dom t = IfStuck (HasDomainWrapper dom t) (ErrOnNotFound dom 'NotFound t) (Pure (ErrOnNotFound dom (HasDomainWrapper dom t) t)) |
class HasSpecificDomain (dom :: Domain) (r :: Type) Source #
Type class that specifies that a certain domain, dom, needs to be present
in some other type, r. This is used to disambiguate what hidden clock,
reset, and enable lines should be exposed in functions such as
withSpecificReset
.
Functions in need of this class should use WithSpecificDomain
though, to
force Clash to display an error instead of letting it silently pass.
Instances
HasSpecificDomain dom a Source # | |
Defined in Clash.Class.HasDomain.HasSpecificDomain |