{-| Copyright : (C) 2013-2016, University of Twente, 2016-2019, Myrtle Software Ltd, 2017 , Google Inc. License : BSD2 (see the file LICENSE) Maintainer : Christiaan Baaij 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 :: 'Nat' -- ^ Clock period in /ps/ , _edge :: 'ActiveEdge' -- ^ Active edge of the clock , _reset :: 'ResetKind' -- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive) , _init :: 'InitBehavior' -- ^ Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value , _polarity :: 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 #-} #if __GLASGOW_HASKELL__ < 806 {-# LANGUAGE TypeInType #-} #endif {-# OPTIONS_HADDOCK show-extensions #-} module Clash.Signal ( -- * Synchronous signals Signal , BiSignalIn , BiSignalOut , BiSignalDefault(..) -- * Domain , Domain , 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 , holdReset -- ** Enabling , Enable , toEnable , fromEnable , S.enableGen -- * Hidden clocks and resets -- $hiddenclockandreset -- ** 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 , 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 -- ** lazy versions , simulate_lazy , simulateB_lazy -- * 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 ) where 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 Clash.Explicit.Signal (resetSynchronizer, systemClockGen, systemResetGen) import qualified Clash.Explicit.Signal as S 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) import Clash.Signal.Internal.Ambiguous (knownVDomain, clockPeriod, activeEdge, resetKind, initBehavior, resetPolarity) import Clash.XException (NFDataX) {- $setup >>> :set -XFlexibleContexts -XTypeApplications >>> 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) >>> :{ sometimes1 = s where s = register Nothing (switch <$> s) switch Nothing = Just 1 switch _ = Nothing :} >>> :{ countSometimes = s where s = regMaybe 0 (plusM (pure <$> s) sometimes1) plusM = liftA2 (liftA2 (+)) :} -} -- * Hidden clock and reset arguments {- $hiddenclockandreset #hiddenclockandreset# Clocks and resets are by default implicitly routed to their components. You can see from the type of a component whether it has hidden clock or reset 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 polarity => ... @ Constraint. Or it has both a hidden clock argument and a hidden reset argument when it has a: @ h :: 'HiddenClockReset' dom => .. @ Constraint. Given a component with an explicit clock and reset arguments, you can turn them into hidden arguments using 'hideClock' and 'hideReset'. So given a: @ f :: Clock dom -> Reset dom -> Signal dom a -> ... @ You hide the clock and reset arguments by: @ -- g :: 'HiddenClockReset' dom => Signal dom a -> ... g = 'hideClockReset' f @ Or, alternatively, by: @ -- h :: HiddenClockResetEnable dom => Signal dom a -> ... h = f 'hasClock' 'hasReset' @ === Assigning explicit clock and reset arguments to hidden clocks and resets Given a component: @ f :: HiddenClockResetEnable dom => Signal dom Int -> Signal dom Int @ which has hidden clock and routed reset arguments, we expose those hidden arguments so that we can explicitly apply them: @ -- g :: Clock dom -> Reset dom -> Signal dom Int -> Signal dom Int g = 'exposeClockResetEnable' f @ or, alternatively, by: @ -- h :: Clock dom -> Reset dom -> Signal dom Int -> Signal dom Int h clk rst = withClock clk rst f @ Similarly, there are 'exposeClock' and 'exposeReset' to connect just expose the hidden clock or the hidden reset argument. You will need to explicitly apply clocks and resets when you want to use components such as PPLs and 'resetSynchronizer': @ topEntity :: Clock System -> Reset System -> Enable System -> Signal System Int -> Signal System Int topEntity clk rst = let (pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' (SSymbol \@\"altpll50\") clk rst rstSync = 'resetSynchronizer' pllOut ('unsafeToAsyncReset' pllStable) in 'exposeClockResetEnable' f pllOut rstSync @ or, using the alternative method: @ topEntity2 :: Clock System -> Reset System -> Signal System Int -> Signal System Int topEntity2 clk rst = let (pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' (SSymbol \@\"altpll50\") clk rst rstSync = 'resetSynchronizer' pllOut ('unsafeToAsyncReset' pllStable) in 'withClockReset' pllOut rstSync f @ -} #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' -- --