{-| Copyright : (C) 2013-2016, University of Twente, 2016 , Myrtle Software, 2017 , Google Inc. License : BSD2 (see the file LICENSE) Maintainer : Christiaan Baaij CλaSH has synchronous 'Signal's in the form of: @ 'Signal' (domain :: 'Domain') a @ Where /a/ is the type of the value of the 'Signal', for example /Int/ or /Bool/, and /domain/ is the /clock-/ (and /reset-/) domain to which the memory elements manipulating these 'Signal's belong. The type-parameter, /domain/, is of the kind 'Domain' which has types of the following shape: @ data Domain = Dom { domainName :: 'GHC.TypeLits.Symbol', clkPeriod :: 'GHC.TypeLits.Nat' } @ Where /domainName/ is a type-level string ('GHC.TypeLits.Symbol') representing the name of the /clock-/ (and /reset-/) domain, and /clkPeriod/ is a type-level natural number ('GHC.TypeLits.Nat') representing the clock period (in __ps__) of the clock lines in the /clock-domain/. * __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! -} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RebindableSyntax #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE Trustworthy #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_HADDOCK show-extensions #-} module Clash.Signal ( -- * Synchronous signals Signal , Domain (..) , System -- * Clock , Clock , ClockKind (..) -- * Reset , Reset , ResetKind (..) , unsafeFromAsyncReset , unsafeToAsyncReset , fromSyncReset , unsafeToSyncReset , resetSynchronizer -- * Hidden clocks and resets -- $hiddenclockandreset -- ** Hidden clock , HiddenClock , hideClock , exposeClock , withClock , hasClock -- ** Hidden reset , HiddenReset , hideReset , exposeReset , withReset , hasReset -- ** Hidden clock and reset , HiddenClockReset , hideClockReset , exposeClockReset , withClockReset , SystemClockReset -- * Basic circuit functions , delay , register , regMaybe , regEn , mux -- * Simulation and testbench functions , clockGen , tbClockGen , asyncResetGen , syncResetGen , systemClockGen , tbSystemClockGen , systemResetGen -- * Boolean connectives , (.&&.), (.||.) -- * Product/Signal isomorphism , Bundle(..) -- * Simulation functions (not synthesisable) , simulate , simulateB -- ** lazy versions , simulate_lazy , simulateB_lazy -- * List \<-\> Signal conversion (not synthesisable) , sample , sampleN , fromList -- ** lazy versions , sample_lazy , sampleN_lazy , fromList_lazy -- * QuickCheck combinators , testFor -- * Type classes -- ** 'Eq'-like , (.==.), (./=.) -- ** 'Ord'-like , (.<.), (.<=.), (.>=.), (.>.) ) where import Control.DeepSeq (NFData) import GHC.Stack (HasCallStack, withFrozenCallStack) import GHC.TypeLits (KnownNat, KnownSymbol) import Data.Bits (Bits) -- Haddock only import Data.Maybe (isJust, fromJust) import Prelude import Test.QuickCheck (Property, property) import Unsafe.Coerce (unsafeCoerce) import Clash.Explicit.Signal (System, resetSynchronizer, systemClockGen, systemResetGen, tbSystemClockGen) import qualified Clash.Explicit.Signal as S import Clash.Hidden import Clash.Promoted.Nat (SNat (..)) import Clash.Promoted.Symbol (SSymbol (..)) import Clash.Signal.Bundle (Bundle (..)) import Clash.Signal.Internal hiding (sample, sample_lazy, sampleN, sampleN_lazy, simulate, simulate_lazy, testFor) import qualified Clash.Signal.Internal as S {- $setup >>> :set -XFlexibleContexts -XTypeApplications >>> 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' domain gated => ... @ Constraint. Or it has a hidden reset when it has a: @ g :: 'HiddenReset' domain synchronous => ... @ Constraint. Or it has both a hidden clock argument and a hidden reset argument when it has a: @ h :: 'HiddenClockReset' domain gated synchronous => .. @ 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 domain gated -> Reset domain synchronous -> Signal domain a -> ... @ You hide the clock and reset arguments by: @ -- g :: 'HiddenClockReset' domain gated synchronous => Signal domain a -> ... g = 'hideClockReset' f @ Or, alternatively, by: @ -- h :: HiddenClockReset domain gated synchronous => Signal domain a -> ... h = f 'hasClock' 'hasReset' @ === Assigning explicit clock and reset arguments to hidden clocks and resets Given a component: @ f :: HiddenClockReset domain gated synchronous => Signal domain Int -> Signal domain Int @ which has hidden clock and routed reset arguments, we expose those hidden arguments so that we can explicitly apply them: @ -- g :: Clock domain gated -> Reset domain synchronous -> Signal domain Int -> Signal domain Int g = 'exposeClockReset' f @ or, alternatively, by: @ -- h :: Clock domain gated -> Reset domain synchronous -> Signal domain Int -> Signal domain 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 Source -> Reset System Asynchronous -> 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 'exposeClockReset' f pllOut rstSync @ or, using the alternative method: @ topEntity2 :: Clock System Source -> Reset System Asynchronous -> 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 @ -} -- | A /constraint/ that indicates the component has a hidden 'Clock' -- --