{-| Copyright : (C) 2013-2016, University of Twente, 2016-2019, Myrtle Software Ltd, 2017 , Google Inc., 2021 , QBayLogic B.V. License : BSD2 (see the file LICENSE) Maintainer : QBayLogic B.V. Clash has synchronous 'Signal's in the form of: @ 'Signal' (dom :: 'Domain') a @ Where /a/ is the type of the value of the 'Signal', for example /Int/ or /Bool/, and /dom/ is the /clock-/ (and /reset-/) domain to which the memory elements manipulating these 'Signal's belong. The type-parameter, /dom/, is of the kind 'Domain' - a simple string. That string refers to a single /synthesis domain/. A synthesis domain describes the behavior of certain aspects of memory elements in it. More specifically, a domain looks like: @ 'DomainConfiguration' { _name :: 'Domain' -- ^ Domain name , _period :: 'Clash.Promoted.Nat.Nat' -- ^ Clock period in /ps/ , _activeEdge :: 'ActiveEdge' -- ^ Active edge of the clock , _resetKind :: 'ResetKind' -- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive) , _initBehavior :: 'InitBehavior' -- ^ Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value , _resetPolarity :: ResetPolarity -- ^ Whether resets are active high or active low } @ Check the documentation of each of the types to see the various options Clash provides. In order to specify a domain, an instance of 'KnownDomain' should be made. Clash provides an implementation 'System' with some common options chosen: @ instance KnownDomain "System" where type KnownConf "System" = 'DomainConfiguration "System" 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh knownDomain = SDomainConfiguration SSymbol SNat SRising SAsynchronous SDefined SActiveHigh @ In words, \"System\" is a synthesis domain with a clock running with a period of 10000 /ps/. Memory elements respond to the rising edge of the clock, asynchronously to changes in their resets, and have defined power up values if applicable. In order to create a new domain, you don't have to instantiate it explicitly. Instead, you can have 'createDomain' create a domain for you. You can also use the same function to subclass existing domains. * __NB__: \"Bad things\"™ happen when you actually use a clock period of @0@, so do __not__ do that! * __NB__: You should be judicious using a clock with period of @1@ as you can never create a clock that goes any faster! * __NB__: Whether 'System' has good defaults depends on your target platform. Check out 'IntelSystem' and 'XilinxSystem' too! -} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ExplicitNamespaces #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE Trustworthy #-} {-# OPTIONS_HADDOCK show-extensions #-} module Clash.Signal ( -- * Synchronous signals Signal , BiSignalIn , BiSignalOut , BiSignalDefault(..) -- * Domain , Domain , sameDomain , KnownDomain(..) , KnownConfiguration , ActiveEdge(..) , SActiveEdge(..) , InitBehavior(..) , SInitBehavior(..) , ResetKind(..) , SResetKind(..) , ResetPolarity(..) , SResetPolarity(..) , DomainConfiguration(..) , SDomainConfiguration(..) -- ** Configuration type families , DomainPeriod , DomainActiveEdge , DomainResetKind , DomainInitBehavior , DomainResetPolarity -- ** Default domains , System , XilinxSystem , IntelSystem , vSystem , vIntelSystem , vXilinxSystem -- ** Domain utilities , VDomainConfiguration(..) , vDomain , createDomain , knownVDomain , clockPeriod , activeEdge , resetKind , initBehavior , resetPolarity -- * Clock , Clock , periodToHz , hzToPeriod #ifdef CLASH_MULTIPLE_HIDDEN -- ** Synchronization primitive , unsafeSynchronizer #endif -- * Reset , Reset , unsafeToReset , unsafeFromReset , unsafeToHighPolarity , unsafeToLowPolarity , unsafeFromHighPolarity , unsafeFromLowPolarity #ifdef CLASH_MULTIPLE_HIDDEN , convertReset #endif , resetSynchronizer , resetGlitchFilter , holdReset -- * Enabling , Enable , toEnable , fromEnable , E.enableGen -- * Hidden clock, reset, and enable arguments -- $hiddenclockandreset -- ** Monomorphism restriction leads to surprising behavior -- $monomorphism -- ** Hidden clock , HiddenClock , hideClock , exposeClock , withClock #ifdef CLASH_MULTIPLE_HIDDEN , exposeSpecificClock , withSpecificClock #endif , hasClock -- ** Hidden reset , HiddenReset , hideReset , exposeReset , withReset #ifdef CLASH_MULTIPLE_HIDDEN , exposeSpecificReset , withSpecificReset #endif , hasReset -- ** Hidden enable , HiddenEnable , hideEnable , exposeEnable , withEnable #ifdef CLASH_MULTIPLE_HIDDEN , exposeSpecificEnable , withSpecificEnable #endif , hasEnable -- ** Hidden clock, reset, and enable , HiddenClockResetEnable , hideClockResetEnable , exposeClockResetEnable , withClockResetEnable #ifdef CLASH_MULTIPLE_HIDDEN , exposeSpecificClockResetEnable , withSpecificClockResetEnable #endif , SystemClockResetEnable -- * Basic circuit functions , andEnable #ifdef CLASH_MULTIPLE_HIDDEN , andSpecificEnable #endif , dflipflop , delay , delayMaybe , delayEn , register , regMaybe , regEn , mux -- * Simulation and testbench functions , clockGen , resetGen , resetGenN , systemClockGen , systemResetGen -- * Boolean connectives , (.&&.), (.||.) -- * Product/Signal isomorphism , Bundle(..) , EmptyTuple(..) , TaggedEmptyTuple(..) -- * Simulation functions (not synthesizable) , simulate , simulateB , simulateN , simulateWithReset , simulateWithResetN , runUntil -- ** lazy versions , simulate_lazy , simulateB_lazy -- ** Automaton , signalAutomaton -- * List \<-\> Signal conversion (not synthesizable) , sample , sampleN , sampleWithReset , sampleWithResetN , fromList , fromListWithReset -- ** lazy versions , sample_lazy , sampleN_lazy , fromList_lazy -- * QuickCheck combinators , testFor -- * Type classes -- ** 'Eq'-like , (.==.), (./=.) -- ** 'Ord'-like , (.<.), (.<=.), (.>=.), (.>.) -- * Bisignal functions , veryUnsafeToBiSignalIn , readFromBiSignal , writeToBiSignal , mergeBiSignalOuts -- * Internals , HiddenClockName , HiddenResetName , HiddenEnableName ) where import Control.Arrow.Transformer.Automaton (Automaton) import GHC.TypeLits (type (<=)) import Data.Proxy (Proxy(..)) import Prelude import Test.QuickCheck (Property, property) #ifdef CLASH_MULTIPLE_HIDDEN import GHC.TypeLits (AppendSymbol) import Clash.Class.HasDomain (WithSingleDomain) #endif import Clash.Class.HasDomain (WithSpecificDomain) import qualified Clash.Explicit.Signal as E import qualified Clash.Explicit.Reset as E import Clash.Explicit.Reset (resetSynchronizer, resetGlitchFilter) import Clash.Explicit.Signal (systemClockGen, systemResetGen) import Clash.Hidden import Clash.Promoted.Nat (SNat (..), snatToNum) import Clash.Signal.Bundle (Bundle (..), EmptyTuple(..), TaggedEmptyTuple(..)) import Clash.Signal.BiSignal --(BisignalIn, BisignalOut, ) import Clash.Signal.Internal hiding (sample, sample_lazy, sampleN, sampleN_lazy, simulate, simulate_lazy, testFor, signalAutomaton) import Clash.Signal.Internal.Ambiguous (knownVDomain, clockPeriod, activeEdge, resetKind, initBehavior, resetPolarity) import Clash.XException (NFDataX, ShowX) {- $setup >>> :set -XFlexibleContexts -XTypeApplications >>> :m -Prelude >>> import Clash.Prelude >>> import Clash.Promoted.Nat (SNat(..)) >>> import Clash.XException (printX) >>> import Control.Applicative (liftA2) >>> let oscillate = register False (not <$> oscillate) >>> let count = regEn 0 oscillate (count + 1) >>> :{ let sometimes1 = s where s = register Nothing (switch <$> s) switch Nothing = Just 1 switch _ = Nothing :} >>> :{ let countSometimes = s where s = regMaybe 0 (plusM (pure <$> s) sometimes1) plusM = liftA2 (liftA2 (+)) :} -} {- $hiddenclockandreset #hiddenclockandreset# Clocks, resets and enables are by default implicitly routed to their components. You can see from the type of a component whether it has hidden clock, reset or enable arguments: It has a hidden clock when it has a: @ f :: 'HiddenClock' dom => ... @ Constraint. Or it has a hidden reset when it has a: @ g :: 'HiddenReset' dom => ... @ Constraint. Or it has a hidden enable when it has a: @ g :: 'HiddenEnable' dom => ... @ Constraint. Or it has a hidden clock argument, a hidden reset argument and a hidden enable argument when it has a: @ h :: 'HiddenClockResetEnable' dom => .. @ Constraint. Given a component with explicit clock, reset and enable arguments, you can turn them into hidden arguments using 'hideClock', 'hideReset', and 'hideEnable'. So given a: @ f :: Clock dom -> Reset dom -> Enable dom -> Signal dom a -> ... @ You hide the clock and reset arguments by: @ -- g :: 'HiddenClockResetEnable' dom => Signal dom a -> ... g = 'hideClockResetEnable' f @ Or, alternatively, by: @ -- h :: 'HiddenClockResetEnable' dom => Signal dom a -> ... h = f 'hasClock' 'hasReset' 'hasEnable' @ == Assigning explicit clock, reset and enable arguments to hidden clocks, resets and enables Given a component: @ f :: 'HiddenClockResetEnable' dom => Signal dom Int -> Signal dom Int @ which has hidden clock, reset and enable arguments, we expose those hidden arguments so that we can explicitly apply them: @ -- g :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int g = 'exposeClockResetEnable' f @ or, alternatively, by: @ -- h :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int h clk rst en = 'withClockResetEnable' clk rst en f @ Similarly, there are 'exposeClock', 'exposeReset' and 'exposeEnable' to just expose the hidden clock, the hidden reset or the hidden enable argument. You will need to explicitly apply clocks and resets when you want to use components such as PLLs and 'resetSynchronizer': @ topEntity :: Clock System -> Reset System -> Signal System Bit -> Signal System (BitVector 8) topEntity clk rst key1 = let (pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' (SSymbol \@\"altpll50\") clk rst rstSync = 'resetSynchronizer' pllOut (unsafeToHighPolarity pllStable) in 'exposeClockResetEnable' leds pllOut rstSync enableGen where key1R = isRising 1 key1 leds = mealy blinkerT (1, False, 0) key1R @ or, using the alternative method: @ topEntity :: Clock System -> Reset System -> Signal System Bit -> Signal System (BitVector 8) topEntity clk rst key1 = let (pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' (SSymbol \@\"altpll50\") clk rst rstSync = 'resetSynchronizer' pllOut (unsafeToHighPolarity pllStable) in 'withClockResetEnable' pllOut rstSync enableGen leds where key1R = isRising 1 key1 leds = mealy blinkerT (1, False, 0) key1R @ -} {- $monomorphism #monomorphism# If you don't provide a type signature for a function, Haskell will infer one for you. Sometimes this inferred type is less general than you would expect. This can be due to the monomorphism restriction, which is a rather intricate technical aspect of Haskell's type system. You don't need to understand it to avoid the problems it creates with hidden parameters, though. The @expose...@ and @with...@ functions for hidden clocks, resets, and enables are intended to be used to resolve a function with hidden parameters into a function without that hidden parameter. Put differently, 'exposeClock' and 'withClock' are not themselves used in a 'HiddenClock' context, and so on for resets and enables. If the rule that they are not themselves in a @Hidden...@ context is observed, they will function as expected. No specific consideration is needed in these cases. However, the function 'andEnable' is explicitly designed to be used within a 'HiddenEnable' context. In such a situation, it is important to provide a type signature for the component that is given to `andEnable` as an argument, and not let Haskell infer one. The use of 'andEnable' has an unfortunate interaction with Haskells monomorphism restriction that can lead to very surprising behavior. All of the following also applies to using 'exposeClock' and 'withClock' inside a 'HiddenClock' context, and so on for resets and enables. When you write a function @ f :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i -- BROKEN where g = register 0 @ you would intuitively think this has the following type for the local function @g@: @ f :: forall dom . HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i where g :: HiddenClockResetEnable dom => Signal dom Int -> Signal dom Int g = register 0 @ but instead, the monomorphism restriction will cause the following type to be inferred: @ f :: forall dom . HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i -- BROKEN where g :: Signal dom Int -> Signal dom Int g = register 0 @ The monomorphism restriction essentially misqualifies the implicit parameter as polymorphism, and tries to remove the implicit parameter from the context of the function's type. It /can/ do that because the outer scope already has a 'HiddenEnable' context. But by getting that implicit parameter of the enclosing function as context, it also gets the value of the parameter of the enclosing function. So the Enable line for @g@ is the Enable line of @f@, and the Enable line produced by 'andEnable' that was intended to be connected to @g@ is not connected to anything! When using 'andEnable', you should always explicitly provide the type signature for the component given to 'andEnable' as an argument, thereby avoiding surprising inferred types. We don't advise you to turn off the monomorphism restriction, as this may have undesirable consequences. Note that the inferred type is not always incorrect. The following variant works correctly: @ f :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i where g i = register 0 i @ This is an instance of the very first example on , @f1@ (as opposed to @f4@). The monomorphism restriction works differently for function bindings and pattern bindings. Since @g@ here has a formal parameter, it is a function binding, and the monomorphish restriction does not kick in. The code works as expected. If a later code change removes the formal parameter, all of a sudden the code silently disregards the @en@ signal! Adhering to the rule that you should always explicitly provide the type signature for the component given to 'andEnable' as an argument would have avoided this hard to debug problem. -} #ifdef CLASH_MULTIPLE_HIDDEN type HiddenClockName dom = AppendSymbol dom "_clk" type HiddenResetName dom = AppendSymbol dom "_rst" type HiddenEnableName dom = AppendSymbol dom "_en" #else type HiddenClockName (dom :: Domain) = "clock" type HiddenResetName (dom :: Domain) = "reset" type HiddenEnableName (dom :: Domain) = "enable" #endif -- | A /constraint/ that indicates the component has a hidden 'Clock' -- --