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 MissingInstance = (((((("This might happen if an instance for TryDomain is missing. Try to determine" :$$$: "which of the types miss an instance, and add them. Example implementations:") :$$$: "") :$$$: " * type instance TryDomain t (MyVector n a) = TryDomain t a") :$$$: " * type instance TryDomain t (MyCircuit dom a) = Found dom") :$$$: " * type instance TryDomain t Terminal = NotFound") :$$$: "") :$$$: "Alternatively, use one of the withSpecific* functions."
- 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 determine a single domain and could therefore not route it.") :$$$: "You possibly used one of these sets of functions:") :$$$: "") :$$$: " * with{ClockResetEnable,Clock,Reset,Enable}") :$$$: " * expose{ClockResetEnable,Clock,Reset,Enable}") :$$$: "") :$$$: "These functions are suitable for components defined over a single domain") :$$$: "only. If you want to use multiple domains, use the following instead:") :$$$: "") :$$$: " * withSpecific{ClockResetEnable,Clock,Reset,Enable}") :$$$: " * exposeSpecific{ClockResetEnable,Clock,Reset,Enable}") :$$$: ""
- type NotFoundError (t :: Type) = (((("Could not find a non-ambiguous domain in the following type:" :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: MissingInstance) :$$$: Outro
- type AmbiguousError (t :: Type) (dom1 :: Domain) (dom2 :: Domain) = ((((((("Could not determine that the domain '" :<<>>: dom1) :<<>>: "'") :$$$: (("was equal to the domain '" :<<>>: dom2) :<<>>: "' in the type:")) :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: "This is usually resolved by adding explicit type signatures.") :$$$: Outro
- type StuckErrorMsg (orig :: Type) (n :: Type) = (((((((((((("Could not determine whether the following type contained a non-ambiguous domain:" :$$$: "") :$$$: (" " :<<>>: n)) :$$$: "") :$$$: "In the full type:") :$$$: "") :$$$: (" " :<<>>: orig)) :$$$: "") :$$$: "Does it contain one?") :$$$: "") :$$$: "------") :$$$: "") :$$$: MissingInstance) :$$$: Outro
- type WithSingleDomain dom r = (HasSingleDomain r, dom ~ GetDomain r)
- data TryDomainResult
- type family Merge' (n :: TryDomainResult) (m :: TryDomainResult) :: TryDomainResult where ...
- type family Merge (orig :: Type) (n :: Type) (m :: Type) :: TryDomainResult where ...
- type family ErrOnConflict (t :: Type) (n :: TryDomainResult) :: Domain where ...
- type family TryDomain (orig :: Type) (n :: Type) :: TryDomainResult
- class HasSingleDomain (r :: Type) where
Documentation
type MissingInstance = (((((("This might happen if an instance for TryDomain is missing. Try to determine" :$$$: "which of the types miss an instance, and add them. Example implementations:") :$$$: "") :$$$: " * type instance TryDomain t (MyVector n a) = TryDomain t a") :$$$: " * type instance TryDomain t (MyCircuit dom a) = Found dom") :$$$: " * type instance TryDomain t Terminal = NotFound") :$$$: "") :$$$: "Alternatively, use one of the withSpecific* functions." Source #
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 determine a single domain and could therefore not route it.") :$$$: "You possibly used one of these sets of functions:") :$$$: "") :$$$: " * with{ClockResetEnable,Clock,Reset,Enable}") :$$$: " * expose{ClockResetEnable,Clock,Reset,Enable}") :$$$: "") :$$$: "These functions are suitable for components defined over a single domain") :$$$: "only. If you want to use multiple domains, use the following instead:") :$$$: "") :$$$: " * withSpecific{ClockResetEnable,Clock,Reset,Enable}") :$$$: " * exposeSpecific{ClockResetEnable,Clock,Reset,Enable}") :$$$: "" Source #
type NotFoundError (t :: Type) = (((("Could not find a non-ambiguous domain in the following type:" :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: MissingInstance) :$$$: Outro Source #
type AmbiguousError (t :: Type) (dom1 :: Domain) (dom2 :: Domain) = ((((((("Could not determine that the domain '" :<<>>: dom1) :<<>>: "'") :$$$: (("was equal to the domain '" :<<>>: dom2) :<<>>: "' in the type:")) :$$$: "") :$$$: (" " :<<>>: t)) :$$$: "") :$$$: "This is usually resolved by adding explicit type signatures.") :$$$: Outro Source #
type StuckErrorMsg (orig :: Type) (n :: Type) = (((((((((((("Could not determine whether the following type contained a non-ambiguous domain:" :$$$: "") :$$$: (" " :<<>>: n)) :$$$: "") :$$$: "In the full type:") :$$$: "") :$$$: (" " :<<>>: orig)) :$$$: "") :$$$: "Does it contain one?") :$$$: "") :$$$: "------") :$$$: "") :$$$: MissingInstance) :$$$: Outro Source #
type WithSingleDomain dom r = (HasSingleDomain r, dom ~ GetDomain r) Source #
Type that forces dom to be the same in all subtypes of r that might contain a domain. If given a polymorphic domain not tied to r, GHC will be allowed to infer that that domain is equal to the one in r on the condition that r contains just a single domain.
type family Merge' (n :: TryDomainResult) (m :: TryDomainResult) :: TryDomainResult where ... Source #
Type family to resolve type conflicts (if any)
type family Merge (orig :: Type) (n :: Type) (m :: Type) :: TryDomainResult where ... Source #
Same as Merge', but will insert a type error if Merge' got stuck.
Merge orig n m = IfStuck (TryDomain orig n) (DelayError (StuckErrorMsg orig n)) (Pure (IfStuck (TryDomain orig m) (DelayError (StuckErrorMsg orig m)) (Pure (Merge' (TryDomain orig n) (TryDomain orig m))))) |
type family ErrOnConflict (t :: Type) (n :: TryDomainResult) :: Domain where ... Source #
ErrOnConflict t 'NotFound = TypeError (NotFoundError t) | |
ErrOnConflict t ('Ambiguous dom1 dom2) = TypeError (AmbiguousError t dom1 dom2) | |
ErrOnConflict t ('Found dom) = dom |
type family TryDomain (orig :: Type) (n :: Type) :: TryDomainResult Source #
Instances
class HasSingleDomain (r :: Type) Source #
Type family that searches a type and checks whether all subtypes that can contain a domain (for example, Signal) contain the same domain. Its associated type, GetDomain, will yield a type error if that doesn't hold OR if it can't check it.
type GetDomain r :: Domain Source #
type GetDomain r = IfStuck (TryDomain r r) (DelayError (StuckErrorMsg r r)) (Pure (ErrOnConflict r (TryDomain r r)))
Instances
HasSingleDomain a Source # | |
Defined in Clash.Class.HasDomain.HasSingleDomain |