-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Clash: a functional hardware description language - Prelude library -- -- Clash is a functional hardware description language that borrows both -- its syntax and semantics from the functional programming language -- Haskell. The Clash compiler transforms these high-level descriptions -- to low-level synthesizable VHDL, Verilog, or SystemVerilog. -- -- Features of Clash: -- -- -- -- This package provides: -- -- -- -- To use the library: -- -- -- -- A preliminary version of a tutorial can be found in -- Clash.Tutorial, for a general overview of the library you -- should however check out Clash.Prelude. Some circuit examples -- can be found in Clash.Examples. @package clash-prelude @version 1.9.0 -- | Using ANN pragma's you can tell the Clash compiler to use a -- custom bit representation for a data type. See DataReprAnn -- for documentation. module Clash.Annotations.BitRepresentation -- | Annotation for custom bit representations of data types -- -- Using ANN pragma's you can tell the Clash compiler to use a -- custom bit-representation for a data type. -- -- For example: -- --
--   data Color = R | G | B
--   {-# ANN module (DataReprAnn
--                     $(liftQ [t|Color|])
--                     2
--                     [ ConstrRepr 'R 0b11 0b00 []
--                     , ConstrRepr 'G 0b11 0b01 []
--                     , ConstrRepr 'B 0b11 0b10 []
--                     ]) #-}
--   
-- -- This specifies that R should be encoded as 0b00, G -- as 0b01, and B as 0b10. The first binary value in every -- ConstrRepr in this example is a mask, indicating which bits -- in the data type are relevant. In this case all of the bits are. -- -- Or if we want to annotate Maybe Color: -- --
--   {-# ANN module ( DataReprAnn
--                      $(liftQ [t|Maybe Color|])
--                      2
--                      [ ConstrRepr 'Nothing 0b11 0b11 []
--                      , ConstrRepr 'Just 0b00 0b00 [0b11]
--                      ] ) #-}
--   
-- -- By default, Maybe Color is a data type which consumes 3 bits. -- A single bit to indicate the constructor (either Just or -- Nothing), and two bits to encode the first field of -- Just. Notice that we saved a single bit by exploiting the -- fact that Color only uses three values (0, 1, 2), but takes -- two bits to encode it. We can therefore use the last - unused - value -- (3), to encode one of the constructors of Maybe. We indicate -- which bits encode the underlying Color field of Just -- by passing [0b11] to ConstrRepr. This indicates that the first -- field is encoded in the first and second bit of the whole datatype -- (0b11). -- -- NB: BitPack for a custom encoding can be derived using -- deriveBitPack. data DataReprAnn DataReprAnn :: Type -> Size -> [ConstrRepr] -> DataReprAnn -- | Annotation for constructors. Indicates how to match this constructor -- based off of the whole datatype. data ConstrRepr ConstrRepr :: Name -> BitMask -> Value -> [FieldAnn] -> ConstrRepr type BitMask = Integer type Value = Integer type Size = Int -- | BitMask used to mask fields type FieldAnn = BitMask -- | Lift values inside of Q to a Template Haskell expression liftQ :: Lift a => Q a -> Q Exp instance Language.Haskell.TH.Syntax.Lift Clash.Annotations.BitRepresentation.ConstrRepr instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.ConstrRepr instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.ConstrRepr instance Data.Data.Data Clash.Annotations.BitRepresentation.ConstrRepr instance GHC.Show.Show Clash.Annotations.BitRepresentation.ConstrRepr instance Language.Haskell.TH.Syntax.Lift Clash.Annotations.BitRepresentation.DataReprAnn instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.DataReprAnn instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.DataReprAnn instance Data.Data.Data Clash.Annotations.BitRepresentation.DataReprAnn instance GHC.Show.Show Clash.Annotations.BitRepresentation.DataReprAnn module Clash.Annotations.BitRepresentation.Internal -- | Create indices based on names of constructors and data types buildCustomReprs :: [DataRepr'] -> CustomReprs dataReprAnnToDataRepr' :: DataReprAnn -> DataRepr' constrReprToConstrRepr' :: Int -> ConstrRepr -> ConstrRepr' -- | Lookup constructor representation based on name getConstrRepr :: Text -> CustomReprs -> Maybe ConstrRepr' -- | Unchecked version of getConstrRepr uncheckedGetConstrRepr :: HasCallStack => Text -> CustomReprs -> ConstrRepr' -- | Lookup data type representation based on name getDataRepr :: Type' -> CustomReprs -> Maybe DataRepr' -- | Convert template haskell type to simple representation of type thTypeToType' :: Type -> Type' -- | Internal version of ConstrRepr data ConstrRepr' ConstrRepr' :: Text -> Int -> BitMask -> Value -> [FieldAnn] -> ConstrRepr' -- | Qualified name of constructor [crName] :: ConstrRepr' -> Text -- | Syntactical position in the custom representations definition [crPosition] :: ConstrRepr' -> Int -- | Mask needed to determine constructor [crMask] :: ConstrRepr' -> BitMask -- | Value after applying mask [crValue] :: ConstrRepr' -> Value -- | Indicates where fields are stored [crFieldAnns] :: ConstrRepr' -> [FieldAnn] -- | Internal version of DataRepr data DataRepr' DataRepr' :: Type' -> Size -> [ConstrRepr'] -> DataRepr' -- | Simple representation of data type [drType] :: DataRepr' -> Type' -- | Size of data type [drSize] :: DataRepr' -> Size -- | Constructors [drConstrs] :: DataRepr' -> [ConstrRepr'] -- | Simple version of template haskell type. Used internally to match on. data Type' -- | Type application AppTy' :: Type' -> Type' -> Type' -- | Qualified name of type ConstTy' :: Text -> Type' -- | Numeral literal (used in BitVector 10, for example) LitTy' :: Integer -> Type' -- | Symbol literal (used in for example (Signal System Int)) SymLitTy' :: Text -> Type' -- | Convenience type for index built by buildCustomReprs type CustomReprs = (Map Type' DataRepr', Map Text ConstrRepr') instance GHC.Show.Show Clash.Annotations.BitRepresentation.Internal.Type' instance GHC.Classes.Ord Clash.Annotations.BitRepresentation.Internal.Type' instance Data.Hashable.Class.Hashable Clash.Annotations.BitRepresentation.Internal.Type' instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.Internal.Type' instance Control.DeepSeq.NFData Clash.Annotations.BitRepresentation.Internal.Type' instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.Internal.Type' instance Data.Hashable.Class.Hashable Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance GHC.Classes.Ord Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance Control.DeepSeq.NFData Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance GHC.Show.Show Clash.Annotations.BitRepresentation.Internal.ConstrRepr' instance GHC.Classes.Ord Clash.Annotations.BitRepresentation.Internal.DataRepr' instance Data.Hashable.Class.Hashable Clash.Annotations.BitRepresentation.Internal.DataRepr' instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.Internal.DataRepr' instance Control.DeepSeq.NFData Clash.Annotations.BitRepresentation.Internal.DataRepr' instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.Internal.DataRepr' instance GHC.Show.Show Clash.Annotations.BitRepresentation.Internal.DataRepr' module Clash.Annotations.BitRepresentation.Util -- | Given a type size and one of its constructor this function will yield -- a specification of which bits the whole type is made up of. I.e., a -- construction plan on how to make the whole data structure, given its -- individual constructor fields. bitOrigins :: DataRepr' -> ConstrRepr' -> [BitOrigin] -- | Same as bitOrigins, but each item in result list represents a single -- bit. bitOrigins' :: DataRepr' -> ConstrRepr' -> [BitOrigin] -- | Determine consecutively set bits in word. Will produce ranges from -- high to low. Examples: -- -- bitRanges 0b10 == [(1,1)] bitRanges 0b101 == [(2,2),(0,0)] bitRanges -- 0b10011001111 == [(10,10),(7,6),(3,0)] bitRanges :: Integer -> [(Int, Int)] isContinuousMask :: Integer -> Bool -- | Result of various utilty functions. Indicates the origin of a certain -- bit: either a literal from the constructor (or an undefined bit), or -- from a literal. data BitOrigin -- | Literal (high, low, undefind) Lit :: [Bit] -> BitOrigin -- | Bits originate from a field. Field fieldnr from -- downto. Field :: Int -> Int -> Int -> BitOrigin data Bit -- | High H :: Bit -- | Low L :: Bit -- | Undefined U :: Bit instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.Util.Bit instance GHC.Show.Show Clash.Annotations.BitRepresentation.Util.Bit instance GHC.Show.Show Clash.Annotations.BitRepresentation.Util.BitOrigin -- | Instruct the Clash compiler to look for primitive HDL templates -- provided inline or in a specified directory. For distribution of new -- packages with primitive HDL templates. Primitive guards can be added -- to warn on instantiating primitives. module Clash.Annotations.Primitive -- | Marks value as not translatable. Clash will error if it finds a -- blackbox definition for it, or when it is forced to translate it. You -- can annotate a variable or function f like: -- --
--   {-# ANN f dontTranslate #-}
--   
dontTranslate :: PrimitiveGuard () -- | Marks a value as having a blackbox. Clash will error if it hasn't -- found a blackbox. You can annotate a variable or function f -- like: -- --
--   {-# ANN f hasBlackBox #-}
--   
hasBlackBox :: PrimitiveGuard () -- | Marks value as non-synthesizable. This will trigger a warning if -- instantiated in a non-testbench context. You can annotate a variable -- or function f like: -- --
--   {-# ANN f (warnNonSynthesizable "Tread carefully, user!") #-}
--   
-- -- Implies hasBlackBox. warnNonSynthesizable :: String -> PrimitiveGuard () -- | Always emit warning upon primitive instantiation. You can annotate a -- variable or function f like: -- --
--   {-# ANN f (warnAlways "Tread carefully, user!") #-}
--   
-- -- Implies hasBlackBox. warnAlways :: String -> PrimitiveGuard () -- | The Primitive constructor instructs the clash compiler to look -- for primitive HDL templates in the indicated directory. -- InlinePrimitive is equivalent but provides the HDL template -- inline. They are intended for the distribution of new packages with -- primitive HDL templates. -- --

Example of Primitive

-- -- You have some existing IP written in one of HDLs supported by Clash, -- and you want to distribute some bindings so that the IP can be easily -- instantiated from Clash. -- -- You create a package which has a myfancyip.cabal file with -- the following stanza: -- --
--   data-files: path/to/MyFancyIP.primitives
--   cpp-options: -DCABAL
--   
-- -- and a MyFancyIP.hs module with the simulation definition and -- primitive. -- --
--   module MyFancyIP where
--   
--   import Clash.Prelude
--   
--   myFancyIP :: ...
--   myFancyIP = ...
--   {-# NOINLINE myFancyIP #-}
--   
-- -- The NOINLINE pragma is needed so that GHC will never inline -- the definition. -- -- Now you need to add the following imports and ANN pragma: -- --
--   #ifdef CABAL
--   import           Clash.Annotations.Primitive
--   import           System.FilePath
--   import qualified Paths_myfancyip
--   import           System.IO.Unsafe
--   
--   {-# ANN module (Primitive [VHDL] (unsafePerformIO Paths_myfancyip.getDataDir </> "path" </> "to")) #-}
--   #endif
--   
-- -- Add more files to the data-files stanza in your -- .cabal files and more ANN pragma's if you want to -- add more primitive templates for other HDLs -- --

Example of InlineYamlPrimitive

-- -- The following example shows off an inline HDL primitive template. It -- uses the string-interpolate package for nicer multiline -- strings. -- --
--   {-# LANGUAGE QuasiQuotes #-}
--   module InlinePrimitive where
--   
--   import           Clash.Annotations.Primitive
--   import           Clash.Prelude
--   import           Data.String.Interpolate      (__i)
--   
--   {-# ANN example (InlineYamlPrimitive [VHDL] [__i|
--     BlackBox:
--       kind: Declaration
--       name: InlinePrimitive.example
--       template: |-
--         -- begin InlinePrimitive example:
--         ~GENSYM[example][0] : block
--         ~RESULT <= 1 + ~ARG[0];
--         end block;
--         -- end InlinePrimitive example
--     |]) #-}
--   {-# NOINLINE example #-}
--   example :: Signal System (BitVector 2) -> Signal System (BitVector 2)
--   example = fmap succ
--   
data Primitive -- | Description of a primitive for a given HDLs in a file at -- FilePath Primitive :: [HDL] -> FilePath -> Primitive -- | Description of a primitive for a given HDLs as an inline JSON -- String InlinePrimitive :: [HDL] -> String -> Primitive -- | Description of a primitive for a given HDLs as an inline YAML -- String InlineYamlPrimitive :: [HDL] -> String -> Primitive -- | A compilation target HDL. data HDL SystemVerilog :: HDL Verilog :: HDL VHDL :: HDL -- | Primitive guard to mark a value as either not translatable or as -- having a blackbox with an optional extra warning. Helps Clash generate -- better error messages. -- -- For use, see dontTranslate, hasBlackBox, -- warnNonSynthesizable and warnAlways. data PrimitiveGuard a -- | Marks value as not translatable. Clash will error if it finds a -- blackbox definition for it, or when it is forced to translate it. DontTranslate :: PrimitiveGuard a -- | Marks a value as having a blackbox. Clash will error if it hasn't -- found a blackbox. HasBlackBox :: [PrimitiveWarning] -> a -> PrimitiveGuard a -- | Warning that will be emitted on instantiating a guarded value. data PrimitiveWarning -- | Marks value as non-synthesizable. This will trigger a warning if -- instantiated in a non-testbench context. WarnNonSynthesizable :: String -> PrimitiveWarning -- | Always emit warning upon primitive instantiation. WarnAlways :: String -> PrimitiveWarning -- | Extract primitive definition from a PrimitiveGuard. Will yield Nothing -- for guards of value DontTranslate. extractPrim :: PrimitiveGuard a -> Maybe a -- | Extract primitive warnings from a PrimitiveGuard. Will yield an empty -- list for guards of value DontTranslate. extractWarnings :: PrimitiveGuard a -> [PrimitiveWarning] instance GHC.Enum.Bounded Clash.Annotations.Primitive.HDL instance GHC.Enum.Enum Clash.Annotations.Primitive.HDL instance Data.Hashable.Class.Hashable Clash.Annotations.Primitive.HDL instance Control.DeepSeq.NFData Clash.Annotations.Primitive.HDL instance GHC.Generics.Generic Clash.Annotations.Primitive.HDL instance Data.Data.Data Clash.Annotations.Primitive.HDL instance GHC.Read.Read Clash.Annotations.Primitive.HDL instance GHC.Show.Show Clash.Annotations.Primitive.HDL instance GHC.Classes.Eq Clash.Annotations.Primitive.HDL instance GHC.Classes.Eq Clash.Annotations.Primitive.Primitive instance Data.Hashable.Class.Hashable Clash.Annotations.Primitive.Primitive instance Control.DeepSeq.NFData Clash.Annotations.Primitive.Primitive instance GHC.Generics.Generic Clash.Annotations.Primitive.Primitive instance Data.Data.Data Clash.Annotations.Primitive.Primitive instance GHC.Read.Read Clash.Annotations.Primitive.Primitive instance GHC.Show.Show Clash.Annotations.Primitive.Primitive instance GHC.Classes.Eq Clash.Annotations.Primitive.PrimitiveWarning instance Data.Binary.Class.Binary Clash.Annotations.Primitive.PrimitiveWarning instance Data.Hashable.Class.Hashable Clash.Annotations.Primitive.PrimitiveWarning instance Control.DeepSeq.NFData Clash.Annotations.Primitive.PrimitiveWarning instance GHC.Generics.Generic Clash.Annotations.Primitive.PrimitiveWarning instance Data.Data.Data Clash.Annotations.Primitive.PrimitiveWarning instance GHC.Read.Read Clash.Annotations.Primitive.PrimitiveWarning instance GHC.Show.Show Clash.Annotations.Primitive.PrimitiveWarning instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Annotations.Primitive.PrimitiveGuard a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Annotations.Primitive.PrimitiveGuard a) instance Data.Traversable.Traversable Clash.Annotations.Primitive.PrimitiveGuard instance Data.Foldable.Foldable Clash.Annotations.Primitive.PrimitiveGuard instance GHC.Base.Functor Clash.Annotations.Primitive.PrimitiveGuard instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Annotations.Primitive.PrimitiveGuard a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Annotations.Primitive.PrimitiveGuard a) instance GHC.Generics.Generic (Clash.Annotations.Primitive.PrimitiveGuard a) instance Data.Data.Data a => Data.Data.Data (Clash.Annotations.Primitive.PrimitiveGuard a) instance GHC.Read.Read a => GHC.Read.Read (Clash.Annotations.Primitive.PrimitiveGuard a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Annotations.Primitive.PrimitiveGuard a) module Clash.Class.Counter.TH counterName :: Name countMinName :: Name countMaxName :: Name countSuccName :: Name countPredName :: Name mkTupTy :: [Type] -> Type mkTup :: [Exp] -> Exp genTupleInstances :: Int -> Q [Dec] genTupleInstance :: Int -> Q Dec genCount :: Name -> Int -> Clause genCountOverflow :: Name -> Int -> Q Clause module Clash.Class.HasDomain.Common -- | Combine multiple lines with line break. Type-level version of the -- unlines function but for ErrorMessage. type family Unlines (ln :: [k]) :: ErrorMessage type (:<<>>:) (k1 :: t1) (k2 :: t2) = ToEM k1 :<>: ToEM k2 infixl 5 :<<>>: type (:$$$:) (k1 :: t1) (k2 :: t2) = ToEM k1 :$$: ToEM k2 infixl 4 :$$$: type family (:++:) (as :: [k]) (bs :: [k]) :: [k] infixl 4 :++: type family ToEM (k :: t) :: ErrorMessage module Clash.Class.Num -- | Adding, subtracting, and multiplying values of two different -- (sub-)types. class ExtendingNum a b where { -- | Type of the result of the addition or subtraction type family AResult a b; -- | Type of the result of the multiplication type family MResult a b; } -- | Add values of different (sub-)types, return a value of a (sub-)type -- that is potentially different from either argument. add :: ExtendingNum a b => a -> b -> AResult a b -- | Subtract values of different (sub-)types, return a value of a -- (sub-)type that is potentially different from either argument. sub :: ExtendingNum a b => a -> b -> AResult a b -- | Multiply values of different (sub-)types, return a value of a -- (sub-)type that is potentially different from either argument. mul :: ExtendingNum a b => a -> b -> MResult a b infixl 7 `mul` infixl 6 `add` infixl 6 `sub` -- | Determine how overflow and underflow are handled by the functions in -- SaturatingNum data SaturationMode -- | Wrap around on overflow and underflow SatWrap :: SaturationMode -- | Become maxBound on overflow, and minBound on underflow SatBound :: SaturationMode -- | Become 0 on overflow and underflow SatZero :: SaturationMode -- | Become maxBound on overflow, and (minBound + 1) -- on underflow for signed numbers, and minBound for unsigned -- numbers. SatSymmetric :: SaturationMode -- | Become an XException on overflow and underflow SatError :: SaturationMode -- | Num operators in which overflow and underflow behavior can be -- specified using SaturationMode. class (Bounded a, Num a) => SaturatingNum a -- | Addition with parameterizable over- and underflow behavior satAdd :: SaturatingNum a => SaturationMode -> a -> a -> a -- | Subtraction with parameterizable over- and underflow behavior satSub :: SaturatingNum a => SaturationMode -> a -> a -> a -- | Multiplication with parameterizable over- and underflow behavior satMul :: SaturatingNum a => SaturationMode -> a -> a -> a -- | Get successor of (or in other words, add 1 to) given number satSucc :: SaturatingNum a => SaturationMode -> a -> a -- | Get predecessor of (or in other words, subtract 1 from) given number satPred :: SaturatingNum a => SaturationMode -> a -> a infixl 6 `satAdd` infixl 6 `satSub` infixl 7 `satMul` -- | Addition that clips to maxBound on overflow, and -- minBound on underflow boundedAdd :: SaturatingNum a => a -> a -> a infixl 6 `boundedAdd` -- | Subtraction that clips to maxBound on overflow, and -- minBound on underflow boundedSub :: SaturatingNum a => a -> a -> a infixl 6 `boundedSub` -- | Multiplication that clips to maxBound on overflow, and -- minBound on underflow boundedMul :: SaturatingNum a => a -> a -> a infixl 7 `boundedMul` instance GHC.Enum.Bounded Clash.Class.Num.SaturationMode instance GHC.Enum.Enum Clash.Class.Num.SaturationMode instance GHC.Classes.Eq Clash.Class.Num.SaturationMode instance GHC.Show.Show Clash.Class.Num.SaturationMode module Clash.Class.Resize -- | Coerce a value to be represented by a different number of bits class Resize (f :: Nat -> Type) -- | A sign-preserving resize operation -- -- resize :: (Resize f, KnownNat a, KnownNat b) => f a -> f b -- | Perform a zeroExtend for unsigned datatypes, and -- signExtend for a signed datatypes extend :: (Resize f, KnownNat a, KnownNat b) => f a -> f (b + a) -- | Add extra zero bits in front of the MSB zeroExtend :: (Resize f, KnownNat a, KnownNat b) => f a -> f (b + a) -- | Add extra sign bits in front of the MSB signExtend :: (Resize f, KnownNat a, KnownNat b) => f a -> f (b + a) -- | Remove bits from the MSB truncateB :: (Resize f, KnownNat a) => f (a + b) -> f a -- | Like resize, but errors if f a is out of bounds for f -- b. Useful when you "know" f a can't be out of bounds, but -- would like to have your assumptions checked. -- -- NB: Check only affects simulation. I.e., no checks will be -- inserted into the generated HDL checkedResize :: forall a b f. (HasCallStack, Resize f, KnownNat a, Integral (f a), KnownNat b, Integral (f b), Bounded (f b)) => f a -> f b -- | Like fromIntegral, but errors if a is out of bounds for -- b. Useful when you "know" a can't be out of bounds, but -- would like to have your assumptions checked. -- -- checkedFromIntegral :: forall a b. HasCallStack => (Integral a, Integral b, Bounded b) => a -> b -- | Like truncateB, but errors if f (a + b) is out of bounds -- for f a. Useful when you "know" f (a + b) can't be out -- of bounds, but would like to have your assumptions checked. -- -- NB: Check only affects simulation. I.e., no checks will be -- inserted into the generated HDL checkedTruncateB :: forall a b f. (HasCallStack, Resize f, KnownNat b, Integral (f (a + b)), KnownNat a, Integral (f a), Bounded (f a)) => f (a + b) -> f a -- | Clash.HaskellPrelude re-exports most of the Haskell -- Prelude with the exception of those functions that the Clash -- API defines to work on Vec from Clash.Sized.Vector -- instead of on lists as the Haskell Prelude does. In addition, for the -- odd and even functions a type class called Parity -- is available at Clash.Class.Parity. module Clash.HaskellPrelude -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. In other words, it evaluates the first -- argument a to weak head normal form (WHNF). seq is -- usually introduced to improve performance by avoiding unneeded -- laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> b -> b infixr 0 `seq` -- | <math>. filter, applied to a predicate and a list, -- returns the list of those elements that satisfy the predicate; i.e., -- --
--   filter p xs = [ x | x <- xs, p x]
--   
-- --
--   >>> filter odd [1, 2, 3]
--   [1,3]
--   
filter :: (a -> Bool) -> [a] -> [a] -- | The print function outputs a value of any printable type to the -- standard output device. Printable types are those that are instances -- of class Show; print converts values to strings for -- output using the show operation and adds a newline. -- -- For example, a program to print the first 20 integers and their powers -- of 2 could be written as: -- --
--   main = print ([(n, 2^n) | n <- [0..19]])
--   
print :: Show a => a -> IO () -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
--   f $ g $ h x  =  f (g (h x))
--   
-- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- -- Note that ($) is levity-polymorphic in its result -- type, so that foo $ True where foo :: Bool -> -- Int# is well-typed. ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $ -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | The Bounded class is used to name the upper and lower limits of -- a type. Ord is not a superclass of Bounded since types -- that are not totally ordered may also have upper and lower bounds. -- -- The Bounded class may be derived for any enumeration type; -- minBound is the first constructor listed in the data -- declaration and maxBound is the last. Bounded may also -- be derived for single-constructor datatypes whose constituent types -- are in Bounded. class Bounded a minBound :: Bounded a => a maxBound :: Bounded a => a -- | Class Enum defines operations on sequentially ordered types. -- -- The enumFrom... methods are used in Haskell's translation of -- arithmetic sequences. -- -- Instances of Enum may be derived for any enumeration type -- (types whose constructors have no fields). The nullary constructors -- are assumed to be numbered left-to-right by fromEnum from -- 0 through n-1. See Chapter 10 of the Haskell -- Report for more details. -- -- For any type that is an instance of class Bounded as well as -- Enum, the following should hold: -- -- -- --
--   enumFrom     x   = enumFromTo     x maxBound
--   enumFromThen x y = enumFromThenTo x y bound
--     where
--       bound | fromEnum y >= fromEnum x = maxBound
--             | otherwise                = minBound
--   
class Enum a -- | the successor of a value. For numeric types, succ adds 1. succ :: Enum a => a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: Enum a => a -> a -- | Convert from an Int. toEnum :: Enum a => Int -> a -- | Convert to an Int. It is implementation-dependent what -- fromEnum returns when applied to a value that is too large to -- fit in an Int. fromEnum :: Enum a => a -> Int -- | Used in Haskell's translation of [n..] with [n..] = -- enumFrom n, a possible implementation being enumFrom n = n : -- enumFrom (succ n). For example: -- -- enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..] with [n,n'..] = -- enumFromThen n n', a possible implementation being -- enumFromThen n n' = n : n' : worker (f x) (f x n'), -- worker s v = v : worker s (s v), x = fromEnum n' - -- fromEnum n and f n y | n > 0 = f (n - 1) (succ y) | n < -- 0 = f (n + 1) (pred y) | otherwise = y For example: -- -- enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m] with [n..m] = -- enumFromTo n m, a possible implementation being enumFromTo n -- m | n <= m = n : enumFromTo (succ n) m | otherwise = []. For -- example: -- -- enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m] with [n,n'..m] -- = enumFromThenTo n n' m, a possible implementation being -- enumFromThenTo n n' m = worker (f x) (c x) n m, x = -- fromEnum n' - fromEnum n, c x = bool (>=) ((x -- 0) f n y | n > 0 = f (n - 1) (succ y) | n < 0 = f (n + -- 1) (pred y) | otherwise = y and worker s c v m | c v m = v : -- worker s c (s v) m | otherwise = [] For example: -- -- enumFromThenTo :: Enum a => a -> a -> a -> [a] -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- The Haskell Report defines no laws for Eq. However, == -- is customarily expected to implement an equivalence relationship where -- two values comparing equal are indistinguishable by "public" -- functions, with a "public" function being one not allowing to see -- implementation details. For example, for a type representing -- non-normalised natural numbers modulo 100, a "public" function doesn't -- make the difference between 1 and 201. It is expected to have the -- following properties: -- -- -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool infix 4 == infix 4 /= -- | Trigonometric and hyperbolic functions and related functions. -- -- The Haskell Report defines no laws for Floating. However, -- (+), (*) and exp are -- customarily expected to define an exponential field and have the -- following properties: -- -- class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a atanh :: Floating a => a -> a infixr 8 ** -- | Fractional numbers, supporting real division. -- -- The Haskell Report defines no laws for Fractional. However, -- (+) and (*) are customarily expected -- to define a division ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- Fractional implement a field. However, all instances in -- base do. class Num a => Fractional a -- | Fractional division. (/) :: Fractional a => a -> a -> a -- | Reciprocal fraction. recip :: Fractional a => a -> a -- | Conversion from a Rational (that is Ratio -- Integer). A floating literal stands for an application of -- fromRational to a value of type Rational, so such -- literals have type (Fractional a) => a. fromRational :: Fractional a => Rational -> a infixl 7 / -- | Integral numbers, supporting integer division. -- -- The Haskell Report defines no laws for Integral. However, -- Integral instances are customarily expected to define a -- Euclidean domain and have the following properties for the -- div/mod and quot/rem pairs, given suitable -- Euclidean functions f and g: -- -- -- -- An example of a suitable Euclidean function, for Integer's -- instance, is abs. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer infixl 7 `mod` infixl 7 `div` infixl 7 `rem` infixl 7 `quot` -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Instances of Monad should satisfy the following: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad (m :: Type -> Type) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. -- -- 'as >>= bs' can be understood as the do -- expression -- --
--   do a <- as
--      bs a
--   
(>>=) :: Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. class Functor (f :: Type -> Type) -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
--   do a <- as
--      pure (f a)
--   
-- -- with an inferred Functor constraint. fmap :: Functor f => (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
--   do bs
--      pure a
--   
-- -- with an inferred Functor constraint. (<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | Basic numeric class. -- -- The Haskell Report defines no laws for Num. However, -- (+) and (*) are customarily expected -- to define a ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- both Num and Ord implement an ordered ring. Indeed, in -- base only Integer and Rational do. class Num a (+) :: Num a => a -> a -> a (-) :: Num a => a -> a -> a (*) :: Num a => a -> a -> a -- | Unary negation. negate :: Num a => a -> a -- | Absolute value. abs :: Num a => a -> a -- | Sign of a number. The functions abs and signum should -- satisfy the law: -- --
--   abs x * signum x == x
--   
-- -- For real numbers, the signum is either -1 (negative), -- 0 (zero) or 1 (positive). signum :: Num a => a -> a -- | Conversion from an Integer. An integer literal represents the -- application of the function fromInteger to the appropriate -- value of type Integer, so such literals have type -- (Num a) => a. fromInteger :: Num a => Integer -> a infixl 6 - infixl 6 + infixl 7 * -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- The Haskell Report defines no laws for Ord. However, -- <= is customarily expected to implement a non-strict partial -- order and have the following properties: -- -- -- -- Note that the following operator interactions are expected to hold: -- --
    --
  1. x >= y = y <= x
  2. --
  3. x < y = x <= y && x /= y
  4. --
  5. x > y = y < x
  6. --
  7. x < y = compare x y == LT
  8. --
  9. x > y = compare x y == GT
  10. --
  11. x == y = compare x y == EQ
  12. --
  13. min x y == if x <= y then x else y = True
  14. --
  15. max x y == if x >= y then x else y = True
  16. --
-- -- Note that (7.) and (8.) do not require min and -- max to return either of their arguments. The result is merely -- required to equal one of the arguments in terms of (==). -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => a -> a -> a infix 4 < infix 4 <= infix 4 > infix 4 >= -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readsPrec d r =  readParen (d > app_prec)
--                            (\r -> [(Leaf m,t) |
--                                    ("Leaf",s) <- lex r,
--                                    (m,t) <- readsPrec (app_prec+1) s]) r
--   
--                         ++ readParen (d > up_prec)
--                            (\r -> [(u:^:v,w) |
--                                    (u,s) <- readsPrec (up_prec+1) r,
--                                    (":^:",t) <- lex s,
--                                    (v,w) <- readsPrec (up_prec+1) t]) r
--   
--             where app_prec = 10
--                   up_prec = 5
--   
-- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readPrec = parens $ (prec app_prec $ do
--                                    Ident "Leaf" <- lexP
--                                    m <- step readPrec
--                                    return (Leaf m))
--   
--                        +++ (prec up_prec $ do
--                                    u <- step readPrec
--                                    Symbol ":^:" <- lexP
--                                    v <- step readPrec
--                                    return (u :^: v))
--   
--             where app_prec = 10
--                   up_prec = 5
--   
--           readListPrec = readListPrecDefault
--   
-- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
--   instance Read T where
--     readPrec     = ...
--     readListPrec = readListPrecDefault
--   
class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] class (Num a, Ord a) => Real a -- | the rational equivalent of its real argument with full precision toRational :: Real a => a -> Rational -- | Efficient, machine-independent access to the components of a -- floating-point number. class (RealFrac a, Floating a) => RealFloat a -- | a constant function, returning the radix of the representation (often -- 2) floatRadix :: RealFloat a => a -> Integer -- | a constant function, returning the number of digits of -- floatRadix in the significand floatDigits :: RealFloat a => a -> Int -- | a constant function, returning the lowest and highest values the -- exponent may assume floatRange :: RealFloat a => a -> (Int, Int) -- | The function decodeFloat applied to a real floating-point -- number returns the significand expressed as an Integer and an -- appropriately scaled exponent (an Int). If -- decodeFloat x yields (m,n), then x -- is equal in value to m*b^^n, where b is the -- floating-point radix, and furthermore, either m and -- n are both zero or else b^(d-1) <= abs m < -- b^d, where d is the value of floatDigits -- x. In particular, decodeFloat 0 = (0,0). If the -- type contains a negative zero, also decodeFloat (-0.0) = -- (0,0). The result of decodeFloat x is -- unspecified if either of isNaN x or -- isInfinite x is True. decodeFloat :: RealFloat a => a -> (Integer, Int) -- | encodeFloat performs the inverse of decodeFloat in the -- sense that for finite x with the exception of -0.0, -- uncurry encodeFloat (decodeFloat x) = x. -- encodeFloat m n is one of the two closest -- representable floating-point numbers to m*b^^n (or -- ±Infinity if overflow occurs); usually the closer, but if -- m contains too many bits, the result may be rounded in the -- wrong direction. encodeFloat :: RealFloat a => Integer -> Int -> a -- | exponent corresponds to the second component of -- decodeFloat. exponent 0 = 0 and for finite -- nonzero x, exponent x = snd (decodeFloat x) -- + floatDigits x. If x is a finite floating-point -- number, it is equal in value to significand x * b ^^ -- exponent x, where b is the floating-point radix. -- The behaviour is unspecified on infinite or NaN values. exponent :: RealFloat a => a -> Int -- | The first component of decodeFloat, scaled to lie in the open -- interval (-1,1), either 0.0 or of absolute -- value >= 1/b, where b is the floating-point -- radix. The behaviour is unspecified on infinite or NaN -- values. significand :: RealFloat a => a -> a -- | multiplies a floating-point number by an integer power of the radix scaleFloat :: RealFloat a => Int -> a -> a -- | True if the argument is an IEEE "not-a-number" (NaN) value isNaN :: RealFloat a => a -> Bool -- | True if the argument is an IEEE infinity or negative infinity isInfinite :: RealFloat a => a -> Bool -- | True if the argument is too small to be represented in -- normalized format isDenormalized :: RealFloat a => a -> Bool -- | True if the argument is an IEEE negative zero isNegativeZero :: RealFloat a => a -> Bool -- | True if the argument is an IEEE floating point number isIEEE :: RealFloat a => a -> Bool -- | a version of arctangent taking two real floating-point arguments. For -- real floating x and y, atan2 y x -- computes the angle (from the positive x-axis) of the vector from the -- origin to the point (x,y). atan2 y x returns -- a value in the range [-pi, pi]. It follows the -- Common Lisp semantics for the origin when signed zeroes are supported. -- atan2 y 1, with y in a type that is -- RealFloat, should return the same value as atan -- y. A default definition of atan2 is provided, but -- implementors can provide a more accurate implementation. atan2 :: RealFloat a => a -> a -> a -- | Extracting components of fractions. class (Real a, Fractional a) => RealFrac a -- | The function properFraction takes a real fractional number -- x and returns a pair (n,f) such that x = -- n+f, and: -- -- -- -- The default definitions of the ceiling, floor, -- truncate and round functions are in terms of -- properFraction. properFraction :: (RealFrac a, Integral b) => a -> (b, a) -- | truncate x returns the integer nearest x -- between zero and x truncate :: (RealFrac a, Integral b) => a -> b -- | round x returns the nearest integer to x; the -- even integer if x is equidistant between two integers round :: (RealFrac a, Integral b) => a -> b -- | ceiling x returns the least integer not less than -- x ceiling :: (RealFrac a, Integral b) => a -> b -- | floor x returns the greatest integer not greater than -- x floor :: (RealFrac a, Integral b) => a -> b -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | When a value is bound in do-notation, the pattern on the left -- hand side of <- might not match. In this case, this class -- provides a function to recover. -- -- A Monad without a MonadFail instance may only be used in -- conjunction with pattern that always match, such as newtypes, tuples, -- data types with only a single data constructor, and irrefutable -- patterns (~pat). -- -- Instances of MonadFail should satisfy the following law: -- fail s should be a left zero for >>=, -- --
--   fail s >>= f  =  fail s
--   
-- -- If your Monad is also MonadPlus, a popular definition is -- --
--   fail _ = mzero
--   
class Monad m => MonadFail (m :: Type -> Type) fail :: MonadFail m => String -> m a -- | A functor with application, providing operations to -- -- -- -- A minimal complete definition must include implementations of -- pure and of either <*> or liftA2. If it -- defines both, then they must behave the same as their default -- definitions: -- --
--   (<*>) = liftA2 id
--   
-- --
--   liftA2 f x y = f <$> x <*> y
--   
-- -- Further, any definition must satisfy the following: -- -- -- -- The other methods have the following default definitions, which may be -- overridden with equivalent specialized implementations: -- -- -- -- As a consequence of these laws, the Functor instance for -- f will satisfy -- -- -- -- It may be useful to note that supposing -- --
--   forall x y. p (q x y) = f x . g y
--   
-- -- it follows from the above that -- --
--   liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v
--   
-- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative (f :: Type -> Type) -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. -- -- Using ApplicativeDo: 'fs <*> as' can be -- understood as the do expression -- --
--   do f <- fs
--      a <- as
--      pure (f a)
--   
(<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. -- -- 'as *> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
-- -- This is a tad complicated for our ApplicativeDo extension -- which will give it a Monad constraint. For an -- Applicative constraint we write it of the form -- --
--   do _ <- as
--      b <- bs
--      pure b
--   
(*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. -- -- Using ApplicativeDo: 'as <* bs' can be -- understood as the do expression -- --
--   do a <- as
--      bs
--      pure a
--   
(<*) :: Applicative f => f a -> f b -> f a infixl 4 <* infixl 4 *> infixl 4 <*> -- | Data structures that can be folded. -- -- For example, given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Foldable Tree where
--      foldMap f Empty = mempty
--      foldMap f (Leaf x) = f x
--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
--   
-- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
--   instance Foldable Tree where
--      foldr f z Empty = z
--      foldr f z (Leaf x) = f x z
--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- --
--   length = getSum . foldMap (Sum . const  1)
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable (t :: Type -> Type) -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The sum function computes the sum of the numbers of a -- structure. sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. product :: (Foldable t, Num a) => t a -> a infix 4 `elem` -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- --
--   t (pure x) = pure x
--   t (f <*> x) = t f <*> t x
--   
-- -- and the identity functor Identity and composition functors -- Compose are from Data.Functor.Identity and -- Data.Functor.Compose. -- -- A result of the naturality law is a purity law for traverse -- --
--   traverse pure = pure
--   
-- -- (The naturality law is implied by parametricity and thus so is the -- purity law [1, p15].) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Traversable Tree where
--      traverse f Empty = pure Empty
--      traverse f (Leaf x) = Leaf <$> f x
--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
--   
-- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- -- -- -- References: [1] The Essence of the Iterator Pattern, Jeremy Gibbons -- and Bruno C. d. S. Oliveira class (Functor t, Foldable t) => Traversable (t :: Type -> Type) -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and collect -- the results. For a version that ignores the results see -- sequenceA_. sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | The class of semigroups (types with an associative binary operation). -- -- Instances should satisfy the following: -- -- class Semigroup a -- | An associative operation. -- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
(<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. -- -- NOTE: Semigroup is a superclass of Monoid since -- base-4.11.0.0. class Semigroup a => Monoid a -- | Identity of mappend -- --
--   >>> "Hello world" <> mempty
--   "Hello world"
--   
mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. -- -- For most types, the default definition for mconcat will be -- used, but the function is included in the class definition so that an -- optimized version can be provided for specific types. -- --
--   >>> mconcat ["Hello", " ", "Haskell", "!"]
--   "Hello Haskell!"
--   
mconcat :: Monoid a => [a] -> a data Bool False :: Bool True :: Bool -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int -- | Arbitrary precision integers. In contrast with fixed-size integral -- types such as Int, the Integer type represents the -- entire infinite range of integers. -- -- For more information about this type's representation, see the -- comments in its implementation. data Integer -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a Nothing :: Maybe a Just :: a -> Maybe a data Ordering LT :: Ordering EQ :: Ordering GT :: Ordering -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a -- | A Word is an unsigned integral type, with the same size as -- Int. data Word -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> s
--   Left "foo"
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> n
--   Right 3
--   
--   >>> :type s
--   s :: Either String Int
--   
--   >>> :type n
--   n :: Either String Int
--   
-- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> fmap (*2) s
--   Left "foo"
--   
--   >>> fmap (*2) n
--   Right 6
--   
-- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
--   >>> import Data.Char ( digitToInt, isDigit )
--   
--   >>> :{
--       let parseEither :: Char -> Either String Int
--           parseEither c
--             | isDigit c = Right (digitToInt c)
--             | otherwise = Left "parse error"
--   
--   >>> :}
--   
-- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither '1'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Right 3
--   
-- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither 'm'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Left "parse error"
--   
data Either a b Left :: a -> Either a b Right :: b -> Either a b -- | A String is a list of characters. String constants in Haskell -- are values of type String. -- -- See Data.List for operations on lists. type String = [Char] -- | Identity function. -- --
--   id x = x
--   
id :: a -> a -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the Left constructor and another -- using the Right constructor. Then we apply "either" the -- length function (if we have a String) or the "times-two" -- function (if we have an Int): -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> either length (*2) s
--   3
--   
--   >>> either length (*2) n
--   6
--   
either :: (a -> c) -> (b -> c) -> Either a b -> c -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a -- | The computation appendFile file str function appends -- the string str, to the file file. -- -- Note that writeFile and appendFile write a literal -- string to a file. To write a value of any printable type, as with -- print, use the show function to convert the value to a -- string first. -- --
--   main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
--   
appendFile :: FilePath -> String -> IO () -- | The computation writeFile file str function writes the -- string str, to the file file. writeFile :: FilePath -> String -> IO () -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | The interact function takes a function of type -- String->String as its argument. The entire input from the -- standard input device is passed to this function as its argument, and -- the resulting string is output on the standard output device. interact :: (String -> String) -> IO () -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | The same as putStr, but adds a newline character. putStrLn :: String -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | File and directory names are values of type String, whose -- precise meaning is operating system dependent. Files can be opened, -- yielding a handle which can then be used to operate on the contents of -- that file. type FilePath = String -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
--   instance Monad IO where
--     ...
--     fail s = ioError (userError s)
--   
userError :: String -> IOError -- | The Haskell 2010 type for exceptions in the IO monad. Any I/O -- operation may raise an IOError instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see Exception. -- -- In Haskell 2010, this is an opaque type. type IOError = IOException -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | Determines whether all elements of the structure satisfy the -- predicate. all :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. any :: Foldable t => (a -> Bool) -> t a -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. or :: Foldable t => t Bool -> Bool -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
--   >>> unwords ["Lorem", "ipsum", "dolor"]
--   "Lorem ipsum dolor"
--   
unwords :: [String] -> String -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
--   >>> words "Lorem ipsum\ndolor"
--   ["Lorem","ipsum","dolor"]
--   
words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
--   >>> unlines ["Hello", "World", "!"]
--   "Hello\nWorld\n!\n"
--   
unlines :: [String] -> String -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
--   >>> lines ""
--   []
--   
-- --
--   >>> lines "\n"
--   [""]
--   
-- --
--   >>> lines "one"
--   ["one"]
--   
-- --
--   >>> lines "one\n"
--   ["one"]
--   
-- --
--   >>> lines "one\n\n"
--   ["one",""]
--   
-- --
--   >>> lines "one\ntwo"
--   ["one","two"]
--   
-- --
--   >>> lines "one\ntwo\n"
--   ["one","two"]
--   
-- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | The read function reads input from a string, which must be -- completely consumed by the input process. read fails with an -- error if the parse is unsuccessful, and it is therefore -- discouraged from being used in real applications. Use readMaybe -- or readEither for safe alternatives. -- --
--   >>> read "123" :: Int
--   123
--   
-- --
--   >>> read "hello" :: Int
--   *** Exception: Prelude.read: no parse
--   
read :: Read a => String -> a -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- -- lex :: ReadS String -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | lcm x y is the smallest positive integer that both -- x and y divide. lcm :: Integral a => a -> a -> a -- | gcd x y is the non-negative factor of both x -- and y of which every common factor of x and -- y is also a factor; for example gcd 4 2 = 2, -- gcd (-4) 6 = 2, gcd 0 4 = 4. -- gcd 0 0 = 0. (That is, the common divisor -- that is "greatest" in the divisibility preordering.) -- -- Note: Since for signed fixed-width integer types, abs -- minBound < 0, the result may be negative if one of the -- arguments is minBound (and necessarily is if the other -- is 0 or minBound) for such types. gcd :: Integral a => a -> a -> a -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | equivalent to showsPrec with a precedence of 0. shows :: Show a => a -> ShowS -- | The shows functions return a function that prepends the -- output String to an existing String. This allows -- constant-time concatenation of results using function composition. type ShowS = String -> String -- | <math>. lookup key assocs looks up a key in an -- association list. -- --
--   >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
--   Just "second"
--   
lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
--   break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4])
--   break (< 9) [1,2,3] == ([],[1,2,3])
--   break (> 9) [1,2,3] == ([1,2,3],[])
--   
-- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
--   span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4])
--   span (< 9) [1,2,3] == ([1,2,3],[])
--   span (< 0) [1,2,3] == ([],[1,2,3])
--   
-- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs: -- --
--   dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3]
--   dropWhile (< 9) [1,2,3] == []
--   dropWhile (< 0) [1,2,3] == [1,2,3]
--   
dropWhile :: (a -> Bool) -> [a] -> [a] -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p: -- --
--   takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2]
--   takeWhile (< 9) [1,2,3] == [1,2,3]
--   takeWhile (< 0) [1,2,3] == []
--   
takeWhile :: (a -> Bool) -> [a] -> [a] -- | cycle ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity on -- infinite lists. cycle :: [a] -> [a] -- | The maybe function takes a default value, a function, and a -- Maybe value. If the Maybe value is Nothing, the -- function returns the default value. Otherwise, it applies the function -- to the value inside the Just and returns the result. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybe False odd (Just 3)
--   True
--   
-- --
--   >>> maybe False odd Nothing
--   False
--   
-- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> maybe 0 (*2) (readMaybe "5")
--   10
--   
--   >>> maybe 0 (*2) (readMaybe "")
--   0
--   
-- -- Apply show to a Maybe Int. If we have Just n, -- we want to show the underlying Int n. But if we have -- Nothing, we return the empty string instead of (for example) -- "Nothing": -- --
--   >>> maybe "" show (Just 5)
--   "5"
--   
--   >>> maybe "" show Nothing
--   ""
--   
maybe :: b -> (a -> b) -> Maybe a -> b -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is function -- application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe -- String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to an -- Either Int String using show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | uncurry converts a curried function to a function on pairs. -- --

Examples

-- --
--   >>> uncurry (+) (1,2)
--   3
--   
-- --
--   >>> uncurry ($) (show, 1)
--   "1"
--   
-- --
--   >>> map (uncurry max) [(1,2), (3,4), (6,8)]
--   [2,4,8]
--   
uncurry :: (a -> b -> c) -> (a, b) -> c -- | curry converts an uncurried function to a curried function. -- --

Examples

-- --
--   >>> curry fst 1 2
--   1
--   
curry :: ((a, b) -> c) -> a -> b -> c -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: a -> a -> a -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | Strict (call-by-value) application operator. It takes a function and -- an argument, evaluates the argument to weak head normal form (WHNF), -- then calls the function with that value. ($!) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $! -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
--   >>> flip (++) "hello" "world"
--   "worldhello"
--   
flip :: (a -> b -> c) -> b -> a -> c -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | const x is a unary function which evaluates to x for -- all inputs. -- --
--   >>> const 42 "hello"
--   42
--   
-- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a -- | error stops execution and displays an error message. error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a (&&) :: Bool -> Bool -> Bool infixr 3 && (||) :: Bool -> Bool -> Bool infixr 2 || not :: Bool -> Bool -- | Hidden arguments module Clash.Hidden -- | A value reflected to, or hiding at, the Constraint level -- -- e.g. a function: -- --
--   f :: Hidden "foo" Int
--     => Bool
--     -> Int
--   f = ...
--   
-- -- has a normal argument of type Bool, and a -- hidden argument called "foo" of type Int. In order to -- apply the Int argument we have to use the expose -- function, so that the hidden argument becomes a normal argument -- again. -- --

Original implementation

-- -- Hidden used to be implemented by: -- --
--   class Hidden (x :: Symbol) a | x -> a where
--     hidden :: a
--   
-- -- which is equivalent to IP, except that IP has magic -- inference rules bestowed by GHC so that there's never any ambiguity. -- We need these magic inference rules so we don't end up in type -- inference absurdity where asking for the type of an type-annotated -- value results in a no-instance-in-scope error. type Hidden (x :: Symbol) a = IP x a -- | Expose a Hidden argument so that it can be applied normally, -- e.g. -- --
--   f :: Hidden "foo" Int
--     => Bool
--     -> Int
--   f = ...
--   
--   g :: Int -> Bool -> Int
--   g = expose @"foo" f
--   
expose :: forall x a r. (Hidden x a => r) -> a -> r -- | Using -XOverloadedLabels and -XRebindableSyntax, we can -- turn any value into a hidden argument using the #foo -- notation, e.g.: -- --
--   f :: Int -> Bool -> Int
--   f = ...
--   
--   g :: Hidden "foo" Bool
--     => Int -> Int
--   g i = f i #foo
--   
fromLabel :: forall x a. Hidden x a => a -- | Add inline documentation to types: -- --
--   fifo
--     :: Clock dom
--     -> Reset dom
--     -> SNat addrSize
--     -> "read request" ::: Signal dom Bool
--     -> "write request" ::: Signal dom (Maybe (BitVector dataSize))
--     -> ( "q"     ::: Signal dom (BitVector dataSize)
--        , "full"  ::: Signal dom Bool
--        , "empty" ::: Signal dom Bool
--        )
--   
-- -- which can subsequently be inspected in the interactive environment: -- --
--   >>> import Clash.Explicit.Prelude
--   
--   >>> :t fifo @System
--   fifo @System
--     :: Clock System
--        -> Reset System
--        -> SNat addrSize
--        -> ("read request" ::: Signal System Bool)
--        -> ("write request" ::: Signal System (Maybe (BitVector dataSize)))
--        -> ("q" ::: Signal System (BitVector dataSize),
--            "full" ::: Signal System Bool, "empty" ::: Signal System Bool)
--   
module Clash.NamedTypes -- | Annotate a type with a name type (name :: k) ::: a = a module Clash.Promoted.Symbol -- | Singleton value for a type-level string s data SSymbol (s :: Symbol) [SSymbol] :: KnownSymbol s => SSymbol s -- | Create a singleton symbol literal SSymbol s from a -- proxy for s ssymbolProxy :: KnownSymbol s => proxy s -> SSymbol s -- | Reify the type-level Symbol s to it's term-level -- String representation. ssymbolToString :: SSymbol s -> String instance GHC.TypeLits.KnownSymbol s => Language.Haskell.TH.Syntax.Lift (Clash.Promoted.Symbol.SSymbol s) instance GHC.Show.Show (Clash.Promoted.Symbol.SSymbol s) -- | Control naming and deduplication in the generated HDL code. Explicitly -- nameable things include: -- -- -- -- Refer to Clash.Annotations.TopEntity for controlling naming of -- entities (VHDL) / modules ((System)Verilog) and their ports. module Clash.Magic -- | Prefix instance and register names with the given Symbol prefixName :: forall (name :: Symbol) a. a -> name ::: a -- | Suffix instance and register names with the given Symbol suffixName :: forall (name :: Symbol) a. a -> name ::: a -- | Suffix instance and register names with the given Symbol, but -- add it in front of other suffixes. -- -- When you write -- --
--   suffixName @"A" (suffixName @"B" f))
--   
-- -- you get register and instance names inside f with the suffix: -- "_B_A" -- -- However, if you want them in the other order you can write: -- --
--   suffixNameP @"A" (suffixName @"B" f))
--   
-- -- so that names inside f will have the suffix "_A_B" suffixNameP :: forall (name :: Symbol) a. a -> name ::: a -- | Suffix instance and register names with the given Nat suffixNameFromNat :: forall (name :: Nat) a. a -> name ::: a -- | Suffix instance and register names with the given Nat, but add -- it in front of other suffixes. -- -- When you write -- --
--   suffixNameNat @1 (suffixName @"B" f))
--   
-- -- you get register and instance names inside f with the suffix: -- "_B_1" -- -- However, if you want them in the other order you can write: -- --
--   suffixNameNatP @1 (suffixName @"B" f))
--   
-- -- so that names inside f will have the suffix "_1_B" suffixNameFromNatP :: forall (name :: Nat) a. a -> name ::: a -- | Name the instance or register with the given Symbol, instead of -- using an auto-generated name. Pre- and suffixes annotated with -- prefixName and suffixName will be added to both -- instances and registers named with setName and instances and -- registers that are auto-named. setName :: forall (name :: Symbol) a. a -> name ::: a -- | Name a given term, such as one of type Signal, using the given -- SSymbol. Results in a declaration with the name used as the -- identifier in the generated HDL code. -- -- Example usage: -- --
--   nameHint (SSymbol @"identifier") term
--   
-- -- NB: The given name should be considered a hint as it may be -- expanded, e.g. if it collides with existing identifiers. nameHint :: SSymbol sym -> a -> a -- | Force deduplication, i.e. share a function or operator between -- multiple branches. -- -- By default Clash converts -- --
--   case x of
--     A -> 3 * y
--     B -> x * x
--   
-- -- to -- --
--   let f_arg0 = case x of {A -> 3; _ -> x}
--       f_arg1 = case x of {A -> y; _ -> x}
--       f_out  = f_arg0 * f_arg1
--   in  case x of
--         A -> f_out
--         B -> f_out
--   
-- -- However, it won't do this for: -- --
--   case x of
--     A -> 3 + y
--     B -> x + x
--   
-- -- Because according to the internal heuristics the multiplexer -- introduced for the deduplication are more expensive than the addition. -- This might not be the case for your particular platform. -- -- In these cases you can force Clash to deduplicate by: -- --
--   case x of
--     A -> deDup (3 + y)
--     B -> deDup (x + x)
--   
deDup :: forall a. a -> a -- | Do not deduplicate, i.e. keep, an applied function inside a -- case-alternative; do not try to share the function between multiple -- branches. -- -- By default Clash converts -- --
--   case x of
--     A -> f 3 y
--     B -> f x x
--     C -> h x
--   
-- -- to -- --
--   let f_arg0 = case x of {A -> 3; _ -> x}
--       f_arg1 = case x of {A -> y; _ -> x}
--       f_out  = f f_arg0 f_arg1
--   in  case x of
--         A -> f_out
--         B -> f_out
--         C -> h x
--   
-- -- i.e. it deduplicates functions (and operators such as multiplication) -- between case-alternatives to save on area. This comes at the cost of -- multiplexing the arguments for the deduplicated function. -- -- There are two reasons you would want to stop Clash from doing this: -- --
    --
  1. The deduplicated function is in the critical path, and the -- addition of the multiplexers further increased the propagation -- delay.
  2. --
  3. Clash's heuristics were off, and the addition of the multiplexers -- actually made the final circuit larger instead of smaller.
  4. --
-- -- In these cases you want to tell Clash not to deduplicate: -- --
--   case x of
--     A -> noDeDup f 3 y
--     B -> f x x
--     C -> h x
--   
-- -- Where the application of f in the A-alternative is now -- explicitly not deduplicated, and given that the f in the -- B-alternative is the only remaining application of f in the -- case-expression it is also not deduplicated. -- -- Note that if the C-alternative also had an application of -- f, then the applications of f in the B- and -- C-alternatives would have been deduplicated; i.e. the final -- circuit would have had two application of f. noDeDup :: forall a. a -> a -- | True in Haskell/Clash simulation. Replaced by False when -- generating HDL. clashSimulation :: Bool -- | A container for data you only want to have around during simulation -- and is ignored during synthesis. Useful for carrying around things -- such as: -- -- data SimOnly a SimOnly :: a -> SimOnly a -- | Same as error but will make HDL generation fail if included in -- the final circuit. -- -- This is useful for the error case of static assertions. -- -- Note that the error message needs to be a literal, and during HDL -- generation the error message does not include a stack trace, so it had -- better be descriptive. clashCompileError :: forall a. HasCallStack => String -> a instance Data.Traversable.Traversable Clash.Magic.SimOnly instance Data.Foldable.Foldable Clash.Magic.SimOnly instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Magic.SimOnly a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Magic.SimOnly a) instance GHC.Base.Functor Clash.Magic.SimOnly instance GHC.Base.Applicative Clash.Magic.SimOnly instance GHC.Base.Monad Clash.Magic.SimOnly instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Clash.Magic.SimOnly a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Clash.Magic.SimOnly a) -- | This module contains code from: -- https://hackage.haskell.org/package/mod and has the following -- license: -- -- Copyright (c) 2019 Andrew Lelechenko -- -- Permission is hereby granted, free of charge, to any person obtaining -- a copy of this software and associated documentation files (the -- Software), to deal in the Software without restriction, -- including without limitation the rights to use, copy, modify, merge, -- publish, distribute, sublicense, and/or sell copies of the Software, -- and to permit persons to whom the Software is furnished to do so, -- subject to the following conditions: -- -- The above copyright notice and this permission notice shall be -- included in all copies or substantial portions of the Software. -- -- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, -- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -- IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -- CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -- TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -- SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. module Clash.Sized.Internal.Mod -- | modular subtraction subMod :: Natural -> Natural -> Natural -> Natural -- | modular addition addMod :: Natural -> Natural -> Natural -> Natural -- | modular multiplication mulMod :: Natural -> Natural -> Natural -> Natural -- | modular multiplication for powers of 2, takes a mask instead of a -- wrap-around point mulMod2 :: Natural -> Natural -> Natural -> Natural -- | modular negations negateMod :: Natural -> Natural -> Natural -- | Given a size in bits, return a function that complements the bits in a -- Natural up to that size. complementMod :: Integer -> Natural -> Natural -- | Keep all the bits up to a certain size maskMod :: Integer -> Natural -> Natural bigNatToNat :: BigNat -> Natural subIfGe :: BigNat -> BigNat -> Natural brokenInvariant :: a -- | XException: An exception for uninitialized values -- --
--   >>> show (errorX "undefined" :: Integer, 4 :: Int)
--   "(*** Exception: X: undefined
--   CallStack (from HasCallStack):
--   ...
--   
--   >>> showX (errorX "undefined" :: Integer, 4 :: Int)
--   "(undefined,4)"
--   
module Clash.XException.Internal -- | An exception representing an "uninitialized" value. newtype XException XException :: String -> XException -- | Like shows, but values that normally throw an XException -- are converted to undefined, instead of error'ing out with an -- exception. showsX :: ShowX a => a -> ShowS -- | Use when you want to create a ShowX instance where: -- -- -- -- Can be used like: -- --
--   data T = ...
--   
--   instance Show T where ...
--   
--   instance ShowX T where
--     showsPrecX = showsPrecXWith showsPrec
--   
showsPrecXWith :: (Int -> a -> ShowS) -> Int -> a -> ShowS showXWith :: (a -> ShowS) -> a -> ShowS class GShowX f gshowsPrecX :: GShowX f => ShowType -> Int -> f a -> ShowS isNullary :: GShowX f => f a -> Bool class GDeepErrorX f gDeepErrorX :: (GDeepErrorX f, HasCallStack) => String -> f a class GHasUndefined f gHasUndefined :: GHasUndefined f => f a -> Bool class GEnsureSpine f gEnsureSpine :: GEnsureSpine f => f a -> f a -- | Hidden internal type-class. Adds a generic implementation for the -- "NFData" part of NFDataX class GNFDataX arity f grnfX :: GNFDataX arity f => RnfArgs arity a -> f a -> () data Zero data One data ShowType Rec :: ShowType Tup :: ShowType Pref :: ShowType Inf :: String -> ShowType data RnfArgs arity a [RnfArgs0] :: RnfArgs Zero a [RnfArgs1] :: (a -> ()) -> RnfArgs One a -- | A class of functors that can be fully evaluated, according to -- semantics of NFDataX. class NFDataX1 f -- | liftRnfX should reduce its argument to normal form (that is, -- fully evaluate all sub-components), given an argument to reduce -- a arguments, and then return (). -- -- See rnfX for the generic deriving. liftRnfX :: NFDataX1 f => (a -> ()) -> f a -> () -- | liftRnfX should reduce its argument to normal form (that is, -- fully evaluate all sub-components), given an argument to reduce -- a arguments, and then return (). -- -- See rnfX for the generic deriving. liftRnfX :: (NFDataX1 f, Generic1 f, GNFDataX One (Rep1 f)) => (a -> ()) -> f a -> () showListX__ :: (a -> ShowS) -> [a] -> ShowS genericShowsPrecX :: (Generic a, GShowX (Rep a)) => Int -> a -> ShowS instance Clash.XException.Internal.GDeepErrorX GHC.Generics.V1 instance Clash.XException.Internal.GDeepErrorX GHC.Generics.U1 instance Clash.XException.Internal.GDeepErrorX a => Clash.XException.Internal.GDeepErrorX (GHC.Generics.M1 m d a) instance (Clash.XException.Internal.GDeepErrorX f, Clash.XException.Internal.GDeepErrorX g) => Clash.XException.Internal.GDeepErrorX (f GHC.Generics.:*: g) instance Clash.XException.NFDataX c => Clash.XException.Internal.GDeepErrorX (GHC.Generics.K1 i c) instance Clash.XException.Internal.GDeepErrorX (f GHC.Generics.:+: g) instance Clash.XException.Internal.GHasUndefined GHC.Generics.U1 instance Clash.XException.NFDataX a => Clash.XException.Internal.GHasUndefined (GHC.Generics.K1 i a) instance Clash.XException.Internal.GHasUndefined a => Clash.XException.Internal.GHasUndefined (GHC.Generics.M1 i c a) instance (Clash.XException.Internal.GHasUndefined a, Clash.XException.Internal.GHasUndefined b) => Clash.XException.Internal.GHasUndefined (a GHC.Generics.:*: b) instance (Clash.XException.Internal.GHasUndefined a, Clash.XException.Internal.GHasUndefined b) => Clash.XException.Internal.GHasUndefined (a GHC.Generics.:+: b) instance Clash.XException.Internal.GHasUndefined GHC.Generics.V1 instance Clash.XException.Internal.NFDataX1 f => Clash.XException.Internal.GNFDataX Clash.XException.Internal.One (GHC.Generics.Rec1 f) instance (Clash.XException.Internal.NFDataX1 f, Clash.XException.Internal.GNFDataX Clash.XException.Internal.One g) => Clash.XException.Internal.GNFDataX Clash.XException.Internal.One (f GHC.Generics.:.: g) instance Clash.XException.Internal.GEnsureSpine GHC.Generics.U1 instance Clash.XException.NFDataX a => Clash.XException.Internal.GEnsureSpine (GHC.Generics.K1 i a) instance Clash.XException.Internal.GEnsureSpine a => Clash.XException.Internal.GEnsureSpine (GHC.Generics.M1 i c a) instance (Clash.XException.Internal.GEnsureSpine a, Clash.XException.Internal.GEnsureSpine b) => Clash.XException.Internal.GEnsureSpine (a GHC.Generics.:*: b) instance (Clash.XException.Internal.GEnsureSpine a, Clash.XException.Internal.GEnsureSpine b) => Clash.XException.Internal.GEnsureSpine (a GHC.Generics.:+: b) instance Clash.XException.Internal.GEnsureSpine GHC.Generics.V1 instance Clash.XException.Internal.GNFDataX arity GHC.Generics.V1 instance Clash.XException.Internal.GNFDataX arity GHC.Generics.U1 instance Clash.XException.NFDataX a => Clash.XException.Internal.GNFDataX arity (GHC.Generics.K1 i a) instance Clash.XException.Internal.GNFDataX arity a => Clash.XException.Internal.GNFDataX arity (GHC.Generics.M1 i c a) instance (Clash.XException.Internal.GNFDataX arity a, Clash.XException.Internal.GNFDataX arity b) => Clash.XException.Internal.GNFDataX arity (a GHC.Generics.:*: b) instance (Clash.XException.Internal.GNFDataX arity a, Clash.XException.Internal.GNFDataX arity b) => Clash.XException.Internal.GNFDataX arity (a GHC.Generics.:+: b) instance Clash.XException.Internal.GNFDataX Clash.XException.Internal.One GHC.Generics.Par1 instance Clash.XException.Internal.GShowX GHC.Generics.U1 instance Clash.XException.ShowX c => Clash.XException.Internal.GShowX (GHC.Generics.K1 i c) instance (Clash.XException.Internal.GShowX a, GHC.Generics.Constructor c) => Clash.XException.Internal.GShowX (GHC.Generics.M1 GHC.Generics.C c a) instance (GHC.Generics.Selector s, Clash.XException.Internal.GShowX a) => Clash.XException.Internal.GShowX (GHC.Generics.M1 GHC.Generics.S s a) instance Clash.XException.Internal.GShowX a => Clash.XException.Internal.GShowX (GHC.Generics.M1 GHC.Generics.D d a) instance (Clash.XException.Internal.GShowX a, Clash.XException.Internal.GShowX b) => Clash.XException.Internal.GShowX (a GHC.Generics.:+: b) instance (Clash.XException.Internal.GShowX a, Clash.XException.Internal.GShowX b) => Clash.XException.Internal.GShowX (a GHC.Generics.:*: b) instance Clash.XException.Internal.GShowX GHC.Generics.UChar instance Clash.XException.Internal.GShowX GHC.Generics.UDouble instance Clash.XException.Internal.GShowX GHC.Generics.UFloat instance Clash.XException.Internal.GShowX GHC.Generics.UInt instance Clash.XException.Internal.GShowX GHC.Generics.UWord instance GHC.Show.Show Clash.XException.Internal.XException instance GHC.Exception.Type.Exception Clash.XException.Internal.XException module Clash.XException.TH -- | Creates instances of ShowX for all tuple sizes listed. See -- mkShowXTupleInstance for more information. mkShowXTupleInstances :: [Int] -> Q [Dec] mkNFDataXTupleInstances :: [Int] -> Q [Dec] -- | Creates an instance of the form: -- -- instance (ShowX a0, ShowX a1) => ShowX (a0, a1) -- -- With n number of variables. mkShowXTupleInstance :: Int -> Dec -- | XException: An exception for uninitialized values -- --
--   >>> show (errorX "undefined" :: Integer, 4 :: Int)
--   "(*** Exception: X: undefined
--   CallStack (from HasCallStack):
--   ...
--   
--   >>> showX (errorX "undefined" :: Integer, 4 :: Int)
--   "(undefined,4)"
--   
module Clash.XException -- | An exception representing an "uninitialized" value. newtype XException XException :: String -> XException -- | Like error, but throwing an XException instead of an -- ErrorCall -- -- The ShowX methods print these error-values as -- undefined; instead of error'ing out with an exception. errorX :: HasCallStack => String -> a -- | Evaluate a value to WHNF, returning Left msg if is a -- XException. -- --
--   isX 42                  = Right 42
--   isX (XException msg)    = Left msg
--   isX (3, XException msg) = Right (3, XException msg)
--   isX (3, _|_)            = Right (3, _|_)
--   isX _|_                 = _|_
--   
isX :: a -> Either String a -- | Fully evaluate a value, returning Left msg if it -- throws XException. If you want to determine if a value contains -- undefined parts, use hasUndefined instead. -- --
--   hasX 42                    = Right 42
--   hasX (XException msg)      = Left msg
--   hasX (3, XException msg)   = Left msg
--   hasX (XException msg, _|_) = _|_
--   hasX (_|_, XException msg) = _|_
--   hasX (3, _|_)              = _|_
--   hasX _|_                   = _|_
--   
-- -- If a data structure contains multiple XExceptions, the "first" -- message is picked according to the implementation of rnfX. hasX :: (NFData a, NFDataX a) => a -> Either String a -- | Evaluate a value to WHNF, returning Nothing if it throws -- XException. -- --
--   maybeIsX 42                  = Just 42
--   maybeIsX (XException msg)    = Nothing
--   maybeIsX (3, XException msg) = Just (3, XException msg)
--   maybeIsX (3, _|_)            = Just (3, _|_)
--   maybeIsX _|_                 = _|_
--   
maybeIsX :: a -> Maybe a -- | Fully evaluate a value, returning Nothing if it throws -- XException. Note that non-XException errors take -- precedence over XException ones. -- --
--   maybeHasX 42                    = Just 42
--   maybeHasX (XException msg)      = Nothing
--   maybeHasX (3, XException msg)   = Nothing
--   maybeHasX (XException msg, _|_) = _|_
--   maybeHasX (_|_, XException msg) = _|_
--   maybeHasX (3, _|_)              = _|_
--   maybeHasX _|_                   = _|_
--   
maybeHasX :: (NFData a, NFDataX a) => a -> Maybe a -- | Same as fromJust, but returns a bottom/undefined value that -- other Clash constructs are aware of. fromJustX :: (HasCallStack, NFDataX a) => Maybe a -> a -- | Call to errorX with default string undefined :: HasCallStack => a -- | Convert XException to ErrorCall -- -- This is useful when tracking the source of XException that gets -- eaten up by pack inside of your circuit; since pack -- translates XException into undefined bits. -- -- So for example if you have some large function f: -- --
--   f a b = ... pack a ... pack b ...
--   
-- -- Where it is basically an error if either a or b ever -- throws an XException, and so you want that to be reported the -- moment a or b is used, instead of it being thrown when -- evaluating the result of f, then do: -- --
--   {-# LANGUAGE ViewPatterns #-}
--   f (xToErrorCtx "a is X" -> a) (xToErrorCtx "b is X" -> b) = ...
--   
-- -- Where we pass an extra string, for context, to know which argument -- evaluated to an XException. We can also use BangPatterns to -- report the potential XException being thrown by a or -- b even earlier, i.e. when f is applied: -- --
--   {-# LANGUAGE ViewPatterns, BangPatterns #-}
--   f (xToErrorCtx "a is X" -> !a) (xToErrorCtx "b is X" -> !b) = ...
--   
-- -- NB: Fully synthesizable, so doesn't have to be removed before -- synthesis -- --

Example

-- --
--   >>> :set -XViewPatterns -XDataKinds
--   
--   >>> import Clash.Sized.BitVector
--   
--   >>> import GHC.Stack
--   
--   >>> :{
--   let h, h' :: Bit -> BitVector 8 -> BitVector 8
--       h (xToErrorCtx "a is X" -> a) (xToErrorCtx "b is X" -> b) = slice d7 d0 (pack a ++# b)
--       h' a b = slice d7 d0 (pack a ++# b)
--   :}
--   
-- --
--   >>> h' (errorX "QQ") 3
--   0b0000_0011
--   
--   >>> h (errorX "QQ") 3
--   *** Exception: a is X
--   X: QQ
--   CallStack (from HasCallStack):
--     errorX, called at ...
--   
xToErrorCtx :: String -> a -> a -- | Convert XException to ErrorCall -- -- This is useful when tracking the source of XException that gets -- eaten up by pack inside of your circuit; since pack -- translates XException into undefined bits. -- -- So for example if you have some large function f: -- --
--   f a b = ... pack a ... pack b ...
--   
-- -- Where it is basically an error if either a or b ever -- throws an XException, and so you want that to be reported the -- moment a or b is used, instead of it being thrown when -- evaluating the result of f, then do: -- --
--   {-# LANGUAGE ViewPatterns #-}
--   f (xToError -> a) (xToError -> b) = ...
--   
-- -- Unlike xToErrorCtx, where we have an extra String argument to -- distinguish one call to xToError to the other, xToError -- will use the CallStack mechanism to aid the user in -- distinguishing different call to xToError. We can also use -- BangPatterns to report the potential XException being thrown by -- a or b even earlier, i.e. when f is applied: -- --
--   {-# LANGUAGE ViewPatterns, BangPatterns #-}
--   f (xToError -> !a) (xToError -> !b) = ...
--   
-- -- NB: Fully synthesizable, so doesn't have to be removed before -- synthesis -- --

Example

-- --
--   >>> :set -XViewPatterns -XDataKinds
--   
--   >>> import Clash.Sized.BitVector
--   
--   >>> import GHC.Stack
--   
--   >>> :{
--   let f, g, h, h' :: HasCallStack => Bit -> BitVector 8 -> BitVector 8
--       f = g
--       g = h
--       h (xToError -> a) (xToError -> b) = slice d7 d0 (pack a ++# b)
--       h' a b = slice d7 d0 (pack a ++# b)
--   :}
--   
-- --
--   >>> h' (errorX "QQ") 3
--   0b0000_0011
--   
--   >>> f (errorX "QQ") 3
--   *** Exception: CallStack (from HasCallStack):
--     xToError, called at ...
--     h, called at ...
--     g, called at ...
--     f, called at ...
--   X: QQ
--   CallStack (from HasCallStack):
--     errorX, called at ...
--   
xToError :: HasCallStack => a -> a -- | Like the Show class, but values that normally throw an -- XException are converted to undefined, instead of -- error'ing out with an exception. -- --
--   >>> show (errorX "undefined" :: Integer, 4 :: Int)
--   "(*** Exception: X: undefined
--   CallStack (from HasCallStack):
--   ...
--   
--   >>> showX (errorX "undefined" :: Integer, 4 :: Int)
--   "(undefined,4)"
--   
-- -- Can be derived using Generics: -- --
--   {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
--   
--   import Clash.Prelude
--   import GHC.Generics
--   
--   data T = MkTA Int | MkTB Bool
--     deriving (Show,Generic,ShowX)
--   
class ShowX a -- | Like showsPrec, but values that normally throw an -- XException are converted to undefined, instead of -- error'ing out with an exception. showsPrecX :: ShowX a => Int -> a -> ShowS -- | Like show, but values that normally throw an XException -- are converted to undefined, instead of error'ing out with an -- exception. showX :: ShowX a => a -> String -- | Like showList, but values that normally throw an -- XException are converted to undefined, instead of -- error'ing out with an exception. showListX :: ShowX a => [a] -> ShowS -- | Like showsPrec, but values that normally throw an -- XException are converted to undefined, instead of -- error'ing out with an exception. showsPrecX :: (ShowX a, Generic a, GShowX (Rep a)) => Int -> a -> ShowS -- | Like shows, but values that normally throw an XException -- are converted to undefined, instead of error'ing out with an -- exception. showsX :: ShowX a => a -> ShowS -- | Like print, but values that normally throw an XException -- are converted to undefined, instead of error'ing out with an -- exception printX :: ShowX a => a -> IO () -- | Use when you want to create a ShowX instance where: -- -- -- -- Can be used like: -- --
--   data T = ...
--   
--   instance Show T where ...
--   
--   instance ShowX T where
--     showsPrecX = showsPrecXWith showsPrec
--   
showsPrecXWith :: (Int -> a -> ShowS) -> Int -> a -> ShowS -- | Like seq, however, whereas seq will always do: -- --
--   seq  _|_              b = _|_
--   
-- -- seqX will do: -- --
--   seqX (XException msg) b = b
--   seqX _|_              b = _|_
--   
seqX :: a -> b -> b infixr 0 `seqX` -- | Like seqX, but will also catch ErrorCall exceptions which are -- thrown. This should be used with care. -- --
--   seqErrorX (ErrorCall msg)  b = b
--   seqErrorX (XException msg) b = b
--   seqErrorX _|_              b = _|_
--   
seqErrorX :: a -> b -> b infixr 0 `seqErrorX` -- | a variant of deepseqX that is useful in some circumstances: -- --
--   forceX x = x `deepseqX` x
--   
forceX :: NFDataX a => a -> a -- | deepseqX: fully evaluates the first argument, before returning -- the second. Does not propagate XExceptions. deepseqX :: NFDataX a => a -> b -> b infixr 0 `deepseqX` -- | Reduce to weak head normal form -- -- Equivalent to \x -> seqX x (). -- -- Useful for defining rnfX for types for which NF=WHNF holds. rwhnfX :: a -> () -- | Either seqX or deepseqX depending on the value of the -- cabal flag '-fsuper-strict'. If enabled, defaultSeqX will be -- deepseqX, otherwise seqX. Flag defaults to false -- and thus seqX. defaultSeqX :: NFDataX a => a -> b -> b infixr 0 `defaultSeqX` -- | Like seqX in simulation, but will force its first argument to -- be rendered in HDL. This is useful for components that need to be -- rendered in hardware, but otherwise have no meaning in simulation. An -- example of such a component would be an ILA: a component monitoring an -- internal signal of a design. The output of such a component (typically -- a unit) can be passed as the first argument to hwSeqX to ensure -- the ILA ends up in the generated HDL. -- -- NB: The result of hwSeqX must (indirectly) be used at -- the very top of a design. If it's not, Clash will remove it like it -- does for any other unused circuit parts. -- -- NB: Make sure the blackbox for the component with zero-width -- results uses RenderVoid hwSeqX :: a -> b -> b infixr 0 `hwSeqX` -- | Class that houses functions dealing with undefined values in -- Clash. See deepErrorX and rnfX. class NFDataX a -- | Create a value where all the elements have an errorX, but the -- spine is defined. deepErrorX :: (NFDataX a, HasCallStack) => String -> a -- | Create a value where all the elements have an errorX, but the -- spine is defined. deepErrorX :: (NFDataX a, HasCallStack, Generic a, GDeepErrorX (Rep a)) => String -> a -- | Determines whether any of parts of a given construct contain undefined -- parts. Note that a negative answer does not mean its bit -- representation is fully defined. For example: -- --
--   >>> m = Nothing :: Maybe Bool
--   
--   >>> hasUndefined m
--   False
--   
--   >>> pack m
--   0b0.
--   
--   >>> hasUndefined (pack m)
--   True
--   
hasUndefined :: NFDataX a => a -> Bool -- | Determines whether any of parts of a given construct contain undefined -- parts. Note that a negative answer does not mean its bit -- representation is fully defined. For example: -- --
--   >>> m = Nothing :: Maybe Bool
--   
--   >>> hasUndefined m
--   False
--   
--   >>> pack m
--   0b0.
--   
--   >>> hasUndefined (pack m)
--   True
--   
hasUndefined :: (NFDataX a, Generic a, GHasUndefined (Rep a)) => a -> Bool -- | Create a value where at the very least the spine is defined. For -- example: -- --
--   >>> spined = ensureSpine (errorX "?" :: (Int, Int))
--   
--   >>> case spined of (_, _) -> 'a'
--   'a'
--   
--   >>> fmap (const 'b') (ensureSpine undefined :: Vec 3 Int)
--   'b' :> 'b' :> 'b' :> Nil
--   
--   >>> fmap (const 'c') (ensureSpine undefined :: RTree 2 Int)
--   <<'c','c'>,<'c','c'>>
--   
-- -- For users familiar with lazyV: this is the generalized version -- of it. ensureSpine :: NFDataX a => a -> a -- | Create a value where at the very least the spine is defined. For -- example: -- --
--   >>> spined = ensureSpine (errorX "?" :: (Int, Int))
--   
--   >>> case spined of (_, _) -> 'a'
--   'a'
--   
--   >>> fmap (const 'b') (ensureSpine undefined :: Vec 3 Int)
--   'b' :> 'b' :> 'b' :> Nil
--   
--   >>> fmap (const 'c') (ensureSpine undefined :: RTree 2 Int)
--   <<'c','c'>,<'c','c'>>
--   
-- -- For users familiar with lazyV: this is the generalized version -- of it. ensureSpine :: (NFDataX a, Generic a, GEnsureSpine (Rep a)) => a -> a -- | Evaluate a value to NF. As opposed to NFDatas rnf, it -- does not bubble up XExceptions. rnfX :: NFDataX a => a -> () -- | Evaluate a value to NF. As opposed to NFDatas rnf, it -- does not bubble up XExceptions. rnfX :: (NFDataX a, Generic a, GNFDataX Zero (Rep a)) => a -> () instance (Clash.XException.NFDataX a0, Clash.XException.NFDataX a1) => Clash.XException.NFDataX (a0, a1) instance (Clash.XException.NFDataX a0, Clash.XException.NFDataX a1, Clash.XException.NFDataX a2) => Clash.XException.NFDataX (a0, a1, a2) instance (Clash.XException.ShowX a0, Clash.XException.ShowX a1) => Clash.XException.ShowX (a0, a1) instance (Clash.XException.ShowX a0, Clash.XException.ShowX a1, Clash.XException.ShowX a2) => Clash.XException.ShowX (a0, a1, a2) instance Clash.XException.NFDataX () instance Clash.XException.NFDataX b => Clash.XException.NFDataX (a -> b) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Ord.Down a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.List.Infinite.Internal.Infinite a) instance Clash.XException.NFDataX GHC.Types.Bool instance Clash.XException.NFDataX GHC.Types.Ordering instance Clash.XException.NFDataX a => Clash.XException.NFDataX [a] instance Clash.XException.NFDataX a => Clash.XException.NFDataX (GHC.Base.NonEmpty a) instance (Clash.XException.NFDataX a, Clash.XException.NFDataX b) => Clash.XException.NFDataX (Data.Either.Either a b) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (GHC.Maybe.Maybe a) instance Clash.XException.NFDataX (Data.Proxy.Proxy a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Functor.Identity.Identity a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Functor.Const.Const a b) instance (Clash.XException.NFDataX (f a), Clash.XException.NFDataX (g a)) => Clash.XException.NFDataX (Data.Functor.Product.Product f g a) instance (Clash.XException.NFDataX (f a), Clash.XException.NFDataX (g a)) => Clash.XException.NFDataX (Data.Functor.Sum.Sum f g a) instance Clash.XException.NFDataX (f (g a)) => Clash.XException.NFDataX (Data.Functor.Compose.Compose f g a) instance Clash.XException.NFDataX GHC.Types.Char instance Clash.XException.NFDataX GHC.Types.Double instance Clash.XException.NFDataX GHC.Types.Float instance Clash.XException.NFDataX GHC.Types.Int instance Clash.XException.NFDataX GHC.Int.Int8 instance Clash.XException.NFDataX GHC.Int.Int16 instance Clash.XException.NFDataX GHC.Int.Int32 instance Clash.XException.NFDataX GHC.Int.Int64 instance Clash.XException.NFDataX GHC.Integer.Type.Integer instance Clash.XException.NFDataX GHC.Natural.Natural instance Clash.XException.NFDataX GHC.Types.Word instance Clash.XException.NFDataX GHC.Word.Word8 instance Clash.XException.NFDataX GHC.Word.Word16 instance Clash.XException.NFDataX GHC.Word.Word32 instance Clash.XException.NFDataX GHC.Word.Word64 instance Clash.XException.NFDataX Foreign.C.Types.CUShort instance Clash.XException.NFDataX Numeric.Half.Internal.Half instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Sequence.Internal.Seq a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (GHC.Real.Ratio a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Complex.Complex a) instance (Clash.XException.NFDataX a, Clash.XException.NFDataX b) => Clash.XException.NFDataX (Data.Semigroup.Arg a b) instance Clash.XException.NFDataX Data.Semigroup.Internal.All instance Clash.XException.NFDataX Data.Semigroup.Internal.Any instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Internal.Dual a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Internal.Endo a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.First a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Last a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Max a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Min a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Internal.Product a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Internal.Sum a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Monoid.First a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Monoid.Last a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Data.Semigroup.Option a) instance Clash.XException.ShowX () instance Clash.XException.ShowX (Data.Proxy.Proxy a) instance Clash.XException.ShowX a => Clash.XException.ShowX (Data.Functor.Identity.Identity a) instance Clash.XException.ShowX a => Clash.XException.ShowX (Data.Functor.Const.Const a b) instance (Clash.XException.ShowX (f a), Clash.XException.ShowX (g a)) => Clash.XException.ShowX (Data.Functor.Product.Product f g a) instance (Clash.XException.ShowX (f a), Clash.XException.ShowX (g a)) => Clash.XException.ShowX (Data.Functor.Sum.Sum f g a) instance Clash.XException.ShowX (f (g a)) => Clash.XException.ShowX (Data.Functor.Compose.Compose f g a) instance Clash.XException.ShowX a => Clash.XException.ShowX [a] instance Clash.XException.ShowX GHC.Types.Char instance Clash.XException.ShowX GHC.Types.Bool instance Clash.XException.ShowX GHC.Types.Double instance Clash.XException.ShowX a => Clash.XException.ShowX (Data.Ord.Down a) instance (Clash.XException.ShowX a, Clash.XException.ShowX b) => Clash.XException.ShowX (Data.Either.Either a b) instance Clash.XException.ShowX GHC.Types.Float instance Clash.XException.ShowX GHC.Types.Int instance Clash.XException.ShowX GHC.Int.Int8 instance Clash.XException.ShowX GHC.Int.Int16 instance Clash.XException.ShowX GHC.Int.Int32 instance Clash.XException.ShowX GHC.Int.Int64 instance Clash.XException.ShowX GHC.Integer.Type.Integer instance Clash.XException.ShowX GHC.Natural.Natural instance Clash.XException.ShowX GHC.Types.Ordering instance Clash.XException.ShowX a => Clash.XException.ShowX (Data.Sequence.Internal.Seq a) instance Clash.XException.ShowX GHC.Types.Word instance Clash.XException.ShowX GHC.Word.Word8 instance Clash.XException.ShowX GHC.Word.Word16 instance Clash.XException.ShowX GHC.Word.Word32 instance Clash.XException.ShowX GHC.Word.Word64 instance Clash.XException.ShowX a => Clash.XException.ShowX (GHC.Maybe.Maybe a) instance Clash.XException.ShowX a => Clash.XException.ShowX (GHC.Real.Ratio a) instance Clash.XException.ShowX a => Clash.XException.ShowX (Data.Complex.Complex a) instance Clash.XException.ShowX GHC.Base.String -- | Helpers to make XException explicit in the type system. Using -- these helpers can help programmers account for XExceptions -- properly in blackbox models or tests. Note that none of these -- operations can be translated to HDL. module Clash.XException.MaybeX -- | Structure helping programmers to deal with XException values. -- For safety reasons it can't be constructed directly, but should be -- constructed using either pure or toMaybeX. After -- construction, it can be deconstructed using either IsX or -- IsDefined. data MaybeX a -- | Upon construction, a evaluated to XException pattern IsX :: forall a. String -> MaybeX a -- | Upon construction, a evaluated to a non-bottom WHNF pattern IsDefined :: forall a. a -> MaybeX a -- | Construct a MaybeX value. If a evaluates to -- XException, this function will return IsX. Otherwise, it -- will return IsDefined. toMaybeX :: a -> MaybeX a -- | Construct a MaybeX value. If hasX evaluates to -- Left, this function will return IsX. Otherwise, it will -- return IsDefined. hasXToMaybeX :: (NFDataX a, NFData a) => a -> MaybeX a -- | Deconstruct MaybeX into an a - the opposite of -- toMaybeX. Be careful when using this function, because it might -- return an XException if the argument was IsX. fromMaybeX :: MaybeX a -> a -- | Implements && accounting for X -- -- TODO: table andX :: MaybeX Bool -> MaybeX Bool -> MaybeX Bool infixr 3 `andX` -- | Implements || accounting for X -- -- TODO: table orX :: MaybeX Bool -> MaybeX Bool -> MaybeX Bool infixr 2 `orX` -- | Map functions over both constructors. maybeX :: (String -> b) -> (a -> b) -> MaybeX a -> b instance GHC.Show.Show a => GHC.Show.Show (Clash.XException.MaybeX.MaybeX a) instance GHC.Base.Functor Clash.XException.MaybeX.MaybeX instance GHC.Base.Applicative Clash.XException.MaybeX.MaybeX module Clash.Promoted.Nat -- | Singleton value for a type-level natural number n -- -- data SNat (n :: Nat) [SNat] :: KnownNat n => SNat n -- | Create an SNat n from a proxy for n snatProxy :: KnownNat n => proxy n -> SNat n -- | Supply a function with a singleton natural n according to the -- context withSNat :: KnownNat n => (SNat n -> a) -> a -- | Reify the type-level Nat n to it's term-level -- Integer representation. snatToInteger :: SNat n -> Integer -- | Reify the type-level Nat n to it's term-level -- Natural. snatToNatural :: SNat n -> Natural -- | Reify the type-level Nat n to it's term-level -- Number. snatToNum :: forall a n. Num a => SNat n -> a -- | Same as snatToInteger and natVal, but doesn't take term -- arguments. Example usage: -- --
--   >>> natToInteger @5
--   5
--   
natToInteger :: forall n. KnownNat n => Integer -- | Same as snatToNatural and natVal, but doesn't take term -- arguments. Example usage: -- --
--   >>> natToNatural @5
--   5
--   
natToNatural :: forall n. KnownNat n => Natural -- | Same as snatToNum, but doesn't take term arguments. Example -- usage: -- --
--   >>> natToNum @5 @Int
--   5
--   
natToNum :: forall n a. (Num a, KnownNat n) => a -- | Add two singleton natural numbers addSNat :: SNat a -> SNat b -> SNat (a + b) infixl 6 `addSNat` -- | Multiply two singleton natural numbers mulSNat :: SNat a -> SNat b -> SNat (a * b) infixl 7 `mulSNat` -- | Power of two singleton natural numbers powSNat :: SNat a -> SNat b -> SNat (a ^ b) infixr 8 `powSNat` minSNat :: SNat a -> SNat b -> SNat (Min a b) maxSNat :: SNat a -> SNat b -> SNat (Max a b) -- | Successor of a singleton natural number succSNat :: SNat a -> SNat (a + 1) -- | Subtract two singleton natural numbers subSNat :: SNat (a + b) -> SNat b -> SNat a infixl 6 `subSNat` -- | Division of two singleton natural numbers divSNat :: 1 <= b => SNat a -> SNat b -> SNat (Div a b) infixl 7 `divSNat` -- | Modulo of two singleton natural numbers modSNat :: 1 <= b => SNat a -> SNat b -> SNat (Mod a b) infixl 7 `modSNat` -- | Floor of the logarithm of a natural number flogBaseSNat :: (2 <= base, 1 <= x) => SNat base -> SNat x -> SNat (FLog base x) -- | Ceiling of the logarithm of a natural number clogBaseSNat :: (2 <= base, 1 <= x) => SNat base -> SNat x -> SNat (CLog base x) -- | Exact integer logarithm of a natural number -- -- NB: Only works when the argument is a power of the base logBaseSNat :: FLog base x ~ CLog base x => SNat base -> SNat x -> SNat (Log base x) -- | Predecessor of a singleton natural number predSNat :: SNat (a + 1) -> SNat a -- | Power of two of a singleton natural number pow2SNat :: SNat a -> SNat (2 ^ a) -- | Ordering relation between two Nats data SNatLE a b [SNatLE] :: forall a b. a <= b => SNatLE a b [SNatGT] :: forall a b. (b + 1) <= a => SNatLE a b -- | Get an ordering relation between two SNats compareSNat :: forall a b. SNat a -> SNat b -> SNatLE a b -- | Unary representation of a type-level natural -- -- NB: Not synthesizable data UNat :: Nat -> Type [UZero] :: UNat 0 [USucc] :: UNat n -> UNat (n + 1) -- | Convert a singleton natural number to its unary representation -- -- NB: Not synthesizable toUNat :: forall n. SNat n -> UNat n -- | Convert a unary-encoded natural number to its singleton representation -- -- NB: Not synthesizable fromUNat :: UNat n -> SNat n -- | Add two unary-encoded natural numbers -- -- NB: Not synthesizable addUNat :: UNat n -> UNat m -> UNat (n + m) -- | Multiply two unary-encoded natural numbers -- -- NB: Not synthesizable mulUNat :: UNat n -> UNat m -> UNat (n * m) -- | Power of two unary-encoded natural numbers -- -- NB: Not synthesizable powUNat :: UNat n -> UNat m -> UNat (n ^ m) -- | Predecessor of a unary-encoded natural number -- -- NB: Not synthesizable predUNat :: UNat (n + 1) -> UNat n -- | Subtract two unary-encoded natural numbers -- -- NB: Not synthesizable subUNat :: UNat (m + n) -> UNat n -> UNat m -- | Base-2 encoded natural number -- -- -- --
--   >>> B0 (B1 (B1 BT))
--   b6
--   
-- --

Constructors

-- -- -- -- data BNat :: Nat -> Type [BT] :: BNat 0 [B0] :: BNat n -> BNat (2 * n) [B1] :: BNat n -> BNat ((2 * n) + 1) -- | Convert a singleton natural number to its base-2 representation -- -- NB: Not synthesizable toBNat :: SNat n -> BNat n -- | Convert a base-2 encoded natural number to its singleton -- representation -- -- NB: Not synthesizable fromBNat :: BNat n -> SNat n -- | Show a base-2 encoded natural as a binary literal -- -- NB: The LSB is shown as the right-most bit -- --
--   >>> d789
--   d789
--   
--   >>> toBNat d789
--   b789
--   
--   >>> showBNat (toBNat d789)
--   "0b1100010101"
--   
--   >>> 0b1100010101 :: Integer
--   789
--   
showBNat :: BNat n -> String -- | Successor of a base-2 encoded natural number -- -- NB: Not synthesizable succBNat :: BNat n -> BNat (n + 1) -- | Add two base-2 encoded natural numbers -- -- NB: Not synthesizable addBNat :: BNat n -> BNat m -> BNat (n + m) -- | Multiply two base-2 encoded natural numbers -- -- NB: Not synthesizable mulBNat :: BNat n -> BNat m -> BNat (n * m) -- | Power of two base-2 encoded natural numbers -- -- NB: Not synthesizable powBNat :: BNat n -> BNat m -> BNat (n ^ m) -- | Predecessor of a base-2 encoded natural number -- -- NB: Not synthesizable predBNat :: 1 <= n => BNat n -> BNat (n - 1) -- | Divide a base-2 encoded natural number by 2 -- -- NB: Not synthesizable div2BNat :: BNat (2 * n) -> BNat n -- | Subtract 1 and divide a base-2 encoded natural number by 2 -- -- NB: Not synthesizable div2Sub1BNat :: BNat ((2 * n) + 1) -> BNat n -- | Get the log2 of a base-2 encoded natural number -- -- NB: Not synthesizable log2BNat :: BNat (2 ^ n) -> BNat n -- | Strip non-contributing zero's from a base-2 encoded natural number -- --
--   >>> B1 (B0 (B0 (B0 BT)))
--   b1
--   
--   >>> showBNat (B1 (B0 (B0 (B0 BT))))
--   "0b0001"
--   
--   >>> showBNat (stripZeros (B1 (B0 (B0 (B0 BT)))))
--   "0b1"
--   
--   >>> stripZeros (B1 (B0 (B0 (B0 BT))))
--   b1
--   
-- -- NB: Not synthesizable stripZeros :: BNat n -> BNat n -- | Change a function that has an argument with an (n ~ (k + m)) -- constraint to a function with an argument that has an (k <= -- n) constraint. -- --

Examples

-- -- Example 1 -- --
--   f :: Index (n+1) -> Index (n + 1) -> Bool
--   
--   g :: forall n. (1 <= n) => Index n -> Index n -> Bool
--   g a b = leToPlus @1 @n (f a b)
--   
-- -- Example 2 -- --
--   head :: Vec (n + 1) a -> a
--   
--   head' :: forall n a. (1 <= n) => Vec n a -> a
--   head' = leToPlus @1 @n head
--   
leToPlus :: forall (k :: Nat) (n :: Nat) r. k <= n => (forall m. n ~ (k + m) => r) -> r -- | Same as leToPlus with added KnownNat constraints leToPlusKN :: forall (k :: Nat) (n :: Nat) r. (k <= n, KnownNat k, KnownNat n) => (forall m. (n ~ (k + m), KnownNat m) => r) -> r instance GHC.Show.Show (Clash.Promoted.Nat.SNatLE a b) instance GHC.TypeNats.KnownNat n => GHC.Show.Show (Clash.Promoted.Nat.BNat n) instance GHC.TypeNats.KnownNat n => Clash.XException.ShowX (Clash.Promoted.Nat.BNat n) instance GHC.TypeNats.KnownNat n => GHC.Show.Show (Clash.Promoted.Nat.UNat n) instance GHC.TypeNats.KnownNat n => Clash.XException.ShowX (Clash.Promoted.Nat.UNat n) instance Language.Haskell.TH.Syntax.Lift (Clash.Promoted.Nat.SNat n) instance GHC.Show.Show (Clash.Promoted.Nat.SNat n) instance Clash.XException.ShowX (Clash.Promoted.Nat.SNat n) module Clash.Sized.Internal.BitVector -- | A single bit -- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. data Bit -- | The constructor, Bit, and the fields, unsafeMask# and -- unsafeToInteger#, are not synthesizable. Bit :: {-# UNPACK #-} !Word -> {-# UNPACK #-} !Word -> Bit [unsafeMask#] :: Bit -> {-# UNPACK #-} !Word [unsafeToInteger#] :: Bit -> {-# UNPACK #-} !Word -- | logic '1' high :: Bit -- | logic '0' low :: Bit eq## :: Bit -> Bit -> Bool neq## :: Bit -> Bit -> Bool lt## :: Bit -> Bit -> Bool ge## :: Bit -> Bit -> Bool gt## :: Bit -> Bit -> Bool le## :: Bit -> Bit -> Bool toEnum## :: Int -> Bit fromInteger## :: Word# -> Integer -> Bit and## :: Bit -> Bit -> Bit or## :: Bit -> Bit -> Bit xor## :: Bit -> Bit -> Bit complement## :: Bit -> Bit pack# :: Bit -> BitVector 1 unpack# :: BitVector 1 -> Bit -- | A vector of bits -- -- -- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. -- -- BitVector has the type role -- --
--   >>> :i BitVector
--   type role BitVector nominal
--   ...
--   
-- -- as it is not safe to coerce between different sizes of BitVector. To -- change the size, use the functions in the Resize class. data BitVector (n :: Nat) -- | The constructor, BV, and the fields, unsafeMask and -- unsafeToNatural, are not synthesizable. BV :: !Natural -> !Natural -> BitVector (n :: Nat) [unsafeMask] :: BitVector (n :: Nat) -> !Natural [unsafeToNatural] :: BitVector (n :: Nat) -> !Natural size# :: KnownNat n => BitVector n -> Int maxIndex# :: KnownNat n => BitVector n -> Int -- | Create a binary literal -- --
--   >>> $(bLit "1001")
--   0b1001
--   
-- -- NB: You can also just write: -- --
--   >>> 0b1001 :: BitVector 4
--   0b1001
--   
-- -- The advantage of bLit is that you can use computations to -- create the string literal: -- --
--   >>> import qualified Data.List as List
--   
--   >>> $(bLit (List.replicate 4 '1'))
--   0b1111
--   
-- -- Also bLit can handle don't care bits: -- --
--   >>> $(bLit "1.0.")
--   0b1.0.
--   
-- -- NB: From Clash 1.6 an onwards bLit will deduce the size -- of the BitVector from the given string and annotate the splice it -- produces accordingly. bLit :: String -> ExpQ -- | Create a hexadecimal literal -- --
--   >>> $(hLit "dead")
--   0b1101_1110_1010_1101
--   
-- -- Don't care digits set 4 bits: -- --
--   >>> $(hLit "de..")
--   0b1101_1110_...._....
--   
hLit :: String -> ExpQ -- | Create an octal literal -- --
--   >>> $(oLit "5234")
--   0b1010_1001_1100
--   
-- -- Don't care digits set 3 bits: -- --
--   >>> $(oLit "52..")
--   0b1010_10.._....
--   
oLit :: String -> ExpQ -- | Create a BitVector with all its bits undefined undefined# :: forall n. KnownNat n => BitVector n -- | Concatenate two BitVectors (++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) reduceAnd# :: KnownNat n => BitVector n -> Bit reduceOr# :: KnownNat n => BitVector n -> Bit reduceXor# :: KnownNat n => BitVector n -> Bit index# :: KnownNat n => BitVector n -> Int -> Bit replaceBit# :: KnownNat n => BitVector n -> Int -> Bit -> BitVector n setSlice# :: forall m i n. SNat ((m + 1) + i) -> BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) -> BitVector ((m + 1) + i) slice# :: BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) split# :: forall n m. KnownNat n => BitVector (m + n) -> (BitVector m, BitVector n) -- | MSB msb# :: forall n. KnownNat n => BitVector n -> Bit -- | LSB lsb# :: BitVector n -> Bit eq# :: KnownNat n => BitVector n -> BitVector n -> Bool neq# :: KnownNat n => BitVector n -> BitVector n -> Bool -- | Check if one BitVector is similar to another, interpreting undefined -- bits in the second argument as being "don't care" bits. This is a more -- lenient version of (==), similar to std_match in VHDL -- or casez in Verilog. -- --
--   >>> let expected = $(bLit "1.")
--   
--   >>> let checked  = $(bLit "11")
--   
-- --
--   >>> checked  `isLike#` expected
--   True
--   
--   >>> expected `isLike#` checked
--   False
--   
-- -- NB: Not synthesizable isLike# :: forall n. KnownNat n => BitVector n -> BitVector n -> Bool lt# :: KnownNat n => BitVector n -> BitVector n -> Bool ge# :: KnownNat n => BitVector n -> BitVector n -> Bool gt# :: KnownNat n => BitVector n -> BitVector n -> Bool le# :: KnownNat n => BitVector n -> BitVector n -> Bool toEnum# :: forall n. KnownNat n => Int -> BitVector n fromEnum# :: forall n. KnownNat n => BitVector n -> Int enumFrom# :: forall n. KnownNat n => BitVector n -> [BitVector n] enumFromThen# :: forall n. KnownNat n => BitVector n -> BitVector n -> [BitVector n] enumFromTo# :: forall n. KnownNat n => BitVector n -> BitVector n -> [BitVector n] enumFromThenTo# :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n -> [BitVector n] minBound# :: BitVector n maxBound# :: forall n. KnownNat n => BitVector n (+#) :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n (-#) :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n (*#) :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n negate# :: forall n. KnownNat n => BitVector n -> BitVector n fromInteger# :: KnownNat n => Natural -> Integer -> BitVector n plus# :: (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (Max m n + 1) minus# :: forall m n. (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (Max m n + 1) times# :: (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (m + n) quot# :: KnownNat n => BitVector n -> BitVector n -> BitVector n rem# :: KnownNat n => BitVector n -> BitVector n -> BitVector n toInteger# :: KnownNat n => BitVector n -> Integer and# :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n or# :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n xor# :: forall n. KnownNat n => BitVector n -> BitVector n -> BitVector n complement# :: forall n. KnownNat n => BitVector n -> BitVector n shiftL# :: forall n. KnownNat n => BitVector n -> Int -> BitVector n shiftR# :: forall n. KnownNat n => BitVector n -> Int -> BitVector n rotateL# :: forall n. KnownNat n => BitVector n -> Int -> BitVector n rotateR# :: forall n. KnownNat n => BitVector n -> Int -> BitVector n popCountBV :: forall n. KnownNat n => BitVector (n + 1) -> Index (n + 2) countLeadingZerosBV :: KnownNat n => BitVector n -> Index (n + 1) countTrailingZerosBV :: KnownNat n => BitVector n -> Index (n + 1) truncateB# :: forall a b. KnownNat a => BitVector (a + b) -> BitVector a -- | shrink for sized unsigned types shrinkSizedUnsigned :: (KnownNat n, Integral (p n)) => p n -> [p n] undefError :: KnownNat n => String -> [BitVector n] -> a -- | Implement BitVector undefinedness checking for unpack functions checkUnpackUndef :: (KnownNat n, Typeable a) => (BitVector n -> a) -> BitVector n -> a -- | Template Haskell macro for generating a pattern matching on some bits -- of a value. -- -- This macro compiles to an efficient view pattern that matches the bits -- of a given value against the bits specified in the pattern. The -- scrutinee can be any type that is an instance of the Num, -- Bits and Eq typeclasses. -- -- The bit pattern is specified by a string which contains: -- -- -- -- The following example matches a byte against two bit patterns where -- some bits are relevant and others are not while binding two variables -- aa and bb: -- --
--   decode :: Unsigned 8 -> Maybe Bool
--   decode $(bitPattern "00.._.110") = Just True
--   decode $(bitPattern "10.._0001") = Just False
--   decode $(bitPattern "aa.._b0b1") = Just (aa + bb > 1)
--   decode _ = Nothing
--   
bitPattern :: String -> Q Pat xToBV :: KnownNat n => BitVector n -> BitVector n instance GHC.Generics.Generic (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Data.Data.Data (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.Generics.Generic Clash.Sized.Internal.BitVector.Bit instance Data.Data.Data Clash.Sized.Internal.BitVector.Bit instance Control.DeepSeq.NFData Clash.Sized.Internal.BitVector.Bit instance GHC.Show.Show Clash.Sized.Internal.BitVector.Bit instance Clash.XException.ShowX Clash.Sized.Internal.BitVector.Bit instance Clash.XException.NFDataX Clash.Sized.Internal.BitVector.Bit instance Language.Haskell.TH.Syntax.Lift Clash.Sized.Internal.BitVector.Bit instance GHC.Classes.Eq Clash.Sized.Internal.BitVector.Bit instance GHC.Classes.Ord Clash.Sized.Internal.BitVector.Bit instance GHC.Enum.Enum Clash.Sized.Internal.BitVector.Bit instance GHC.Enum.Bounded Clash.Sized.Internal.BitVector.Bit instance Data.Default.Class.Default Clash.Sized.Internal.BitVector.Bit instance GHC.Num.Num Clash.Sized.Internal.BitVector.Bit instance GHC.Real.Real Clash.Sized.Internal.BitVector.Bit instance GHC.Real.Integral Clash.Sized.Internal.BitVector.Bit instance Data.Bits.Bits Clash.Sized.Internal.BitVector.Bit instance Data.Bits.FiniteBits Clash.Sized.Internal.BitVector.Bit instance Control.DeepSeq.NFData (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Show.Show (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Clash.XException.ShowX (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Clash.XException.NFDataX (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Classes.Eq (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Classes.Ord (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Enum (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Bounded (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Num.Num (Clash.Sized.Internal.BitVector.BitVector n) instance (GHC.TypeNats.KnownNat m, GHC.TypeNats.KnownNat n) => Clash.Class.Num.ExtendingNum (Clash.Sized.Internal.BitVector.BitVector m) (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Real.Real (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => GHC.Real.Integral (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Data.Bits.Bits (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Data.Bits.FiniteBits (Clash.Sized.Internal.BitVector.BitVector n) instance Data.Default.Class.Default (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Class.Resize.Resize Clash.Sized.Internal.BitVector.BitVector instance GHC.TypeNats.KnownNat n => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Clash.Class.Num.SaturatingNum (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Internal.BitVector.BitVector n) instance GHC.TypeNats.KnownNat n => Control.Lens.At.Ixed (Clash.Sized.Internal.BitVector.BitVector n) module Clash.Sized.BitVector -- | A single bit -- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. data Bit -- | logic '1' high :: Bit -- | logic '0' low :: Bit -- | A vector of bits -- -- -- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. -- -- BitVector has the type role -- --
--   >>> :i BitVector
--   type role BitVector nominal
--   ...
--   
-- -- as it is not safe to coerce between different sizes of BitVector. To -- change the size, use the functions in the Resize class. data BitVector (n :: Nat) size# :: KnownNat n => BitVector n -> Int maxIndex# :: KnownNat n => BitVector n -> Int -- | Create a binary literal -- --
--   >>> $(bLit "1001")
--   0b1001
--   
-- -- NB: You can also just write: -- --
--   >>> 0b1001 :: BitVector 4
--   0b1001
--   
-- -- The advantage of bLit is that you can use computations to -- create the string literal: -- --
--   >>> import qualified Data.List as List
--   
--   >>> $(bLit (List.replicate 4 '1'))
--   0b1111
--   
-- -- Also bLit can handle don't care bits: -- --
--   >>> $(bLit "1.0.")
--   0b1.0.
--   
-- -- NB: From Clash 1.6 an onwards bLit will deduce the size -- of the BitVector from the given string and annotate the splice it -- produces accordingly. bLit :: String -> ExpQ -- | Create a hexadecimal literal -- --
--   >>> $(hLit "dead")
--   0b1101_1110_1010_1101
--   
-- -- Don't care digits set 4 bits: -- --
--   >>> $(hLit "de..")
--   0b1101_1110_...._....
--   
hLit :: String -> ExpQ -- | Create an octal literal -- --
--   >>> $(oLit "5234")
--   0b1010_1001_1100
--   
-- -- Don't care digits set 3 bits: -- --
--   >>> $(oLit "52..")
--   0b1010_10.._....
--   
oLit :: String -> ExpQ -- | Concatenate two BitVectors (++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) -- | Shift in a bit from the MSB side of a BitVector. Equal to right -- shifting the BitVector by one and replacing the MSB with the -- bit to be shifted in. -- --
--   >>> 1 +>>. 0b1111_0000 :: BitVector 8
--   0b1111_1000
--   
--   >>> 0 +>>. 0b1111_0000 :: BitVector 8
--   0b0111_1000
--   
(+>>.) :: forall n. KnownNat n => Bit -> BitVector n -> BitVector n infixr 4 +>>. -- | Shift in a bit from the LSB side of a BitVector. Equal to left -- shifting the BitVector by one and replacing the LSB with the -- bit to be shifted in. -- --
--   >>> 0b1111_0000 .<<+ 0 :: BitVector 8
--   0b1110_0000
--   
--   >>> 0b1111_0000 .<<+ 1 :: BitVector 8
--   0b1110_0001
--   
(.<<+) :: forall n. KnownNat n => BitVector n -> Bit -> BitVector n infixr 4 .<<+ -- | Template Haskell macro for generating a pattern matching on some bits -- of a value. -- -- This macro compiles to an efficient view pattern that matches the bits -- of a given value against the bits specified in the pattern. The -- scrutinee can be any type that is an instance of the Num, -- Bits and Eq typeclasses. -- -- The bit pattern is specified by a string which contains: -- -- -- -- The following example matches a byte against two bit patterns where -- some bits are relevant and others are not while binding two variables -- aa and bb: -- --
--   decode :: Unsigned 8 -> Maybe Bool
--   decode $(bitPattern "00.._.110") = Just True
--   decode $(bitPattern "10.._0001") = Just False
--   decode $(bitPattern "aa.._b0b1") = Just (aa + bb > 1)
--   decode _ = Nothing
--   
bitPattern :: String -> Q Pat module Clash.Signal.Internal -- | Clash has synchronous Signals 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 Signals 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. -- -- -- -- Signals have the type role -- --
--   >>> :i Signal
--   type role Signal nominal representational
--   ...
--   
-- -- as it is safe to coerce the underlying value of a signal, but not safe -- to coerce a signal between different synthesis domains. -- -- See the module documentation of Clash.Signal for more -- information about domains. data Signal (dom :: Domain) a -- | The constructor, (:-), is not synthesizable. (:-) :: a -> Signal dom a -> Signal (dom :: Domain) a infixr 5 :- head# :: Signal dom a -> a tail# :: Signal dom a -> Signal dom a type Domain = Symbol -- | We either get evidence that this function was instantiated with the -- same domains, or Nothing. sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB) -- | A KnownDomain constraint indicates that a circuit's behavior -- depends on some properties of a domain. See DomainConfiguration -- for more information. class (KnownSymbol dom, KnownNat (DomainPeriod dom)) => KnownDomain (dom :: Domain) where { type family KnownConf dom :: DomainConfiguration; } -- | Returns SDomainConfiguration corresponding to an instance's -- DomainConfiguration. -- -- Example usage: -- --
--   >>> knownDomain @System
--   SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
--   
knownDomain :: KnownDomain dom => SDomainConfiguration dom (KnownConf dom) type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) -- | Version of knownDomain that takes a SSymbol. For -- example: -- --
--   >>> knownDomainByName (SSymbol @"System")
--   SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
--   
knownDomainByName :: forall dom. KnownDomain dom => SSymbol dom -> SDomainConfiguration dom (KnownConf dom) -- | Determines clock edge memory elements are sensitive to. Not yet -- implemented. data ActiveEdge -- | Elements are sensitive to the rising edge (low-to-high) of the clock. Rising :: ActiveEdge -- | Elements are sensitive to the falling edge (high-to-low) of the clock. Falling :: ActiveEdge -- | Singleton version of ActiveEdge data SActiveEdge (edge :: ActiveEdge) [SRising] :: SActiveEdge 'Rising [SFalling] :: SActiveEdge 'Falling data InitBehavior -- | Power up value of memory elements is unknown. Unknown :: InitBehavior -- | If applicable, power up value of a memory element is defined. Applies -- to registers for example, but not to blockRam. Defined :: InitBehavior data SInitBehavior (init :: InitBehavior) [SUnknown] :: SInitBehavior 'Unknown [SDefined] :: SInitBehavior 'Defined data ResetKind -- | Elements respond asynchronously to changes in their reset -- input. This means that they do not wait for the next active -- clock edge, but respond immediately instead. Common on Intel FPGA -- platforms. Asynchronous :: ResetKind -- | Elements respond synchronously to changes in their reset input. -- This means that changes in their reset input won't take effect until -- the next active clock edge. Common on Xilinx FPGA platforms. Synchronous :: ResetKind -- | Singleton version of ResetKind data SResetKind (resetKind :: ResetKind) [SAsynchronous] :: SResetKind 'Asynchronous [SSynchronous] :: SResetKind 'Synchronous -- | Determines the value for which a reset line is considered "active" data ResetPolarity -- | Reset is considered active if underlying signal is True. ActiveHigh :: ResetPolarity -- | Reset is considered active if underlying signal is False. ActiveLow :: ResetPolarity -- | Singleton version of ResetPolarity data SResetPolarity (polarity :: ResetPolarity) [SActiveHigh] :: SResetPolarity 'ActiveHigh [SActiveLow] :: SResetPolarity 'ActiveLow -- | A domain with a name (Domain). Configures the behavior of -- various aspects of a circuits. See the documentation of this record's -- field types for more information on the options. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. data DomainConfiguration DomainConfiguration :: Domain -> Nat -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> DomainConfiguration -- | Domain name [_name] :: DomainConfiguration -> Domain -- | Period of clock in ps [_period] :: DomainConfiguration -> Nat -- | Active edge of the clock [_activeEdge] :: DomainConfiguration -> ActiveEdge -- | Whether resets are synchronous (edge-sensitive) or asynchronous -- (level-sensitive) [_resetKind] :: DomainConfiguration -> ResetKind -- | Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value [_initBehavior] :: DomainConfiguration -> InitBehavior -- | Whether resets are active high or active low [_resetPolarity] :: DomainConfiguration -> ResetPolarity -- | Singleton version of DomainConfiguration data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) [SDomainConfiguration] :: {sName :: SSymbol dom " Domain name", sPeriod :: SNat period " Period of clock in /ps/", sActiveEdge :: SActiveEdge edge " Active edge of the clock (not yet implemented)", sResetKind :: SResetKind reset " Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)", sInitBehavior :: SInitBehavior init " Whether the initial (or "power up") value of memory elements is unknown/undefined, or configurable to a specific value", sResetPolarity :: SResetPolarity polarity " Whether resets are active high or active low"} -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) -- | Convenience type to help to extract a period from a domain. Example -- usage: -- --
--   myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...
--   
type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) -- | Convenience type to help to extract the active edge from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...
--   
type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) -- | Convenience type to help to extract the reset synchronicity from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) => ...
--   
type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) -- | Convenience type to help to extract the initial value behavior from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...
--   
type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) -- | Convenience type to help to extract the reset polarity from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...
--   
type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) -- | Helper type family for DomainPeriod type family DomainConfigurationPeriod (config :: DomainConfiguration) :: Nat -- | Helper type family for DomainActiveEdge type family DomainConfigurationActiveEdge (config :: DomainConfiguration) :: ActiveEdge -- | Helper type family for DomainResetKind type family DomainConfigurationResetKind (config :: DomainConfiguration) :: ResetKind -- | Helper type family for DomainInitBehavior type family DomainConfigurationInitBehavior (config :: DomainConfiguration) :: InitBehavior -- | Helper type family for DomainResetPolarity type family DomainConfigurationResetPolarity (config :: DomainConfiguration) :: ResetPolarity -- | Convenience type to constrain a domain to have synchronous resets. -- Example usage: -- --
--   myFunc :: HasSynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) -- | Convenience type to constrain a domain to have asynchronous resets. -- Example usage: -- --
--   myFunc :: HasAsynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) -- | Convenience type to constrain a domain to have initial values. Example -- usage: -- --
--   myFunc :: HasDefinedInitialValues dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Note that there is no UnknownInitialValues dom as a component -- that works without initial values will also work if it does have them. -- -- Click here for usage hints type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) -- | Gets time in Picoseconds from time in Seconds type Seconds (s :: Nat) = Milliseconds (1000 * s) -- | Gets time in Picoseconds from time in Milliseconds type Milliseconds (ms :: Nat) = Microseconds (1000 * ms) -- | Gets time in Picoseconds from time in Microseconds type Microseconds (us :: Nat) = Nanoseconds (1000 * us) -- | Gets time in Picoseconds from time in Nanoseconds type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns) -- | Gets time in Picoseconds from time in picoseconds, essentially -- id type Picoseconds (ps :: Nat) = ps -- | The domain's clock frequency in hertz, calculated based on the period -- stored in picoseconds. This might lead to rounding errors. type DomainToHz (dom :: Domain) = PeriodToHz (DomainPeriod dom) -- | Converts a frequency in hertz to a period in picoseconds. This might -- lead to rounding errors. type HzToPeriod (hz :: Nat) = Seconds 1 `Div` hz -- | Converts a period in picoseconds to a frequency in hertz. This might -- lead to rounding errors. type PeriodToHz (period :: Nat) = (Seconds 1) `Div` period -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed type PeriodToCycles (dom :: Domain) (period :: Nat) = period `DivRU` DomainPeriod dom -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed. The same as -- PeriodToCycles. type ClockDivider (dom :: Domain) (period :: Nat) = PeriodToCycles dom period -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type System = ("System" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and synchronously to -- changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type XilinxSystem = ("XilinxSystem" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type IntelSystem = ("IntelSystem" :: Domain) -- | Convenience value to allow easy "subclassing" of System domain. Should -- be used in combination with createDomain. For example, if you -- just want to change the period but leave all other settings intact -- use: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
vSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of IntelSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vIntelSystem{vName="Intel10", vPeriod=10}
--   
vIntelSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of XilinxSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}
--   
vXilinxSystem :: VDomainConfiguration -- | Same as SDomainConfiguration but allows for easy updates through -- record update syntax. Should be used in combination with -- vDomain and createDomain. Example: -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
data VDomainConfiguration VDomainConfiguration :: String -> Natural -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> VDomainConfiguration -- | Corresponds to _name on DomainConfiguration [vName] :: VDomainConfiguration -> String -- | Corresponds to _period on DomainConfiguration [vPeriod] :: VDomainConfiguration -> Natural -- | Corresponds to _activeEdge on DomainConfiguration [vActiveEdge] :: VDomainConfiguration -> ActiveEdge -- | Corresponds to _resetKind on DomainConfiguration [vResetKind] :: VDomainConfiguration -> ResetKind -- | Corresponds to _initBehavior on DomainConfiguration [vInitBehavior] :: VDomainConfiguration -> InitBehavior -- | Corresponds to _resetPolarity on DomainConfiguration [vResetPolarity] :: VDomainConfiguration -> ResetPolarity -- | Convert SDomainConfiguration to VDomainConfiguration. -- Should be used in combination with createDomain only. vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration -- | Convenience method to express new domains in terms of others. -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
-- -- The function will create two extra identifiers. The first: -- --
--   type System10 = ..
--   
-- -- You can use that as the dom to Clocks/Resets/Enables/Signals. For -- example: Signal System10 Int. Additionally, it will create a -- VDomainConfiguration that you can use in later calls to -- createDomain: -- --
--   vSystem10 = knownVDomain @System10
--   
-- -- It will also make System10 an instance of KnownDomain. -- -- If either identifier is already in scope it will not be generated a -- second time. Note: This can be useful for example when documenting a -- new domain: -- --
--   -- | Here is some documentation for CustomDomain
--   type CustomDomain = ("CustomDomain" :: Domain)
--   
--   -- | Here is some documentation for vCustomDomain
--   createDomain vSystem{vName="CustomDomain"}
--   
createDomain :: VDomainConfiguration -> Q [Dec] -- | A clock signal belonging to a domain named dom. data Clock (dom :: Domain) Clock :: SSymbol dom -> Maybe (Signal dom Femtoseconds) -> Clock (dom :: Domain) -- | Domain associated with the clock [clockTag] :: Clock (dom :: Domain) -> SSymbol dom -- | Periods of the clock. This is an experimental feature used to simulate -- clock frequency correction mechanisms. Currently, all ways to contruct -- such a clock are hidden from the public API. [clockPeriods] :: Clock (dom :: Domain) -> Maybe (Signal dom Femtoseconds) -- | The negative or inverted phase of a differential clock signal. HDL -- generation will treat it the same as Clock, except that no -- create_clock command is issued in the SDC file for -- ClockN. Used in DiffClock. newtype ClockN (dom :: Domain) ClockN :: SSymbol dom -> ClockN (dom :: Domain) [clockNTag] :: ClockN (dom :: Domain) -> SSymbol dom -- | A differential clock signal belonging to a domain named dom. -- The clock input of a design with such an input has two ports which are -- in antiphase. The first input is the positive phase, the second the -- negative phase. When using makeTopEntity, the names of the -- inputs will end in _p and _n respectively. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. data DiffClock (dom :: Domain) DiffClock :: ("p" ::: Clock dom) -> ("n" ::: ClockN dom) -> DiffClock (dom :: Domain) -- | Calculate the period in ps, given a frequency in Hz -- -- I.e., to calculate the clock period for a circuit to run at 240 MHz we -- get -- --
--   >>> hzToPeriod 240e6
--   4166
--   
-- -- If the value hzToPeriod is applied to is not of the type -- Ratio Natural, you can use hzToPeriod -- (realToFrac f). Note that if f is negative, -- realToFrac will give an Underflow :: -- ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Natural. To -- get the old behavior of this function, use a type application: -- --
--   >>> hzToPeriod @Natural 240e6
--   4166
--   
-- -- hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a -- | Calculate the frequency in Hz, given the period in ps -- -- I.e., to calculate the clock frequency of a clock with a period of -- 5000 ps: -- --
--   >>> periodToHz 5000
--   2.0e8
--   
-- -- Note that if p in periodToHz (fromIntegral p) -- is negative, fromIntegral will give an Underflow -- :: ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Ratio -- Natural. To get the old behavior of this function, use a type -- application: -- --
--   >>> periodToHz @(Ratio Natural) 5000
--   200000000 % 1
--   
-- -- NB: This function is not synthesizable periodToHz :: (HasCallStack, Fractional a) => Natural -> a data ClockAB -- | Clock edge A produced ClockA :: ClockAB -- | Clock edge B produced ClockB :: ClockAB -- | Clock edges coincided ClockAB :: ClockAB -- | Given two clocks, produce a list of clock ticks indicating which clock -- (or both) ticked. Can be used in components handling multiple clocks, -- such as unsafeSynchronizer or dual clock FIFOs. -- -- If your primitive does not care about coincided clock edges, it should -- - by convention - replace it by ClockB:ClockA:. clockTicks :: (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> [ClockAB] -- | Given two clock periods, produce a list of clock ticks indicating -- which clock (or both) ticked. Can be used in components handling -- multiple clocks, such as unsafeSynchronizer or dual clock -- FIFOs. -- -- If your primitive does not care about coincided clock edges, it should -- - by convention - replace it by ClockB:ClockA:. clockTicksEither :: Either Int64 (Signal domA Int64) -> Either Int64 (Signal domB Int64) -> [ClockAB] -- | A signal of booleans, indicating whether a component is enabled. No -- special meaning is implied, it's up to the component itself to decide -- how to respond to its enable line. It is used throughout Clash as a -- global enable signal. data Enable dom Enable :: Signal dom Bool -> Enable dom -- | Convert a signal of bools to an Enable construct toEnable :: Signal dom Bool -> Enable dom -- | Convert Enable construct to its underlying representation: a -- signal of bools. fromEnable :: Enable dom -> Signal dom Bool -- | Enable generator for some domain. Is simply always True. enableGen :: Enable dom -- | A reset signal belonging to a domain called dom. -- -- The underlying representation of resets is Bool. data Reset (dom :: Domain) Reset :: Signal dom Bool -> Reset (dom :: Domain) -- | unsafeToReset is unsafe. For asynchronous resets it is unsafe -- because it can introduce combinatorial loops. In case of synchronous -- resets it can lead to meta-stability issues in the presence of -- asynchronous resets. -- -- NB: You probably want to use unsafeFromActiveLow or -- unsafeFromActiveHigh. unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom -- | unsafeFromReset is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- -- NB: You probably want to use unsafeToActiveLow or -- unsafeToActiveHigh. unsafeFromReset :: Reset dom -> Signal dom Bool -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Invert reset signal invertReset :: KnownDomain dom => Reset dom -> Reset dom delay# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a -- | A register with a power up and reset value. Power up values are not -- supported on all platforms, please consult the manual of your target -- platform and check the notes below. -- -- Xilinx: power up values and reset values MUST be the same. If they are -- not, the Xilinx tooling will ignore the reset value and use the -- power up value instead. Source: MIA -- -- Intel: power up values and reset values MUST be the same. If they are -- not, the Intel tooling will ignore the power up value and use -- the reset value instead. Source: -- https://www.intel.com/content/www/us/en/programmable/support/support-resources/knowledge-base/solutions/rd01072011_91.html register# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a -- | Version of register# that simulates a register on an -- asynchronous domain. Is synthesizable. asyncRegister# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a -- | Version of register# that simulates a register on a synchronous -- domain. Not synthesizable. syncRegister# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a -- | Acts like id if given domain allows powerup values, but returns -- a value constructed with deepErrorX otherwise. registerPowerup# :: forall dom a. (KnownDomain dom, NFDataX a, HasCallStack) => Clock dom -> a -> a -- | The above type is a generalization for: -- --
--   mux :: Signal Bool -> Signal a -> Signal a -> Signal a
--   
-- -- A multiplexer. Given "mux b t f", output t -- when b is True, and f when b is -- False. mux :: Applicative f => f Bool -> f a -> f a -> f a -- | Clock generator for simulations. Do not use this clock -- generator for the testBench function, use tbClockGen -- instead. -- -- To be used like: -- --
--   clkSystem = clockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. clockGen :: KnownDomain dom => Clock dom -- | Clock generator to be used in the testBench function. -- -- To be used like: -- --
--   clkSystem en = tbClockGen @System en
--   
-- --

Example

-- --
--   module Example where
--   
--   import Clash.Explicit.Prelude
--   import Clash.Explicit.Testbench
--   
--   -- Fast domain: twice as fast as "Slow"
--   createDomain vSystem{vName="Fast", vPeriod=10}
--   
--   -- Slow domain: twice as slow as "Fast"
--   createDomain vSystem{vName="Slow", vPeriod=20}
--   
--   topEntity
--     :: Clock "Fast"
--     -> Reset "Fast"
--     -> Enable "Fast"
--     -> Clock "Slow"
--     -> Signal "Fast" (Unsigned 8)
--     -> Signal "Slow" (Unsigned 8, Unsigned 8)
--   topEntity clk1 rst1 en1 clk2 i =
--     let h = register clk1 rst1 en1 0 (register clk1 rst1 en1 0 i)
--         l = register clk1 rst1 en1 0 i
--     in  unsafeSynchronizer clk1 clk2 (bundle (h, l))
--   
--   testBench
--     :: Signal "Slow" Bool
--   testBench = done
--     where
--       testInput      = stimuliGenerator clkA1 rstA1 $(listToVecTH [1::Unsigned 8,2,3,4,5,6,7,8])
--       expectedOutput = outputVerifier   clkB2 rstB2 $(listToVecTH [(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)])
--       done           = expectedOutput (topEntity clkA1 rstA1 enableGen clkB2 testInput)
--       notDone        = not <$> done
--       clkA1          = tbClockGen @"Fast" (unsafeSynchronizer clkB2 clkA1 notDone)
--       clkB2          = tbClockGen @"Slow" notDone
--       rstA1          = resetGen @"Fast"
--       rstB2          = resetGen @"Slow"
--   
tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom -- | Femtoseconds expressed as an Int64. Is a newtype to prevent -- accidental mixups with picoseconds - the unit used in -- DomainConfiguration. newtype Femtoseconds Femtoseconds :: Int64 -> Femtoseconds -- | Calculate the frequency in Hz, given the period in fs -- -- I.e., to calculate the clock frequency of a clock with a period of -- 5000 fs: -- --
--   >>> fsToHz (Femtoseconds 5000)
--   2.0e11
--   
-- -- NB: This function is not synthesizable fsToHz :: (HasCallStack, Fractional a) => Femtoseconds -> a -- | Calculate the period in fs, given a frequency in Hz -- -- I.e., to calculate the clock period for a circuit to run at 240 MHz we -- get -- --
--   >>> hzToFs 240e6
--   Femtoseconds 4166666
--   
-- -- If the value hzToFs is applied to is not of the type -- Ratio Natural, you can use hzToFs (realToFrac -- f). Note that if f is negative, realToFrac will -- give an Underflow :: ArithException without a -- call stack, making debugging cumbersome. -- -- hzToFs :: HasCallStack => Ratio Natural -> Femtoseconds -- | Strip newtype wrapper Femtoseconds unFemtoseconds :: Femtoseconds -> Int64 -- | Map Int64 fields in Femtoseconds mapFemtoseconds :: (Int64 -> Int64) -> Femtoseconds -> Femtoseconds -- | Clock generator with dynamic clock periods for simulations. This is an -- experimental feature and hence not part of the public API. Like -- tbClockGen -- -- To be used like: -- --
--   clkSystem = dynamicClockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. tbDynamicClockGen :: KnownDomain dom => Signal dom Femtoseconds -> Signal dom Bool -> Clock dom -- | Clock generator with dynamic clock periods for simulations. This is an -- experimental feature and hence not part of the public API. -- -- To be used like: -- --
--   clkSystem = dynamicClockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. dynamicClockGen :: KnownDomain dom => Signal dom Femtoseconds -> Clock dom -- | Reset generator for simulation purposes. Asserts the reset for a -- single cycle. -- -- To be used like: -- --
--   rstSystem = resetGen @System
--   
-- -- See tbClockGen for example usage. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGen :: forall dom. KnownDomain dom => Reset dom -- | Reset generator for simulation purposes. Asserts the reset for the -- first n cycles. -- -- To be used like: -- --
--   rstSystem5 = resetGen @System d5
--   
-- -- Example usage: -- --
--   >>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
--   [True,True,True,False,False,False,False]
--   
-- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom -- | The above type is a generalization for: -- --
--   (.&&.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (&&) that returns a Signal of -- Bool (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 .&&. -- | The above type is a generalization for: -- --
--   (.||.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (||) that returns a Signal of -- Bool (.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 .||. -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
--   [8,8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
--   [8,8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] -- | Build an Automaton from a function over Signals. -- -- NB: Consumption of continuation of the Automaton must be -- affine; that is, you can only apply the continuation associated with a -- particular element at most once. signalAutomaton :: forall dom a b. (Signal dom a -> Signal dom b) -> Automaton (->) a b -- | The above type is a generalization for: -- --
--   sample :: Signal a -> [a]
--   
-- -- Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- NB: This function is not synthesizable sample :: (Foldable f, NFDataX a) => f a -> [a] -- | The above type is a generalization for: -- --
--   sampleN :: Int -> Signal a -> [a]
--   
-- -- Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN 3 s == [s0, s1, s2]
--   
-- -- NB: This function is not synthesizable sampleN :: (Foldable f, NFDataX a) => Int -> f a -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5])
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList :: NFDataX a => [a] -> Signal dom a -- | The above type is a generalization for: -- --
--   sample :: Signal a -> [a]
--   
-- -- Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- NB: This function is not synthesizable sample_lazy :: Foldable f => f a -> [a] -- | The above type is a generalization for: -- --
--   sampleN :: Int -> Signal a -> [a]
--   
-- -- Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN 3 s == [s0, s1, s2]
--   
-- -- NB: This function is not synthesizable sampleN_lazy :: Foldable f => Int -> f a -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList_lazy :: [a] -> Signal dom a -- | The above type is a generalization for: -- --
--   testFor :: Int -> Signal Bool -> Property
--   
-- -- testFor n s tests the signal s for n -- cycles. -- -- NB: This function is not synthesizable testFor :: Foldable f => Int -> f Bool -> Property -- | The above type is a generalization for: -- --
--   (.==.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (==) that returns a Signal of -- Bool (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 .==. -- | The above type is a generalization for: -- --
--   (./=.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (/=) that returns a Signal of -- Bool (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 ./=. -- | The above type is a generalization for: -- --
--   (.<.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<) that returns a Signal of -- Bool (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<. -- | The above type is a generalization for: -- --
--   (.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<=) that returns a Signal of -- Bool (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<=. -- | The above type is a generalization for: -- --
--   (.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>=) that returns a Signal of -- Bool (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>=. -- | The above type is a generalization for: -- --
--   (.>.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>) that returns a Signal of -- Bool (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>. mapSignal# :: forall a b dom. (a -> b) -> Signal dom a -> Signal dom b signal# :: a -> Signal dom a appSignal# :: Signal dom (a -> b) -> Signal dom a -> Signal dom b -- | NB: Not synthesizable -- -- NB: In "foldr# f z s": -- -- foldr# :: (a -> b -> b) -> b -> Signal dom a -> b traverse# :: Applicative f => (a -> f b) -> Signal dom a -> f (Signal dom b) -- | WARNING: EXTREMELY EXPERIMENTAL -- -- The circuit semantics of this operation are unclear and/or -- non-existent. There is a good reason there is no Monad instance -- for Signal. -- -- Is currently treated as id by the Clash compiler. joinSignal# :: Signal dom (Signal dom a) -> Signal dom a -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveLow instead. This function -- will be removed in Clash 1.12. unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveLow instead. This function -- will be removed in Clash 1.12. unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool instance Data.Binary.Class.Binary Clash.Signal.Internal.ActiveEdge instance Data.Hashable.Class.Hashable Clash.Signal.Internal.ActiveEdge instance Data.Data.Data Clash.Signal.Internal.ActiveEdge instance Control.DeepSeq.NFData Clash.Signal.Internal.ActiveEdge instance GHC.Generics.Generic Clash.Signal.Internal.ActiveEdge instance GHC.Classes.Ord Clash.Signal.Internal.ActiveEdge instance GHC.Classes.Eq Clash.Signal.Internal.ActiveEdge instance GHC.Read.Read Clash.Signal.Internal.ActiveEdge instance GHC.Show.Show Clash.Signal.Internal.ActiveEdge instance Data.Binary.Class.Binary Clash.Signal.Internal.ResetKind instance Data.Hashable.Class.Hashable Clash.Signal.Internal.ResetKind instance Data.Data.Data Clash.Signal.Internal.ResetKind instance Control.DeepSeq.NFData Clash.Signal.Internal.ResetKind instance GHC.Generics.Generic Clash.Signal.Internal.ResetKind instance GHC.Classes.Ord Clash.Signal.Internal.ResetKind instance GHC.Classes.Eq Clash.Signal.Internal.ResetKind instance GHC.Read.Read Clash.Signal.Internal.ResetKind instance GHC.Show.Show Clash.Signal.Internal.ResetKind instance Data.Binary.Class.Binary Clash.Signal.Internal.ResetPolarity instance Data.Hashable.Class.Hashable Clash.Signal.Internal.ResetPolarity instance Data.Data.Data Clash.Signal.Internal.ResetPolarity instance Control.DeepSeq.NFData Clash.Signal.Internal.ResetPolarity instance GHC.Generics.Generic Clash.Signal.Internal.ResetPolarity instance GHC.Read.Read Clash.Signal.Internal.ResetPolarity instance GHC.Show.Show Clash.Signal.Internal.ResetPolarity instance GHC.Classes.Ord Clash.Signal.Internal.ResetPolarity instance GHC.Classes.Eq Clash.Signal.Internal.ResetPolarity instance Data.Binary.Class.Binary Clash.Signal.Internal.InitBehavior instance Data.Hashable.Class.Hashable Clash.Signal.Internal.InitBehavior instance Data.Data.Data Clash.Signal.Internal.InitBehavior instance Control.DeepSeq.NFData Clash.Signal.Internal.InitBehavior instance GHC.Generics.Generic Clash.Signal.Internal.InitBehavior instance GHC.Classes.Ord Clash.Signal.Internal.InitBehavior instance GHC.Classes.Eq Clash.Signal.Internal.InitBehavior instance GHC.Read.Read Clash.Signal.Internal.InitBehavior instance GHC.Show.Show Clash.Signal.Internal.InitBehavior instance Data.Binary.Class.Binary Clash.Signal.Internal.VDomainConfiguration instance GHC.Read.Read Clash.Signal.Internal.VDomainConfiguration instance GHC.Show.Show Clash.Signal.Internal.VDomainConfiguration instance Control.DeepSeq.NFData Clash.Signal.Internal.VDomainConfiguration instance GHC.Generics.Generic Clash.Signal.Internal.VDomainConfiguration instance GHC.Classes.Eq Clash.Signal.Internal.VDomainConfiguration instance GHC.Classes.Ord Clash.Signal.Internal.Femtoseconds instance Language.Haskell.TH.Syntax.Lift Clash.Signal.Internal.Femtoseconds instance Control.DeepSeq.NFData Clash.Signal.Internal.Femtoseconds instance Clash.XException.NFDataX Clash.Signal.Internal.Femtoseconds instance GHC.Generics.Generic Clash.Signal.Internal.Femtoseconds instance GHC.Classes.Eq Clash.Signal.Internal.Femtoseconds instance GHC.Show.Show Clash.Signal.Internal.Femtoseconds instance Clash.XException.NFDataX Clash.Signal.Internal.ClockAB instance Control.DeepSeq.NFData Clash.Signal.Internal.ClockAB instance GHC.Show.Show Clash.Signal.Internal.ClockAB instance GHC.Classes.Eq Clash.Signal.Internal.ClockAB instance GHC.Generics.Generic Clash.Signal.Internal.ClockAB instance GHC.Show.Show (Clash.Signal.Internal.SDomainConfiguration dom conf) instance GHC.Show.Show (Clash.Signal.Internal.DiffClock dom) instance GHC.Show.Show (Clash.Signal.Internal.Clock dom) instance GHC.Show.Show (Clash.Signal.Internal.ClockN dom) instance GHC.Show.Show a => GHC.Show.Show (Clash.Signal.Internal.Signal dom a) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (Clash.Signal.Internal.Signal dom a) instance Data.Default.Class.Default a => Data.Default.Class.Default (Clash.Signal.Internal.Signal dom a) instance GHC.Base.Functor (Clash.Signal.Internal.Signal dom) instance GHC.Base.Applicative (Clash.Signal.Internal.Signal dom) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Signal.Internal.Signal domain a) instance GHC.Num.Num a => GHC.Num.Num (Clash.Signal.Internal.Signal dom a) instance Data.Foldable.Foldable (Clash.Signal.Internal.Signal dom) instance Data.Traversable.Traversable (Clash.Signal.Internal.Signal dom) instance GHC.Real.Fractional a => GHC.Real.Fractional (Clash.Signal.Internal.Signal dom a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Signal.Internal.Signal dom a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Signal.Internal.Signal dom a) instance Clash.Signal.Internal.KnownDomain Clash.Signal.Internal.System instance Clash.Signal.Internal.KnownDomain Clash.Signal.Internal.XilinxSystem instance Clash.Signal.Internal.KnownDomain Clash.Signal.Internal.IntelSystem instance GHC.Show.Show (Clash.Signal.Internal.SInitBehavior init) instance GHC.Show.Show (Clash.Signal.Internal.SResetPolarity polarity) instance GHC.Show.Show (Clash.Signal.Internal.SResetKind reset) instance GHC.Show.Show (Clash.Signal.Internal.SActiveEdge edge) -- | Verification module Clash.Verification.Internal -- | A result of some property. Besides carrying the actual boolean result, -- it carries some properties used to make reports. data AssertionResult AssertionResult :: !String -> !Bool -> AssertionResult -- | Name of property belonging to this result [cvPropName] :: AssertionResult -> !String -- | False whenever property is violated, True otherwise [cvPass] :: AssertionResult -> !Bool -- | A property is a temporal or basic assertion that's specified to either -- used as an _assert_ or _cover_ statement. See assert and -- cover. newtype Property (dom :: Domain) Property :: Property' (Maybe Text, Signal dom Bool) -> Property (dom :: Domain) data Assertion (dom :: Domain) Assertion :: IsTemporal -> Assertion' (Maybe Text, Signal dom Bool) -> Assertion (dom :: Domain) -- | Render target for HDL data RenderAs -- | Property Specification Language PSL :: RenderAs -- | SystemVerilog Assertions SVA :: RenderAs -- | Use SVA for SystemVerilog, PSL for others AutoRenderAs :: RenderAs -- | Yosys Formal Extensions for Verilog and SystemVerilog. See: -- https://symbiyosys.readthedocs.io/en/latest/verilog.html and -- https://symbiyosys.readthedocs.io/en/latest/verific.html -- -- Falls back to PSL for VHDL, however currently Clash's PSL syntax isn't -- suported by GHDL+SymbiYosys; YosysFormal :: RenderAs data IsTemporal IsNotTemporal :: IsTemporal IsTemporal :: IsTemporal -- | An AssertionValue is a bool-like value or stream that can be used in -- property specifications. Clash implements two: a stream of booleans -- (Signal dom Bool), and the result of a property expression (Assertion -- dom). class AssertionValue dom a | a -> dom -- | Convert given type into a Assertion. toAssertionValue :: AssertionValue dom a => a -> Assertion dom -- | Internal version of Assertion. data Assertion' a -- | (Bootstrapping) signal of booleans CvPure :: a -> Assertion' a -- | Tag to force a non-temporal assertion to a temporal one CvToTemporal :: Assertion' a -> Assertion' a -- | Boolean literal CvLit :: Bool -> Assertion' a -- | Logical not CvNot :: Assertion' a -> Assertion' a -- | Logical and CvAnd :: Assertion' a -> Assertion' a -> Assertion' a -- | Logical or CvOr :: Assertion' a -> Assertion' a -> Assertion' a -- | Logical implies CvImplies :: Assertion' a -> Assertion' a -> Assertion' a -- | Moves start point of assertion n cycles forward CvNext :: Word -> Assertion' a -> Assertion' a -- | Before CvBefore a b is the same as CvAnd a (CvNext 1 -- b) CvBefore :: Assertion' a -> Assertion' a -> Assertion' a -- | Temporal implies CvTemporalImplies n a b: -- -- n | n == 0 -> same as CvImplies a b | otherwise -> same -- as CvImplies a (CvNextN n b) CvTemporalImplies :: Word -> Assertion' a -> Assertion' a -> Assertion' a -- | Assertion should _always_ hold CvAlways :: Assertion' a -> Assertion' a -- | Assertion should _never_ hold (not supported by SVA) CvNever :: Assertion' a -> Assertion' a -- | Assertion should _eventually_ hold CvEventually :: Assertion' a -> Assertion' a -- | Internal version of Property. All user facing will instantiate -- a with (Maybe Text, Signal dom Bool). Blackboxes -- will instantiate it with (Maybe Text, Term) instead. data Property' a CvAssert :: Assertion' a -> Property' a CvCover :: Assertion' a -> Property' a CvAssume :: Assertion' a -> Property' a toTemporal :: Assertion dom -> Assertion' (Maybe Text, Signal dom Bool) isTemporal :: Assertion dom -> IsTemporal assertion :: Assertion dom -> Assertion' (Maybe Text, Signal dom Bool) instance GHC.Classes.Eq Clash.Verification.Internal.RenderAs instance GHC.Show.Show Clash.Verification.Internal.RenderAs instance GHC.Classes.Ord Clash.Verification.Internal.IsTemporal instance GHC.Classes.Eq Clash.Verification.Internal.IsTemporal instance Data.Traversable.Traversable Clash.Verification.Internal.Assertion' instance Data.Foldable.Foldable Clash.Verification.Internal.Assertion' instance GHC.Base.Functor Clash.Verification.Internal.Assertion' instance GHC.Show.Show a => GHC.Show.Show (Clash.Verification.Internal.Assertion' a) instance Data.Traversable.Traversable Clash.Verification.Internal.Property' instance Data.Foldable.Foldable Clash.Verification.Internal.Property' instance GHC.Base.Functor Clash.Verification.Internal.Property' instance GHC.Show.Show a => GHC.Show.Show (Clash.Verification.Internal.Property' a) instance GHC.Classes.Eq Clash.Verification.Internal.AssertionResult instance Clash.Verification.Internal.AssertionValue dom (Clash.Signal.Internal.Signal dom GHC.Types.Bool) instance Clash.Verification.Internal.AssertionValue dom (Clash.Verification.Internal.Assertion dom) module Clash.Signal.Internal.Ambiguous -- | Like 'knownDomain but yields a VDomainConfiguration. Should -- only be used in combination with createDomain. knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration -- | Get the clock period from a KnownDomain context clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period -- | Get ActiveEdge from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case activeEdge @dom of
--       SRising -> foo
--       SFalling -> bar
--   
activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge -- | Get ResetKind from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetKind @dom of
--       SAsynchronous -> foo
--       SSynchronous -> bar
--   
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync -- | Get InitBehavior from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case initBehavior @dom of
--       SDefined -> foo
--       SUnknown -> bar
--   
initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init -- | Get ResetPolarity from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetPolarity @dom of
--       SActiveHigh -> foo
--       SActiveLow -> bar
--   
resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity -- | Verification primitives for Clash. Currently implements PSL (Property -- Specification Language) and SVA (SystemVerilog Assertions). For a good -- overview of PSL and an introduction to the concepts of property -- checking, read -- https://standards.ieee.org/standard/62531-2012.html. -- -- The verification API is currently experimental and subject to change. module Clash.Explicit.Verification data Assertion (dom :: Domain) -- | A property is a temporal or basic assertion that's specified to either -- used as an _assert_ or _cover_ statement. See assert and -- cover. data Property (dom :: Domain) -- | An AssertionValue is a bool-like value or stream that can be used in -- property specifications. Clash implements two: a stream of booleans -- (Signal dom Bool), and the result of a property expression (Assertion -- dom). class AssertionValue dom a | a -> dom -- | Render target for HDL data RenderAs -- | Property Specification Language PSL :: RenderAs -- | SystemVerilog Assertions SVA :: RenderAs -- | Use SVA for SystemVerilog, PSL for others AutoRenderAs :: RenderAs -- | Yosys Formal Extensions for Verilog and SystemVerilog. See: -- https://symbiyosys.readthedocs.io/en/latest/verilog.html and -- https://symbiyosys.readthedocs.io/en/latest/verific.html -- -- Falls back to PSL for VHDL, however currently Clash's PSL syntax isn't -- suported by GHDL+SymbiYosys; YosysFormal :: RenderAs -- | Convert a signal to a cv expression with a name hint. Clash will try -- its best to use this name in the rendered assertion, but might run -- into collisions. You can skip using name altogether. Clash will -- then try its best to get a readable name from context. name :: Text -> Signal dom Bool -> Assertion dom -- | For using a literal (either True or False) in assertions lit :: Bool -> Assertion dom -- | Truth table for not: -- --
--   a     | not a
--   ------------
--   True  | False
--   False | True
--   
not :: AssertionValue dom a => a -> Assertion dom -- | Truth table for and: -- --
--   a     | b     | a `and` b
--   --------------|----------
--   False | False | False
--   False | True  | False
--   True  | False | False
--   True  | True  | True
--   
and :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for or: -- --
--   a     | b     | a `or` b
--   --------------|---------
--   False | False | False
--   False | True  | True
--   True  | False | True
--   True  | True  | True
--   
or :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for implies: -- --
--   a     | b     | a `implies` b
--   --------------|--------------
--   False | False | True
--   False | True  | True
--   True  | False | False
--   True  | True  | True
--   
implies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for next: -- --
--   a[n]  | a[n+1] | a `implies` next a
--   ---------------|-------------------
--   False | False  | True
--   False | True   | True
--   True  | False  | False
--   True  | True   | True
--   
-- -- where a[n] represents the value of a at cycle n and -- a[n+1] represents the value of a at cycle -- n+1. Cycle n is an arbitrary cycle. next :: AssertionValue dom a => a -> Assertion dom -- | Truth table for nextN: -- --
--   a[n]  | a[n+m] | a `implies` next m a
--   ---------------|---------------------
--   False | False  | True
--   False | True   | True
--   True  | False  | False
--   True  | True   | True
--   
-- -- where a[n] represents the value of a at cycle n and -- a[n+m] represents the value of a at cycle n+m. Cycle -- n is an arbitrary cycle. nextN :: AssertionValue dom a => Word -> a -> Assertion dom -- | Same as a && next b but with a nice syntax. E.g., -- a && next b could be written as a before -- b. Might be read as "a happens one cycle before b". before :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Same as a implies next b but with a nice syntax. E.g., -- a implies next b could be written as a -- timplies b. Might be read as "a at cycle n implies b at -- cycle n+1". timplies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Same as implies but strictly temporal. timpliesOverlapping :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Specify assertion should _always_ hold always :: AssertionValue dom a => a -> Assertion dom -- | Specify assertion should _never_ hold (not supported by SVA) never :: AssertionValue dom a => a -> Assertion dom -- | Specify assertion should _eventually_ hold eventually :: AssertionValue dom a => a -> Assertion dom -- | Check whether given assertion always holds. Results can be collected -- with check. assert :: AssertionValue dom a => a -> Property dom -- | Check whether given assertion holds for at least a single cycle. -- Results can be collected with check. cover :: AssertionValue dom a => a -> Property dom -- | Inform the prover that this property is true. This is the same as -- assert for simulations. assume :: AssertionValue dom a => a -> Property dom -- | Print property as PSL/SVA in HDL. Clash simulation support not yet -- implemented. check :: KnownDomain dom => Clock dom -> Reset dom -> Text -> RenderAs -> Property dom -> Signal dom AssertionResult -- | Same as check, but doesn't require a design to explicitly -- carried to top-level. checkI :: KnownDomain dom => Clock dom -> Reset dom -> Text -> RenderAs -> Property dom -> Signal dom a -> Signal dom a -- | Print assertions in HDL hideAssertion :: Signal dom AssertionResult -> Signal dom a -> Signal dom a module Clash.Signal.Delayed.Internal -- | A synchronized signal with samples of type a, synchronized to -- clock clk, that has accumulated delay amount of -- samples delay along its path. -- -- DSignal has the type role -- --
--   >>> :i DSignal
--   type role DSignal nominal nominal representational
--   ...
--   
-- -- as it is safe to coerce the values in the signal, but not safe to -- coerce the synthesis domain or delay in the signal. newtype DSignal (dom :: Domain) (delay :: Nat) a DSignal :: Signal dom a -> DSignal (dom :: Domain) (delay :: Nat) a -- | Strip a DSignal of its delay information. [toSignal] :: DSignal (dom :: Domain) (delay :: Nat) a -> Signal dom a -- | Feed the delayed result of a function back to its input: -- --
--   mac
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = feedback (mac' x y)
--     where
--       mac'
--         :: DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> (DSignal dom 0 Int, DSignal dom 1 Int)
--       mac' a b acc = let acc' = a * b + acc
--                      in  (acc, delayedI clk rst en 0 acc')
--   
-- --
--   >>> sampleN 7 (toSignal (mac systemClockGen systemResetGen enableGen (dfromList [0..]) (dfromList [0..])))
--   [0,0,1,5,14,30,55]
--   
feedback :: (DSignal dom n a -> (DSignal dom n a, DSignal dom ((n + m) + 1) a)) -> DSignal dom n a -- | Signals are not delayed fromSignal :: Signal dom a -> DSignal dom 0 a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList :: NFDataX a => [a] -> DSignal dom 0 a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList_lazy :: [a] -> DSignal dom 0 a -- | EXPERIMENTAL -- -- Unsafely convert a Signal to a DSignal with an -- arbitrary delay. -- -- NB: Should only be used to interface with functions specified -- in terms of Signal. unsafeFromSignal :: Signal dom a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the future in the present. Often -- required When writing a circuit that requires feedback from itself. -- --
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = acc'
--     where
--       acc' = (x * y) + antiDelay d1 acc
--       acc  = delayedI clk rst en 0 acc'
--   
antiDelay :: SNat d -> DSignal dom (n + d) a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the past in the present. In -- contrast with delayed and friends forward does not insert any -- logic. This means using this function violates the delay invariant of -- DSignal. This is sometimes useful when combining unrelated -- delayed signals where inserting logic is not wanted or when -- abstracting over internal delayed signals where the internal delay -- information should not be leaked. -- -- For example, the circuit below returns a sequence of numbers as a pair -- but the internal delay information between the elements of the pair -- should not leak into the type. -- --
--   numbers
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 5 (Int, Int)
--   numbers clk rst en = DB.bundle (forward d1 s1, s2)
--     where
--       s1 :: DSignal dom 4 Int
--       s1 = delayed clk rst en (100 :> 10 :> 5 :> 1 :> Nil) (pure 200)
--       s2 :: DSignal dom 5 Int
--       s2 = fmap (2*) $ delayN d1 0 en clk s1
--   
-- --
--   >>> sampleN 8 (toSignal (numbers systemClockGen systemResetGen enableGen))
--   [(1,0),(1,2),(5,2),(10,10),(100,20),(200,200),(200,400),(200,400)]
--   
forward :: SNat d -> DSignal dom n a -> DSignal dom (n + d) a instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance Data.Traversable.Traversable (Clash.Signal.Delayed.Internal.DSignal dom delay) instance Data.Foldable.Foldable (Clash.Signal.Delayed.Internal.DSignal dom delay) instance GHC.Real.Fractional a => GHC.Real.Fractional (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance GHC.Num.Num a => GHC.Num.Num (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance GHC.Base.Applicative (Clash.Signal.Delayed.Internal.DSignal dom delay) instance GHC.Base.Functor (Clash.Signal.Delayed.Internal.DSignal dom delay) instance Data.Default.Class.Default a => Data.Default.Class.Default (Clash.Signal.Delayed.Internal.DSignal dom delay a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Signal.Delayed.Internal.DSignal dom delay a) module Clash.Promoted.Nat.Unsafe -- | I hope you know what you're doing unsafeSNat :: Integer -> SNat k module Clash.Promoted.Nat.TH -- | Create an SNat literal -- --
--   $(decLiteralD 1111)
--   
-- --
--   >>> :t d1111
--   d1111 :: SNat 1111
--   
decLiteralD :: Integer -> Q [Dec] -- | Create a range of SNat literals -- --
--   $(decLiteralsD 1200 1202)
--   
-- --
--   >>> :t d1200
--   d1200 :: SNat 1200
--   
--   >>> :t d1201
--   d1201 :: SNat 1201
--   
--   >>> :t d1202
--   d1202 :: SNat 1202
--   
decLiteralsD :: Integer -> Integer -> Q [Dec] -- | Predefined SNat singleton literals in the range [0 .. 1024] -- -- Defines: -- --
--   d0 = SNat :: SNat 0
--   d1 = SNat :: SNat 1
--   d2 = SNat :: SNat 2
--   ...
--   d1024 = SNat :: SNat 1024
--   
-- -- You can generate more SNat literals using decLiteralsD -- from Clash.Promoted.Nat.TH module Clash.Promoted.Nat.Literals module Clash.Class.HasDomain.CodeGen mkTryDomainTuples :: Name -> Name -> Q [Dec] mkHasDomainTuples :: Name -> Name -> Q [Dec] module Clash.Class.BitPack.Internal.TH -- | Contruct all the tuple (starting at size 3) instances for BitPack. deriveBitPackTuples :: Name -> Name -> Name -> Name -> DecsQ module Clash.Class.BitPack.Internal -- | Convert data to/from a BitVector. This allows functions to be -- defined on the underlying representation of data, while exposing a -- nicer API using pack / unpack at the boundaries. For -- example: -- --
--   f :: forall a b. (BitPack a, BitPack b) => a -> b
--   f = unpack . go . pack
--    where
--     go :: BitVector (BitSize a) -> BitVector (BitSize b)
--     go = _ -- A function on the underlying bit vector
--   
-- -- A type should only implement this class if it has a statically known -- size, as otherwise it is not possible to determine how many bits are -- needed to represent values. This means that types such as [a] -- cannot have BitPack instances, as even if a has a -- statically known size, the length of the list cannot be known in -- advance. -- -- It is not possible to give data a custom bit representation by -- providing a BitPack instance. A BitPack instance -- allows no creativity and should always accurately reflect the bit -- representation of the data in HDL. You should always derive -- (Generic, BitPack) unless you use a custom data -- representation, in which case you should use deriveBitPack. -- Custom encodings can be created with -- Clash.Annotations.BitRepresentation and -- Clash.Annotations.BitRepresentation.Deriving. -- -- If the BitPack instance does not accurately match the bit -- representation of the data in HDL, Clash designs will exhibit -- incorrect behavior in various places. -- -- Clash provides some generic functions on packable types in the -- prelude, such as indexing into packable stuctures (see -- Clash.Class.BitPack.BitIndex) and bitwise reduction of packable -- data (see Clash.Class.BitPack.BitReduction). class KnownNat (BitSize a) => BitPack a where { -- | Number of Bits needed to represents elements of type a -- -- Can be derived using Generics: -- --
    --   import Clash.Prelude
    --   import GHC.Generics
    --   
    --   data MyProductType = MyProductType { a :: Int, b :: Bool }
    --     deriving (Generic, BitPack)
    --   
type family BitSize a :: Nat; type BitSize a = (CLog 2 (GConstructorCount (Rep a))) + (GFieldSize (Rep a)); } -- | Convert element of type a to a BitVector -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
pack :: BitPack a => a -> BitVector (BitSize a) -- | Convert element of type a to a BitVector -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
pack :: (BitPack a, Generic a, GBitPack (Rep a), KnownNat (BitSize a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => a -> BitVector (BitSize a) -- | Convert a BitVector to an element of type a -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> let x = pack (-5 :: Signed 6)
--   
--   >>> unpack x :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
unpack :: BitPack a => BitVector (BitSize a) -> a -- | Convert a BitVector to an element of type a -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> let x = pack (-5 :: Signed 6)
--   
--   >>> unpack x :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
unpack :: (BitPack a, Generic a, GBitPack (Rep a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => BitVector (BitSize a) -> a packXWith :: KnownNat n => (a -> BitVector n) -> a -> BitVector n -- | Pack both arguments to a BitVector and use isLike# to -- compare them. This is a more lentiant comparison than (==), -- behaving more like (but not necessarily exactly the same as) -- std_match in VHDL or casez in Verilog. -- -- Unlike (==), isLike is not symmetric. The reason for this is -- that a defined bit is said to be like an undefined bit, but not -- vice-versa: -- --
--   >>> isLike (12 :: Signed 8) undefined
--   True
--   
--   >>> isLike undefined (12 :: Signed 8)
--   False
--   
-- -- However, it is still trivially reflexive and transitive: -- --
--   >>> :set -XTemplateHaskell
--   
--   >>> let x1 = $(bLit "0010")
--   
--   >>> let x2 = $(bLit "0.10")
--   
--   >>> let x3 = $(bLit "0.1.")
--   
--   >>> isLike x1 x1
--   True
--   
--   >>> isLike x1 x2
--   True
--   
--   >>> isLike x2 x3
--   True
--   
--   >>> isLike x1 x3
--   True
--   
-- -- NB: Not synthesizable isLike :: BitPack a => a -> a -> Bool -- | Coerce a value from one type to another through its bit -- representation. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> bitCoerce (-5 :: Signed 6) :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
bitCoerce :: (BitPack a, BitPack b, BitSize a ~ BitSize b) => a -> b -- | Map a value by first coercing to another type through its bit -- representation. -- --
--   >>> pack (-5 :: Signed 32)
--   0b1111_1111_1111_1111_1111_1111_1111_1011
--   
--   >>> bitCoerceMap @(Vec 4 (BitVector 8)) (replace 1 0) (-5 :: Signed 32)
--   -16711685
--   
--   >>> pack (-16711685 :: Signed 32)
--   0b1111_1111_0000_0000_1111_1111_1111_1011
--   
bitCoerceMap :: forall a b. (BitPack a, BitPack b, BitSize a ~ BitSize b) => (a -> a) -> b -> b packFloat# :: Float -> BitVector 32 unpackFloat# :: BitVector 32 -> Float packDouble# :: Double -> BitVector 64 unpackDouble# :: BitVector 64 -> Double class GBitPack f where { -- | Size of fields. If multiple constructors exist, this is the maximum of -- the sum of each of the constructors fields. type family GFieldSize f :: Nat; -- | Number of constructors this type has. Indirectly indicates how many -- bits are needed to represent the constructor. type family GConstructorCount f :: Nat; } -- | Pack fields of a type. Caller should pack and prepend the constructor -- bits. gPackFields :: GBitPack f => Int -> f a -> (Int, BitVector (GFieldSize f)) -- | Unpack whole type. gUnpack :: GBitPack f => Int -> Int -> BitVector (GFieldSize f) -> f a -- | Zero-extend a Boolean value to a BitVector of the -- appropriate size. -- --
--   >>> boolToBV True :: BitVector 6
--   0b00_0001
--   
--   >>> boolToBV False :: BitVector 6
--   0b00_0000
--   
boolToBV :: KnownNat n => Bool -> BitVector (n + 1) -- | Convert a Bool to a Bit boolToBit :: Bool -> Bit -- | Convert a Bit to a Bool bitToBool :: Bit -> Bool instance (Clash.Class.BitPack.Internal.BitPack a1, GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.BitSize a1), Clash.Class.BitPack.Internal.BitPack (a2, a3), GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.BitSize (a2, a3))) => Clash.Class.BitPack.Internal.BitPack (a1, a2, a3) instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Bool instance GHC.TypeNats.KnownNat n => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Class.BitPack.Internal.BitPack Clash.Sized.Internal.BitVector.Bit instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Int instance Clash.Class.BitPack.Internal.BitPack GHC.Int.Int8 instance Clash.Class.BitPack.Internal.BitPack GHC.Int.Int16 instance Clash.Class.BitPack.Internal.BitPack GHC.Int.Int32 instance Clash.Class.BitPack.Internal.BitPack GHC.Int.Int64 instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Word instance Clash.Class.BitPack.Internal.BitPack GHC.Word.Word8 instance Clash.Class.BitPack.Internal.BitPack GHC.Word.Word16 instance Clash.Class.BitPack.Internal.BitPack GHC.Word.Word32 instance Clash.Class.BitPack.Internal.BitPack GHC.Word.Word64 instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Float instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Double instance Clash.Class.BitPack.Internal.BitPack Foreign.C.Types.CUShort instance Clash.Class.BitPack.Internal.BitPack Numeric.Half.Internal.Half instance Clash.Class.BitPack.Internal.BitPack () instance (Clash.Class.BitPack.Internal.BitPack a, Clash.Class.BitPack.Internal.BitPack b) => Clash.Class.BitPack.Internal.BitPack (a, b) instance Clash.Class.BitPack.Internal.BitPack c => Clash.Class.BitPack.Internal.GBitPack (GHC.Generics.K1 i c) instance Clash.Class.BitPack.Internal.BitPack GHC.Types.Ordering instance (Clash.Class.BitPack.Internal.BitPack a, Clash.Class.BitPack.Internal.BitPack b) => Clash.Class.BitPack.Internal.BitPack (Data.Either.Either a b) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (GHC.Maybe.Maybe a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Data.Complex.Complex a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Data.Ord.Down a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Data.Functor.Identity.Identity a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Data.Functor.Const.Const a b) instance (Clash.Class.BitPack.Internal.BitPack (f a), Clash.Class.BitPack.Internal.BitPack (g a)) => Clash.Class.BitPack.Internal.BitPack (Data.Functor.Product.Product f g a) instance (Clash.Class.BitPack.Internal.BitPack (f a), Clash.Class.BitPack.Internal.BitPack (g a)) => Clash.Class.BitPack.Internal.BitPack (Data.Functor.Sum.Sum f g a) instance Clash.Class.BitPack.Internal.BitPack (f (g a)) => Clash.Class.BitPack.Internal.BitPack (Data.Functor.Compose.Compose f g a) instance Clash.Class.BitPack.Internal.GBitPack a => Clash.Class.BitPack.Internal.GBitPack (GHC.Generics.M1 m d a) instance (GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.GFieldSize g), GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.GFieldSize f), GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.GConstructorCount f), Clash.Class.BitPack.Internal.GBitPack f, Clash.Class.BitPack.Internal.GBitPack g) => Clash.Class.BitPack.Internal.GBitPack (f GHC.Generics.:+: g) instance (GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.GFieldSize g), GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.GFieldSize f), Clash.Class.BitPack.Internal.GBitPack f, Clash.Class.BitPack.Internal.GBitPack g) => Clash.Class.BitPack.Internal.GBitPack (f GHC.Generics.:*: g) instance Clash.Class.BitPack.Internal.GBitPack GHC.Generics.U1 module Clash.Explicit.BlockRam.Internal -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) [MemBlob] :: (KnownNat n, KnownNat m) => {memBlobRunsLen :: !Int, memBlobRuns :: Addr#, memBlobEndsLen :: !Int, memBlobEnds :: Addr#} -> MemBlob n m -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] unpackMemBlob0 :: forall n m. MemBlob n m -> IO [BitVector m] packBVs :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> Either String (Int, ByteString, ByteString) packAsNats :: forall a f. Foldable f => Int -> (a -> Natural) -> f a -> (ByteString, ByteString) unpackNats :: Int -> Int -> ByteString -> ByteString -> [Natural] unpackW64s :: ByteString -> [Word64] unpackEnds :: Int -> Int -> [Word64] -> [Natural] instance GHC.Show.Show (Clash.Explicit.BlockRam.Internal.MemBlob n m) module Clash.Class.BitPack.BitReduction -- | Are all bits set to '1'? -- --
--   >>> pack (-2 :: Signed 6)
--   0b11_1110
--   
--   >>> reduceAnd (-2 :: Signed 6)
--   0
--   
--   >>> pack (-1 :: Signed 6)
--   0b11_1111
--   
--   >>> reduceAnd (-1 :: Signed 6)
--   1
--   
-- -- Zero width types will evaluate to '1': -- --
--   >>> reduceAnd (0 :: Unsigned 0)
--   1
--   
reduceAnd :: BitPack a => a -> Bit -- | Is there at least one bit set to '1'? -- --
--   >>> pack (5 :: Signed 6)
--   0b00_0101
--   
--   >>> reduceOr (5 :: Signed 6)
--   1
--   
--   >>> pack (0 :: Signed 6)
--   0b00_0000
--   
--   >>> reduceOr (0 :: Signed 6)
--   0
--   
-- -- Zero width types will evaluate to '0': -- --
--   >>> reduceOr (0 :: Unsigned 0)
--   0
--   
reduceOr :: BitPack a => a -> Bit -- | Is the number of bits set to '1' uneven? -- --
--   >>> pack (5 :: Signed 6)
--   0b00_0101
--   
--   >>> reduceXor (5 :: Signed 6)
--   0
--   
--   >>> pack (28 :: Signed 6)
--   0b01_1100
--   
--   >>> reduceXor (28 :: Signed 6)
--   1
--   
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> reduceXor (-5 :: Signed 6)
--   1
--   
-- -- Zero width types will evaluate to '0': -- --
--   >>> reduceXor (0 :: Unsigned 0)
--   0
--   
reduceXor :: BitPack a => a -> Bit module Clash.Class.BitPack.BitIndex -- | Get the bit at the specified bit index. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> (7 :: Unsigned 6) ! 1
--   1
--   
--   >>> (7 :: Unsigned 6) ! 5
--   0
--   
--   >>> (7 :: Unsigned 6) ! 6
--   *** Exception: (!): 6 is out of range [5..0]
--   ...
--   
(!) :: (BitPack a, Enum i) => a -> i -> Bit -- | Get a slice between bit index m and and bit index n. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> slice d4 d2 (7 :: Unsigned 6)
--   0b001
--   
-- --
--   >>> slice d6 d4 (7 :: Unsigned 6)
--   
--   <interactive>:...
--       • Couldn't match type ‘7 + i0’ with ‘6’
--           arising from a use of ‘slice’
--         The type variable ‘i0’ is ambiguous
--       • In the expression: slice d6 d4 (7 :: Unsigned 6)
--         In an equation for ‘it’: it = slice d6 d4 (7 :: Unsigned 6)
--   
slice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> a -> BitVector ((m + 1) - n) -- | Split a value of a bit size m + n into a tuple of values with -- size m and size n. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> split (7 :: Unsigned 6) :: (BitVector 2, BitVector 4)
--   (0b00,0b0111)
--   
split :: (BitPack a, BitSize a ~ (m + n), KnownNat n) => a -> (BitVector m, BitVector n) -- | Set the bit at the specified index -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> replaceBit 4 0 (-5 :: Signed 6)
--   -21
--   
--   >>> pack (-21 :: Signed 6)
--   0b10_1011
--   
--   >>> replaceBit 5 0 (-5 :: Signed 6)
--   27
--   
--   >>> pack (27 :: Signed 6)
--   0b01_1011
--   
--   >>> replaceBit 6 0 (-5 :: Signed 6)
--   *** Exception: replaceBit: 6 is out of range [5..0]
--   ...
--   
replaceBit :: (BitPack a, Enum i) => i -> Bit -> a -> a -- | Set the bits between bit index m and bit index n. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> setSlice d4 d3 0 (-5 :: Signed 6)
--   -29
--   
--   >>> pack (-29 :: Signed 6)
--   0b10_0011
--   
-- --
--   >>> setSlice d6 d5 0 (-5 :: Signed 6)
--   
--   <interactive>:...
--       • Couldn't match type ‘7 + i0’ with ‘6’
--           arising from a use of ‘setSlice’
--         The type variable ‘i0’ is ambiguous
--       • In the expression: setSlice d6 d5 0 (- 5 :: Signed 6)
--         In an equation for ‘it’: it = setSlice d6 d5 0 (- 5 :: Signed 6)
--   
setSlice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> BitVector ((m + 1) - n) -> a -> a -- | Get the most significant bit. -- --
--   >>> pack (-4 :: Signed 6)
--   0b11_1100
--   
--   >>> msb (-4 :: Signed 6)
--   1
--   
--   >>> pack (4 :: Signed 6)
--   0b00_0100
--   
--   >>> msb (4 :: Signed 6)
--   0
--   
msb :: BitPack a => a -> Bit -- | Get the least significant bit. -- --
--   >>> pack (-9 :: Signed 6)
--   0b11_0111
--   
--   >>> lsb (-9 :: Signed 6)
--   1
--   
--   >>> pack (-8 :: Signed 6)
--   0b11_1000
--   
--   >>> lsb (-8 :: Signed 6)
--   0
--   
lsb :: BitPack a => a -> Bit module Clash.Class.BitPack -- | Convert data to/from a BitVector. This allows functions to be -- defined on the underlying representation of data, while exposing a -- nicer API using pack / unpack at the boundaries. For -- example: -- --
--   f :: forall a b. (BitPack a, BitPack b) => a -> b
--   f = unpack . go . pack
--    where
--     go :: BitVector (BitSize a) -> BitVector (BitSize b)
--     go = _ -- A function on the underlying bit vector
--   
-- -- A type should only implement this class if it has a statically known -- size, as otherwise it is not possible to determine how many bits are -- needed to represent values. This means that types such as [a] -- cannot have BitPack instances, as even if a has a -- statically known size, the length of the list cannot be known in -- advance. -- -- It is not possible to give data a custom bit representation by -- providing a BitPack instance. A BitPack instance -- allows no creativity and should always accurately reflect the bit -- representation of the data in HDL. You should always derive -- (Generic, BitPack) unless you use a custom data -- representation, in which case you should use deriveBitPack. -- Custom encodings can be created with -- Clash.Annotations.BitRepresentation and -- Clash.Annotations.BitRepresentation.Deriving. -- -- If the BitPack instance does not accurately match the bit -- representation of the data in HDL, Clash designs will exhibit -- incorrect behavior in various places. -- -- Clash provides some generic functions on packable types in the -- prelude, such as indexing into packable stuctures (see -- Clash.Class.BitPack.BitIndex) and bitwise reduction of packable -- data (see Clash.Class.BitPack.BitReduction). class KnownNat (BitSize a) => BitPack a where { -- | Number of Bits needed to represents elements of type a -- -- Can be derived using Generics: -- --
    --   import Clash.Prelude
    --   import GHC.Generics
    --   
    --   data MyProductType = MyProductType { a :: Int, b :: Bool }
    --     deriving (Generic, BitPack)
    --   
type family BitSize a :: Nat; type BitSize a = (CLog 2 (GConstructorCount (Rep a))) + (GFieldSize (Rep a)); } -- | Convert element of type a to a BitVector -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
pack :: BitPack a => a -> BitVector (BitSize a) -- | Convert element of type a to a BitVector -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
pack :: (BitPack a, Generic a, GBitPack (Rep a), KnownNat (BitSize a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => a -> BitVector (BitSize a) -- | Convert a BitVector to an element of type a -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> let x = pack (-5 :: Signed 6)
--   
--   >>> unpack x :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
unpack :: BitPack a => BitVector (BitSize a) -> a -- | Convert a BitVector to an element of type a -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> let x = pack (-5 :: Signed 6)
--   
--   >>> unpack x :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
unpack :: (BitPack a, Generic a, GBitPack (Rep a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => BitVector (BitSize a) -> a -- | Pack both arguments to a BitVector and use isLike# to -- compare them. This is a more lentiant comparison than (==), -- behaving more like (but not necessarily exactly the same as) -- std_match in VHDL or casez in Verilog. -- -- Unlike (==), isLike is not symmetric. The reason for this is -- that a defined bit is said to be like an undefined bit, but not -- vice-versa: -- --
--   >>> isLike (12 :: Signed 8) undefined
--   True
--   
--   >>> isLike undefined (12 :: Signed 8)
--   False
--   
-- -- However, it is still trivially reflexive and transitive: -- --
--   >>> :set -XTemplateHaskell
--   
--   >>> let x1 = $(bLit "0010")
--   
--   >>> let x2 = $(bLit "0.10")
--   
--   >>> let x3 = $(bLit "0.1.")
--   
--   >>> isLike x1 x1
--   True
--   
--   >>> isLike x1 x2
--   True
--   
--   >>> isLike x2 x3
--   True
--   
--   >>> isLike x1 x3
--   True
--   
-- -- NB: Not synthesizable isLike :: BitPack a => a -> a -> Bool -- | Coerce a value from one type to another through its bit -- representation. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> bitCoerce (-5 :: Signed 6) :: Unsigned 6
--   59
--   
--   >>> pack (59 :: Unsigned 6)
--   0b11_1011
--   
bitCoerce :: (BitPack a, BitPack b, BitSize a ~ BitSize b) => a -> b -- | Map a value by first coercing to another type through its bit -- representation. -- --
--   >>> pack (-5 :: Signed 32)
--   0b1111_1111_1111_1111_1111_1111_1111_1011
--   
--   >>> bitCoerceMap @(Vec 4 (BitVector 8)) (replace 1 0) (-5 :: Signed 32)
--   -16711685
--   
--   >>> pack (-16711685 :: Signed 32)
--   0b1111_1111_0000_0000_1111_1111_1111_1011
--   
bitCoerceMap :: forall a b. (BitPack a, BitPack b, BitSize a ~ BitSize b) => (a -> a) -> b -> b -- | Zero-extend a Boolean value to a BitVector of the -- appropriate size. -- --
--   >>> boolToBV True :: BitVector 6
--   0b00_0001
--   
--   >>> boolToBV False :: BitVector 6
--   0b00_0000
--   
boolToBV :: KnownNat n => Bool -> BitVector (n + 1) -- | Convert a Bool to a Bit boolToBit :: Bool -> Bit -- | Convert a Bit to a Bool bitToBool :: Bit -> Bool packXWith :: KnownNat n => (a -> BitVector n) -> a -> BitVector n -- | Get the bit at the specified bit index. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> (7 :: Unsigned 6) ! 1
--   1
--   
--   >>> (7 :: Unsigned 6) ! 5
--   0
--   
--   >>> (7 :: Unsigned 6) ! 6
--   *** Exception: (!): 6 is out of range [5..0]
--   ...
--   
(!) :: (BitPack a, Enum i) => a -> i -> Bit -- | Get a slice between bit index m and and bit index n. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> slice d4 d2 (7 :: Unsigned 6)
--   0b001
--   
-- --
--   >>> slice d6 d4 (7 :: Unsigned 6)
--   
--   <interactive>:...
--       • Couldn't match type ‘7 + i0’ with ‘6’
--           arising from a use of ‘slice’
--         The type variable ‘i0’ is ambiguous
--       • In the expression: slice d6 d4 (7 :: Unsigned 6)
--         In an equation for ‘it’: it = slice d6 d4 (7 :: Unsigned 6)
--   
slice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> a -> BitVector ((m + 1) - n) -- | Split a value of a bit size m + n into a tuple of values with -- size m and size n. -- --
--   >>> pack (7 :: Unsigned 6)
--   0b00_0111
--   
--   >>> split (7 :: Unsigned 6) :: (BitVector 2, BitVector 4)
--   (0b00,0b0111)
--   
split :: (BitPack a, BitSize a ~ (m + n), KnownNat n) => a -> (BitVector m, BitVector n) -- | Set the bit at the specified index -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> replaceBit 4 0 (-5 :: Signed 6)
--   -21
--   
--   >>> pack (-21 :: Signed 6)
--   0b10_1011
--   
--   >>> replaceBit 5 0 (-5 :: Signed 6)
--   27
--   
--   >>> pack (27 :: Signed 6)
--   0b01_1011
--   
--   >>> replaceBit 6 0 (-5 :: Signed 6)
--   *** Exception: replaceBit: 6 is out of range [5..0]
--   ...
--   
replaceBit :: (BitPack a, Enum i) => i -> Bit -> a -> a -- | Set the bits between bit index m and bit index n. -- -- NB: Bit indices are DESCENDING. -- --
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> setSlice d4 d3 0 (-5 :: Signed 6)
--   -29
--   
--   >>> pack (-29 :: Signed 6)
--   0b10_0011
--   
-- --
--   >>> setSlice d6 d5 0 (-5 :: Signed 6)
--   
--   <interactive>:...
--       • Couldn't match type ‘7 + i0’ with ‘6’
--           arising from a use of ‘setSlice’
--         The type variable ‘i0’ is ambiguous
--       • In the expression: setSlice d6 d5 0 (- 5 :: Signed 6)
--         In an equation for ‘it’: it = setSlice d6 d5 0 (- 5 :: Signed 6)
--   
setSlice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> BitVector ((m + 1) - n) -> a -> a -- | Get the most significant bit. -- --
--   >>> pack (-4 :: Signed 6)
--   0b11_1100
--   
--   >>> msb (-4 :: Signed 6)
--   1
--   
--   >>> pack (4 :: Signed 6)
--   0b00_0100
--   
--   >>> msb (4 :: Signed 6)
--   0
--   
msb :: BitPack a => a -> Bit -- | Get the least significant bit. -- --
--   >>> pack (-9 :: Signed 6)
--   0b11_0111
--   
--   >>> lsb (-9 :: Signed 6)
--   1
--   
--   >>> pack (-8 :: Signed 6)
--   0b11_1000
--   
--   >>> lsb (-8 :: Signed 6)
--   0
--   
lsb :: BitPack a => a -> Bit -- | Are all bits set to '1'? -- --
--   >>> pack (-2 :: Signed 6)
--   0b11_1110
--   
--   >>> reduceAnd (-2 :: Signed 6)
--   0
--   
--   >>> pack (-1 :: Signed 6)
--   0b11_1111
--   
--   >>> reduceAnd (-1 :: Signed 6)
--   1
--   
-- -- Zero width types will evaluate to '1': -- --
--   >>> reduceAnd (0 :: Unsigned 0)
--   1
--   
reduceAnd :: BitPack a => a -> Bit -- | Is there at least one bit set to '1'? -- --
--   >>> pack (5 :: Signed 6)
--   0b00_0101
--   
--   >>> reduceOr (5 :: Signed 6)
--   1
--   
--   >>> pack (0 :: Signed 6)
--   0b00_0000
--   
--   >>> reduceOr (0 :: Signed 6)
--   0
--   
-- -- Zero width types will evaluate to '0': -- --
--   >>> reduceOr (0 :: Unsigned 0)
--   0
--   
reduceOr :: BitPack a => a -> Bit -- | Is the number of bits set to '1' uneven? -- --
--   >>> pack (5 :: Signed 6)
--   0b00_0101
--   
--   >>> reduceXor (5 :: Signed 6)
--   0
--   
--   >>> pack (28 :: Signed 6)
--   0b01_1100
--   
--   >>> reduceXor (28 :: Signed 6)
--   1
--   
--   >>> pack (-5 :: Signed 6)
--   0b11_1011
--   
--   >>> reduceXor (-5 :: Signed 6)
--   1
--   
-- -- Zero width types will evaluate to '0': -- --
--   >>> reduceXor (0 :: Unsigned 0)
--   0
--   
reduceXor :: BitPack a => a -> Bit module Clash.Class.Parity -- | Determine whether value is odd or even class Parity a -- | Check if value is even -- --
--   >>> even (4 :: Unsigned 4)
--   True
--   
even :: Parity a => a -> Bool -- | Check if value is odd -- --
--   >>> odd (4 :: Unsigned 4)
--   False
--   
odd :: Parity a => a -> Bool instance Clash.Class.Parity.Parity GHC.Integer.Type.Integer instance GHC.TypeNats.KnownNat n => Clash.Class.Parity.Parity (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Class.Parity.Parity GHC.Types.Bool instance Clash.Class.Parity.Parity Foreign.C.Types.CUShort instance Clash.Class.Parity.Parity GHC.Types.Word instance Clash.Class.Parity.Parity GHC.Word.Word8 instance Clash.Class.Parity.Parity GHC.Word.Word16 instance Clash.Class.Parity.Parity GHC.Word.Word32 instance Clash.Class.Parity.Parity GHC.Word.Word64 instance Clash.Class.Parity.Parity GHC.Types.Int instance Clash.Class.Parity.Parity GHC.Int.Int8 instance Clash.Class.Parity.Parity GHC.Int.Int16 instance Clash.Class.Parity.Parity GHC.Int.Int32 instance Clash.Class.Parity.Parity GHC.Int.Int64 module Clash.Sized.Internal.Unsigned -- | Arbitrary-width unsigned integer represented by n bits -- -- Given n bits, an Unsigned n number has a -- range of: [0 .. 2^n-1] -- -- -- --
--   >>> maxBound :: Unsigned 3
--   7
--   
--   >>> minBound :: Unsigned 3
--   0
--   
--   >>> read (show (maxBound :: Unsigned 3)) :: Unsigned 3
--   7
--   
--   >>> 1 + 2 :: Unsigned 3
--   3
--   
--   >>> 2 + 6 :: Unsigned 3
--   0
--   
--   >>> 1 - 3 :: Unsigned 3
--   6
--   
--   >>> 2 * 3 :: Unsigned 3
--   6
--   
--   >>> 2 * 4 :: Unsigned 3
--   0
--   
--   >>> (2 :: Unsigned 3) `mul` (4 :: Unsigned 3) :: Unsigned 6
--   8
--   
--   >>> (2 :: Unsigned 3) `add` (6 :: Unsigned 3) :: Unsigned 4
--   8
--   
--   >>> satAdd SatSymmetric 2 6 :: Unsigned 3
--   7
--   
--   >>> satSub SatSymmetric 2 3 :: Unsigned 3
--   0
--   
-- -- Unsigned has the type role -- --
--   >>> :i Unsigned
--   type role Unsigned nominal
--   ...
--   
-- -- as it is not safe to coerce between different width Unsigned. To -- change the width, use the functions in the Resize class. newtype Unsigned (n :: Nat) -- | The constructor, U, and the field, unsafeToNatural, are -- not synthesizable. U :: Natural -> Unsigned (n :: Nat) [unsafeToNatural] :: Unsigned (n :: Nat) -> Natural size# :: KnownNat n => Unsigned n -> Int pack# :: Unsigned n -> BitVector n unpack# :: KnownNat n => BitVector n -> Unsigned n eq# :: Unsigned n -> Unsigned n -> Bool neq# :: Unsigned n -> Unsigned n -> Bool lt# :: Unsigned n -> Unsigned n -> Bool ge# :: Unsigned n -> Unsigned n -> Bool gt# :: Unsigned n -> Unsigned n -> Bool le# :: Unsigned n -> Unsigned n -> Bool toEnum# :: forall n. KnownNat n => Int -> Unsigned n fromEnum# :: forall n. KnownNat n => Unsigned n -> Int enumFrom# :: forall n. KnownNat n => Unsigned n -> [Unsigned n] enumFromThen# :: forall n. KnownNat n => Unsigned n -> Unsigned n -> [Unsigned n] enumFromTo# :: forall n. KnownNat n => Unsigned n -> Unsigned n -> [Unsigned n] enumFromThenTo# :: forall n. KnownNat n => Unsigned n -> Unsigned n -> Unsigned n -> [Unsigned n] minBound# :: Unsigned n maxBound# :: forall n. KnownNat n => Unsigned n (+#) :: forall n. KnownNat n => Unsigned n -> Unsigned n -> Unsigned n (-#) :: forall n. KnownNat n => Unsigned n -> Unsigned n -> Unsigned n (*#) :: forall n. KnownNat n => Unsigned n -> Unsigned n -> Unsigned n negate# :: forall n. KnownNat n => Unsigned n -> Unsigned n fromInteger# :: forall n. KnownNat n => Integer -> Unsigned n plus# :: Unsigned m -> Unsigned n -> Unsigned (Max m n + 1) minus# :: forall m n. (KnownNat m, KnownNat n) => Unsigned m -> Unsigned n -> Unsigned (Max m n + 1) times# :: Unsigned m -> Unsigned n -> Unsigned (m + n) quot# :: Unsigned n -> Unsigned n -> Unsigned n rem# :: Unsigned n -> Unsigned n -> Unsigned n toInteger# :: Unsigned n -> Integer and# :: Unsigned n -> Unsigned n -> Unsigned n or# :: Unsigned n -> Unsigned n -> Unsigned n xor# :: Unsigned n -> Unsigned n -> Unsigned n complement# :: forall n. KnownNat n => Unsigned n -> Unsigned n shiftL# :: forall n. KnownNat n => Unsigned n -> Int -> Unsigned n shiftR# :: forall n. KnownNat n => Unsigned n -> Int -> Unsigned n rotateL# :: forall n. KnownNat n => Unsigned n -> Int -> Unsigned n rotateR# :: forall n. KnownNat n => Unsigned n -> Int -> Unsigned n resize# :: forall n m. KnownNat m => Unsigned n -> Unsigned m unsignedToWord :: Unsigned 64 -> Word unsigned8toWord8 :: Unsigned 8 -> Word8 unsigned16toWord16 :: Unsigned 16 -> Word16 unsigned32toWord32 :: Unsigned 32 -> Word32 instance GHC.Generics.Generic (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Data.Data.Data (Clash.Sized.Internal.Unsigned.Unsigned n) instance Control.DeepSeq.NFData (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.Show.Show (Clash.Sized.Internal.Unsigned.Unsigned n) instance Clash.XException.ShowX (Clash.Sized.Internal.Unsigned.Unsigned n) instance Clash.XException.NFDataX (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Read.Read (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.Classes.Eq (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.Classes.Ord (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Enum (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Bounded (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Num.Num (Clash.Sized.Internal.Unsigned.Unsigned n) instance (GHC.TypeNats.KnownNat m, GHC.TypeNats.KnownNat n) => Clash.Class.Num.ExtendingNum (Clash.Sized.Internal.Unsigned.Unsigned m) (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Real.Real (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Real.Integral (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Text.Printf.PrintfArg (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Clash.Class.Parity.Parity (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Data.Bits.Bits (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Data.Bits.FiniteBits (Clash.Sized.Internal.Unsigned.Unsigned n) instance Clash.Class.Resize.Resize Clash.Sized.Internal.Unsigned.Unsigned instance Data.Default.Class.Default (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Clash.Class.Num.SaturatingNum (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Control.Lens.At.Ixed (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => GHC.Ix.Ix (Clash.Sized.Internal.Unsigned.Unsigned n) module Clash.Sized.Unsigned -- | Arbitrary-width unsigned integer represented by n bits -- -- Given n bits, an Unsigned n number has a -- range of: [0 .. 2^n-1] -- -- -- --
--   >>> maxBound :: Unsigned 3
--   7
--   
--   >>> minBound :: Unsigned 3
--   0
--   
--   >>> read (show (maxBound :: Unsigned 3)) :: Unsigned 3
--   7
--   
--   >>> 1 + 2 :: Unsigned 3
--   3
--   
--   >>> 2 + 6 :: Unsigned 3
--   0
--   
--   >>> 1 - 3 :: Unsigned 3
--   6
--   
--   >>> 2 * 3 :: Unsigned 3
--   6
--   
--   >>> 2 * 4 :: Unsigned 3
--   0
--   
--   >>> (2 :: Unsigned 3) `mul` (4 :: Unsigned 3) :: Unsigned 6
--   8
--   
--   >>> (2 :: Unsigned 3) `add` (6 :: Unsigned 3) :: Unsigned 4
--   8
--   
--   >>> satAdd SatSymmetric 2 6 :: Unsigned 3
--   7
--   
--   >>> satSub SatSymmetric 2 3 :: Unsigned 3
--   0
--   
-- -- Unsigned has the type role -- --
--   >>> :i Unsigned
--   type role Unsigned nominal
--   ...
--   
-- -- as it is not safe to coerce between different width Unsigned. To -- change the width, use the functions in the Resize class. data Unsigned (n :: Nat) module Clash.Sized.Internal.Signed -- | Arbitrary-width signed integer represented by n bits, -- including the sign bit -- -- Uses standard 2-complements representation. Meaning that, given -- n bits, a Signed n number has a range of: -- [-(2^(n-1)) .. 2^(n-1)-1] for n > 0. -- When n = 0, both the min and max bound are 0. -- -- -- --
--   >>> maxBound :: Signed 3
--   3
--   
--   >>> minBound :: Signed 3
--   -4
--   
--   >>> read (show (minBound :: Signed 3)) :: Signed 3
--   -4
--   
--   >>> 1 + 2 :: Signed 3
--   3
--   
--   >>> 2 + 3 :: Signed 3
--   -3
--   
--   >>> (-2) + (-3) :: Signed 3
--   3
--   
--   >>> 2 * 3 :: Signed 4
--   6
--   
--   >>> 2 * 4 :: Signed 4
--   -8
--   
--   >>> (2 :: Signed 3) `mul` (4 :: Signed 4) :: Signed 7
--   8
--   
--   >>> (2 :: Signed 3) `add` (3 :: Signed 3) :: Signed 4
--   5
--   
--   >>> (-2 :: Signed 3) `add` (-3 :: Signed 3) :: Signed 4
--   -5
--   
--   >>> satAdd SatSymmetric 2 3 :: Signed 3
--   3
--   
--   >>> satAdd SatSymmetric (-2) (-3) :: Signed 3
--   -3
--   
-- -- Signed has the type role -- --
--   >>> :i Signed
--   type role Signed nominal
--   ...
--   
-- -- as it is not safe to coerce between different width Signed. To change -- the width, use the functions in the Resize class. newtype Signed (n :: Nat) -- | The constructor, S, and the field, unsafeToInteger, are -- not synthesizable. S :: Integer -> Signed (n :: Nat) [unsafeToInteger] :: Signed (n :: Nat) -> Integer size# :: KnownNat n => Signed n -> Int pack# :: forall n. KnownNat n => Signed n -> BitVector n unpack# :: forall n. KnownNat n => BitVector n -> Signed n eq# :: Signed n -> Signed n -> Bool neq# :: Signed n -> Signed n -> Bool lt# :: Signed n -> Signed n -> Bool ge# :: Signed n -> Signed n -> Bool gt# :: Signed n -> Signed n -> Bool le# :: Signed n -> Signed n -> Bool toEnum# :: forall n. KnownNat n => Int -> Signed n fromEnum# :: forall n. KnownNat n => Signed n -> Int enumFrom# :: forall n. KnownNat n => Signed n -> [Signed n] enumFromThen# :: forall n. KnownNat n => Signed n -> Signed n -> [Signed n] enumFromTo# :: forall n. KnownNat n => Signed n -> Signed n -> [Signed n] enumFromThenTo# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n -> [Signed n] minBound# :: forall n. KnownNat n => Signed n maxBound# :: forall n. KnownNat n => Signed n (+#) :: forall n. KnownNat n => Signed n -> Signed n -> Signed n (-#) :: forall n. KnownNat n => Signed n -> Signed n -> Signed n (*#) :: forall n. KnownNat n => Signed n -> Signed n -> Signed n negate# :: forall n. KnownNat n => Signed n -> Signed n abs# :: forall n. KnownNat n => Signed n -> Signed n fromInteger# :: forall n. KnownNat n => Integer -> Signed (n :: Nat) plus# :: Signed m -> Signed n -> Signed (Max m n + 1) minus# :: Signed m -> Signed n -> Signed (Max m n + 1) times# :: Signed m -> Signed n -> Signed (m + n) quot# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n rem# :: Signed n -> Signed n -> Signed n div# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n mod# :: Signed n -> Signed n -> Signed n toInteger# :: Signed n -> Integer and# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n or# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n xor# :: forall n. KnownNat n => Signed n -> Signed n -> Signed n complement# :: forall n. KnownNat n => Signed n -> Signed n shiftL# :: forall n. KnownNat n => Signed n -> Int -> Signed n shiftR# :: forall n. KnownNat n => Signed n -> Int -> Signed n rotateL# :: forall n. KnownNat n => Signed n -> Int -> Signed n rotateR# :: forall n. KnownNat n => Signed n -> Int -> Signed n resize# :: forall m n. (KnownNat n, KnownNat m) => Signed n -> Signed m truncateB# :: forall m n. KnownNat m => Signed (m + n) -> Signed m minBoundSym# :: KnownNat n => Signed n instance GHC.Generics.Generic (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Data.Data.Data (Clash.Sized.Internal.Signed.Signed n) instance Clash.XException.NFDataX (Clash.Sized.Internal.Signed.Signed n) instance Control.DeepSeq.NFData (Clash.Sized.Internal.Signed.Signed n) instance GHC.Show.Show (Clash.Sized.Internal.Signed.Signed n) instance Clash.XException.ShowX (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Read.Read (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Internal.Signed.Signed n) instance GHC.Classes.Eq (Clash.Sized.Internal.Signed.Signed n) instance GHC.Classes.Ord (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Enum (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Bounded (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Num.Num (Clash.Sized.Internal.Signed.Signed n) instance Clash.Class.Num.ExtendingNum (Clash.Sized.Internal.Signed.Signed m) (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Real.Real (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Real.Integral (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Text.Printf.PrintfArg (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Clash.Class.Parity.Parity (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Data.Bits.Bits (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Data.Bits.FiniteBits (Clash.Sized.Internal.Signed.Signed n) instance Clash.Class.Resize.Resize Clash.Sized.Internal.Signed.Signed instance GHC.TypeNats.KnownNat n => Data.Default.Class.Default (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Clash.Class.Num.SaturatingNum (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Control.Lens.At.Ixed (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => GHC.Ix.Ix (Clash.Sized.Internal.Signed.Signed n) module Clash.Sized.Signed -- | Arbitrary-width signed integer represented by n bits, -- including the sign bit -- -- Uses standard 2-complements representation. Meaning that, given -- n bits, a Signed n number has a range of: -- [-(2^(n-1)) .. 2^(n-1)-1] for n > 0. -- When n = 0, both the min and max bound are 0. -- -- -- --
--   >>> maxBound :: Signed 3
--   3
--   
--   >>> minBound :: Signed 3
--   -4
--   
--   >>> read (show (minBound :: Signed 3)) :: Signed 3
--   -4
--   
--   >>> 1 + 2 :: Signed 3
--   3
--   
--   >>> 2 + 3 :: Signed 3
--   -3
--   
--   >>> (-2) + (-3) :: Signed 3
--   3
--   
--   >>> 2 * 3 :: Signed 4
--   6
--   
--   >>> 2 * 4 :: Signed 4
--   -8
--   
--   >>> (2 :: Signed 3) `mul` (4 :: Signed 4) :: Signed 7
--   8
--   
--   >>> (2 :: Signed 3) `add` (3 :: Signed 3) :: Signed 4
--   5
--   
--   >>> (-2 :: Signed 3) `add` (-3 :: Signed 3) :: Signed 4
--   -5
--   
--   >>> satAdd SatSymmetric 2 3 :: Signed 3
--   3
--   
--   >>> satAdd SatSymmetric (-2) (-3) :: Signed 3
--   -3
--   
-- -- Signed has the type role -- --
--   >>> :i Signed
--   type role Signed nominal
--   ...
--   
-- -- as it is not safe to coerce between different width Signed. To change -- the width, use the functions in the Resize class. data Signed (n :: Nat) -- | Fixed point numbers -- -- -- -- BEWARE: rounding by truncation can introduce errors larger than -- naively assumed; e.g. for Fixed 16 1, rounding by truncation -- turns the real number 4.99 to 4.5, not 5.0, i.e. an error or 0.49 -- instead of 0.01 -- -- BEWARE: rounding by truncation introduces a sign bias! -- -- -- --

Reasoning about precision

-- -- Givens the real numbers A and B, and the corresponding -- fixed point numbers FA+-da and FB+db, where da -- and db denote the (potential) error introduced by truncation -- w.r.t. the original A and B, the arithmetic operators on -- fixed point numbers have the following error propagation properties: -- -- -- --

Additional error from truncation

-- -- Given: -- --
--   >>> 4.13 :: UFixed 16 3
--   4.125
--   
--   >>> 20.9 :: UFixed 16 3
--   20.875
--   
-- -- The expected error that we would get from multiplication is: -- 20.875*0.005 + 4.125*0.025 + 0.025*0.005 = 0.207625 -- --
--   >>> 4.13 * 20.9 :: Double
--   86.317
--   
--   >>> (4.13 :: UFixed 16 3) `mul` (20.9 :: UFixed 16 3) :: UFixed 32 6
--   86.109375
--   
--   >>> 86.109375 + 0.207625 :: Double
--   86.317
--   
-- -- However the 0.109375 is smaller than 2^-3, so the -- regular multiplication operator that uses truncation introduces an -- additional error of 0.109375: -- --
--   >>> (4.13 :: UFixed 16 3) * (20.9 :: UFixed 16 3) :: UFixed 16 3
--   86.0
--   
module Clash.Sized.Fixed -- | Signed Fixed-point number, with int integer bits -- (including sign-bit) and frac fractional bits. -- -- -- --
--   >>> maxBound :: SFixed 3 4
--   3.9375
--   
--   >>> minBound :: SFixed 3 4
--   -4.0
--   
--   >>> read (show (maxBound :: SFixed 3 4)) :: SFixed 3 4
--   3.9375
--   
--   >>> 1 + 2 :: SFixed 3 4
--   3.0
--   
--   >>> 2 + 3 :: SFixed 3 4
--   3.9375
--   
--   >>> (-2) + (-3) :: SFixed 3 4
--   -4.0
--   
--   >>> 1.375 * (-0.8125) :: SFixed 3 4
--   -1.125
--   
--   >>> (1.375 :: SFixed 3 4) `mul` (-0.8125 :: SFixed 3 4) :: SFixed 6 8
--   -1.1171875
--   
--   >>> (2 :: SFixed 3 4) `add` (3 :: SFixed 3 4) :: SFixed 4 4
--   5.0
--   
--   >>> (-2 :: SFixed 3 4) `add` (-3 :: SFixed 3 4) :: SFixed 4 4
--   -5.0
--   
type SFixed = Fixed Signed -- | Treat a Signed integer as a Signed -- Fixed-point integer -- --
--   >>> sf d4 (-22 :: Signed 7)
--   -1.375
--   
sf :: SNat frac -> Signed (int + frac) -> SFixed int frac -- | See the underlying representation of a Signed Fixed-point integer unSF :: SFixed int frac -> Signed (int + frac) -- | Unsigned Fixed-point number, with int integer bits and -- frac fractional bits -- -- -- --
--   >>> maxBound :: UFixed 3 4
--   7.9375
--   
--   >>> minBound :: UFixed 3 4
--   0.0
--   
--   >>> 1 + 2 :: UFixed 3 4
--   3.0
--   
--   >>> 2 + 6 :: UFixed 3 4
--   7.9375
--   
--   >>> 1 - 3 :: UFixed 3 4
--   0.0
--   
--   >>> 1.375 * 0.8125 :: UFixed 3 4
--   1.0625
--   
--   >>> (1.375 :: UFixed 3 4) `mul` (0.8125 :: UFixed 3 4) :: UFixed 6 8
--   1.1171875
--   
--   >>> (2 :: UFixed 3 4) `add` (6 :: UFixed 3 4) :: UFixed 4 4
--   8.0
--   
-- -- However, sub does not saturate to minBound on underflow: -- --
--   >>> (1 :: UFixed 3 4) `sub` (3 :: UFixed 3 4) :: UFixed 4 4
--   14.0
--   
type UFixed = Fixed Unsigned -- | Treat an Unsigned integer as a Unsigned -- Fixed-point number -- --
--   >>> uf d4 (92 :: Unsigned 7)
--   5.75
--   
uf :: SNat frac -> Unsigned (int + frac) -> UFixed int frac -- | See the underlying representation of an Unsigned Fixed-point integer unUF :: UFixed int frac -> Unsigned (int + frac) -- | Fixed point division -- -- When used in a polymorphic setting, use the following Constraint -- synonyms for less verbose type signatures: -- -- divide :: DivideC rep int1 frac1 int2 frac2 => Fixed rep int1 frac1 -> Fixed rep int2 frac2 -> Fixed rep ((int1 + frac2) + 1) (int2 + frac1) -- | Convert, at compile-time, a Double constant to a -- Fixed-point literal. The conversion saturates on -- overflow, and uses truncation as its rounding method. -- -- So when you type: -- --
--   n = $$(fLit pi) :: SFixed 4 4
--   
-- -- The compiler sees: -- --
--   n = Fixed (fromInteger 50) :: SFixed 4 4
--   
-- -- Upon evaluation you see that the value is rounded / truncated in -- accordance to the fixed point representation: -- --
--   >>> n
--   3.125
--   
-- -- Further examples: -- --
--   >>> sin 0.5 :: Double
--   0.479425538604203
--   
--   >>> $$(fLit (sin 0.5)) :: SFixed 1 8
--   0.4765625
--   
--   >>> atan 0.2 :: Double
--   0.19739555984988078
--   
--   >>> $$(fLit (atan 0.2)) :: SFixed 1 8
--   0.1953125
--   
--   >>> $$(fLit (atan 0.2)) :: SFixed 1 20
--   0.19739532470703125
--   
fLit :: forall rep int frac size. (size ~ (int + frac), KnownNat frac, Bounded (rep size), Integral (rep size)) => Double -> Q (TExp (Fixed rep int frac)) -- | Convert, at run-time, a Double to a Fixed-point. -- -- NB: This function is not synthesizable -- --

Creating data-files

-- -- An example usage of this function is to convert a data file containing -- Doubles to a data file with ASCII-encoded binary numbers to be -- used by a synthesizable function like asyncRomFile. For -- example, consider a file Data.txt containing: -- --
--   1.2 2.0 3.0 4.0
--   -1.0 -2.0 -3.5 -4.0
--   
-- -- which we want to put in a ROM, interpreting them as 8.8 -- signed fixed point numbers. What we do is that we first create a -- conversion utility, createRomFile, which uses fLitR: -- -- createRomFile.hs: -- --
--   module Main where
--   
--   import Clash.Prelude
--   import Clash.Prelude.ROM.File
--   import System.Environment
--   import qualified Data.List as L
--   
--   createRomFile
--     :: BitPack a
--     => (Double -> a)
--     -> FilePath
--     -> FilePath
--     -> IO ()
--   createRomFile convert fileR fileW = do
--     f <- readFile fileR
--     let ds :: [Double]
--         ds = L.concat . (L.map . L.map) read . L.map words $ lines f
--         fes = L.map convert ds
--     writeFile fileW (memFile Nothing fes)
--   
--   toSFixed8_8 :: Double -> SFixed 8 8
--   toSFixed8_8 = fLitR
--   
--   main :: IO ()
--   main = do
--     [fileR,fileW] <- getArgs
--     createRomFile toSFixed8_8 fileR fileW
--   
-- -- We then compile this to an executable: -- --
--   $ clash --make createRomFile.hs
--   
-- -- We can then use this utility to convert our Data.txt file -- which contains Doubles to a Data.bin file which will -- containing the desired ASCII-encoded binary data: -- --
--   $ ./createRomFile Data.txt Data.bin
--   
-- -- Which results in a Data.bin file containing: -- --
--   0000000100110011
--   0000001000000000
--   0000001100000000
--   0000010000000000
--   1111111100000000
--   1111111000000000
--   1111110010000000
--   1111110000000000
--   
-- -- We can then use this Data.bin file in for our ROM: -- --
--   romF :: Unsigned 3 -> Unsigned 3 -> SFixed 8 8
--   romF rowAddr colAddr = unpack
--                        $ asyncRomFile d8 "Data.bin" ((rowAddr * 4) + colAddr)
--   
-- -- And see that it works as expected: -- --
--   >>> romF 1 2
--   -3.5
--   >>> romF 0 0
--   1.19921875
--   
-- --

Using Template Haskell

-- -- For those of us who like to live on the edge, another option is to -- convert our Data.txt at compile-time using Template -- Haskell. For this we first create a module -- CreateRomFileTH.hs: -- --
--   module CreateRomFileTH (romDataFromFile) where
--   
--   import Clash.Prelude
--   import Clash.Prelude.ROM.File
--   import qualified Data.List as L
--   import Language.Haskell.TH (ExpQ, litE, stringL)
--   import Language.Haskell.TH.Syntax (qRunIO)
--   
--   createRomFile :: BitPack a => (Double -> a)
--                 -> FilePath -> FilePath -> IO ()
--   createRomFile convert fileR fileW = do
--     f <- readFile fileR
--     let ds :: [Double]
--         ds = L.concat . (L.map . L.map) read . L.map words $ lines f
--         fes = L.map convert ds
--     writeFile fileW (memFile Nothing fes)
--   
--   romDataFromFile :: BitPack a => (Double -> a) -> String -> ExpQ
--   romDataFromFile convert fileR = do
--     let fileW = fileR L.++ ".bin"
--     qRunIO (createRomFile convert fileR fileW)
--     litE (stringL fileW)
--   
-- -- Instead of first converting Data.txt to Data.bin, we -- will now use the romDataFromFile function to convert -- Data.txt to a new file in the proper format at compile-time -- of our new romF' function: -- --
--   import Clash.Prelude
--   import CreateRomFileTH
--   
--   romF' :: Unsigned 3 -> Unsigned 3 -> SFixed 8 8
--   romF' rowAddr colAddr = unpack $
--     asyncRomFile d8
--                  $(romDataFromFile (fLitR :: Double -> SFixed 8 8) "Data.txt") -- Template Haskell splice
--                  ((rowAddr * 4) + colAddr)
--   
-- -- And see that it works just like the romF function from -- earlier: -- --
--   >>> romF' 1 2
--   -3.5
--   >>> romF' 0 0
--   1.19921875
--   
fLitR :: forall rep int frac size. (size ~ (int + frac), KnownNat frac, Bounded (rep size), Integral (rep size)) => Double -> Fixed rep int frac -- | Fixed-point number -- -- Where: -- -- -- -- The Num operators for this type saturate to maxBound on -- overflow and minBound on underflow, and use truncation as the -- rounding method. -- -- Fixed has the type role -- --
--   >>> :i Fixed
--   type role Fixed representational nominal nominal
--   ...
--   
-- -- as it is safe to coerce between different compatible underlying types, -- but not necessasrily safe to coerce between different widths of this -- type. To change the width, use the functions in the Resize -- class. newtype Fixed (rep :: Nat -> Type) (int :: Nat) (frac :: Nat) Fixed :: rep (int + frac) -> Fixed (rep :: Nat -> Type) (int :: Nat) (frac :: Nat) [unFixed] :: Fixed (rep :: Nat -> Type) (int :: Nat) (frac :: Nat) -> rep (int + frac) -- | Saturating resize operation, truncates for rounding -- --
--   >>> 0.8125 :: SFixed 3 4
--   0.8125
--   
--   >>> resizeF (0.8125 :: SFixed 3 4) :: SFixed 2 3
--   0.75
--   
--   >>> 3.4 :: SFixed 3 4
--   3.375
--   
--   >>> resizeF (3.4 :: SFixed 3 4) :: SFixed 2 3
--   1.875
--   
--   >>> maxBound :: SFixed 2 3
--   1.875
--   
-- -- When used in a polymorphic setting, use the following Constraint -- synonyms for less verbose type signatures: -- -- resizeF :: forall rep int1 frac1 int2 frac2. ResizeFC rep int1 frac1 int2 frac2 => Fixed rep int1 frac1 -> Fixed rep int2 frac2 -- | Get the position of the virtual point of a -- Fixed-point number fracShift :: KnownNat frac => Fixed rep int frac -> Int -- | Constraint for the Num instance of SFixed type NumSFixedC int frac = (KnownNat ((int + int) + (frac + frac)), KnownNat (frac + frac), KnownNat (int + int), KnownNat (int + frac), KnownNat frac, KnownNat int) -- | Constraint for the ExtendingNum instance of SFixed type ENumSFixedC int1 frac1 int2 frac2 = (KnownNat (int2 + frac2), KnownNat (1 + Max int1 int2 + Max frac1 frac2), KnownNat (Max frac1 frac2), KnownNat (1 + Max int1 int2), KnownNat (int1 + frac1), KnownNat frac2, KnownNat int2, KnownNat frac1, KnownNat int1) -- | Constraint for the Fractional instance of SFixed type FracSFixedC int frac = (NumSFixedC int frac, KnownNat ((int + frac + 1) + (int + frac))) -- | Constraint for the resizeF function, specialized for -- SFixed type ResizeSFC int1 frac1 int2 frac2 = (KnownNat int1, KnownNat frac1, KnownNat int2, KnownNat frac2, KnownNat (int2 + frac2), KnownNat (int1 + frac1)) -- | Constraint for the divide function, specialized for -- SFixed type DivideSC int1 frac1 int2 frac2 = (KnownNat (((int1 + frac2) + 1) + (int2 + frac1)), KnownNat frac2, KnownNat int2, KnownNat frac1, KnownNat int1) -- | Constraint for the Num instance of UFixed type NumUFixedC int frac = NumSFixedC int frac -- | Constraint for the ExtendingNum instance of UFixed type ENumUFixedC int1 frac1 int2 frac2 = ENumSFixedC int1 frac1 int2 frac2 -- | Constraint for the Fractional instance of UFixed type FracUFixedC int frac = FracSFixedC int frac -- | Constraint for the resizeF function, specialized for -- UFixed type ResizeUFC int1 frac1 int2 frac2 = ResizeSFC int1 frac1 int2 frac2 -- | Constraint for the divide function, specialized for -- UFixed type DivideUC int1 frac1 int2 frac2 = DivideSC int1 frac1 int2 frac2 -- | Constraint for the Num instance of Fixed type NumFixedC rep int frac = (SaturatingNum (rep (int + frac)), ExtendingNum (rep (int + frac)) (rep (int + frac)), MResult (rep (int + frac)) (rep (int + frac)) ~ rep ((int + int) + (frac + frac)), BitSize (rep ((int + int) + (frac + frac))) ~ (int + ((int + frac) + frac)), BitPack (rep ((int + int) + (frac + frac))), Bits (rep ((int + int) + (frac + frac))), BitPack (rep (int + frac)), Bits (rep (int + frac)), Integral (rep (int + frac)), Resize rep, Typeable rep, KnownNat int, KnownNat frac) -- | Constraint for the ExtendingNum instance of Fixed type ENumFixedC rep int1 frac1 int2 frac2 = (Bounded (rep ((1 + Max int1 int2) + Max frac1 frac2)), Num (rep ((1 + Max int1 int2) + Max frac1 frac2)), Bits (rep ((1 + Max int1 int2) + Max frac1 frac2)), ExtendingNum (rep (int1 + frac1)) (rep (int2 + frac2)), MResult (rep (int1 + frac1)) (rep (int2 + frac2)) ~ rep ((int1 + int2) + (frac1 + frac2)), KnownNat int1, KnownNat int2, KnownNat frac1, KnownNat frac2, Resize rep) -- | Constraint for the Fractional instance of Fixed type FracFixedC rep int frac = (NumFixedC rep int frac, DivideC rep int frac int frac) -- | Constraint for the resizeF function type ResizeFC rep int1 frac1 int2 frac2 = (Resize rep, Ord (rep (int1 + frac1)), Num (rep (int1 + frac1)), Bits (rep (int1 + frac1)), Bits (rep (int2 + frac2)), Bounded (rep (int2 + frac2)), KnownNat int1, KnownNat frac1, KnownNat int2, KnownNat frac2) -- | Constraint for the divide function type DivideC rep int1 frac1 int2 frac2 = (Resize rep, Integral (rep (((int1 + frac2) + 1) + (int2 + frac1))), Bits (rep (((int1 + frac2) + 1) + (int2 + frac1))), KnownNat int1, KnownNat frac1, KnownNat int2, KnownNat frac2) -- | Fixed as a Proxy for it's representation type -- rep asRepProxy :: Fixed rep int frac -> Proxy rep -- | Fixed as a Proxy for the number of integer bits -- int asIntProxy :: Fixed rep int frac -> Proxy int instance Control.DeepSeq.NFData (rep (int GHC.TypeNats.+ frac)) => Control.DeepSeq.NFData (Clash.Sized.Fixed.Fixed rep int frac) instance (Data.Typeable.Internal.Typeable rep, Data.Typeable.Internal.Typeable int, Data.Typeable.Internal.Typeable frac, Data.Data.Data (rep (int GHC.TypeNats.+ frac))) => Data.Data.Data (Clash.Sized.Fixed.Fixed rep int frac) instance GHC.Classes.Eq (rep (int GHC.TypeNats.+ frac)) => GHC.Classes.Eq (Clash.Sized.Fixed.Fixed rep int frac) instance GHC.Classes.Ord (rep (int GHC.TypeNats.+ frac)) => GHC.Classes.Ord (Clash.Sized.Fixed.Fixed rep int frac) instance GHC.Enum.Bounded (rep (int GHC.TypeNats.+ frac)) => GHC.Enum.Bounded (Clash.Sized.Fixed.Fixed rep int frac) instance Data.Default.Class.Default (rep (int GHC.TypeNats.+ frac)) => Data.Default.Class.Default (Clash.Sized.Fixed.Fixed rep int frac) instance Test.QuickCheck.Arbitrary.Arbitrary (rep (int GHC.TypeNats.+ frac)) => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Fixed.Fixed rep int frac) instance Test.QuickCheck.Arbitrary.CoArbitrary (rep (int GHC.TypeNats.+ frac)) => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Fixed.Fixed rep int frac) instance Data.Bits.FiniteBits (rep (int GHC.TypeNats.+ frac)) => Data.Bits.FiniteBits (Clash.Sized.Fixed.Fixed rep int frac) instance Data.Bits.Bits (rep (int GHC.TypeNats.+ frac)) => Data.Bits.Bits (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.FracFixedC rep int frac => GHC.Real.Fractional (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.FracFixedC rep int frac => GHC.Real.RealFrac (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.NumFixedC rep int frac => GHC.Num.Num (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.NumFixedC rep int frac => GHC.Enum.Enum (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.NumFixedC rep int frac => Clash.Class.Num.SaturatingNum (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.NumFixedC rep int frac => GHC.Real.Real (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Sized.Fixed.ENumFixedC rep int1 frac1 int2 frac2 => Clash.Class.Num.ExtendingNum (Clash.Sized.Fixed.Fixed rep int1 frac1) (Clash.Sized.Fixed.Fixed rep int2 frac2) instance (size GHC.Types.~ (int GHC.TypeNats.+ frac), GHC.TypeNats.KnownNat frac, GHC.Real.Integral (rep size)) => GHC.Show.Show (Clash.Sized.Fixed.Fixed rep int frac) instance (size GHC.Types.~ (int GHC.TypeNats.+ frac), GHC.TypeNats.KnownNat frac, GHC.Real.Integral (rep size)) => Clash.XException.ShowX (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.XException.NFDataX (rep (int GHC.TypeNats.+ frac)) => Clash.XException.NFDataX (Clash.Sized.Fixed.Fixed rep int frac) instance (size GHC.Types.~ (int GHC.TypeNats.+ frac), GHC.TypeNats.KnownNat frac, GHC.Enum.Bounded (rep size), GHC.Real.Integral (rep size)) => GHC.Read.Read (Clash.Sized.Fixed.Fixed rep int frac) instance (Clash.Class.BitPack.Internal.BitPack (rep (int GHC.TypeNats.+ frac)), GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.BitSize (rep (int GHC.TypeNats.+ frac)))) => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Fixed.Fixed rep int frac) instance (Language.Haskell.TH.Syntax.Lift (rep (int GHC.TypeNats.+ frac)), GHC.TypeNats.KnownNat frac, GHC.TypeNats.KnownNat int, Data.Typeable.Internal.Typeable rep) => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Fixed.Fixed rep int frac) module Clash.Sized.Internal.Index -- | Arbitrarily-bounded unsigned integer represented by -- ceil(log_2(n)) bits -- -- Given an upper bound n, an Index n number has -- a range of: [0 .. n-1] -- --
--   >>> maxBound :: Index 8
--   7
--   
--   >>> minBound :: Index 8
--   0
--   
--   >>> read (show (maxBound :: Index 8)) :: Index 8
--   7
--   
--   >>> 1 + 2 :: Index 8
--   3
--   
--   >>> 2 + 6 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
--   ...
--   
--   >>> 1 - 3 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result -2 is out of bounds: [0..7]
--   ...
--   
--   >>> 2 * 3 :: Index 8
--   6
--   
--   >>> 2 * 4 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
--   ...
--   
-- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. -- -- Index has the type role -- --
--   >>> :i Index
--   type role Index nominal
--   ...
--   
-- -- as it is not safe to coerce between Indexes with different -- ranges. To change the size, use the functions in the Resize -- class. newtype Index (n :: Nat) -- | The constructor, I, and the field, unsafeToInteger, are -- not synthesizable. I :: Integer -> Index (n :: Nat) [unsafeToInteger] :: Index (n :: Nat) -> Integer -- | Safely convert an SNat value to an Index fromSNat :: (KnownNat m, (n + 1) <= m) => SNat n -> Index m size# :: (KnownNat n, 1 <= n) => Index n -> Int pack# :: Index n -> BitVector (CLog 2 n) unpack# :: (KnownNat n, 1 <= n) => BitVector (CLog 2 n) -> Index n eq# :: Index n -> Index n -> Bool neq# :: Index n -> Index n -> Bool lt# :: Index n -> Index n -> Bool ge# :: Index n -> Index n -> Bool gt# :: Index n -> Index n -> Bool le# :: Index n -> Index n -> Bool toEnum# :: forall n. KnownNat n => Int -> Index n fromEnum# :: forall n. KnownNat n => Index n -> Int enumFrom# :: forall n. KnownNat n => Index n -> [Index n] enumFromThen# :: forall n. KnownNat n => Index n -> Index n -> [Index n] enumFromTo# :: Index n -> Index n -> [Index n] enumFromThenTo# :: Index n -> Index n -> Index n -> [Index n] maxBound# :: forall n. KnownNat n => Index n (+#) :: KnownNat n => Index n -> Index n -> Index n (-#) :: KnownNat n => Index n -> Index n -> Index n (*#) :: KnownNat n => Index n -> Index n -> Index n negate# :: KnownNat n => Index n -> Index n fromInteger# :: KnownNat n => Integer -> Index n plus# :: Index m -> Index n -> Index ((m + n) - 1) minus# :: Index m -> Index n -> Index ((m + n) - 1) times# :: Index m -> Index n -> Index (((m - 1) * (n - 1)) + 1) quot# :: Index n -> Index n -> Index n rem# :: Index n -> Index n -> Index n toInteger# :: Index n -> Integer resize# :: KnownNat m => Index n -> Index m instance GHC.Generics.Generic (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Data.Data.Data (Clash.Sized.Internal.Index.Index n) instance Control.DeepSeq.NFData (Clash.Sized.Internal.Index.Index n) instance (GHC.TypeNats.KnownNat n, 1 GHC.TypeNats.<= n) => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Internal.Index.Index n) instance GHC.Classes.Eq (Clash.Sized.Internal.Index.Index n) instance GHC.Classes.Ord (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Enum (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Enum.Bounded (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Num.Num (Clash.Sized.Internal.Index.Index n) instance Clash.Class.Num.ExtendingNum (Clash.Sized.Internal.Index.Index m) (Clash.Sized.Internal.Index.Index n) instance (GHC.TypeNats.KnownNat n, 1 GHC.TypeNats.<= n) => Clash.Class.Num.SaturatingNum (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Real.Real (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Real.Integral (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Text.Printf.PrintfArg (Clash.Sized.Internal.Index.Index n) instance (GHC.TypeNats.KnownNat n, 1 GHC.TypeNats.<= n) => Clash.Class.Parity.Parity (Clash.Sized.Internal.Index.Index n) instance (GHC.TypeNats.KnownNat n, 1 GHC.TypeNats.<= n) => Data.Bits.Bits (Clash.Sized.Internal.Index.Index n) instance (GHC.TypeNats.KnownNat n, 1 GHC.TypeNats.<= n) => Data.Bits.FiniteBits (Clash.Sized.Internal.Index.Index n) instance Clash.Class.Resize.Resize Clash.Sized.Internal.Index.Index instance GHC.TypeNats.KnownNat n => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Internal.Index.Index n) instance GHC.Show.Show (Clash.Sized.Internal.Index.Index n) instance Clash.XException.ShowX (Clash.Sized.Internal.Index.Index n) instance Clash.XException.NFDataX (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Read.Read (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Data.Default.Class.Default (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => GHC.Ix.Ix (Clash.Sized.Internal.Index.Index n) module Clash.Sized.Index -- | Arbitrarily-bounded unsigned integer represented by -- ceil(log_2(n)) bits -- -- Given an upper bound n, an Index n number has -- a range of: [0 .. n-1] -- --
--   >>> maxBound :: Index 8
--   7
--   
--   >>> minBound :: Index 8
--   0
--   
--   >>> read (show (maxBound :: Index 8)) :: Index 8
--   7
--   
--   >>> 1 + 2 :: Index 8
--   3
--   
--   >>> 2 + 6 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
--   ...
--   
--   >>> 1 - 3 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result -2 is out of bounds: [0..7]
--   ...
--   
--   >>> 2 * 3 :: Index 8
--   6
--   
--   >>> 2 * 4 :: Index 8
--   *** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
--   ...
--   
-- -- NB: The usual Haskell method of converting an integral numeric -- type to another, fromIntegral, is not well suited for Clash as -- it will go through Integer which is arbitrarily bounded in HDL. -- Instead use bitCoerce and the Resize class. -- -- Index has the type role -- --
--   >>> :i Index
--   type role Index nominal
--   ...
--   
-- -- as it is not safe to coerce between Indexes with different -- ranges. To change the size, use the functions in the Resize -- class. data Index (n :: Nat) -- | An alternative implementation of unpack for the Index -- data type; for when you know the size of the BitVector and want -- to determine the size of the Index. -- -- That is, the type of unpack is: -- --
--   unpack :: BitVector (CLog 2 n) -> Index n
--   
-- -- And is useful when you know the size of the Index, and want to -- get a value from a BitVector that is large enough (CLog 2 -- n) enough to hold an Index. Note that unpack can -- fail at run-time when the value inside the BitVector is -- higher than 'n-1'. -- -- bv2i on the other hand will never fail at run-time, -- because the BitVector argument determines the size. bv2i :: KnownNat n => BitVector n -> Index (2 ^ n) -- | Safely convert an SNat value to an Index fromSNat :: (KnownNat m, (n + 1) <= m) => SNat n -> Index m module Clash.Sized.Vector -- | Fixed size vectors. -- -- data Vec :: Nat -> Type -> Type [Nil] :: Vec 0 a [Cons] :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the head of a vector. -- --
--   >>> 3:>4:>5:>Nil
--   3 :> 4 :> 5 :> Nil
--   
--   >>> let x = 3:>4:>5:>Nil
--   
--   >>> :t x
--   x :: Num a => Vec 3 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (x :> y :> _) = x + y
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   7
--   
-- -- Also in conjunctions with (:<): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:>) :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the tail of a vector. -- --
--   >>> (3:>4:>5:>Nil) :< 1
--   3 :> 4 :> 5 :> 1 :> Nil
--   
--   >>> let x = (3:>4:>5:>Nil) :< 1
--   
--   >>> :t x
--   x :: Num a => Vec 4 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (_ :< y :< x) = y + x
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   13
--   
-- -- Also in conjunctions with (:>): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:<) :: Vec n a -> a -> Vec (n + 1) a infixr 5 :> infixl 5 :< infixr 5 `Cons` -- | The length of a Vector as an Int value. -- --
--   >>> length (6 :> 7 :> 8 :> Nil)
--   3
--   
length :: KnownNat n => Vec n a -> Int -- | Length of a Vector as an SNat value lengthS :: KnownNat n => Vec n a -> SNat n -- | "xs !! n" returns the n'th element of -- xs. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> (1:>2:>3:>4:>5:>Nil) !! 4
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! (length (1:>2:>3:>4:>5:>Nil) - 1)
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 1
--   2
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 4
--   ...
--   
(!!) :: (KnownNat n, Enum i) => Vec n a -> i -> a -- | Extract the first element of a vector -- --
--   >>> head (1:>2:>3:>Nil)
--   1
--   
-- --
--   >>> head Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘head’, namely ‘Nil’
--         In the expression: head Nil
--         In an equation for ‘it’: it = head Nil
--   
head :: Vec (n + 1) a -> a -- | Extract the last element of a vector -- --
--   >>> last (1:>2:>3:>Nil)
--   3
--   
-- --
--   >>> last Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘last’, namely ‘Nil’
--         In the expression: last Nil
--         In an equation for ‘it’: it = last Nil
--   
last :: Vec (n + 1) a -> a -- | "at n xs" returns n'th element of xs -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> at (SNat :: SNat 1) (1:>2:>3:>4:>5:>Nil)
--   2
--   
--   >>> at d1               (1:>2:>3:>4:>5:>Nil)
--   2
--   
at :: SNat m -> Vec (m + (n + 1)) a -> a -- | Generate a vector of indices. -- --
--   >>> indices d4
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indices :: KnownNat n => SNat n -> Vec n (Index n) -- | Generate a vector of indices, where the length of the vector is -- determined by the context. -- --
--   >>> indicesI :: Vec 4 (Index 4)
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indicesI :: KnownNat n => Vec n (Index n) -- | "findIndex p xs" returns the index of the first -- element of xs satisfying the predicate p, or -- Nothing if there is no such element. -- --
--   >>> findIndex (> 3) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 3
--   
--   >>> findIndex (> 8) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
findIndex :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe (Index n) -- | "elemIndex a xs" returns the index of the first -- element which is equal (by ==) to the query element a, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> elemIndex 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
elemIndex :: (KnownNat n, Eq a) => a -> Vec n a -> Maybe (Index n) -- | Extract the elements after the head of a vector -- --
--   >>> tail (1:>2:>3:>Nil)
--   2 :> 3 :> Nil
--   
-- --
--   >>> tail Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘tail’, namely ‘Nil’
--         In the expression: tail Nil
--         In an equation for ‘it’: it = tail Nil
--   
tail :: Vec (n + 1) a -> Vec n a -- | Extract all the elements of a vector except the last element -- --
--   >>> init (1:>2:>3:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> init Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘init’, namely ‘Nil’
--         In the expression: init Nil
--         In an equation for ‘it’: it = init Nil
--   
init :: Vec (n + 1) a -> Vec n a -- | "take n xs" returns the n-length prefix of -- xs. -- --
--   >>> take (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d3               (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d0               (1:>2:>Nil)
--   Nil
--   
-- --
--   >>> take d4               (1:>2:>Nil)
--   
--   <interactive>:...
--       • Couldn't match type ‘4 + n0’ with ‘2’
--         Expected type: Vec (4 + n0) a
--           Actual type: Vec (1 + 1) a
--         The type variable ‘n0’ is ambiguous
--       • In the second argument of ‘take’, namely ‘(1 :> 2 :> Nil)’
--         In the expression: take d4 (1 :> 2 :> Nil)
--         In an equation for ‘it’: it = take d4 (1 :> 2 :> Nil)
--   
take :: SNat m -> Vec (m + n) a -> Vec m a -- | "takeI xs" returns the prefix of xs as demanded -- by the context. -- --
--   >>> takeI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   1 :> 2 :> Nil
--   
takeI :: KnownNat m => Vec (m + n) a -> Vec m a -- | "drop n xs" returns the suffix of xs after the -- first n elements. -- --
--   >>> drop (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d3               (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d0               (1:>2:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> drop d4               (1:>2:>Nil)
--   
--   <interactive>:...: error:...
--       • Couldn't match...type ‘4 + n0...
--         The type variable ‘n0’ is ambiguous
--       • In the first argument of ‘print’, namely ‘it’
--         In a stmt of an interactive GHCi command: print it
--   
drop :: SNat m -> Vec (m + n) a -> Vec n a -- | "dropI xs" returns the suffix of xs as demanded -- by the context. -- --
--   >>> dropI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   4 :> 5 :> Nil
--   
dropI :: KnownNat m => Vec (m + n) a -> Vec n a -- | "select f s n xs" selects n elements with -- step-size s and offset f from xs. -- --
--   >>> select (SNat :: SNat 1) (SNat :: SNat 2) (SNat :: SNat 3) (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
--   >>> select d1 d2 d3 (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
select :: CmpNat (i + s) (s * n) ~ 'GT => SNat f -> SNat s -> SNat n -> Vec (f + i) a -> Vec n a -- | "selectI f s xs" selects as many elements as demanded -- by the context with step-size s and offset f from -- xs. -- --
--   >>> selectI d1 d2 (1:>2:>3:>4:>5:>6:>7:>8:>Nil) :: Vec 2 Int
--   2 :> 4 :> Nil
--   
selectI :: (CmpNat (i + s) (s * n) ~ 'GT, KnownNat n) => SNat f -> SNat s -> Vec (f + i) a -> Vec n a -- | Split a vector into two vectors at the given point. -- --
--   >>> splitAt (SNat :: SNat 3) (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
--   >>> splitAt d3 (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
splitAt :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector into two vectors where the length of the two is -- determined by the context. -- --
--   >>> splitAtI (1:>2:>3:>7:>8:>Nil) :: (Vec 2 Int, Vec 3 Int)
--   (1 :> 2 :> Nil,3 :> 7 :> 8 :> Nil)
--   
splitAtI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector of (n * m) elements into a vector of "vectors of length -- m", where the length m is given. -- --
--   >>> unconcat d4 (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil) :> (5 :> 6 :> 7 :> 8 :> Nil) :> (9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) -- | Split a vector of (n * m) elements into a vector of "vectors of -- length m", where the length m is determined by the -- context. -- --
--   >>> unconcatI (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil) :: Vec 2 (Vec 6 Int)
--   (1 :> 2 :> 3 :> 4 :> 5 :> 6 :> Nil) :> (7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) -- | Create a vector of one element -- --
--   >>> singleton 5
--   5 :> Nil
--   
singleton :: a -> Vec 1 a -- | "replicate n a" returns a vector that has n -- copies of a. -- --
--   >>> replicate (SNat :: SNat 3) 6
--   6 :> 6 :> 6 :> Nil
--   
--   >>> replicate d3 6
--   6 :> 6 :> 6 :> Nil
--   
replicate :: SNat n -> a -> Vec n a -- | "repeat a" creates a vector with as many copies of -- a as demanded by the context. -- --
--   >>> repeat 6 :: Vec 5 Int
--   6 :> 6 :> 6 :> 6 :> 6 :> Nil
--   
repeat :: KnownNat n => a -> Vec n a -- | "iterate n f x" returns a vector starting with -- x followed by n repeated applications of f to -- x. -- --
--   iterate (SNat :: SNat 4) f x == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   iterate d4 f x               == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> iterate d4 (+1) 1
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- "iterate n f z" corresponds to the following circuit -- layout: -- iterate :: SNat n -> (a -> a) -> a -> Vec n a -- | "iterateI f x" returns a vector starting with -- x followed by n repeated applications of f -- to x, where n is determined by the context. -- --
--   iterateI f x :: Vec 3 a == (x :> f x :> f (f x) :> Nil)
--   
-- --
--   >>> iterateI (+1) 1 :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- -- "iterateI f z" corresponds to the following circuit -- layout: -- iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a -- | "generate n f x" returns a vector with n -- repeated applications of f to x. -- --
--   generate (SNat :: SNat 4) f x == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   generate d4 f x               == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   
-- --
--   >>> generate d4 (+1) 1
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "generate n f z" corresponds to the following circuit -- layout: -- generate :: SNat n -> (a -> a) -> a -> Vec n a -- | "generateI f x" returns a vector with n -- repeated applications of f to x, where n is -- determined by the context. -- --
--   generateI f x :: Vec 3 a == (f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> generateI (+1) 1 :: Vec 3 Int
--   2 :> 3 :> 4 :> Nil
--   
-- -- "generateI f z" corresponds to the following circuit -- layout: -- generateI :: KnownNat n => (a -> a) -> a -> Vec n a -- | "unfoldr n f s" builds a vector of length n -- from a seed value s, where every element a is -- created by successive calls of f on s. Unlike -- unfoldr from Data.List the generating function -- f cannot dictate the length of the resulting vector, it must -- be statically known. -- -- a simple use of unfoldr: -- --
--   >>> unfoldr d10 (\s -> (s,s-1)) 10
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldr :: SNat n -> (s -> (a, s)) -> s -> Vec n a -- | "unfoldrI f s" builds a vector from a seed value -- s, where every element a is created by successive -- calls of f on s; the length of the vector is -- inferred from the context. Unlike unfoldr from Data.List -- the generating function f cannot dictate the length of the -- resulting vector, it must be statically known. -- -- a simple use of unfoldrI: -- --
--   >>> unfoldrI (\s -> (s,s-1)) 10 :: Vec 10 Int
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldrI :: KnownNat n => (s -> (a, s)) -> s -> Vec n a -- | Create a vector literal from a list literal. -- --
--   $(listToVecTH [1::Signed 8,2,3,4,5]) == (8:>2:>3:>4:>5:>Nil) :: Vec 5 (Signed 8)
--   
-- --
--   >>> [1 :: Signed 8,2,3,4,5]
--   [1,2,3,4,5]
--   
--   >>> $(listToVecTH [1::Signed 8,2,3,4,5])
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
listToVecTH :: Lift a => [a] -> ExpQ -- | Append two vectors. -- --
--   >>> (1:>2:>3:>Nil) ++ (7:>8:>Nil)
--   1 :> 2 :> 3 :> 7 :> 8 :> Nil
--   
(++) :: Vec n a -> Vec m a -> Vec (n + m) a infixr 5 ++ -- | Add an element to the head of a vector, and extract all but the last -- element. -- --
--   >>> 1 +>> (3:>4:>5:>Nil)
--   1 :> 3 :> 4 :> Nil
--   
--   >>> 1 +>> Nil
--   Nil
--   
(+>>) :: KnownNat n => a -> Vec n a -> Vec n a infixr 4 +>> -- | Add an element to the tail of a vector, and extract all but the first -- element. -- --
--   >>> (3:>4:>5:>Nil) <<+ 1
--   4 :> 5 :> 1 :> Nil
--   
--   >>> Nil <<+ 1
--   Nil
--   
(<<+) :: Vec n a -> a -> Vec n a infixl 4 <<+ -- | Concatenate a vector of vectors. -- --
--   >>> concat ((1:>2:>3:>Nil) :> (4:>5:>6:>Nil) :> (7:>8:>9:>Nil) :> (10:>11:>12:>Nil) :> Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil
--   
concat :: Vec n (Vec m a) -> Vec (n * m) a -- | Map a function over all the elements of a vector and concatentate the -- resulting vectors. -- --
--   >>> concatMap (replicate d3) (1:>2:>3:>Nil)
--   1 :> 1 :> 1 :> 2 :> 2 :> 2 :> 3 :> 3 :> 3 :> Nil
--   
concatMap :: (a -> Vec m b) -> Vec n a -> Vec (n * m) b -- | Shift in elements to the head of a vector, bumping out elements at the -- tail. The result is a tuple containing: -- -- -- --
--   >>> shiftInAt0 (1 :> 2 :> 3 :> 4 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> 0 :> 1 :> 2 :> Nil,3 :> 4 :> Nil)
--   
--   >>> shiftInAt0 (1 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> Nil,0 :> 1 :> Nil)
--   
shiftInAt0 :: KnownNat n => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift in element to the tail of a vector, bumping out elements at the -- head. The result is a tuple containing: -- -- -- --
--   >>> shiftInAtN (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> Nil)
--   (3 :> 4 :> 5 :> 6 :> Nil,1 :> 2 :> Nil)
--   
--   >>> shiftInAtN (1 :> Nil) (2 :> 3 :> Nil)
--   (3 :> Nil,1 :> 2 :> Nil)
--   
shiftInAtN :: KnownNat m => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift m elements out from the head of a vector, filling up the -- tail with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFrom0 d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (3 :> 4 :> 5 :> 0 :> 0 :> Nil,1 :> 2 :> Nil)
--   
shiftOutFrom0 :: (Default a, KnownNat m) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Shift m elements out from the tail of a vector, filling up the -- head with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFromN d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (0 :> 0 :> 1 :> 2 :> 3 :> Nil,4 :> 5 :> Nil)
--   
shiftOutFromN :: (Default a, KnownNat n) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Merge two vectors, alternating their elements, i.e., -- --
--   >>> merge (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> 7 :> 8 :> Nil)
--   1 :> 5 :> 2 :> 6 :> 3 :> 7 :> 4 :> 8 :> Nil
--   
merge :: KnownNat n => Vec n a -> Vec n a -> Vec (2 * n) a -- | "replace n a xs" returns the vector xs where -- the n'th element is replaced by a. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> replace 3 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 7 :> 5 :> Nil
--   
--   >>> replace 0 7 (1:>2:>3:>4:>5:>Nil)
--   7 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
--   >>> replace 9 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 4
--   ...
--   
replace :: (KnownNat n, Enum i) => i -> a -> Vec n a -> Vec n a -- | Forward permutation specified by an index mapping, ix. The -- result vector is initialized by the given defaults, def, and an -- further values that are permuted into the result are added to the -- current value using the given combination function, f. -- -- The combination function must be associative and -- commutative. permute :: (Enum i, KnownNat n, KnownNat m) => (a -> a -> a) -> Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "backpermute xs is" is equivalent to "map -- (xs !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> backpermute input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
backpermute :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | Copy elements from the source vector, xs, to the destination -- vector according to an index mapping is. This is a forward -- permute operation where a to vector encodes an input to output -- index mapping. Output elements for indices that are not mapped assume -- the value in the default vector def. -- -- For example: -- --
--   >>> let defVec = 0:>0:>0:>0:>0:>0:>0:>0:>0:>Nil
--   
--   >>> let to = 1:>3:>7:>2:>5:>8:>Nil
--   
--   >>> let input = 1:>9:>6:>4:>4:>2:>5:>Nil
--   
--   >>> scatter defVec to input
--   0 :> 1 :> 4 :> 9 :> 0 :> 4 :> 0 :> 6 :> 2 :> Nil
--   
-- -- NB: If the same index appears in the index mapping more than -- once, the latest mapping is chosen. scatter :: (Enum i, KnownNat n, KnownNat m) => Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "gather xs is" is equivalent to "map (xs -- !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> gather input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
gather :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | The elements in a vector in reverse order. -- --
--   >>> reverse (1:>2:>3:>4:>Nil)
--   4 :> 3 :> 2 :> 1 :> Nil
--   
reverse :: Vec n a -> Vec n a -- | Transpose a matrix: go from row-major to column-major -- --
--   >>> let xss = (1:>2:>Nil):>(3:>4:>Nil):>(5:>6:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> Nil) :> (3 :> 4 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
--   >>> transpose xss
--   (1 :> 3 :> 5 :> Nil) :> (2 :> 4 :> 6 :> Nil) :> Nil
--   
transpose :: KnownNat n => Vec m (Vec n a) -> Vec n (Vec m a) -- | "interleave d xs" creates a vector: -- --
--   <x_0,x_d,x_(2d),...,x_1,x_(d+1),x_(2d+1),...,x_(d-1),x_(2d-1),x_(3d-1)>
--   
-- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> Nil
--   
--   >>> interleave d3 xs
--   1 :> 4 :> 7 :> 2 :> 5 :> 8 :> 3 :> 6 :> 9 :> Nil
--   
interleave :: (KnownNat n, KnownNat d) => SNat d -> Vec (n * d) a -> Vec (d * n) a -- | Dynamically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeft xs 1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
--   >>> rotateLeft xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateLeft xs (-1)
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateLeftS if you want to rotate left by a -- static amount. rotateLeft :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Dynamically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRight xs 1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
--   >>> rotateRight xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateRight xs (-1)
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateRightS if you want to rotate right by a -- static amount. rotateRight :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Statically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeftS xs d1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateLeft if you want to rotate left by a -- dynamic amount. rotateLeftS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Statically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRightS xs d1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateRight if you want to rotate right by a -- dynamic amount. rotateRightS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | "map f xs" is the vector obtained by applying f -- to each element of xs, i.e., -- --
--   map f (x1 :> x2 :>  ... :> xn :> Nil) == (f x1 :> f x2 :> ... :> f xn :> Nil)
--   
-- -- and corresponds to the following circuit layout: -- map :: (a -> b) -> Vec n a -> Vec n b -- | Apply a function of every element of a vector and its index. -- --
--   >>> :t imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   imap (+) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Index 4)
--   
--   >>> imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   2 :> 3 :> *** Exception: X: Clash.Sized.Index: result 4 is out of bounds: [0..3]
--   ...
--   
--   >>> imap (\i a -> extend (bitCoerce i) + a) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Unsigned 8)
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- imap :: forall n a b. KnownNat n => (Index n -> a -> b) -> Vec n a -> Vec n b -- | Apply a function to every element of a vector and the element's -- position (as an SNat value) in the vector. -- --
--   >>> let rotateMatrix = smap (flip rotateRightS)
--   
--   >>> let xss = (1:>2:>3:>Nil):>(1:>2:>3:>Nil):>(1:>2:>3:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> Nil
--   
--   >>> rotateMatrix xss
--   (1 :> 2 :> 3 :> Nil) :> (3 :> 1 :> 2 :> Nil) :> (2 :> 3 :> 1 :> Nil) :> Nil
--   
smap :: forall k a b. KnownNat k => (forall l. SNat l -> a -> b) -> Vec k a -> Vec k b -- | zipWith generalizes zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "zipWith (+)" applied to two vectors produces -- the vector of corresponding sums. -- --
--   zipWith f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) == (f x1 y1 :> f x2 y2 :> ... :> f xn yn :> Nil)
--   
-- -- "zipWith f xs ys" corresponds to the following circuit -- layout: -- -- -- NB: zipWith is strict in its second argument, and -- lazy in its third. This matters when zipWith is used in -- a recursive setting. See lazyV for more information. zipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | zipWith3 generalizes zip3 by zipping with the function -- given as the first argument, instead of a tupling function. -- --
--   zipWith3 f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) (z1 :> z2 :> ... :> zn :> Nil) == (f x1 y1 z1 :> f x2 y2 z2 :> ... :> f xn yn zn :> Nil)
--   
-- -- "zipWith3 f xs ys zs" corresponds to the following -- circuit layout: -- -- -- NB: zipWith3 is strict in its second argument, -- and lazy in its third and fourth. This matters when -- zipWith3 is used in a recursive setting. See lazyV for -- more information. zipWith3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d zipWith4 :: (a -> b -> c -> d -> e) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n h -- | zip takes two vectors and returns a vector of corresponding -- pairs. -- --
--   >>> zip (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil)
--   (1,4) :> (2,3) :> (3,2) :> (4,1) :> Nil
--   
zip :: Vec n a -> Vec n b -> Vec n (a, b) -- | zip3 takes three vectors and returns a vector of corresponding -- triplets. -- --
--   >>> zip3 (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil) (5:>6:>7:>8:>Nil)
--   (1,4,5) :> (2,3,6) :> (3,2,7) :> (4,1,8) :> Nil
--   
zip3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) -- | zip4 takes four vectors and returns a list of quadruples, -- analogous to zip. zip4 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n (a, b, c, d) -- | zip5 takes five vectors and returns a list of five-tuples, -- analogous to zip. zip5 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n (a, b, c, d, e) -- | zip6 takes six vectors and returns a list of six-tuples, -- analogous to zip. zip6 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n (a, b, c, d, e, f) -- | zip7 takes seven vectors and returns a list of seven-tuples, -- analogous to zip. zip7 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n (a, b, c, d, e, f, g) -- | Zip two vectors with a functions that also takes the elements' -- indices. -- --
--   >>> izipWith (\i a b -> i + a + b) (2 :> 2 :> Nil)  (3 :> 3:> Nil)
--   *** Exception: X: Clash.Sized.Index: result 3 is out of bounds: [0..1]
--   ...
--   
--   >>> izipWith (\i a b -> extend (bitCoerce i) + a + b) (2 :> 2 :> Nil) (3 :> 3 :> Nil) :: Vec 2 (Unsigned 8)
--   5 :> 6 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- -- -- NB: izipWith is strict in its second argument, -- and lazy in its third. This matters when izipWith is -- used in a recursive setting. See lazyV for more information. izipWith :: KnownNat n => (Index n -> a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | unzip transforms a vector of pairs into a vector of first -- components and a vector of second components. -- --
--   >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
--   
unzip :: Vec n (a, b) -> (Vec n a, Vec n b) -- | unzip3 transforms a vector of triplets into a vector of first -- components, a vector of second components, and a vector of third -- components. -- --
--   >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
--   
unzip3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) -- | unzip4 takes a vector of quadruples and returns four vectors, -- analogous to unzip. unzip4 :: Vec n (a, b, c, d) -> (Vec n a, Vec n b, Vec n c, Vec n d) -- | unzip5 takes a vector of five-tuples and returns five vectors, -- analogous to unzip. unzip5 :: Vec n (a, b, c, d, e) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e) -- | unzip6 takes a vector of six-tuples and returns six vectors, -- analogous to unzip. unzip6 :: Vec n (a, b, c, d, e, f) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f) -- | unzip7 takes a vector of seven-tuples and returns seven -- vectors, analogous to unzip. unzip7 :: Vec n (a, b, c, d, e, f, g) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f, Vec n g) -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a vector, reduces -- the vector using the binary operator, from right to left: -- --
--   foldr f z (x1 :> ... :> xn1 :> xn :> Nil) == x1 `f` (... (xn1 `f` (xn `f` z))...)
--   foldr r z Nil                             == z
--   
-- --
--   >>> foldr (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   1.875
--   
-- -- "foldr f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldr :: (a -> b -> b) -> b -> Vec n a -> b -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a vector, reduces -- the vector using the binary operator, from left to right: -- --
--   foldl f z (x1 :> x2 :> ... :> xn :> Nil) == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   foldl f z Nil                            == z
--   
-- --
--   >>> foldl (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldl :: forall b a n. (b -> a -> b) -> b -> Vec n a -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldr1 f (x1 :> ... :> xn2 :> xn1 :> xn :> Nil) == x1 `f` (... (xn2 `f` (xn1 `f` xn))...)
--   foldr1 f (x1 :> Nil)                            == x1
--   foldr1 f Nil                                    == TYPE ERROR
--   
-- --
--   >>> foldr1 (/) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   1.875
--   
-- -- "foldr1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldl1 f (x1 :> x2 :> x3 :> ... :> xn :> Nil) == (...((x1 `f` x2) `f` x3) `f`...) `f` xn
--   foldl1 f (x1 :> Nil)                          == x1
--   foldl1 f Nil                                  == TYPE ERROR
--   
-- --
--   >>> foldl1 (/) (1 :> 5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | fold is a variant of foldr1 and foldl1, but -- instead of reducing from right to left, or left to right, it reduces a -- vector using a tree-like structure. The depth, or delay, of the -- structure produced by "fold f xs", is hence -- O(log_2(length xs)), and not O(length -- xs). -- -- NB: The binary operator "f" in "fold f -- xs" must be associative. -- --
--   fold f (x1 :> x2 :> ... :> xn1 :> xn :> Nil) == ((x1 `f` x2) `f` ...) `f` (... `f` (xn1 `f` xn))
--   fold f (x1 :> Nil)                           == x1
--   fold f Nil                                   == TYPE ERROR
--   
-- --
--   >>> fold (+) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   15
--   
-- -- "fold f xs" corresponds to the following circuit -- layout: -- fold :: forall n a. (a -> a -> a) -> Vec (n + 1) a -> a -- | Right fold (function applied to each element and its index) -- --
--   >>> let findLeftmost x xs = ifoldr (\i a b -> if a == x then Just i else b) Nothing xs
--   
--   >>> findLeftmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> findLeftmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldr f z xs" corresponds to the following circuit -- layout: -- ifoldr :: KnownNat n => (Index n -> a -> b -> b) -> b -> Vec n a -> b -- | Left fold (function applied to each element and its index) -- --
--   >>> let findRightmost x xs = ifoldl (\a i b -> if b == x then Just i else a) Nothing xs
--   
--   >>> findRightmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 4
--   
--   >>> findRightmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldl f z xs" corresponds to the following circuit -- layout: -- ifoldl :: KnownNat n => (a -> Index n -> b -> a) -> a -> Vec n b -> a -- | A dependently typed fold. -- --

doctests setup

-- --
--   >>> :seti -fplugin GHC.TypeLits.Normalise
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply (Append m a) l = Vec (l + m) a
--   
--   >>> let append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- --

Example usage

-- -- Using lists, we can define append (a.k.a. -- Data.List.++) in terms of -- Data.List.foldr: -- --
--   >>> import qualified Data.List
--   
--   >>> let append xs ys = Data.List.foldr (:) ys xs
--   
--   >>> append [1,2] [3,4]
--   [1,2,3,4]
--   
-- -- However, when we try to do the same for Vec, by defining -- append' in terms of Clash.Sized.Vector.foldr: -- --
--   append' xs ys = foldr (:>) ys xs
--   
-- -- we get a type error: -- --
--   >>> let append' xs ys = foldr (:>) ys xs
--   
--   <interactive>:...
--       • Occurs check: cannot construct the infinite type: ... ~ ... + 1
--         Expected type: a -> Vec ... a -> Vec ... a
--           Actual type: a -> Vec ... a -> Vec (... + 1) a
--       • In the first argument of ‘foldr’, namely ‘(:>)’
--         In the expression: foldr (:>) ys xs
--         In an equation for ‘append'’: append' xs ys = foldr (:>) ys xs
--       • Relevant bindings include
--           ys :: Vec ... a (bound at ...)
--           append' :: Vec n a -> Vec ... a -> Vec ... a
--             (bound at ...)
--   
-- -- The reason is that the type of foldr is: -- --
--   >>> :t foldr
--   foldr :: (a -> b -> b) -> b -> Vec n a -> b
--   
-- -- While the type of (:>) is: -- --
--   >>> :t (:>)
--   (:>) :: a -> Vec n a -> Vec (n + 1) a
--   
-- -- We thus need a fold function that can handle the growing -- vector type: dfold. Compared to foldr, dfold -- takes an extra parameter, called the motive, that allows the -- folded function to have an argument and result type that -- depends on the current length of the vector. Using -- dfold, we can now correctly define append': -- --
--   import Data.Singletons
--   import Data.Proxy
--   
--   data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   type instance Apply (Append m a) l = Vec (l + m) a
--   
--   append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- -- We now see that append' has the appropriate type: -- --
--   >>> :t append'
--   append' :: KnownNat k => Vec k a -> Vec m a -> Vec (k + m) a
--   
-- -- And that it works: -- --
--   >>> append' (1 :> 2 :> Nil) (3 :> 4 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: "dfold m f z xs" creates a linear -- structure, which has a depth, or delay, of O(length -- xs). Look at dtfold for a dependently typed fold -- that produces a structure with a depth of O(log_2(length -- xs)). dfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (forall l. SNat l -> a -> (p @@ l) -> p @@ (l + 1)) -> (p @@ 0) -> Vec k a -> p @@ k -- | A combination of dfold and fold: a dependently -- typed fold that reduces a vector in a tree-like structure. -- --

doctests setup

-- --
--   >>> :seti -XUndecidableInstances
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data IIndex (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply IIndex l = Index ((2^l)+1)
--   
--   >>> :{
--   let populationCount' :: (KnownNat k, KnownNat (2^k)) => BitVector (2^k) -> Index ((2^k)+1)
--       populationCount' bv = dtfold (Proxy @IIndex)
--                                    fromIntegral
--                                    (\_ x y -> add x y)
--                                    (bv2v bv)
--   :}
--   
-- --

Example usage

-- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- sum, because it gives a nice (log2(n)) tree-structure -- of adders: -- --
--   populationCount :: (KnownNat (n+1), KnownNat (n+2))
--                   => BitVector (n+1) -> Index (n+2)
--   populationCount = sum . map fromIntegral . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (n+2) -> Index (n+2) -> Index (n+2).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of addes: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (n+1), KnownNat (n+2))
--                        => BitVector (n+1) -> Index (n+2)
--       populationCount' = fold add . map fromIntegral . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘((n + 2) + (n + 2)) - 1’ with ‘n + 2’
--         Expected type: Index (n + 2) -> Index (n + 2) -> Index (n + 2)
--           Actual type: Index (n + 2)
--                        -> Index (n + 2) -> AResult (Index (n + 2)) (Index (n + 2))
--       • In the first argument of ‘fold’, namely ‘add’
--         In the first argument of ‘(.)’, namely ‘fold add’
--         In the expression: fold add . map fromIntegral . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (n + 1) -> Index (n + 2)
--             (bound at ...)
--   
-- -- because fold expects a function of type "a -> a -> -- a", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   import Data.Proxy
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = dtfold (Proxy @IIndex)
--                                fromIntegral
--                                (\_ x y -> add x y)
--                                (bv2v bv)
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
-- -- Some final remarks: -- -- -- -- NB: The depth, or delay, of the structure produced by -- "dtfold m f g xs" is O(log_2(length -- xs)). dtfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> Vec (2 ^ k) a -> p @@ k -- | Specialised version of dfold that builds a triangular -- computational structure. -- --

doctests setup

-- --
--   >>> let compareSwap a b = if a > b then (a,b) else (b,a)
--   
--   >>> let insert y xs = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   
--   >>> let insertionSort = vfold (const insert)
--   
-- --

Example usage

-- --
--   compareSwap a b = if a > b then (a,b) else (b,a)
--   insert y xs     = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   insertionSort   = vfold (const insert)
--   
-- -- Builds a triangular structure of compare and swaps to sort a row. -- --
--   >>> insertionSort (7 :> 3 :> 9 :> 1 :> Nil)
--   1 :> 3 :> 7 :> 9 :> Nil
--   
-- -- The circuit layout of insertionSort, build using -- vfold, is: -- vfold :: forall k a b. KnownNat k => (forall l. SNat l -> a -> Vec l b -> Vec (l + 1) b) -> Vec k a -> Vec k b -- | The largest element of a non-empty vector maximum :: Ord a => Vec (n + 1) a -> a -- | The least element of a non-empty vector minimum :: Ord a => Vec (n + 1) a -> a -- | scanl is similar to foldl, but returns a vector of -- successive reduced values from the left: -- --
--   scanl f z (x1 :> x2 :> ... :> Nil) == z :> (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> scanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   0 :> 5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "scanl f z xs" corresponds to the following circuit -- layout: -- -- -- scanl :: (b -> a -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanl with no seed value -- --
--   >>> scanl1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> -1 :> -4 :> -8 :> Nil
--   
scanl1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | scanr is similar to foldr, but returns a vector of -- successive reduced values from the right: -- --
--   scanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> z :> Nil
--   
-- --
--   >>> scanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> 0 :> Nil
--   
-- -- "scanr f z xs" corresponds to the following circuit -- layout: -- -- -- scanr :: (a -> b -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanr with no seed value -- --
--   >>> scanr1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   -2 :> 3 :> -1 :> 4 :> Nil
--   
scanr1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | postscanl is a variant of scanl where the first result -- is dropped: -- --
--   postscanl f z (x1 :> x2 :> ... :> Nil) == (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> postscanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "postscanl f z xs" corresponds to the following -- circuit layout: -- postscanl :: (b -> a -> b) -> b -> Vec n a -> Vec n b -- | postscanr is a variant of scanr that where the last -- result is dropped: -- --
--   postscanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> Nil
--   
-- --
--   >>> postscanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> Nil
--   
-- -- "postscanr f z xs" corresponds to the following -- circuit layout: -- postscanr :: (a -> b -> b) -> b -> Vec n a -> Vec n b -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumL (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,1 :> 2 :> 4 :> 7 :> Nil)
--   
-- -- "mapAccumL f acc xs" corresponds to the following -- circuit layout: -- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumR (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,10 :> 8 :> 5 :> 1 :> Nil)
--   
-- -- "mapAccumR f acc xs" corresponds to the following -- circuit layout: -- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | 1-dimensional stencil computations -- -- "stencil1d stX f xs", where xs has stX + -- n elements, applies the stencil computation f on: n + -- 1 overlapping (1D) windows of length stX, drawn from -- xs. The resulting vector has n + 1 elements. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t stencil1d d2 sum xs
--   stencil1d d2 sum xs :: Num b => Vec 5 b
--   
--   >>> stencil1d d2 sum xs
--   3 :> 5 :> 7 :> 9 :> 11 :> Nil
--   
stencil1d :: KnownNat n => SNat (stX + 1) -> (Vec (stX + 1) a -> b) -> Vec ((stX + n) + 1) a -> Vec (n + 1) b -- | 2-dimensional stencil computations -- -- "stencil2d stY stX f xss", where xss is a -- matrix of stY + m rows of stX + n elements, applies the -- stencil computation f on: (m + 1) * (n + 1) overlapping -- (2D) windows of stY rows of stX elements, drawn from -- xss. The result matrix has m + 1 rows of n + 1 -- elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
-- --
--   >>> :t stencil2d d2 d2 (sum . map sum) xss
--   stencil2d d2 d2 (sum . map sum) xss :: Num b => Vec 3 (Vec 3 b)
--   
-- --
--   >>> stencil2d d2 d2 (sum . map sum) xss
--   (14 :> 18 :> 22 :> Nil) :> (30 :> 34 :> 38 :> Nil) :> (46 :> 50 :> 54 :> Nil) :> Nil
--   
stencil2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> (Vec (stY + 1) (Vec (stX + 1) a) -> b) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) b) -- | "windows1d stX xs", where the vector xs has -- stX + n elements, returns a vector of n + 1 overlapping -- (1D) windows of xs of length stX. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t windows1d d2 xs
--   windows1d d2 xs :: Num a => Vec 5 (Vec 2 a)
--   
--   >>> windows1d d2 xs
--   (1 :> 2 :> Nil) :> (2 :> 3 :> Nil) :> (3 :> 4 :> Nil) :> (4 :> 5 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
windows1d :: KnownNat n => SNat (stX + 1) -> Vec ((stX + n) + 1) a -> Vec (n + 1) (Vec (stX + 1) a) -- | "windows2d stY stX xss", where matrix xss has -- stY + m rows of stX + n, returns a matrix of m+1 -- rows of n+1 elements. The elements of this new matrix are the -- overlapping (2D) windows of xss, where every window has -- stY rows of stX elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
--   >>> :t windows2d d2 d2 xss
--   windows2d d2 d2 xss :: Num a => Vec 3 (Vec 3 (Vec 2 (Vec 2 a)))
--   
--   >>> windows2d d2 d2 xss
--   (((1 :> 2 :> Nil) :> (5 :> 6 :> Nil) :> Nil) :> ((2 :> 3 :> Nil) :> (6 :> 7 :> Nil) :> Nil) :> ((3 :> 4 :> Nil) :> (7 :> 8 :> Nil) :> Nil) :> Nil) :> (((5 :> 6 :> Nil) :> (9 :> 10 :> Nil) :> Nil) :> ((6 :> 7 :> Nil) :> (10 :> 11 :> Nil) :> Nil) :> ((7 :> 8 :> Nil) :> (11 :> 12 :> Nil) :> Nil) :> Nil) :> (((9 :> 10 :> Nil) :> (13 :> 14 :> Nil) :> Nil) :> ((10 :> 11 :> Nil) :> (14 :> 15 :> Nil) :> Nil) :> ((11 :> 12 :> Nil) :> (15 :> 16 :> Nil) :> Nil) :> Nil) :> Nil
--   
windows2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) (Vec (stY + 1) (Vec (stX + 1) a))) -- | Convert a vector to a list. -- --
--   >>> toList (1:>2:>3:>Nil)
--   [1,2,3]
--   
-- -- NB: This function is not synthesizable toList :: Vec n a -> [a] -- | Convert a list to a vector. This function returns Nothing if the size -- of the list is not equal to the size of the resulting vector. -- --
--   >>> Vec.fromList [1,2,3,4,5] :: Maybe (Vec 5 Int)
--   Just (1 :> 2 :> 3 :> 4 :> 5 :> Nil)
--   
-- --
--   >>> Vec.fromList [1,2,3,4,5] :: Maybe (Vec 3 Int)
--   Nothing
--   
-- --
--   >>> Vec.fromList [1,2,3,4,5] :: Maybe (Vec 10 Int)
--   Nothing
--   
-- -- fromList :: forall n a. KnownNat n => [a] -> Maybe (Vec n a) -- | Convert a list to a vector. This function always returns a vector of -- the desired length, by either truncating the list or padding the -- vector with undefined elements. -- --
--   >>> Vec.unsafeFromList [1,2,3,4,5] :: Vec 5 Int
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
-- --
--   >>> Vec.unsafeFromList [1,2,3,4,5] :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- --
--   >>> Vec.unsafeFromList [1,2,3,4,5] :: Vec 10 Int
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.unsafeFromList: vector larger than list
--   ...
--   
-- -- unsafeFromList :: forall n a. KnownNat n => [a] -> Vec n a -- | Convert a BitVector to a Vec of Bits. -- --
--   >>> let x = 6 :: BitVector 8
--   
--   >>> x
--   0b0000_0110
--   
--   >>> bv2v x
--   0 :> 0 :> 0 :> 0 :> 0 :> 1 :> 1 :> 0 :> Nil
--   
bv2v :: KnownNat n => BitVector n -> Vec n Bit -- | Convert a Vec of Bits to a BitVector. -- --
--   >>> let x = (0:>0:>0:>1:>0:>0:>1:>0:>Nil) :: Vec 8 Bit
--   
--   >>> x
--   0 :> 0 :> 0 :> 1 :> 0 :> 0 :> 1 :> 0 :> Nil
--   
--   >>> v2bv x
--   0b0001_0010
--   
v2bv :: KnownNat n => Vec n Bit -> BitVector n -- | What you should use when your vector functions are too strict in their -- arguments. -- --

doctests setup

-- --
--   >>> let compareSwapL a b = if a < b then (a,b) else (b,a)
--   
--   >>> :{
--   let sortVL :: (Ord a, KnownNat (n + 1)) => Vec ((n + 1) + 1) a -> Vec ((n + 1) + 1) a
--       sortVL xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith compareSwapL (lazyV lefts) rights
--   :}
--   
-- --
--   >>> :{
--   let sortV_flip xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith (flip compareSwapL) rights lefts
--   :}
--   
-- --

Example usage

-- -- For example: -- --
--   -- Bubble sort for 1 iteration
--   sortV xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL lefts rights
--   
--   -- Compare and swap
--   compareSwapL a b = if a < b then (a,b)
--                               else (b,a)
--   
-- -- Will not terminate because zipWith is too strict in its second -- argument. -- -- In this case, adding lazyV on zipWiths second argument: -- --
--   sortVL xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL (lazyV lefts) rights
--   
-- -- Results in a successful computation: -- --
--   >>> sortVL (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: There is also a solution using flip, but it slightly -- obfuscates the meaning of the code: -- --
--   sortV_flip xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith (flip compareSwapL) rights lefts
--   
-- --
--   >>> sortV_flip (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
lazyV :: KnownNat n => Vec n a -> Vec n a -- | To be used as the motive p for dfold, when the f -- in "dfold p f" is a variation on (:>), e.g.: -- --
--   map' :: forall n a b . KnownNat n => (a -> b) -> Vec n a -> Vec n b
--   map' f = dfold (Proxy @(VCons b)) (_ x xs -> f x :> xs)
--   
data VCons (a :: Type) (f :: TyFun Nat Type) :: Type -- | Vector as a Proxy for Nat asNatProxy :: Vec n a -> Proxy n -- | Evaluate all elements of a vector to WHNF, returning the second -- argument seqV :: KnownNat n => Vec n a -> b -> b infixr 0 `seqV` -- | Evaluate all elements of a vector to WHNF forceV :: KnownNat n => Vec n a -> Vec n a -- | Evaluate all elements of a vector to WHNF, returning the second -- argument. Does not propagate XExceptions. seqVX :: KnownNat n => Vec n a -> b -> b infixr 0 `seqVX` -- | Evaluate all elements of a vector to WHNF. Does not propagate -- XExceptions. forceVX :: KnownNat n => Vec n a -> Vec n a traverse# :: forall a f b n. Applicative f => (a -> f b) -> Vec n a -> f (Vec n b) concatBitVector# :: forall n m. (KnownNat n, KnownNat m) => Vec n (BitVector m) -> BitVector (n * m) unconcatBitVector# :: forall n m. (KnownNat n, KnownNat m) => BitVector (n * m) -> Vec n (BitVector m) instance GHC.TypeNats.KnownNat n => GHC.Generics.Generic (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, Data.Typeable.Internal.Typeable a, Data.Data.Data a) => Data.Data.Data (Clash.Sized.Vector.Vec n a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Sized.Vector.Vec n a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Sized.Vector.Vec n a) instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, GHC.Classes.Eq a) => GHC.Classes.Eq (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, GHC.Classes.Ord a) => GHC.Classes.Ord (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, GHC.Base.Semigroup a) => GHC.Base.Semigroup (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, GHC.Base.Monoid a) => GHC.Base.Monoid (Clash.Sized.Vector.Vec n a) instance GHC.TypeNats.KnownNat n => GHC.Base.Applicative (Clash.Sized.Vector.Vec n) instance GHC.TypeNats.KnownNat n => Data.Foldable.Foldable (Clash.Sized.Vector.Vec n) instance GHC.Base.Functor (Clash.Sized.Vector.Vec n) instance GHC.TypeNats.KnownNat n => Data.Traversable.Traversable (Clash.Sized.Vector.Vec n) instance (Data.Default.Class.Default a, GHC.TypeNats.KnownNat n) => Data.Default.Class.Default (Clash.Sized.Vector.Vec n a) instance (Clash.XException.NFDataX a, GHC.TypeNats.KnownNat n) => Clash.XException.NFDataX (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, Clash.Class.BitPack.Internal.BitPack a) => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.Vector.Vec n a) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat n, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.Vector.Vec n a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.Vector.Vec n a) instance GHC.TypeNats.KnownNat n => Control.Lens.At.Ixed (Clash.Sized.Vector.Vec n a) -- | Tooling to safely work around incomplete-uni-patterns and -- incomplete-patterns warnings. See vecToTuple for more -- information and examples. -- -- Note: This module has been added to make upgrading to GHC 9.2 easier. -- As of GHC 9.2, the incomplete-uni-patterns has been added to -- the -Wall, making previously warning-free code now produce -- warnings. module Clash.Sized.Vector.ToTuple class VecToTuple a where { type family TupType a = r | r -> a; } -- | Given a vector with three elements: -- --
--   >>> myVec = (1 :> 2 :> 3 :> Nil) :: Vec 3 Int
--   
-- -- The following would produce a warning even though we can be sure no -- other pattern can ever apply: -- --
--   >>> (a :> b :> c :> Nil) = myVec
--   
-- -- vecToTuple can be used to work around the warning: -- --
--   >>> (a, b, c) = vecToTuple myVec
--   
-- -- Of course, you will still get an error if you try to match a vector of -- the wrong length: -- --
--   >>> (a, b, c, d) = vecToTuple myVec
--   ...
--       • Couldn't match type: (Int, Int, Int)
--                               ^
--                        with: (a, b, c, d)
--   ...
--   
vecToTuple :: VecToTuple a => a -> TupType a instance Clash.Sized.Vector.ToTuple.VecToTuple (Clash.Sized.Vector.Vec 3 a) instance Clash.Sized.Vector.ToTuple.VecToTuple (Clash.Sized.Vector.Vec 0 a) instance Clash.Sized.Vector.ToTuple.VecToTuple (Clash.Sized.Vector.Vec 2 a) -- | I/O actions that are translatable to HDL module Clash.Explicit.SimIO -- | Simulation-level I/O environment that can be synthesized to HDL-level -- I/O. Note that it is unlikely that the HDL-level I/O can subsequently -- be synthesized to a circuit. -- --

Example

-- --
--   tbMachine :: (File,File) -> Int -> SimIO Int
--   tbMachine (fileIn,fileOut) regOut = do
--     eofFileOut <- isEOF fileOut
--     eofFileIn  <- isEOF fileIn
--     when (eofFileIn || eofFileOut) $ do
--       display "success"
--       finish 0
--   
--     goldenIn  <- getChar fileIn
--     goldenOut <- getChar fileOut
--     res <- if regOut == fromEnum goldenOut then do
--              return (fromEnum goldenIn)
--            else do
--              display "Output doesn't match golden output"
--              finish 1
--     display ("Output matches golden output")
--     return res
--   
--   tbInit :: (File,File)
--   tbInit = do
--     fileIn  <- openFile "./goldenInput00.txt" "r"
--     fileOut <- openFile "./goldenOutput00.txt" "r"
--     return (fileIn,fileOut)
--   
--   topEntity :: Signal System Int
--   topEntity = regOut
--     where
--       clk = systemClockGen
--       rst = resetGen
--       ena = enableGen
--   
--       regOut = register clk rst ena (fromEnum 'a') regIn
--       regIn  = mealyIO clk tbMachine tbInit regOut
--   
mealyIO :: KnownDomain dom => Clock dom -> (s -> i -> SimIO o) -> SimIO s -> Signal dom i -> Signal dom o -- | Simulation-level I/O environment; synthesizable to HDL I/O, which in -- itself is unlikely to be synthesisable to a digital circuit. -- -- See mealyIO as to its use. data SimIO a -- | Display a string on stdout display :: String -> SimIO () -- | Finish the simulation with an exit code finish :: Integer -> SimIO a -- | Mutable reference data Reg a -- | Create a new mutable reference with the given starting value reg :: a -> SimIO (Reg a) -- | Read value from a mutable reference readReg :: Reg a -> SimIO a -- | Write new value to the mutable reference writeReg :: Reg a -> a -> SimIO () -- | File handle data File -- | Open a file openFile :: FilePath -> String -> SimIO File -- | Close a file closeFile :: File -> SimIO () -- | Read one character from a file getChar :: File -> SimIO Char -- | Insert a character into a buffer specified by the file putChar :: Char -> File -> SimIO () -- | Read one line from a file getLine :: forall n. KnownNat n => File -> Reg (Vec n (Unsigned 8)) -> SimIO Int -- | Determine whether we've reached the end of the file isEOF :: File -> SimIO Bool -- | Write any buffered output to file flush :: File -> SimIO () -- | Set the position of the next operation on the file seek :: File -> Integer -> Int -> SimIO Int -- | Set the position of the next operation to the beginning of the file rewind :: File -> SimIO Int -- | Returns the offset from the beginning of the file (in bytes). tell :: File -> SimIO Integer instance GHC.Base.Functor Clash.Explicit.SimIO.SimIO instance GHC.Base.Applicative Clash.Explicit.SimIO.SimIO instance GHC.Base.Monad Clash.Explicit.SimIO.SimIO -- | ROMs module Clash.Explicit.ROM -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: (KnownDomain dom, KnownNat n, NFDataX a, Enum addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: (KnownDomain dom, KnownNat n, NFDataX a) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | ROM primitive rom# :: forall dom n a. (KnownDomain dom, KnownNat n, NFDataX a) => Clock dom -> Enable dom -> Vec n a -> Signal dom Int -> Signal dom a -- | Internals for Clash.Class.HasDomain module Clash.Class.HasDomain.HasSpecificDomain 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 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 WithSpecificDomain dom r = (HasSpecificDomain dom r, dom ~ GetDomain dom r) data HasDomainWrapperResult -- | No domain found NotFound :: HasDomainWrapperResult -- | Found the specific domain caller was looking for Found :: HasDomainWrapperResult -- | Merge two HasDomainWrapperResults according to the semantics of -- 'HasDomain. type family MergeWorker (n :: HasDomainWrapperResult) (m :: HasDomainWrapperResult) :: HasDomainWrapperResult type Merge (dom :: Domain) (n :: Type) (m :: Type) = MergeWorker (HasDomainWrapper dom n) (HasDomainWrapper dom m) type family DomEqWorker (n :: Domain) (m :: Domain) :: HasDomainWrapperResult -- | 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 DomEq (n :: Domain) (m :: Domain) = IfStuck (DomEqWorker n m) ('NotFound) (Pure (DomEqWorker n m)) -- | 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". type family HasDomain (dom :: Domain) (n :: Type) :: HasDomainWrapperResult type family ErrOnNotFound (dom :: Domain) (n :: HasDomainWrapperResult) (t :: Type) :: Domain -- | Wrapper that checks for stuckness and returns 'NotFound if so type family HasDomainWrapper (dom :: Domain) (n :: Type) :: HasDomainWrapperResult -- | 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.. type family ResolveOrErr (dom :: Domain) (t :: Type) :: Domain -- | 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. class HasSpecificDomain (dom :: Domain) (r :: Type) where { type family GetDomain dom r :: Domain; type GetDomain dom r = ResolveOrErr dom r; } instance Clash.Class.HasDomain.HasSpecificDomain.HasSpecificDomain dom a -- | API for synthesis attributes (sometimes referred to as "synthesis -- directives", "pragmas", or "logic synthesis directives"). This is an -- experimental feature, please report any unexpected or broken behavior -- to Clash's GitHub page -- (https://github.com/clash-lang/clash-compiler/issues). module Clash.Annotations.SynthesisAttributes -- | Synthesis attributes are directives passed to synthesis tools, such as -- Quartus. An example of such an attribute in VHDL: -- --
--   attribute chip_pin : string;
--   attribute chip_pin of sel : signal is "C4";
--   attribute chip_pin of data : signal is "D1, D2, D3, D4";
--   
-- -- This would instruct the synthesis tool to map the wire sel to -- pin C4, and wire data to pins D1, D2, -- D3, and D4. To achieve this in Clash, Attrs are -- used. An example of the same annotation: -- --
--   import Clash.Annotations.SynthesisAttributes (Attr (..), Annotate )
--   
--   myFunc
--       :: (Signal System Bool `Annotate` 'StringAttr "chip_pin" "C4")
--       -> (Signal System Int4 `Annotate` 'StringAttr "chip_pin" "D1, D2, D3, D4")
--       -> ...
--   myFunc sel data = ...
--   {-# NOINLINE myFunc #-}
--   
-- -- To ensure this function will be rendered as its own module, do not -- forget a NOINLINE pragma. -- -- Multiple attributes for the same argument can be specified by -- using a list. For example: -- --
--   Signal System Bool `Annotate`
--     [ 'StringAttr "chip_pin" "C4"
--     , 'BoolAttr "direct_enable" 'True
--     , 'IntegerAttr "max_depth" 512
--     , 'Attr "keep"
--     ]
--   
-- -- For Verilog see: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vlog/vlog_file_dir.htm -- -- For VHDL, see: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vhdl/vhdl_file_dir.htm -- --

Warnings

-- -- When using annotations, it is important that annotated arguments are -- not eta-reduced, as this may result in the annotation being stripped -- by GHC. For example -- --
--   f :: Signal System Bool `Annotate` 'StringAttr "chip_pin" "C4"
--     -> Signal System Bool
--   f x = id x -- Using a lambda, i.e. f = \x -> id x also works
--   
-- -- will reliably show the annotation in the generated HDL, but -- --
--   g :: Signal System Bool `Annotate` 'StringAttr "chip_pin" "C4"
--     -> Signal System Bool
--   g = id
--   
-- -- will not work. -- -- This is an experimental feature, please report any unexpected or -- broken behavior to Clash's GitHub page -- (https://github.com/clash-lang/clash-compiler/issues). -- -- Use annotate if you wish to annotate an intermediate signal. -- Its use is preferred over type level annotations. data Attr a -- | Attribute which argument is rendered as a bool. Example: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vlog/vlog_file_dir_direct_enable.htm BoolAttr :: a -> Bool -> Attr a -- | Attribute which argument is rendered as a integer. Example: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vlog/vlog_file_dir_max_depth.htm IntegerAttr :: a -> Integer -> Attr a -- | Attribute which argument is rendered as a string. Example: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vlog/vlog_file_dir_chip.htm StringAttr :: a -> a -> Attr a -- | Attribute rendered as constant. Example: -- https://www.intel.com/content/www/us/en/programmable/quartushelp/current/index.htm#hdl/vlog/vlog_file_dir_keep.htm Attr :: a -> Attr a type Annotate (a :: Type) (attrs :: k) = a -- | Create a new identifier in HDL and inserts given synthesis attributes. -- The name of the intermediate signal can be influenced using naming -- functions in Clash.Magic. annotate :: forall n dom a. Vec n (Attr String) -> Signal dom a -> Signal dom a -- | Insert attributes such that signals are preserved in major synthesis -- tools. Also inserts "mark_debug", a way of signalling Vivado a signal -- should show up in a list of signals desired for ILA/VIO insertion. -- -- Attributes inserted: keep, mark_debug, -- noprune, and preserve. markDebug :: Signal dom a -> Signal dom a instance GHC.Base.Functor Clash.Annotations.SynthesisAttributes.Attr instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Annotations.SynthesisAttributes.Attr a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Annotations.SynthesisAttributes.Attr a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Annotations.SynthesisAttributes.Attr a) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (Clash.Annotations.SynthesisAttributes.Attr a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Annotations.SynthesisAttributes.Attr a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Annotations.SynthesisAttributes.Attr a) instance GHC.Generics.Generic (Clash.Annotations.SynthesisAttributes.Attr a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Annotations.SynthesisAttributes.Attr a) module Clash.Sized.RTree -- | Perfect depth binary tree. -- -- data RTree :: Nat -> Type -> Type [RLeaf] :: a -> RTree 0 a [RBranch] :: RTree d a -> RTree d a -> RTree (d + 1) a -- | RLeaf of a perfect depth tree -- --
--   >>> LR 1
--   1
--   
--   >>> let x = LR 1
--   
--   >>> :t x
--   x :: Num a => RTree 0 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (LR a) (LR b) = a + b
--   
--   >>> :t f
--   f :: Num a => RTree 0 a -> RTree 0 a -> a
--   
--   >>> f (LR 1) (LR 2)
--   3
--   
pattern LR :: a -> RTree 0 a -- | RBranch of a perfect depth tree -- --
--   >>> BR (LR 1) (LR 2)
--   <1,2>
--   
--   >>> let x = BR (LR 1) (LR 2)
--   
--   >>> :t x
--   x :: Num a => RTree 1 a
--   
-- -- Case be used a pattern: -- --
--   >>> let f (BR (LR a) (LR b)) = LR (a + b)
--   
--   >>> :t f
--   f :: Num a => RTree 1 a -> RTree 0 a
--   
--   >>> f (BR (LR 1) (LR 2))
--   3
--   
pattern BR :: RTree d a -> RTree d a -> RTree (d + 1) a -- | "treplicate d a" returns a tree of depth d, and -- has 2^d copies of a. -- --
--   >>> treplicate (SNat :: SNat 3) 6
--   <<<6,6>,<6,6>>,<<6,6>,<6,6>>>
--   
--   >>> treplicate d3 6
--   <<<6,6>,<6,6>>,<<6,6>,<6,6>>>
--   
treplicate :: forall d a. SNat d -> a -> RTree d a -- | "trepeat a" creates a tree with as many copies of -- a as demanded by the context. -- --
--   >>> trepeat 6 :: RTree 2 Int
--   <<6,6>,<6,6>>
--   
trepeat :: KnownNat d => a -> RTree d a -- | Extract the first element of a tree -- -- The first element is defined to be the bottom-left leaf. -- --
--   >>> thead $ BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))
--   1
--   
thead :: RTree n a -> a -- | Extract the last element of a tree -- -- The last element is defined to be the bottom-right leaf. -- --
--   >>> tlast $ BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))
--   4
--   
tlast :: RTree n a -> a -- | "indexTree t n" returns the n'th element of -- t. -- -- The bottom-left leaf had index 0, and the bottom-right leaf has -- index 2^d-1, where d is the depth of the tree -- --
--   >>> indexTree (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))) 0
--   1
--   
--   >>> indexTree (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))) 2
--   3
--   
--   >>> indexTree (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))) 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 3
--   ...
--   
indexTree :: (KnownNat d, Enum i) => RTree d a -> i -> a -- | Generate a tree of indices, where the depth of the tree is determined -- by the context. -- --
--   >>> tindices :: RTree 3 (Index 8)
--   <<<0,1>,<2,3>>,<<4,5>,<6,7>>>
--   
tindices :: forall d. KnownNat d => RTree d (Index (2 ^ d)) -- | "replaceTree n a t" returns the tree t where -- the n'th element is replaced by a. -- -- The bottom-left leaf had index 0, and the bottom-right leaf has -- index 2^d-1, where d is the depth of the tree -- --
--   >>> replaceTree 0 5 (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4)))
--   <<5,2>,<3,4>>
--   
--   >>> replaceTree 2 7 (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4)))
--   <<1,2>,<7,4>>
--   
--   >>> replaceTree 9 6 (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4)))
--   <<1,2>,<3,*** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 3
--   ...
--   
replaceTree :: (KnownNat d, Enum i) => i -> a -> RTree d a -> RTree d a -- | "tmap f t" is the tree obtained by apply f to -- each element of t, i.e., -- --
--   tmap f (BR (LR a) (LR b)) == BR (LR (f a)) (LR (f b))
--   
tmap :: forall d a b. KnownNat d => (a -> b) -> RTree d a -> RTree d b -- | tzipWith generalizes tzip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "tzipWith (+)" applied to two trees produces the tree of -- corresponding sums. -- --
--   tzipWith f (BR (LR a1) (LR b1)) (BR (LR a2) (LR b2)) == BR (LR (f a1 a2)) (LR (f b1 b2))
--   
tzipWith :: forall a b c d. KnownNat d => (a -> b -> c) -> RTree d a -> RTree d b -> RTree d c -- | tzip takes two trees and returns a tree of corresponding pairs. tzip :: KnownNat d => RTree d a -> RTree d b -> RTree d (a, b) -- | tunzip transforms a tree of pairs into a tree of first -- components and a tree of second components. tunzip :: forall d a b. KnownNat d => RTree d (a, b) -> (RTree d a, RTree d b) -- | Reduce a tree to a single element tfold :: forall d a b. KnownNat d => (a -> b) -> (b -> b -> b) -> RTree d a -> b -- | A dependently typed fold over trees. -- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- tfold, because it gives a nice (log2(n)) -- tree-structure of adders: -- --
--   populationCount :: (KnownNat (2^d), KnownNat d, KnownNat (2^d+1))
--                   => BitVector (2^d) -> Index (2^d+1)
--   populationCount = tfold (resize . bv2i . pack) (+) . v2t . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (2^d+1) -> Index (2^d+1) -> Index (2^d+1).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of adds: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (2^d), KnownNat d, KnownNat (2^d+1))
--                        => BitVector (2^d) -> Index (2^d+1)
--       populationCount' = tfold (resize . bv2i . pack) add . v2t . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘(((2 ^ d) + 1) + ((2 ^ d) + 1)) - 1’
--                        with ‘(2 ^ d) + 1’
--         Expected type: Index ((2 ^ d) + 1)
--                        -> Index ((2 ^ d) + 1) -> Index ((2 ^ d) + 1)
--           Actual type: Index ((2 ^ d) + 1)
--                        -> Index ((2 ^ d) + 1)
--                        -> AResult (Index ((2 ^ d) + 1)) (Index ((2 ^ d) + 1))
--       • In the second argument of ‘tfold’, namely ‘add’
--         In the first argument of ‘(.)’, namely
--           ‘tfold (resize . bv2i . pack) add’
--         In the expression: tfold (resize . bv2i . pack) add . v2t . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (2 ^ d) -> Index ((2 ^ d) + 1)
--             (bound at ...)
--   
-- -- because tfold expects a function of type "b -> b -> -- b", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = tdfold (Proxy @IIndex)
--                                (resize . bv2i . pack)
--                                (\_ x y -> add x y)
--                                (v2t (bv2v bv))
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
tdfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> RTree k a -> p @@ k -- | tscanl applied to Vec -- --
--   >>> scanlPar (+) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> 3 :> 6 :> 10 :> Nil
--   
scanlPar :: KnownNat n => (a -> a -> a) -> Vec (2 ^ n) a -> Vec (2 ^ n) a -- | Low-depth left scan -- -- tscanl is similar to foldl, but returns a tree of -- successive reduced values from the left: -- --
--   tscanl f [x1, x2, x3, ...] == [x1, x1 `f` x2, x1 `f` x2 `f` x3, ...]
--   
-- --
--   >>> tscanl (+) (v2t (1 :> 2 :> 3 :> 4 :> Nil))
--   <<1,3>,<6,10>>
--   
-- tscanl :: forall a n. KnownNat n => (a -> a -> a) -> RTree n a -> RTree n a -- | tscanr applied to Vec -- --
--   >>> scanrPar (+) (1 :> 2 :> 3 :> 4 :> Nil)
--   10 :> 9 :> 7 :> 4 :> Nil
--   
scanrPar :: KnownNat n => (a -> a -> a) -> Vec (2 ^ n) a -> Vec (2 ^ n) a -- | Low-depth right scan -- -- tscanr is similar to foldr, but returns a tree of -- successive reduced values from the left: -- --
--   tscanr f [..., xn2, xn1, xn] == [..., xn2 `f` xn1 `f` xn, xn1 `f` xn, xn]
--   
-- --
--   >>> tscanr (+) (v2t (1 :> 2 :> 3 :> 4 :> Nil))
--   <<10,9>,<7,4>>
--   
tscanr :: forall a n. KnownNat n => (a -> a -> a) -> RTree n a -> RTree n a -- | Convert a vector with 2^d elements to a tree of depth d. -- --
--   >>> v2t (1 :> 2 :> 3 :> 4:> Nil)
--   <<1,2>,<3,4>>
--   
v2t :: forall d a. KnownNat d => Vec (2 ^ d) a -> RTree d a -- | Convert a tree of depth d to a vector of 2^d elements -- --
--   >>> (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4)))
--   <<1,2>,<3,4>>
--   
--   >>> t2v (BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4)))
--   1 :> 2 :> 3 :> 4 :> Nil
--   
t2v :: forall d a. KnownNat d => RTree d a -> Vec (2 ^ d) a -- | Given a function f that is strict in its nth -- RTree argument, make it lazy by applying lazyT to this -- argument: -- --
--   f x0 x1 .. (lazyT xn) .. xn_plus_k
--   
lazyT :: KnownNat d => RTree d a -> RTree d a instance GHC.TypeNats.KnownNat d => Data.Traversable.Traversable (Clash.Sized.RTree.RTree d) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, GHC.Classes.Eq a) => GHC.Classes.Eq (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, GHC.Classes.Ord a) => GHC.Classes.Ord (Clash.Sized.RTree.RTree d a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Sized.RTree.RTree n a) instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Sized.RTree.RTree n a) instance GHC.TypeNats.KnownNat d => GHC.Base.Functor (Clash.Sized.RTree.RTree d) instance GHC.TypeNats.KnownNat d => GHC.Base.Applicative (Clash.Sized.RTree.RTree d) instance GHC.TypeNats.KnownNat d => Data.Foldable.Foldable (Clash.Sized.RTree.RTree d) instance (GHC.TypeNats.KnownNat d, Clash.Class.BitPack.Internal.BitPack a) => Clash.Class.BitPack.Internal.BitPack (Clash.Sized.RTree.RTree d a) instance GHC.TypeNats.KnownNat d => Control.Lens.At.Ixed (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, Data.Default.Class.Default a) => Data.Default.Class.Default (Clash.Sized.RTree.RTree d a) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, Test.QuickCheck.Arbitrary.CoArbitrary a) => Test.QuickCheck.Arbitrary.CoArbitrary (Clash.Sized.RTree.RTree d a) instance (GHC.TypeNats.KnownNat d, Clash.XException.NFDataX a) => Clash.XException.NFDataX (Clash.Sized.RTree.RTree d a) -- | The Product/Signal isomorphism module Clash.Signal.Bundle -- | Isomorphism between a Signal of a product type (e.g. a tuple) -- and a product type of Signals. -- -- Instances of Bundle must satisfy the following laws: -- --
--   bundle . unbundle = id
--   unbundle . bundle = id
--   
-- -- By default, bundle and unbundle, are defined as the -- identity, that is, writing: -- --
--   data D = A | B
--   
--   instance Bundle D
--   
-- -- is the same as: -- --
--   data D = A | B
--   
--   instance Bundle D where
--     type Unbundled clk D = Signal clk D
--     bundle   s = s
--     unbundle s = s
--   
-- -- For custom product types you'll have to write the instance manually: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b }
--   
--   instance Bundle (Pair a b) where
--     type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b)
--   
--     -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b)
--     bundle   (MkPair as bs) = MkPair <$> as <*> bs
--   
--     -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b)
--     unbundle pairs = MkPair (getA <$> pairs) (getB <$> pairs)
--   
class Bundle a where { type family Unbundled (dom :: Domain) a = res | res -> dom a; type Unbundled dom a = Signal dom a; } -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: Bundle a => Unbundled dom a -> Signal dom a -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: (Bundle a, Signal dom a ~ Unbundled dom a) => Unbundled dom a -> Signal dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: Bundle a => Signal dom a -> Unbundled dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: (Bundle a, Unbundled dom a ~ Signal dom a) => Signal dom a -> Unbundled dom a -- | See TaggedEmptyTuple data EmptyTuple EmptyTuple :: EmptyTuple -- | Helper type to emulate the "old" behavior of Bundle's unit instance. -- I.e., the instance for Bundle () used to be defined as: -- --
--   class Bundle () where
--     bundle   :: () -> Signal dom ()
--     unbundle :: Signal dom () -> ()
--   
-- -- In order to have sensible type inference, the Bundle class -- specifies that the argument type of bundle should uniquely -- identify the result type, and vice versa for unbundle. The type -- signatures in the snippet above don't though, as () doesn't -- uniquely map to a specific domain. In other words, domain -- should occur in both the argument and result of both functions. -- -- TaggedEmptyTuple tackles this by carrying the domain in its -- type. The bundle and unbundle instance now looks like: -- --
--   class Bundle EmptyTuple where
--     bundle   :: TaggedEmptyTuple dom -> Signal dom EmptyTuple
--     unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
--   
-- -- dom is now mentioned both the argument and result for both -- bundle and unbundle. data TaggedEmptyTuple (dom :: Domain) TaggedEmptyTuple :: TaggedEmptyTuple (dom :: Domain) vecBundle# :: Vec n (Signal t a) -> Signal t (Vec n a) instance Clash.Signal.Bundle.Bundle Clash.Signal.Bundle.EmptyTuple instance Clash.Signal.Bundle.Bundle (a1, a2) instance Clash.Signal.Bundle.Bundle (a1, a2, a3) instance GHC.TypeNats.KnownNat n => Clash.Signal.Bundle.Bundle (Clash.Sized.Vector.Vec n a) instance GHC.TypeNats.KnownNat d => Clash.Signal.Bundle.Bundle (Clash.Sized.RTree.RTree d a) instance Clash.Signal.Bundle.Bundle ((GHC.Generics.:*:) f g a) instance Clash.Signal.Bundle.Bundle () instance Clash.Signal.Bundle.Bundle GHC.Types.Bool instance Clash.Signal.Bundle.Bundle GHC.Integer.Type.Integer instance Clash.Signal.Bundle.Bundle GHC.Types.Int instance Clash.Signal.Bundle.Bundle GHC.Types.Float instance Clash.Signal.Bundle.Bundle GHC.Types.Double instance Clash.Signal.Bundle.Bundle (GHC.Maybe.Maybe a) instance Clash.Signal.Bundle.Bundle (Data.Either.Either a b) instance Clash.Signal.Bundle.Bundle Clash.Sized.Internal.BitVector.Bit instance Clash.Signal.Bundle.Bundle (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Signal.Bundle.Bundle (Clash.Sized.Internal.Index.Index n) instance Clash.Signal.Bundle.Bundle (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Signal.Bundle.Bundle (Clash.Sized.Internal.Signed.Signed n) instance Clash.Signal.Bundle.Bundle (Clash.Sized.Internal.Unsigned.Unsigned n) -- |

Initializing a block RAM with a data file

-- -- Block RAM primitives that can be initialized with a data file. The BNF -- grammar for this data file is simple: -- --
--   FILE = LINE+
--   LINE = BIT+
--   BIT  = '0'
--        | '1'
--   
-- -- Consecutive LINEs correspond to consecutive memory addresses -- starting at 0. For example, a data file memory.bin -- containing the 9-bit unsigned numbers 7 to 13 looks -- like: -- --
--   000000111
--   000001000
--   000001001
--   000001010
--   000001011
--   000001100
--   000001101
--   
-- -- Such a file can be produced with memFile: -- --
--   writeFile "memory.bin" (memFile Nothing [7 :: Unsigned 9 .. 13])
--   
-- -- We can instantiate a block RAM using the contents of the file above -- like so: -- --
--   f :: KnownDomain dom
--     => Clock  dom
--     -> Enable dom
--     -> Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 9)
--   f clk en rd = unpack <$> blockRamFile clk en d7 "memory.bin" rd (signal Nothing)
--   
-- -- In the example above, we basically treat the block RAM as a -- synchronous ROM. We can see that it works as expected: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ f systemClockGen enableGen (fromList [3..5])
--   [10,11,12]
--   
-- -- However, we can also interpret the same data as a tuple of a 6-bit -- unsigned number, and a 3-bit signed number: -- --
--   g :: KnownDomain dom
--     => Clock  dom
--     -> Enable dom
--     -> Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 6,Signed 3)
--   g clk en rd = unpack <$> blockRamFile clk en d7 "memory.bin" rd (signal Nothing)
--   
-- -- And then we would see: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ g systemClockGen enableGen (fromList [3..5])
--   [(1,2),(1,3)(1,-4)]
--   
module Clash.Explicit.BlockRam.File -- | Create a block RAM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFile :: (KnownDomain dom, KnownNat m, Enum addr, NFDataX addr, HasCallStack) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFilePow2 :: forall dom n m. (KnownDomain dom, KnownNat m, KnownNat n, HasCallStack) => Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Convert data to the String contents of a memory file. -- -- -- --

Example

-- -- The Maybe datatype has don't care bits, where the actual -- value does not matter. But the bits need a defined value in the -- memory. Either 0 or 1 can be used, and both are valid representations -- of the data. -- --
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8]
--   
--   >>> mapM_ (putStrLn . show . pack) es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> putStr (memFile (Just 0) es)
--   000000000
--   100000111
--   100001000
--   
--   >>> putStr (memFile (Just 1) es)
--   011111111
--   100000111
--   100001000
--   
memFile :: forall a f. (BitPack a, Foldable f, HasCallStack) => Maybe Bit -> f a -> String -- | blockRamFile primitive blockRamFile# :: forall m dom n. (KnownDomain dom, KnownNat m, HasCallStack) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m) -> Signal dom (BitVector m) -- | NB: Not synthesizable initMem :: KnownNat n => FilePath -> IO [BitVector n] -- | Configurable model for true dual-port block RAM module Clash.Explicit.BlockRam.Model -- | Helper used in getConflict data Conflict Conflict :: !MaybeX Bool -> !MaybeX Bool -> !MaybeX Bool -> Conflict -- | Read/Write conflict for output A [cfRWA] :: Conflict -> !MaybeX Bool -- | Read/Write conflict for output B [cfRWB] :: Conflict -> !MaybeX Bool -- | Write/Write conflict [cfWW] :: Conflict -> !MaybeX Bool -- | Determines whether there was a write-write or read-write conflict. A -- conflict occurs when two ports tried to (potentially, in case of -- undefined values) access the same address and one or both tried to -- write to it. See documentation of Conflict for more -- information. getConflict :: (MaybeX Bool, MaybeX Bool, MaybeX Int) -> (MaybeX Bool, MaybeX Bool, MaybeX Int) -> Maybe Conflict -- | Step through a cycle of a TDP block RAM where only one clock is -- active. Like accessRam, it accounts for XException in -- all values supplied by the user of the block RAM. cycleOne :: forall nAddrs a writeEnable. (HasCallStack, NFDataX a) => SNat nAddrs -> TdpbramModelConfig writeEnable a -> a -> Seq a -> (MaybeX Bool, MaybeX Int, MaybeX writeEnable, a) -> (Seq a, a) -- | Step through a cycle of a TDP block RAM where the clock edges of port -- A and port B coincided. Like accessRam, it accounts for -- XException in all values supplied by the user of the block RAM. cycleBoth :: forall nAddrs a writeEnable. (NFDataX a, HasCallStack) => SNat nAddrs -> TdpbramModelConfig writeEnable a -> a -> a -> Seq a -> (MaybeX Bool, MaybeX Int, MaybeX writeEnable, a) -> (MaybeX Bool, MaybeX Int, MaybeX writeEnable, a) -> (Seq a, a, a) -- | Access a RAM and account for undefined values in the address, write -- enable, and data to write. Return read after write value. accessRam :: forall nAddrs a writeEnable. (NFDataX a, HasCallStack) => SNat nAddrs -> (MaybeX writeEnable -> MaybeX Bool) -> (Int -> MaybeX writeEnable -> a -> Seq a -> Seq a) -> MaybeX Int -> MaybeX writeEnable -> a -> Seq a -> (a, Seq a) data TdpbramModelConfig writeEnable a TdpbramModelConfig :: (MaybeX writeEnable -> MaybeX Bool) -> (MaybeX Bool -> MaybeX writeEnable -> MaybeX writeEnable) -> (Int -> MaybeX writeEnable -> a -> Seq a -> Seq a) -> TdpbramModelConfig writeEnable a -- | Determine whether a write enable is active [tdpIsActiveWriteEnable] :: TdpbramModelConfig writeEnable a -> MaybeX writeEnable -> MaybeX Bool -- | Merge global enable with write enable [tdpMergeWriteEnable] :: TdpbramModelConfig writeEnable a -> MaybeX Bool -> MaybeX writeEnable -> MaybeX writeEnable -- | Update memory with a defined address [tdpUpdateRam] :: TdpbramModelConfig writeEnable a -> Int -> MaybeX writeEnable -> a -> Seq a -> Seq a -- | Haskell model for a true dual-port block RAM which is polymorphic in -- its write enables tdpbramModel :: forall nAddrs domA domB a writeEnable. (HasCallStack, KnownNat nAddrs, KnownDomain domA, KnownDomain domB, NFDataX a) => TdpbramModelConfig writeEnable a -> Clock domA -> Signal domA Bool -> Signal domA (Index nAddrs) -> Signal domA writeEnable -> Signal domA a -> Clock domB -> Signal domB Bool -> Signal domB (Index nAddrs) -> Signal domB writeEnable -> Signal domB a -> (Signal domA a, Signal domB a) instance GHC.Show.Show Clash.Explicit.BlockRam.Model.Conflict -- | Internals for Clash.Class.HasDomain module Clash.Class.HasDomain.HasSingleDomain 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 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 WithSingleDomain dom r = (HasSingleDomain r, dom ~ GetDomain r) data TryDomainResult NotFound :: TryDomainResult Ambiguous :: Domain -> Domain -> TryDomainResult Found :: Domain -> TryDomainResult -- | Type family to resolve type conflicts (if any) type family Merge' (n :: TryDomainResult) (m :: TryDomainResult) :: TryDomainResult -- | Same as Merge', but will insert a type error if Merge' got stuck. type family Merge (orig :: Type) (n :: Type) (m :: Type) :: TryDomainResult type family ErrOnConflict (t :: Type) (n :: TryDomainResult) :: Domain type family TryDomain (orig :: Type) (n :: Type) :: TryDomainResult -- | 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. class HasSingleDomain (r :: Type) where { type family GetDomain r :: Domain; type GetDomain r = IfStuck (TryDomain r r) (DelayError (StuckErrorMsg r r)) (Pure (ErrOnConflict r (TryDomain r r))); } instance Clash.Class.HasDomain.HasSingleDomain.HasSingleDomain a module Clash.Class.HasDomain -- | 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 WithSpecificDomain dom r = (HasSpecificDomain dom r, dom ~ GetDomain dom r) -- | 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 WithSingleDomain dom r = (HasSingleDomain r, dom ~ GetDomain r) -- | 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". type family HasDomain (dom :: Domain) (n :: Type) :: HasDomainWrapperResult type family TryDomain (orig :: Type) (n :: Type) :: TryDomainResult data TryDomainResult NotFound :: TryDomainResult Ambiguous :: Domain -> Domain -> TryDomainResult Found :: Domain -> TryDomainResult -- | 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 DomEq (n :: Domain) (m :: Domain) = IfStuck (DomEqWorker n m) ('NotFound) (Pure (DomEqWorker n m)) -- | Wires are fundamentally bidirectional, and in traditional HDLs we can -- exploit this aspect by explicitly marking the endpoint, or port, of -- such a wire as inout, thereby making this port function as both -- a source and a drain for the signals flowing over the wire. -- -- Clash has support for inout ports through the implementation -- of BiSignals. To cleanly map to functions (and thus support -- software simulation using Haskell), a BiSignal comes in two -- parts; the in part: -- --
--   BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
--   
-- -- and the out part: -- --
--   BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
--   
-- -- Where: -- -- -- -- BiSignalIn is used by Clash to generate the inout -- ports on a HDL level, while BiSignalOut is only used for -- simulation purposes and generally discarded by the compiler. -- --

Example

-- -- The following describes a system where two circuits, in alternating -- fashion, read the current value from the bus, increment it, and -- write it on the next cycle. -- --
--   import Clash.Explicit.Prelude
--   import Clash.Signal.BiSignal
--   
--   -- | Alternatingly read / increment+write
--   counter
--     :: (Bool, Int)
--     -- ^ Internal flip + previous read
--     -> Int
--     -- ^ Int from inout
--     -> ((Bool, Int), Maybe Int)
--   counter (write, prevread) i = ((write', prevread'), output)
--     where
--       output    = if write then Just (succ prevread) else Nothing
--       prevread' = if write then prevread else i
--       write' = not write
--   
--   -- | Write on odd cyles
--   f :: Clock System
--     -> Reset System
--     -> Enable System
--     -> BiSignalIn  'Floating System (BitSize Int)
--     -> BiSignalOut 'Floating System (BitSize Int)
--   f clk rst en s = writeToBiSignal s (mealy clk rst en counter (False, 0) (readFromBiSignal s))
--   
--   -- | Write on even cyles
--   g :: Clock System
--     -> Reset System
--     -> Enable System
--     -> BiSignalIn  'Floating System (BitSize Int)
--     -> BiSignalOut 'Floating System (BitSize Int)
--   g clk rst en s = writeToBiSignal s (mealy clk rst en counter (True, 0) (readFromBiSignal s))
--   
--   
--   -- | Connect the /f/ and /g/ circuits to the same bus
--   topEntity
--     :: Clock System
--     -> Reset System
--     -> Enable System
--     -> Signal System Int
--   topEntity clk rst en = readFromBiSignal bus'
--     where
--       bus  = mergeBiSignalOuts $ f clk rst en bus' :> g clk rst en bus' :> Nil
--       bus' = veryUnsafeToBiSignalIn bus
--   
module Clash.Signal.BiSignal -- | The in part of an inout port. BiSignalIn has the type -- role -- --
--   >>> :i BiSignalIn
--   type role BiSignalIn nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | The out part of an inout port -- -- Wraps (multiple) writing signals. The semantics are such that only one -- of the signals may write at a single time step. -- -- BiSignalOut has the type role -- --
--   >>> :i BiSignalOut
--   type role BiSignalOut nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | Used to specify the default behavior of a "BiSignal", i.e. what -- value is read when no value is being written to it. data BiSignalDefault -- | inout port behaves as if connected to a pull-up resistor PullUp :: BiSignalDefault -- | inout port behaves as if connected to a pull-down resistor PullDown :: BiSignalDefault -- | inout port behaves as if is floating. Reading a -- floating "BiSignal" value in simulation will yield an errorX -- (undefined value). Floating :: BiSignalDefault -- | Singleton versions of BiSignalDefault data SBiSignalDefault :: BiSignalDefault -> Type [SPullUp] :: SBiSignalDefault 'PullUp [SPullDown] :: SBiSignalDefault 'PullDown [SFloating] :: SBiSignalDefault 'Floating -- | Type class for BiSignalDefault: can be used as a constraint and -- for obtaining the pull-up mode class HasBiSignalDefault (ds :: BiSignalDefault) pullUpMode :: HasBiSignalDefault ds => BiSignalIn ds dom n -> SBiSignalDefault ds -- | Combine several inout signals into one. mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m -- | Read the value from an inout port readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a -- | Write to an inout port writeToBiSignal :: (HasCallStack, BitPack a, NFDataX a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a) -- | Converts the out part of a BiSignal to an in part. -- In simulation it checks whether multiple components are writing and -- will error accordingly. Make sure this is only called ONCE for every -- BiSignal. veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n instance GHC.Show.Show Clash.Signal.BiSignal.BiSignalDefault instance GHC.Base.Semigroup (Clash.Signal.BiSignal.BiSignalOut defaultState dom n) instance GHC.Base.Monoid (Clash.Signal.BiSignal.BiSignalOut defaultState dom n) instance Clash.Signal.BiSignal.HasBiSignalDefault 'Clash.Signal.BiSignal.PullUp instance Clash.Signal.BiSignal.HasBiSignalDefault 'Clash.Signal.BiSignal.PullDown instance Clash.Signal.BiSignal.HasBiSignalDefault 'Clash.Signal.BiSignal.Floating instance Data.Reflection.Given (Clash.Signal.BiSignal.SBiSignalDefault 'Clash.Signal.BiSignal.PullUp) instance Data.Reflection.Given (Clash.Signal.BiSignal.SBiSignalDefault 'Clash.Signal.BiSignal.PullDown) instance Data.Reflection.Given (Clash.Signal.BiSignal.SBiSignalDefault 'Clash.Signal.BiSignal.Floating) -- | Clash has synchronous Signals in the form of: -- --
--   Signal (dom :: Symbol) 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 Signals 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:: Symbol
--     -- ^ 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 a standard -- implementation, called System, that is configured as follows: -- --
--   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 (100 MHz). Memory elements update their -- state on the rising edge of the clock, can be reset asynchronously -- with regards to the clock, 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. -- -- -- --

Explicit clocks and resets, and meta-stability

-- -- When using multiple clocks and/or reset lines there are ways to -- accidentally introduce situations that are prone to -- metastability. These bugs are incredibly hard to debug as they -- often cannot be simulated, so it's best to prevent them in the first -- place. This section outlines the situations in which metastability -- arises and how to prevent it. -- -- Two types of resets exist: synchronous and asynchronous resets. These -- reset types are encoded in a synthesis domain. For the following -- examples we assume the following exist: -- --
--   DomainConfiguration "SyncExample" _period _edge Synchronous _init
--   DomainConfiguration "AsyncExample" _period _edge Asynchronous _init
--   
-- -- See the previous section on how to use domains. -- -- We now go over the clock and reset line combinations and explain when -- they can potentially introduce situations prone to meta-stability: -- -- module Clash.Explicit.Signal -- | Clash has synchronous Signals 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 Signals 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. -- -- -- -- Signals have the type role -- --
--   >>> :i Signal
--   type role Signal nominal representational
--   ...
--   
-- -- as it is safe to coerce the underlying value of a signal, but not safe -- to coerce a signal between different synthesis domains. -- -- See the module documentation of Clash.Signal for more -- information about domains. data Signal (dom :: Domain) a -- | The in part of an inout port. BiSignalIn has the type -- role -- --
--   >>> :i BiSignalIn
--   type role BiSignalIn nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | The out part of an inout port -- -- Wraps (multiple) writing signals. The semantics are such that only one -- of the signals may write at a single time step. -- -- BiSignalOut has the type role -- --
--   >>> :i BiSignalOut
--   type role BiSignalOut nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | Used to specify the default behavior of a "BiSignal", i.e. what -- value is read when no value is being written to it. data BiSignalDefault -- | inout port behaves as if connected to a pull-up resistor PullUp :: BiSignalDefault -- | inout port behaves as if connected to a pull-down resistor PullDown :: BiSignalDefault -- | inout port behaves as if is floating. Reading a -- floating "BiSignal" value in simulation will yield an errorX -- (undefined value). Floating :: BiSignalDefault type Domain = Symbol -- | A KnownDomain constraint indicates that a circuit's behavior -- depends on some properties of a domain. See DomainConfiguration -- for more information. class (KnownSymbol dom, KnownNat (DomainPeriod dom)) => KnownDomain (dom :: Domain) where { type family KnownConf dom :: DomainConfiguration; } -- | Returns SDomainConfiguration corresponding to an instance's -- DomainConfiguration. -- -- Example usage: -- --
--   >>> knownDomain @System
--   SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
--   
knownDomain :: KnownDomain dom => SDomainConfiguration dom (KnownConf dom) type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) -- | Determines clock edge memory elements are sensitive to. Not yet -- implemented. data ActiveEdge -- | Elements are sensitive to the rising edge (low-to-high) of the clock. Rising :: ActiveEdge -- | Elements are sensitive to the falling edge (high-to-low) of the clock. Falling :: ActiveEdge -- | Singleton version of ActiveEdge data SActiveEdge (edge :: ActiveEdge) [SRising] :: SActiveEdge 'Rising [SFalling] :: SActiveEdge 'Falling data InitBehavior -- | Power up value of memory elements is unknown. Unknown :: InitBehavior -- | If applicable, power up value of a memory element is defined. Applies -- to registers for example, but not to blockRam. Defined :: InitBehavior data SInitBehavior (init :: InitBehavior) [SUnknown] :: SInitBehavior 'Unknown [SDefined] :: SInitBehavior 'Defined data ResetKind -- | Elements respond asynchronously to changes in their reset -- input. This means that they do not wait for the next active -- clock edge, but respond immediately instead. Common on Intel FPGA -- platforms. Asynchronous :: ResetKind -- | Elements respond synchronously to changes in their reset input. -- This means that changes in their reset input won't take effect until -- the next active clock edge. Common on Xilinx FPGA platforms. Synchronous :: ResetKind -- | Singleton version of ResetKind data SResetKind (resetKind :: ResetKind) [SAsynchronous] :: SResetKind 'Asynchronous [SSynchronous] :: SResetKind 'Synchronous -- | Determines the value for which a reset line is considered "active" data ResetPolarity -- | Reset is considered active if underlying signal is True. ActiveHigh :: ResetPolarity -- | Reset is considered active if underlying signal is False. ActiveLow :: ResetPolarity -- | Singleton version of ResetPolarity data SResetPolarity (polarity :: ResetPolarity) [SActiveHigh] :: SResetPolarity 'ActiveHigh [SActiveLow] :: SResetPolarity 'ActiveLow -- | A domain with a name (Domain). Configures the behavior of -- various aspects of a circuits. See the documentation of this record's -- field types for more information on the options. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. data DomainConfiguration DomainConfiguration :: Domain -> Nat -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> DomainConfiguration -- | Domain name [_name] :: DomainConfiguration -> Domain -- | Period of clock in ps [_period] :: DomainConfiguration -> Nat -- | Active edge of the clock [_activeEdge] :: DomainConfiguration -> ActiveEdge -- | Whether resets are synchronous (edge-sensitive) or asynchronous -- (level-sensitive) [_resetKind] :: DomainConfiguration -> ResetKind -- | Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value [_initBehavior] :: DomainConfiguration -> InitBehavior -- | Whether resets are active high or active low [_resetPolarity] :: DomainConfiguration -> ResetPolarity -- | Singleton version of DomainConfiguration data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) [SDomainConfiguration] :: {sName :: SSymbol dom " Domain name", sPeriod :: SNat period " Period of clock in /ps/", sActiveEdge :: SActiveEdge edge " Active edge of the clock (not yet implemented)", sResetKind :: SResetKind reset " Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)", sInitBehavior :: SInitBehavior init " Whether the initial (or "power up") value of memory elements is unknown/undefined, or configurable to a specific value", sResetPolarity :: SResetPolarity polarity " Whether resets are active high or active low"} -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) -- | Convenience type to help to extract a period from a domain. Example -- usage: -- --
--   myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...
--   
type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) -- | Convenience type to help to extract the active edge from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...
--   
type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) -- | Convenience type to help to extract the reset synchronicity from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) => ...
--   
type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) -- | Convenience type to help to extract the initial value behavior from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...
--   
type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) -- | Convenience type to help to extract the reset polarity from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...
--   
type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) -- | Convenience type to constrain a domain to have synchronous resets. -- Example usage: -- --
--   myFunc :: HasSynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) -- | Convenience type to constrain a domain to have asynchronous resets. -- Example usage: -- --
--   myFunc :: HasAsynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) -- | Convenience type to constrain a domain to have initial values. Example -- usage: -- --
--   myFunc :: HasDefinedInitialValues dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Note that there is no UnknownInitialValues dom as a component -- that works without initial values will also work if it does have them. -- -- Click here for usage hints type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) -- | Gets time in Picoseconds from time in Seconds type Seconds (s :: Nat) = Milliseconds (1000 * s) -- | Gets time in Picoseconds from time in Milliseconds type Milliseconds (ms :: Nat) = Microseconds (1000 * ms) -- | Gets time in Picoseconds from time in Microseconds type Microseconds (us :: Nat) = Nanoseconds (1000 * us) -- | Gets time in Picoseconds from time in Nanoseconds type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns) -- | Gets time in Picoseconds from time in picoseconds, essentially -- id type Picoseconds (ps :: Nat) = ps -- | The domain's clock frequency in hertz, calculated based on the period -- stored in picoseconds. This might lead to rounding errors. type DomainToHz (dom :: Domain) = PeriodToHz (DomainPeriod dom) -- | Converts a frequency in hertz to a period in picoseconds. This might -- lead to rounding errors. type HzToPeriod (hz :: Nat) = Seconds 1 `Div` hz -- | Converts a period in picoseconds to a frequency in hertz. This might -- lead to rounding errors. type PeriodToHz (period :: Nat) = (Seconds 1) `Div` period -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed type PeriodToCycles (dom :: Domain) (period :: Nat) = period `DivRU` DomainPeriod dom -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed. The same as -- PeriodToCycles. type ClockDivider (dom :: Domain) (period :: Nat) = PeriodToCycles dom period -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type System = ("System" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and synchronously to -- changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type XilinxSystem = ("XilinxSystem" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type IntelSystem = ("IntelSystem" :: Domain) -- | Convenience value to allow easy "subclassing" of System domain. Should -- be used in combination with createDomain. For example, if you -- just want to change the period but leave all other settings intact -- use: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
vSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of IntelSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vIntelSystem{vName="Intel10", vPeriod=10}
--   
vIntelSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of XilinxSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}
--   
vXilinxSystem :: VDomainConfiguration -- | Same as SDomainConfiguration but allows for easy updates through -- record update syntax. Should be used in combination with -- vDomain and createDomain. Example: -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
data VDomainConfiguration VDomainConfiguration :: String -> Natural -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> VDomainConfiguration -- | Corresponds to _name on DomainConfiguration [vName] :: VDomainConfiguration -> String -- | Corresponds to _period on DomainConfiguration [vPeriod] :: VDomainConfiguration -> Natural -- | Corresponds to _activeEdge on DomainConfiguration [vActiveEdge] :: VDomainConfiguration -> ActiveEdge -- | Corresponds to _resetKind on DomainConfiguration [vResetKind] :: VDomainConfiguration -> ResetKind -- | Corresponds to _initBehavior on DomainConfiguration [vInitBehavior] :: VDomainConfiguration -> InitBehavior -- | Corresponds to _resetPolarity on DomainConfiguration [vResetPolarity] :: VDomainConfiguration -> ResetPolarity -- | Convert SDomainConfiguration to VDomainConfiguration. -- Should be used in combination with createDomain only. vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration -- | Convenience method to express new domains in terms of others. -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
-- -- The function will create two extra identifiers. The first: -- --
--   type System10 = ..
--   
-- -- You can use that as the dom to Clocks/Resets/Enables/Signals. For -- example: Signal System10 Int. Additionally, it will create a -- VDomainConfiguration that you can use in later calls to -- createDomain: -- --
--   vSystem10 = knownVDomain @System10
--   
-- -- It will also make System10 an instance of KnownDomain. -- -- If either identifier is already in scope it will not be generated a -- second time. Note: This can be useful for example when documenting a -- new domain: -- --
--   -- | Here is some documentation for CustomDomain
--   type CustomDomain = ("CustomDomain" :: Domain)
--   
--   -- | Here is some documentation for vCustomDomain
--   createDomain vSystem{vName="CustomDomain"}
--   
createDomain :: VDomainConfiguration -> Q [Dec] -- | Like 'knownDomain but yields a VDomainConfiguration. Should -- only be used in combination with createDomain. knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration -- | Get the clock period from a KnownDomain context clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period -- | Get ActiveEdge from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case activeEdge @dom of
--       SRising -> foo
--       SFalling -> bar
--   
activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge -- | Get ResetKind from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetKind @dom of
--       SAsynchronous -> foo
--       SSynchronous -> bar
--   
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync -- | Get InitBehavior from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case initBehavior @dom of
--       SDefined -> foo
--       SUnknown -> bar
--   
initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init -- | Get ResetPolarity from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetPolarity @dom of
--       SActiveHigh -> foo
--       SActiveLow -> bar
--   
resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity -- | A signal of booleans, indicating whether a component is enabled. No -- special meaning is implied, it's up to the component itself to decide -- how to respond to its enable line. It is used throughout Clash as a -- global enable signal. data Enable dom -- | Convert a signal of bools to an Enable construct toEnable :: Signal dom Bool -> Enable dom -- | Convert Enable construct to its underlying representation: a -- signal of bools. fromEnable :: Enable dom -> Signal dom Bool -- | Enable generator for some domain. Is simply always True. enableGen :: Enable dom -- | A clock signal belonging to a domain named dom. data Clock (dom :: Domain) -- | A differential clock signal belonging to a domain named dom. -- The clock input of a design with such an input has two ports which are -- in antiphase. The first input is the positive phase, the second the -- negative phase. When using makeTopEntity, the names of the -- inputs will end in _p and _n respectively. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. data DiffClock (dom :: Domain) -- | Calculate the frequency in Hz, given the period in ps -- -- I.e., to calculate the clock frequency of a clock with a period of -- 5000 ps: -- --
--   >>> periodToHz 5000
--   2.0e8
--   
-- -- Note that if p in periodToHz (fromIntegral p) -- is negative, fromIntegral will give an Underflow -- :: ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Ratio -- Natural. To get the old behavior of this function, use a type -- application: -- --
--   >>> periodToHz @(Ratio Natural) 5000
--   200000000 % 1
--   
-- -- NB: This function is not synthesizable periodToHz :: (HasCallStack, Fractional a) => Natural -> a -- | Calculate the period in ps, given a frequency in Hz -- -- I.e., to calculate the clock period for a circuit to run at 240 MHz we -- get -- --
--   >>> hzToPeriod 240e6
--   4166
--   
-- -- If the value hzToPeriod is applied to is not of the type -- Ratio Natural, you can use hzToPeriod -- (realToFrac f). Note that if f is negative, -- realToFrac will give an Underflow :: -- ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Natural. To -- get the old behavior of this function, use a type application: -- --
--   >>> hzToPeriod @Natural 240e6
--   4166
--   
-- -- hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a -- | The unsafeSynchronizer function is a primitive that must be -- used to connect one clock domain to the other, and will be synthesized -- to a (bundle of) wire(s) in the eventual circuit. This function should -- only be used as part of a proper synchronization component, such as -- the following dual flip-flop synchronizer: -- --
--   dualFlipFlop
--     :: Clock domA
--     -> Clock domB
--     -> Enable domA
--     -> Enable domB
--     -> Bit
--     -> Signal domA Bit
--     -> Signal domB Bit
--   dualFlipFlop clkA clkB enA enB dflt =
--     delay clkB enB dflt . delay clkB enB dflt . unsafeSynchronizer clkA clkB
--   
-- -- The unsafeSynchronizer works in such a way that, given 2 -- clocks: -- --
--   createDomain vSystem{vName="Dom7", vPeriod=7}
--   
--   clk7 :: Clock Dom7
--   clk7 = clockGen
--   
--   en7 :: Enable Dom7
--   en7 = enableGen
--   
-- -- and -- --
--   createDomain vSystem{vName="Dom2", vPeriod=2}
--   
--   clk2 :: Clock Dom2
--   clk2 = clockGen
--   
--   en2 :: Enable Dom2
--   en2 = enableGen
--   
-- -- Oversampling followed by compression is the identity function plus 2 -- initial values: -- --
--   delay clkB enB dflt $
--   unsafeSynchronizer clkA clkB $
--   delay clkA enA dflt $
--   unsafeSynchronizer clkB clkA $
--   delay clkB enB s
--   
--   ==
--   
--   dflt :- dflt :- s
--   
-- -- Something we can easily observe: -- --
--   oversampling clkA clkB enA enB dflt =
--     delay clkB enB dflt
--       . unsafeSynchronizer clkA clkB
--       . delay clkA enA dflt
--   almostId clkA clkB enA enB dflt =
--     delay clkB enB dflt
--       . unsafeSynchronizer clkA clkB
--       . delay clkA enA dflt
--       . unsafeSynchronizer clkB clkA
--       . delay clkB enB dflt
--   
-- --
--   >>> sampleN 37 (oversampling clk7 clk2 en7 en2 0 (fromList [(1::Int)..10]))
--   [0,0,1,1,1,2,2,2,2,3,3,3,4,4,4,4,5,5,5,6,6,6,6,7,7,7,8,8,8,8,9,9,9,10,10,10,10]
--   
--   >>> sampleN 12 (almostId clk2 clk7 en2 en7 0 (fromList [(1::Int)..10]))
--   [0,0,1,2,3,4,5,6,7,8,9,10]
--   
unsafeSynchronizer :: forall dom1 dom2 a. (KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Signal dom1 a -> Signal dom2 a -- | Same as unsafeSynchronizer, but with manually supplied clock -- periods. -- -- Note: this unsafeSynchronizer is defined to be consistent with the -- vhdl and verilog implementations however as only synchronous signals -- are represented in Clash this cannot be done precisely and can lead to -- odd behavior. For example, -- --
--   sample $ unsafeSynchronizer @Dom2 @Dom7 . unsafeSynchronizer @Dom7 @Dom2 $ fromList [0..10]
--   > [0,4,4,4,7,7,7,7,11,11,11..
--   
-- -- is quite different from the identity, -- --
--   sample $ fromList [0..10]
--   > [0,1,2,3,4,5,6,7,8,9,10..
--   
-- -- with values appearing from the "future". veryUnsafeSynchronizer :: Either Int (Signal dom1 Int) -> Either Int (Signal dom2 Int) -> Signal dom1 a -> Signal dom2 a -- | A reset signal belonging to a domain called dom. -- -- The underlying representation of resets is Bool. data Reset (dom :: Domain) -- | unsafeToReset is unsafe. For asynchronous resets it is unsafe -- because it can introduce combinatorial loops. In case of synchronous -- resets it can lead to meta-stability issues in the presence of -- asynchronous resets. -- -- NB: You probably want to use unsafeFromActiveLow or -- unsafeFromActiveHigh. unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom -- | unsafeFromReset is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- -- NB: You probably want to use unsafeToActiveLow or -- unsafeToActiveHigh. unsafeFromReset :: Reset dom -> Signal dom Bool -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Merge enable signal with signal of bools by applying the boolean AND -- operation. andEnable :: Enable dom -> Signal dom Bool -> Enable dom -- | Special version of delay that doesn't take enable signals of -- any kind. Initial value will be undefined. dflipflop :: (KnownDomain dom, NFDataX a) => Clock dom -> Signal dom a -> Signal dom a -- | "delay clk s" delays the values in Signal -- s for once cycle, the value at time 0 is dflt. -- --
--   >>> sampleN 3 (delay systemClockGen enableGen 0 (fromList [1,2,3,4]))
--   [0,1,2]
--   
delay :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a -- | Version of delay that only updates when its third argument is a -- Just value. -- --
--   >>> let input = fromList [Just 1, Just 2, Nothing, Nothing, Just 5, Just 6, Just (7::Int)]
--   
--   >>> sampleN 7 (delayMaybe systemClockGen enableGen 0 input)
--   [0,1,2,2,2,5,6]
--   
delayMaybe :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom (Maybe a) -> Signal dom a -- | Version of delay that only updates when its third argument is -- asserted. -- --
--   >>> let input = fromList [1,2,3,4,5,6,7::Int]
--   
--   >>> let enable = fromList [True,True,False,False,True,True,True]
--   
--   >>> sampleN 7 (delayEn systemClockGen enableGen 0 enable input)
--   [0,1,2,2,2,5,6]
--   
delayEn :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | "register clk rst en i s" delays the values in -- Signal s for one cycle, and sets the value to i -- the moment the reset becomes False. -- --
--   >>> sampleN 5 (register systemClockGen resetGen enableGen 8 (fromList [1,1,2,3,4]))
--   [8,8,1,2,3]
--   
register :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a -- | Version of register that only updates its content when its -- fourth argument is a Just value. So given: -- --
--   sometimes1 clk rst en = s where
--     s = register clk rst en Nothing (switch <$> s)
--   
--     switch Nothing = Just 1
--     switch _       = Nothing
--   
--   countSometimes clk rst en = s where
--     s     = regMaybe clk rst en 0 (plusM (pure <$> s) (sometimes1 clk rst en))
--     plusM = liftA2 (liftA2 (+))
--   
-- -- We get: -- --
--   >>> sampleN 9 (sometimes1 systemClockGen resetGen enableGen)
--   [Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]
--   
--   >>> sampleN 9 (count systemClockGen resetGen enableGen)
--   [0,0,0,1,1,2,2,3,3]
--   
regMaybe :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom (Maybe a) -> Signal dom a -- | Version of register that only updates its content when its -- fourth argument is asserted. So given: -- --
--   oscillate clk rst en = let s = register clk rst en False (not <$> s) in s
--   count clk rst en     = let s = 'regEn clk rst en 0 (oscillate clk rst en) (s + 1) in s
--   
-- -- We get: -- --
--   >>> sampleN 9 (oscillate systemClockGen resetGen enableGen)
--   [False,False,True,False,True,False,True,False,True]
--   
--   >>> sampleN 9 (count systemClockGen resetGen enableGen)
--   [0,0,0,1,1,2,2,3,3]
--   
regEn :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | The above type is a generalization for: -- --
--   mux :: Signal Bool -> Signal a -> Signal a -> Signal a
--   
-- -- A multiplexer. Given "mux b t f", output t -- when b is True, and f when b is -- False. mux :: Applicative f => f Bool -> f a -> f a -> f a -- | Clock generator for simulations. Do not use this clock -- generator for the testBench function, use tbClockGen -- instead. -- -- To be used like: -- --
--   clkSystem = clockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. clockGen :: KnownDomain dom => Clock dom -- | Reset generator for simulation purposes. Asserts the reset for a -- single cycle. -- -- To be used like: -- --
--   rstSystem = resetGen @System
--   
-- -- See tbClockGen for example usage. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGen :: forall dom. KnownDomain dom => Reset dom -- | Reset generator for simulation purposes. Asserts the reset for the -- first n cycles. -- -- To be used like: -- --
--   rstSystem5 = resetGen @System d5
--   
-- -- Example usage: -- --
--   >>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
--   [True,True,True,False,False,False,False]
--   
-- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom -- | Clock generator for the System clock domain. -- -- NB: Should only be used for simulation, and not for the -- testBench function. For the testBench function, used -- tbSystemClockGen systemClockGen :: Clock System -- | Reset generator for use in simulation, for the System clock -- domain. Asserts the reset for a single cycle. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
systemResetGen :: Reset System -- | The above type is a generalization for: -- --
--   (.&&.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (&&) that returns a Signal of -- Bool (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 .&&. -- | The above type is a generalization for: -- --
--   (.||.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (||) that returns a Signal of -- Bool (.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 .||. -- | Isomorphism between a Signal of a product type (e.g. a tuple) -- and a product type of Signals. -- -- Instances of Bundle must satisfy the following laws: -- --
--   bundle . unbundle = id
--   unbundle . bundle = id
--   
-- -- By default, bundle and unbundle, are defined as the -- identity, that is, writing: -- --
--   data D = A | B
--   
--   instance Bundle D
--   
-- -- is the same as: -- --
--   data D = A | B
--   
--   instance Bundle D where
--     type Unbundled clk D = Signal clk D
--     bundle   s = s
--     unbundle s = s
--   
-- -- For custom product types you'll have to write the instance manually: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b }
--   
--   instance Bundle (Pair a b) where
--     type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b)
--   
--     -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b)
--     bundle   (MkPair as bs) = MkPair <$> as <*> bs
--   
--     -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b)
--     unbundle pairs = MkPair (getA <$> pairs) (getB <$> pairs)
--   
class Bundle a where { type family Unbundled (dom :: Domain) a = res | res -> dom a; type Unbundled dom a = Signal dom a; } -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: Bundle a => Unbundled dom a -> Signal dom a -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: (Bundle a, Signal dom a ~ Unbundled dom a) => Unbundled dom a -> Signal dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: Bundle a => Signal dom a -> Unbundled dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: (Bundle a, Unbundled dom a ~ Signal dom a) => Signal dom a -> Unbundled dom a -- | See TaggedEmptyTuple data EmptyTuple EmptyTuple :: EmptyTuple -- | Helper type to emulate the "old" behavior of Bundle's unit instance. -- I.e., the instance for Bundle () used to be defined as: -- --
--   class Bundle () where
--     bundle   :: () -> Signal dom ()
--     unbundle :: Signal dom () -> ()
--   
-- -- In order to have sensible type inference, the Bundle class -- specifies that the argument type of bundle should uniquely -- identify the result type, and vice versa for unbundle. The type -- signatures in the snippet above don't though, as () doesn't -- uniquely map to a specific domain. In other words, domain -- should occur in both the argument and result of both functions. -- -- TaggedEmptyTuple tackles this by carrying the domain in its -- type. The bundle and unbundle instance now looks like: -- --
--   class Bundle EmptyTuple where
--     bundle   :: TaggedEmptyTuple dom -> Signal dom EmptyTuple
--     unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
--   
-- -- dom is now mentioned both the argument and result for both -- bundle and unbundle. data TaggedEmptyTuple (dom :: Domain) TaggedEmptyTuple :: TaggedEmptyTuple (dom :: Domain) -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
--   [8,8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] -- | Simulate a (Unbundled a -> Unbundled b) -- function given a list of samples of type a -- --
--   >>> simulateB (unbundle . register systemClockGen resetGen enableGen (8,8) . bundle) [(1,1), (1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB :: (Bundle a, Bundle b, NFDataX a, NFDataX b) => (Unbundled dom1 a -> Unbundled dom2 b) -> [a] -> [b] -- | Same as simulate, but with the reset line asserted for n -- cycles. Similar to simulate, simulateWithReset will drop -- the output values produced while the reset is asserted. While the -- reset is asserted, the first value from [a] is fed to the -- circuit. simulateWithReset :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulateWithReset, but only sample the first Int -- output values. simulateWithResetN :: (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> Int -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) -> [a] -> [b] -- | Simulate a component until it matches a condition -- -- It prints a message of the form -- --
--   Signal sampled for N cycles until value X
--   
-- -- NB: This function is not synthesizable -- --

Example with test bench

-- -- A common usage is with a test bench using outputVerifier. -- -- NB: Since this uses assert, when using clashi, -- read the note at Clash.Explicit.Testbench#assert-clashi. -- --
--   import Clash.Prelude
--   import Clash.Explicit.Testbench
--   
--   topEntity
--     :: Signal System Int
--     -> Signal System Int
--   topEntity = id
--   
--   testBench
--     :: Signal System Bool
--   testBench = done
--    where
--     testInput = stimuliGenerator clk rst $(listToVecTH [1 :: Int .. 10])
--     expectedOutput =
--       outputVerifier' clk rst $(listToVecTH $ [1 :: Int .. 9] <> [42])
--     done = expectedOutput $ topEntity testInput
--     clk = tbSystemClockGen (not <$> done)
--     rst = systemResetGen
--   
-- --
--   > runUntil id testBench
--   
--   
--   cycle(<Clock: System>): 10, outputVerifier
--   expected value: 42, not equal to actual value: 10
--   Signal sampled for 11 cycles until value True
--   
-- -- When you need to verify multiple test benches, the following -- invocations come in handy: -- --
--   > mapM_ (runUntil id) [ testBenchA, testBenchB ]
--   
-- -- or when the test benches are in different clock domains: -- --
--   testBenchA :: Signal DomA Bool
--   testBenchB :: Signal DomB Bool
--   
-- --
--   > sequence_ [ runUntil id testBenchA, runUntil id testBenchB ]
--   
runUntil :: forall dom a. (KnownDomain dom, NFDataX a, ShowX a) => (a -> Bool) -> Signal dom a -> IO () -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
--   [8,8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] -- | Lazily simulate a (Unbundled a -> -- Unbundled b) function given a list of samples of type -- a -- --
--   >>> simulateB (unbundle . register systemClockGen resetGen enableGen (8,8) . bundle) [(1,1), (1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB_lazy :: (Bundle a, Bundle b) => (Unbundled dom1 a -> Unbundled dom2 b) -> [a] -> [b] -- | Build an Automaton from a function over Signals. -- -- NB: Consumption of continuation of the Automaton must be -- affine; that is, you can only apply the continuation associated with a -- particular element at most once. signalAutomaton :: forall dom a b. (Signal dom a -> Signal dom b) -> Automaton (->) a b -- | The above type is a generalization for: -- --
--   sample :: Signal a -> [a]
--   
-- -- Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- NB: This function is not synthesizable sample :: (Foldable f, NFDataX a) => f a -> [a] -- | The above type is a generalization for: -- --
--   sampleN :: Int -> Signal a -> [a]
--   
-- -- Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN 3 s == [s0, s1, s2]
--   
-- -- NB: This function is not synthesizable sampleN :: (Foldable f, NFDataX a) => Int -> f a -> [a] -- | Get a list of samples from a Signal, while asserting the reset -- line for n clock cycles. sampleWithReset does not return -- the first n cycles, i.e., when the reset is asserted. -- -- NB: This function is not synthesizable sampleWithReset :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a) -> [a] -- | Get a fine list of m samples from a Signal, while -- asserting the reset line for n clock cycles. -- sampleWithReset does not return the first n cycles, -- i.e., while the reset is asserted. -- -- NB: This function is not synthesizable sampleWithResetN :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> Int -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a) -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5])
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList :: NFDataX a => [a] -> Signal dom a -- | Like fromList, but resets on reset and has a defined reset -- value. -- --
--   >>> let rst = unsafeFromActiveHigh (fromList [True, True, False, False, True, False])
--   
--   >>> let res = fromListWithReset @System rst Nothing [Just 'a', Just 'b', Just 'c']
--   
--   >>> sampleN 6 res
--   [Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
--   
-- -- NB: This function is not synthesizable fromListWithReset :: forall dom a. (KnownDomain dom, NFDataX a) => Reset dom -> a -> [a] -> Signal dom a -- | The above type is a generalization for: -- --
--   sample :: Signal a -> [a]
--   
-- -- Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- NB: This function is not synthesizable sample_lazy :: Foldable f => f a -> [a] -- | The above type is a generalization for: -- --
--   sampleN :: Int -> Signal a -> [a]
--   
-- -- Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN 3 s == [s0, s1, s2]
--   
-- -- NB: This function is not synthesizable sampleN_lazy :: Foldable f => Int -> f a -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList_lazy :: [a] -> Signal dom a -- | The above type is a generalization for: -- --
--   testFor :: Int -> Signal Bool -> Property
--   
-- -- testFor n s tests the signal s for n -- cycles. -- -- NB: This function is not synthesizable testFor :: Foldable f => Int -> f Bool -> Property -- | The above type is a generalization for: -- --
--   (.==.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (==) that returns a Signal of -- Bool (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 .==. -- | The above type is a generalization for: -- --
--   (./=.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (/=) that returns a Signal of -- Bool (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 ./=. -- | The above type is a generalization for: -- --
--   (.<.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<) that returns a Signal of -- Bool (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<. -- | The above type is a generalization for: -- --
--   (.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<=) that returns a Signal of -- Bool (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<=. -- | The above type is a generalization for: -- --
--   (.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>=) that returns a Signal of -- Bool (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>=. -- | The above type is a generalization for: -- --
--   (.>.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>) that returns a Signal of -- Bool (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>. -- | Converts the out part of a BiSignal to an in part. -- In simulation it checks whether multiple components are writing and -- will error accordingly. Make sure this is only called ONCE for every -- BiSignal. veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n -- | Read the value from an inout port readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a -- | Write to an inout port writeToBiSignal :: (HasCallStack, BitPack a, NFDataX a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a) -- | Combine several inout signals into one. mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveLow instead. This function -- will be removed in Clash 1.12. unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveLow instead. This function -- will be removed in Clash 1.12. unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool module Clash.Explicit.Signal.Delayed -- | A synchronized signal with samples of type a, synchronized to -- clock clk, that has accumulated delay amount of -- samples delay along its path. -- -- DSignal has the type role -- --
--   >>> :i DSignal
--   type role DSignal nominal nominal representational
--   ...
--   
-- -- as it is safe to coerce the values in the signal, but not safe to -- coerce the synthesis domain or delay in the signal. data DSignal (dom :: Domain) (delay :: Nat) a -- | Delay a DSignal for d periods. -- --
--   delay3
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom n Int
--     -> DSignal dom (n + 3) Int
--   delay3 clk rst en = delayed clk rst en (-1 :> -1 :> -1 :> Nil)
--   
-- --
--   >>> sampleN 7 (delay3 systemClockGen resetGen enableGen (dfromList [0..]))
--   [-1,-1,-1,-1,1,2,3]
--   
delayed :: forall dom a n d. (KnownDomain dom, KnownNat d, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> Vec d a -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d periods, where d is -- derived from the context. -- --
--   delay2
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Int
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delay2 = delayedI
--   
-- --
--   >>> sampleN 7 (delay2 systemClockGen resetGen enableGen (-1) (dfromList ([0..])))
--   [-1,-1,-1,1,2,3,4]
--   
-- -- d can also be specified using type application: -- --
--   >>> :t delayedI @3
--   delayedI @3
--     :: ... =>
--        Clock dom
--        -> Reset dom
--        -> Enable dom
--        -> a
--        -> DSignal dom n a
--        -> DSignal dom (n + 3) a
--   
delayedI :: (KnownNat d, KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d cycles, the value at time 0..d-1 -- is a. -- --
--   delayN2
--     :: KnownDomain dom
--     => Int
--     -> Enable dom
--     -> Clock dom
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delayN2 = delayN d2
--   
-- --
--   >>> printX $ sampleN 6 (delayN2 (-1) enableGen systemClockGen (dfromList [1..]))
--   [-1,-1,1,2,3,4]
--   
delayN :: forall dom a d n. (KnownDomain dom, NFDataX a) => SNat d -> a -> Enable dom -> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d cycles, where d is -- derived from the context. The value at time 0..d-1 is a default value. -- --
--   delayI2
--     :: KnownDomain dom
--     => Int
--     -> Enable dom
--     -> Clock dom
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delayI2 = delayI
--   
-- --
--   >>> sampleN 6 (delayI2 (-1) enableGen systemClockGen (dfromList [1..]))
--   [-1,-1,1,2,3,4]
--   
-- -- You can also use type application to do the same: -- --
--   >>> sampleN 6 (delayI @2 (-1) enableGen systemClockGen (dfromList [1..]))
--   [-1,-1,1,2,3,4]
--   
delayI :: forall d n a dom. (NFDataX a, KnownDomain dom, KnownNat d) => a -> Enable dom -> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a -- | Tree fold over a Vec of DSignals with a combinatorial -- function, and delaying delay cycles after each application. -- Values at times 0..(delay*k)-1 are set to a default. -- --
--   countingSignals :: Vec 4 (DSignal dom 0 Int)
--   countingSignals = repeat (dfromList [0..])
--   
-- --
--   >>> printX $ sampleN 6 (delayedFold  d1 (-1) (+) enableGen systemClockGen countingSignals)
--   [-1,-2,0,4,8,12]
--   
-- --
--   >>> printX $ sampleN 8 (delayedFold d2 (-1) (*) enableGen systemClockGen countingSignals)
--   [-1,-1,1,1,0,1,16,81]
--   
delayedFold :: forall dom n delay k a. (NFDataX a, KnownDomain dom, KnownNat delay, KnownNat k) => SNat delay -> a -> (a -> a -> a) -> Enable dom -> Clock dom -> Vec (2 ^ k) (DSignal dom n a) -> DSignal dom (n + (delay * k)) a -- | Feed the delayed result of a function back to its input: -- --
--   mac
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = feedback (mac' x y)
--     where
--       mac'
--         :: DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> (DSignal dom 0 Int, DSignal dom 1 Int)
--       mac' a b acc = let acc' = a * b + acc
--                      in  (acc, delayedI clk rst en 0 acc')
--   
-- --
--   >>> sampleN 7 (toSignal (mac systemClockGen systemResetGen enableGen (dfromList [0..]) (dfromList [0..])))
--   [0,0,1,5,14,30,55]
--   
feedback :: (DSignal dom n a -> (DSignal dom n a, DSignal dom ((n + m) + 1) a)) -> DSignal dom n a -- | Signals are not delayed fromSignal :: Signal dom a -> DSignal dom 0 a -- | Strip a DSignal of its delay information. toSignal :: DSignal dom delay a -> Signal dom a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList :: NFDataX a => [a] -> DSignal dom 0 a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList_lazy :: [a] -> DSignal dom 0 a -- | EXPERIMENTAL -- -- Unsafely convert a Signal to a DSignal with an -- arbitrary delay. -- -- NB: Should only be used to interface with functions specified -- in terms of Signal. unsafeFromSignal :: Signal dom a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the future in the present. Often -- required When writing a circuit that requires feedback from itself. -- --
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = acc'
--     where
--       acc' = (x * y) + antiDelay d1 acc
--       acc  = delayedI clk rst en 0 acc'
--   
antiDelay :: SNat d -> DSignal dom (n + d) a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the past in the present. In -- contrast with delayed and friends forward does not insert any -- logic. This means using this function violates the delay invariant of -- DSignal. This is sometimes useful when combining unrelated -- delayed signals where inserting logic is not wanted or when -- abstracting over internal delayed signals where the internal delay -- information should not be leaked. -- -- For example, the circuit below returns a sequence of numbers as a pair -- but the internal delay information between the elements of the pair -- should not leak into the type. -- --
--   numbers
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 5 (Int, Int)
--   numbers clk rst en = DB.bundle (forward d1 s1, s2)
--     where
--       s1 :: DSignal dom 4 Int
--       s1 = delayed clk rst en (100 :> 10 :> 5 :> 1 :> Nil) (pure 200)
--       s2 :: DSignal dom 5 Int
--       s2 = fmap (2*) $ delayN d1 0 en clk s1
--   
-- --
--   >>> sampleN 8 (toSignal (numbers systemClockGen systemResetGen enableGen))
--   [(1,0),(1,2),(5,2),(10,10),(100,20),(200,200),(200,400),(200,400)]
--   
forward :: SNat d -> DSignal dom n a -> DSignal dom (n + d) a -- |

Initializing a ROM with a data file

-- -- ROMs initialized with a data file. The BNF grammar for this data file -- is simple: -- --
--   FILE = LINE+
--   LINE = BIT+
--   BIT  = '0'
--        | '1'
--   
-- -- Consecutive LINEs correspond to consecutive memory addresses -- starting at 0. For example, a data file memory.bin -- containing the 9-bit unsigned numbers 7 to 13 looks -- like: -- --
--   000000111
--   000001000
--   000001001
--   000001010
--   000001011
--   000001100
--   000001101
--   
-- -- Such a file can be produced with memFile: -- --
--   writeFile "memory.bin" (memFile Nothing [7 :: Unsigned 9 .. 13])
--   
-- -- We can instantiate a synchronous ROM using the contents of the file -- above like so: -- --
--   f :: KnownDomain dom
--     => Clock  dom
--     -> Enable dom
--     -> Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 9)
--   f clk en rd = unpack <$> romFile clk en d7 "memory.bin" rd
--   
-- -- And see that it works as expected: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ f systemClockGen (fromList [3..5])
--   [10,11,12]
--   
-- -- However, we can also interpret the same data as a tuple of a 6-bit -- unsigned number, and a 3-bit signed number: -- --
--   g :: KnownDomain dom
--     => Clock  dom
--     -> Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 6,Signed 3)
--   g clk en rd = unpack <$> romFile clk en d7 "memory.bin" rd
--   
-- -- And then we would see: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ g systemClockGen (fromList [3..5])
--   [(1,2),(1,3)(1,-4)]
--   
module Clash.Explicit.ROM.File -- | A ROM with a synchronous read port, with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- romFile :: (KnownNat m, Enum addr, KnownDomain dom) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- -- TODO: table -- --

See also:

-- -- romFilePow2 :: forall dom n m. (KnownNat m, KnownNat n, KnownDomain dom) => Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Convert data to the String contents of a memory file. -- -- -- --

Example

-- -- The Maybe datatype has don't care bits, where the actual -- value does not matter. But the bits need a defined value in the -- memory. Either 0 or 1 can be used, and both are valid representations -- of the data. -- --
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8]
--   
--   >>> mapM_ (putStrLn . show . pack) es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> putStr (memFile (Just 0) es)
--   000000000
--   100000111
--   100001000
--   
--   >>> putStr (memFile (Just 1) es)
--   011111111
--   100000111
--   100001000
--   
memFile :: forall a f. (BitPack a, Foldable f, HasCallStack) => Maybe Bit -> f a -> String -- | romFile primitive romFile# :: forall m dom n. (KnownNat m, KnownDomain dom) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom (BitVector m) -- | RAM primitives with a combinational read port. module Clash.Explicit.RAM -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> SNat n -> Signal rdom addr -> Signal wdom (Maybe (addr, a)) -> Signal rdom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: forall wdom rdom n a. (KnownNat n, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> Signal rdom (Unsigned n) -> Signal wdom (Maybe (Unsigned n, a)) -> Signal rdom a -- | RAM primitive asyncRam# :: forall wdom rdom n a. (HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> SNat n -> Signal rdom Int -> Signal wdom Bool -> Signal wdom Int -> Signal wdom a -> Signal rdom a -- | Whereas the output of a Mealy machine depends on current -- transition, the output of a Moore machine depends on the -- previous state. -- -- Moore machines are strictly less expressive, but may impose laxer -- timing requirements. module Clash.Explicit.Moore -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = moore clk rst en macT id 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore clk rst en macT id 0 (bundle (a,x))
--       s2 = moore clk rst en macT id 0 (bundle (b,y))
--   
moore :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore clk rst en t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore clk rst en t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB clk rst en t o 0 (a,b)
--       (i2,b2) = mooreB clk rst en t o 3 (c,i1)
--   
mooreB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine without any output logic medvedev :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> s -> Signal dom i -> Signal dom s -- | A version of medvedev that does automatic Bundleing medvedevB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> s -> Unbundled dom i -> Unbundled dom s -- | Whereas the output of a Moore machine depends on the previous -- state, the output of a Mealy machine depends on current -- transition. -- -- Mealy machines are strictly more expressive, but may impose stricter -- timing requirements. module Clash.Explicit.Mealy -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   import qualified Data.List as L
--   
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = mealy clk rst en macT 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy clk rst en macT 0 (bundle (a,x))
--       s2 = mealy clk rst en macT 0 (bundle (b,y))
--   
mealy :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | Create a synchronous function from a combinational function describing -- a mealy machine using the state monad. This can be particularly useful -- when combined with lenses or optics to replicate imperative -- algorithms. -- --
--   data DelayState = DelayState
--     { _history    :: Vec 4 Int
--     , _untilValid :: Index 4
--     }
--     deriving (Generic, NFDataX)
--   makeLenses ''DelayState
--   
--   initialDelayState = DelayState (repeat 0) maxBound
--   
--   delayS :: Int -> State DelayState (Maybe Int)
--   delayS n = do
--     history   %= (n +>>)
--     remaining <- use untilValid
--     if remaining > 0
--     then do
--        untilValid -= 1
--        return Nothing
--      else do
--        out <- uses history last
--        return (Just out)
--   
--   delayTop ::KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int -> Signal dom (Maybe Int))
--   delayTop clk rst en = mealyS clk rst en delayS initialDelayState
--   
-- --
--   >>> L.take 7 $ simulate (delayTop systemClockGen systemResetGen enableGen) [-100,1,2,3,4,5,6,7,8]
--   [Nothing,Nothing,Nothing,Nothing,Just 1,Just 2,Just 3]
--   
mealyS :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool,Int) -> (Int,(Int,Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy clk rst en f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy clk rst en f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB clk rst en f 0 (a,b)
--       (i2,b2) = mealyB clk rst en f 3 (c,i1)
--   
mealyB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | A version of mealyS that does automatic Bundleing, see -- mealyB for details. mealySB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o -- |

Efficient bundling of initial RAM content with the compiled -- code

-- -- Leveraging Template Haskell, the initial content for the block RAM -- components in this module is stored alongside the compiled Haskell -- code. It covers use cases where passing the initial content as a -- Vec turns out to be problematically slow. -- -- The data is stored efficiently, with very little overhead (worst-case -- 7%, often no overhead at all). -- -- Unlike Clash.Explicit.BlockRam.File, -- Clash.Explicit.BlockRam.Blob generates practically the same HDL -- as Clash.Explicit.BlockRam and is compatible with all tools -- consuming the generated HDL. module Clash.Explicit.BlockRam.Blob -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (KnownDomain dom, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | blockRAMBlob primitive blockRamBlob# :: forall dom m n. KnownDomain dom => Clock dom -> Enable dom -> MemBlob n m -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m) -> Signal dom (BitVector m) -- |

Efficient bundling of ROM content with the compiled code

-- -- Leveraging Template Haskell, the content for the ROM components in -- this module is stored alongside the compiled Haskell code. It covers -- use cases where passing the initial content as a Vec turns out -- to be problematically slow. -- -- The data is stored efficiently, with very little overhead (worst-case -- 7%, often no overhead at all). -- -- Unlike Clash.Explicit.ROM.File, Clash.Explicit.ROM.Blob -- generates practically the same HDL as Clash.Explicit.ROM and is -- compatible with all tools consuming the generated HDL. module Clash.Explicit.ROM.Blob -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (KnownDomain dom, Enum addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | ROM primitive romBlob# :: forall dom m n. KnownDomain dom => Clock dom -> Enable dom -> MemBlob n m -> Signal dom Int -> Signal dom (BitVector m) -- | Block RAM primitives -- --

Using RAMs

-- -- We will show a rather elaborate example on how you can, and why you -- might want to use block RAMs. We will build a "small" CPU + Memory + -- Program ROM where we will slowly evolve to using block RAMs. Note that -- the code is not meant as a de-facto standard on how to do CPU -- design in Clash. -- -- We start with the definition of the Instructions, Register names and -- machine codes: -- --
--   {-# LANGUAGE RecordWildCards, TupleSections, DeriveAnyClass #-}
--   
--   module CPU where
--   
--   import Clash.Explicit.Prelude
--   
--   type InstrAddr = Unsigned 8
--   type MemAddr   = Unsigned 5
--   type Value     = Signed 8
--   
--   data Instruction
--     = Compute Operator Reg Reg Reg
--     | Branch Reg Value
--     | Jump Value
--     | Load MemAddr Reg
--     | Store Reg MemAddr
--     | Nop
--     deriving (Eq, Show, Generic, NFDataX)
--   
--   data Reg
--     = Zero
--     | PC
--     | RegA
--     | RegB
--     | RegC
--     | RegD
--     | RegE
--     deriving (Eq, Show, Enum, Generic, NFDataX)
--   
--   data Operator = Add | Sub | Incr | Imm | CmpGt
--     deriving (Eq, Show, Generic, NFDataX)
--   
--   data MachCode
--     = MachCode
--     { inputX  :: Reg
--     , inputY  :: Reg
--     , result  :: Reg
--     , aluCode :: Operator
--     , ldReg   :: Reg
--     , rdAddr  :: MemAddr
--     , wrAddrM :: Maybe MemAddr
--     , jmpM    :: Maybe Value
--     }
--   
--   nullCode =
--     MachCode
--       { inputX = Zero
--       , inputY = Zero
--       , result = Zero
--       , aluCode = Imm
--       , ldReg = Zero
--       , rdAddr = 0
--       , wrAddrM = Nothing
--       , jmpM = Nothing
--       }
--   
-- -- Next we define the CPU and its ALU: -- --
--   cpu
--     :: Vec 7 Value          -- ^ Register bank
--     -> (Value,Instruction)  -- ^ (Memory output, Current instruction)
--     -> ( Vec 7 Value
--        , (MemAddr, Maybe (MemAddr,Value), InstrAddr)
--        )
--   cpu regbank (memOut, instr) =
--     (regbank', (rdAddr, (,aluOut) <$> wrAddrM, bitCoerce ipntr))
--    where
--     -- Current instruction pointer
--     ipntr = regbank !! PC
--   
--     -- Decoder
--     (MachCode {..}) = case instr of
--       Compute op rx ry res -> nullCode {inputX=rx,inputY=ry,result=res,aluCode=op}
--       Branch cr a          -> nullCode {inputX=cr,jmpM=Just a}
--       Jump a               -> nullCode {aluCode=Incr,jmpM=Just a}
--       Load a r             -> nullCode {ldReg=r,rdAddr=a}
--       Store r a            -> nullCode {inputX=r,wrAddrM=Just a}
--       Nop                  -> nullCode
--   
--     -- ALU
--     regX   = regbank !! inputX
--     regY   = regbank !! inputY
--     aluOut = alu aluCode regX regY
--   
--     -- next instruction
--     nextPC =
--       case jmpM of
--         Just a | aluOut /= 0 -> ipntr + a
--         _                    -> ipntr + 1
--   
--     -- update registers
--     regbank' = replace Zero   0
--              $ replace PC     nextPC
--              $ replace result aluOut
--              $ replace ldReg  memOut
--              $ regbank
--   
--   alu Add   x y = x + y
--   alu Sub   x y = x - y
--   alu Incr  x _ = x + 1
--   alu Imm   x _ = x
--   alu CmpGt x y = if x > y then 1 else 0
--   
-- -- We initially create a memory out of simple registers: -- --
--   dataMem
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom MemAddr
--     -- ^ Read address
--     -> Signal dom (Maybe (MemAddr,Value))
--     -- ^ (write address, data in)
--     -> Signal dom Value
--     -- ^ data out
--   dataMem clk rst en rd wrM =
--     mealy clk rst en dataMemT (replicate d32 0) (bundle (rd,wrM))
--    where
--     dataMemT mem (rd,wrM) = (mem',dout)
--       where
--         dout = mem !! rd
--         mem' =
--           case wrM of
--             Just (wr,din) -> replace wr din mem
--             _             -> mem
--   
-- -- And then connect everything: -- --
--   system
--     :: ( KnownDomain dom
--        , KnownNat n )
--     => Vec n Instruction
--     -> Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom Value
--   system instrs clk rst en = memOut
--    where
--     memOut = dataMem clk rst en rdAddr dout
--     (rdAddr,dout,ipntr) = mealyB clk rst en cpu (replicate d7 0) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- Create a simple program that calculates the GCD of 4 and 6: -- --
--   -- Compute GCD of 4 and 6
--   prog = -- 0 := 4
--          Compute Incr Zero RegA RegA :>
--          replicate d3 (Compute Incr RegA Zero RegA) ++
--          Store RegA 0 :>
--          -- 1 := 6
--          Compute Incr Zero RegA RegA :>
--          replicate d5 (Compute Incr RegA Zero RegA) ++
--          Store RegA 1 :>
--          -- A := 4
--          Load 0 RegA :>
--          -- B := 6
--          Load 1 RegB :>
--          -- start
--          Compute CmpGt RegA RegB RegC :>
--          Branch RegC 4 :>
--          Compute CmpGt RegB RegA RegC :>
--          Branch RegC 4 :>
--          Jump 5 :>
--          -- (a > b)
--          Compute Sub RegA RegB RegA :>
--          Jump (-6) :>
--          -- (b > a)
--          Compute Sub RegB RegA RegB :>
--          Jump (-8) :>
--          -- end
--          Store RegA 2 :>
--          Load 2 RegC :>
--          Nil
--   
-- -- And test our system: -- --
--   >>> sampleN 32 $ system prog systemClockGen resetGen enableGen
--   [0,0,0,0,0,0,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- -- to see that our system indeed calculates that the GCD of 6 and 4 is 2. -- --

Improvement 1: using asyncRam

-- -- As you can see, it's fairly straightforward to build a memory using -- registers and read (!!) and write (replace) logic. This -- might however not result in the most efficient hardware structure, -- especially when building an ASIC. -- -- Instead it is preferable to use the asyncRam function which has -- the potential to be translated to a more efficient structure: -- --
--   system2
--     :: ( KnownDomain dom
--        , KnownNat n )
--     => Vec n Instruction
--     -> Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom Value
--   system2 instrs clk rst en = memOut
--    where
--     memOut = asyncRam clk clk en d32 rdAddr dout
--     (rdAddr,dout,ipntr) = mealyB clk rst en cpu (replicate d7 0) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- Again, we can simulate our system and see that it works. This time -- however, we need to disregard the first few output samples, because -- the initial content of an asyncRam is undefined, and -- consequently, the first few output samples are also undefined. -- We use the utility function printX to conveniently filter out -- the undefinedness and replace it with the string "undefined" -- in the first few leading outputs. -- --
--   >>> printX $ sampleN 32 $ system2 prog systemClockGen resetGen enableGen
--   [undefined,undefined,undefined,undefined,undefined,undefined,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- --

Improvement 2: using blockRam

-- -- Finally we get to using blockRam. On FPGAs, asyncRam -- will be implemented in terms of LUTs, and therefore take up logic -- resources. FPGAs also have large(r) memory structures called block -- RAMs, which are preferred, especially as the memories we need for -- our application get bigger. The blockRam function will be -- translated to such a block RAM. -- -- One important aspect of block RAMs is that they have a -- synchronous read port, meaning unlike an asyncRam, the -- result of a read command given at time t is output at time -- t + 1. -- -- For us that means we need to change the design of our CPU. Right now, -- upon a load instruction we generate a read address for the memory, and -- the value at that read address is immediately available to be put in -- the register bank. We will be using a block RAM, so the value is -- delayed until the next cycle. Thus, we will also need to delay the -- register address to which the memory address is loaded: -- --
--   cpu2
--     :: (Vec 7 Value,Reg)    -- ^ (Register bank, Load reg addr)
--     -> (Value,Instruction)  -- ^ (Memory output, Current instruction)
--     -> ( (Vec 7 Value, Reg)
--        , (MemAddr, Maybe (MemAddr,Value), InstrAddr)
--        )
--   cpu2 (regbank, ldRegD) (memOut, instr) =
--     ((regbank', ldRegD'), (rdAddr, (,aluOut) <$> wrAddrM, bitCoerce ipntr))
--    where
--     -- Current instruction pointer
--     ipntr = regbank !! PC
--   
--     -- Decoder
--     (MachCode {..}) = case instr of
--       Compute op rx ry res -> nullCode {inputX=rx,inputY=ry,result=res,aluCode=op}
--       Branch cr a          -> nullCode {inputX=cr,jmpM=Just a}
--       Jump a               -> nullCode {aluCode=Incr,jmpM=Just a}
--       Load a r             -> nullCode {ldReg=r,rdAddr=a}
--       Store r a            -> nullCode {inputX=r,wrAddrM=Just a}
--       Nop                  -> nullCode
--   
--     -- ALU
--     regX   = regbank !! inputX
--     regY   = regbank !! inputY
--     aluOut = alu aluCode regX regY
--   
--     -- next instruction
--     nextPC =
--       case jmpM of
--         Just a | aluOut /= 0 -> ipntr + a
--         _                    -> ipntr + 1
--   
--     -- update registers
--     ldRegD'  = ldReg  -- Delay the ldReg by 1 cycle
--     regbank' = replace Zero   0
--              $ replace PC     nextPC
--              $ replace result aluOut
--              $ replace ldRegD memOut
--              $ regbank
--   
-- -- We can now finally instantiate our system with a blockRam: -- --
--   system3
--     :: ( KnownDomain dom
--        , KnownNat n )
--     => Vec n Instruction
--     -> Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom Value
--   system3 instrs clk rst en = memOut
--    where
--     memOut = blockRam clk en (replicate d32 0) rdAddr dout
--     (rdAddr,dout,ipntr) = mealyB clk rst en cpu2 ((replicate d7 0),Zero) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- We are, however, not done. We will also need to update our program. -- The reason being that values that we try to load in our registers -- won't be loaded into the register until the next cycle. This is a -- problem when the next instruction immediately depends on this memory -- value. In our example, this was only the case when we loaded the value -- 6, which was stored at address 1, into -- RegB. Our updated program is thus: -- --
--   prog2 = -- 0 := 4
--          Compute Incr Zero RegA RegA :>
--          replicate d3 (Compute Incr RegA Zero RegA) ++
--          Store RegA 0 :>
--          -- 1 := 6
--          Compute Incr Zero RegA RegA :>
--          replicate d5 (Compute Incr RegA Zero RegA) ++
--          Store RegA 1 :>
--          -- A := 4
--          Load 0 RegA :>
--          -- B := 6
--          Load 1 RegB :>
--          Nop :> -- Extra NOP
--          -- start
--          Compute CmpGt RegA RegB RegC :>
--          Branch RegC 4 :>
--          Compute CmpGt RegB RegA RegC :>
--          Branch RegC 4 :>
--          Jump 5 :>
--          -- (a > b)
--          Compute Sub RegA RegB RegA :>
--          Jump (-6) :>
--          -- (b > a)
--          Compute Sub RegB RegA RegB :>
--          Jump (-8) :>
--          -- end
--          Store RegA 2 :>
--          Load 2 RegC :>
--          Nil
--   
-- -- When we simulate our system we see that it works. This time again, we -- need to disregard the first sample, because the initial output of a -- blockRam is undefined. We use the utility function -- printX to conveniently filter out the undefinedness and replace -- it with the string "undefined". -- --
--   >>> printX $ sampleN 34 $ system3 prog2 systemClockGen resetGen enableGen
--   [undefined,0,0,0,0,0,0,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- -- This concludes the short introduction to using blockRam. module Clash.Explicit.BlockRam -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: Clock  dom
--     -> Enable  dom
--     -> Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 clk en = blockRam clk en (replicate d40 1)
--   
blockRam :: (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: Clock dom
--     -> Enable dom
--     -> Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 clk en = blockRamPow2 clk en (replicate d32 1)
--   
blockRamPow2 :: (KnownDomain dom, HasCallStack, NFDataX a, KnownNat n) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | A version of blockRam that has no default values set. May be -- cleared to an arbitrary state using a reset function. blockRamU :: forall n dom a r addr. (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => Clock dom -> Reset dom -> Enable dom -> ResetStrategy r -> SNat n -> (Index n -> a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | A version of blockRam that is initialized with the same value -- on all memory positions blockRam1 :: forall n dom a r addr. (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => Clock dom -> Reset dom -> Enable dom -> ResetStrategy r -> SNat n -> a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a data ResetStrategy (r :: Bool) [ClearOnReset] :: ResetStrategy 'True [NoClearOnReset] :: ResetStrategy 'False -- | Create a read-after-write block RAM from a read-before-write one readNew :: (KnownDomain dom, NFDataX a, Eq addr) => Clock dom -> Reset dom -> Enable dom -> (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs domA domB a. (HasCallStack, KnownNat nAddrs, KnownDomain domA, KnownDomain domB, NFDataX a) => Clock domA -> Clock domB -> Signal domA (RamOp nAddrs a) -> Signal domB (RamOp nAddrs a) -> (Signal domA a, Signal domB a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a -- | blockRAM primitive blockRam# :: forall dom a n. (KnownDomain dom, HasCallStack, NFDataX a) => Clock dom -> Enable dom -> Vec n a -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom a -> Signal dom a -- | blockRAMU primitive blockRamU# :: forall n dom a. (KnownDomain dom, HasCallStack, NFDataX a) => Clock dom -> Enable dom -> SNat n -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom a -> Signal dom a -- | blockRAM1 primitive blockRam1# :: forall n dom a. (KnownDomain dom, HasCallStack, NFDataX a) => Clock dom -> Enable dom -> SNat n -> a -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom a -> Signal dom a -- | Primitive for trueDualPortBlockRam trueDualPortBlockRam# :: forall nAddrs domA domB a. (HasCallStack, KnownNat nAddrs, KnownDomain domA, KnownDomain domB, NFDataX a) => Clock domA -> Signal domA Bool -> Signal domA Bool -> Signal domA (Index nAddrs) -> Signal domA a -> Clock domB -> Signal domB Bool -> Signal domB Bool -> Signal domB (Index nAddrs) -> Signal domB a -> (Signal domA a, Signal domB a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Explicit.BlockRam.RamOp n a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Explicit.BlockRam.RamOp n a) instance GHC.Generics.Generic (Clash.Explicit.BlockRam.RamOp n a) -- | Synchronizer circuits for safe clock domain crossings module Clash.Explicit.Synchronizer -- | Synchronizer based on two sequentially connected flip-flops. -- -- dualFlipFlopSynchronizer :: (NFDataX a, KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Reset dom2 -> Enable dom2 -> a -> Signal dom1 a -> Signal dom2 a -- | Synchronizer implemented as a FIFO around a synchronous RAM. Based on -- the design described in Clash.Tutorial#multiclock, which is -- itself based on the design described in -- http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf. -- However, this FIFO uses a synchronous dual-ported RAM which, unlike -- those designs using RAM with an asynchronous read port, is nearly -- guaranteed to actually synthesize into one of the dual-ported RAMs -- found on most FPGAs. -- -- NB: This synchronizer can be used for -- word-synchronization. NB: This synchronizer will only -- work safely when you set up the proper bus skew and maximum delay -- constraints inside your synthesis tool for the clock domain crossings -- of the gray pointers. asyncFIFOSynchronizer :: (KnownDomain wdom, KnownDomain rdom, 2 <= addrSize, NFDataX a) => SNat addrSize -> Clock wdom -> Clock rdom -> Reset wdom -> Reset rdom -> Enable wdom -> Enable rdom -> Signal rdom Bool -> Signal wdom (Maybe a) -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool) -- | Utilities to deal with resets. module Clash.Explicit.Reset -- | The resetSynchronizer will synchronize an incoming reset according to -- whether the domain is synchronous or asynchronous. -- -- For asynchronous resets this synchronizer ensures the reset will only -- be de-asserted synchronously but it can still be asserted -- asynchronously. The reset assert is immediate, but reset de-assertion -- is delayed by two cycles. -- -- Normally, asynchronous resets can be both asynchronously asserted and -- de-asserted. Asynchronous de-assertion can induce meta-stability in -- the component which is being reset. To ensure this doesn't happen, -- resetSynchronizer ensures that de-assertion of a reset happens -- synchronously. Assertion of the reset remains asynchronous. -- -- Note that asynchronous assertion does not induce meta-stability in the -- component whose reset is asserted. However, when a component "A" in -- another clock or reset domain depends on the value of a component "B" -- being reset, then asynchronous assertion of the reset of component "B" -- can induce meta-stability in component "A". To prevent this from -- happening you need to use a proper synchronizer, for example one of -- the synchronizers in Clash.Explicit.Synchronizer. -- -- For synchronous resets this function ensures that the reset is -- asserted and de-asserted synchronously. Both the assertion and -- de-assertion of the reset are delayed by two cycles. -- --

Example 1

-- -- The circuit below detects a rising bit (i.e., a transition from 0 to -- 1) in a given argument. It takes a reset that is not synchronized to -- any of the other incoming signals and synchronizes it using -- resetSynchronizer. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk asyncRst key1 =
--     withClockResetEnable clk rst enableGen leds
--    where
--     rst   = resetSynchronizer clk asyncRst
--     key1R = isRising 1 key1
--     leds  = mealy blinkerT (1, False, 0) key1R
--   
-- --

Example 2

-- -- Similar to Example 1 this circuit detects a rising bit (i.e., a -- transition from 0 to 1) in a given argument. It takes a clock that is -- not stable yet and a reset signal that is not synchronized to any -- other signals. It stabilizes the clock and then synchronizes the reset -- signal. -- -- Note that the function altpllSync provides this functionality -- in a convenient form, obviating the need for -- resetSynchronizer for this use case. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk rst key1 =
--       let  (pllOut,pllStable) = unsafeAltpll clk rst
--            rstSync            = resetSynchronizer pllOut (unsafeFromActiveLow pllStable)
--       in   exposeClockResetEnable leds pllOut rstSync enableGen
--     where
--       key1R  = isRising 1 key1
--       leds   = mealy blinkerT (1, False, 0) key1R
--   
-- --

Implementation details

-- -- resetSynchronizer implements the following circuit for -- asynchronous domains: -- --
--                                   rst
--   --------------------------------------+
--                       |                 |
--                  +----v----+       +----v----+
--     deasserted   |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
-- -- This corresponds to figure 3d at -- https://www.embedded.com/asynchronous-reset-synchronization-and-distribution-challenges-and-solutions/ -- -- For synchronous domains two sequential dflipflops are used: -- --
--                  +---------+       +---------+
--     rst          |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Reset dom -- | Filter glitches from reset signals by only triggering a reset after it -- has been asserted for glitchlessPeriod cycles. Similarly, it -- will stay asserted until a glitchlessPeriod number of -- deasserted cycles have been observed. -- -- This circuit can only be used on platforms supporting initial values. -- This restriction can be worked around by using -- unsafeResetGlitchFilter but this is not recommended. -- -- On platforms without initial values, you should instead use -- resetGlitchFilterWithReset with an additional power-on reset, -- or holdReset if filtering is only needed on deassertion. -- -- At power-on, the reset will be asserted. If the filtered reset input -- remains unasserted, the output reset will deassert after -- glitchlessPeriod clock cycles. -- -- If resetGlitchFilter is used in a domain with asynchronous -- resets (Asynchronous), resetGlitchFilter will first -- synchronize the reset input with dualFlipFlopSynchronizer. -- --

Example 1

-- --
--   >>> let sampleResetN n = sampleN n . unsafeToActiveHigh
--   
--   >>> let resetFromList = unsafeFromActiveHigh . fromList
--   
--   >>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True, True]
--   
--   >>> sampleResetN 12 (resetGlitchFilter d2 (clockGen @XilinxSystem) rst)
--   [True,True,True,True,False,False,False,False,False,True,True,True]
--   
resetGlitchFilter :: forall dom glitchlessPeriod. (HasCallStack, HasDefinedInitialValues dom, 1 <= glitchlessPeriod) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom -- | Filter glitches from reset signals by only triggering a reset after it -- has been asserted for glitchlessPeriod cycles. Similarly, it -- will stay asserted until a glitchlessPeriod number of -- deasserted cycles have been observed. -- -- Compared to resetGlitchFilter, this function adds an additional -- power-on reset input. As soon as the power-on reset asserts, the reset -- output will assert, and after the power-on reset deasserts, the reset -- output will stay asserted for another glitchlessPeriod clock -- cycles. This is identical behavior to holdReset where it -- concerns the power-on reset, and differs from the filtered reset, -- which will only cause an assertion after glitchlessPeriod -- cycles. -- -- If resetGlitchFilterWithReset is used in a domain with -- asynchronous resets (Asynchronous), -- resetGlitchFilterWithReset will first synchronize the reset -- input with dualFlipFlopSynchronizer. resetGlitchFilterWithReset :: forall dom glitchlessPeriod. (HasCallStack, KnownDomain dom, 1 <= glitchlessPeriod) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom -> Reset dom -- | Filter glitches from reset signals by only triggering a reset after it -- has been asserted for glitchlessPeriod cycles. Similarly, it -- will stay asserted until a glitchlessPeriod number of -- deasserted cycles have been observed. -- -- On platforms without initial values (Unknown), -- resetGlitchFilter cannot be used and you should use -- resetGlitchFilterWithReset with an additional power-on reset, -- or holdReset if filtering is only needed on deassertion. -- -- unsafeResetGlitchFilter allows breaking the requirement of -- initial values, but by doing so it is possible that the design starts -- up with a period of up to 2 * glitchlessPeriod clock cycles -- where the reset output is unasserted (or longer in the case of -- glitches on the filtered reset input). This can cause a number of -- problems. The outputs/tri-states of the design might output random -- things, including coherent but incorrect streams of data. This might -- have grave repercussions in the design's environment (sending network -- packets, overwriting non-volatile memory, in extreme cases destroying -- controlled equipment or causing harm to living beings, ...). -- -- Without initial values, the synthesized result of -- unsafeResetGlitchFilter eventually correctly outputs a -- filtered version of the reset input. However, in simulation, it will -- indefinitely output an undefined value. This happens both in Clash -- simulation and in HDL simulation. Therefore, simulation should not -- include the unsafeResetGlitchFilter. -- -- If unsafeResetGlitchFilter is used in a domain with -- asynchronous resets (Asynchronous), -- unsafeResetGlitchFilter will first synchronize the reset -- input with dualFlipFlopSynchronizer. unsafeResetGlitchFilter :: forall dom glitchlessPeriod. (HasCallStack, KnownDomain dom, 1 <= glitchlessPeriod) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom -- | Hold reset for a number of cycles relative to an incoming reset -- signal. -- -- Example: -- --
--   >>> let sampleWithReset = sampleN 8 . unsafeToActiveHigh
--   
--   >>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (resetGenN (SNat @3)))
--   [True,True,True,True,True,False,False,False]
--   
-- -- holdReset holds the reset for an additional 2 clock cycles for -- a total of 5 clock cycles where the reset is asserted. -- holdReset also works on intermediate assertions of the reset -- signal: -- --
--   >>> let rst = fromList [True, False, False, False, True, False, False, False]
--   
--   >>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (unsafeFromActiveHigh rst))
--   [True,True,True,False,True,True,True,False]
--   
holdReset :: forall dom n. KnownDomain dom => Clock dom -> Enable dom -> SNat n -> Reset dom -> Reset dom -- | Convert between different types of reset, adding a synchronizer when -- the domains are not the same. See resetSynchronizer for further -- details about reset synchronization. -- -- If domA has Synchronous resets, a flip-flop is -- inserted in domA to filter glitches. This adds one -- domA clock cycle delay. convertReset :: forall domA domB. (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> Reset domA -> Reset domB -- | A reset that is never asserted noReset :: KnownDomain dom => Reset dom -- | Output reset will be asserted when both input resets are asserted andReset :: forall dom. HasSynchronousReset dom => Reset dom -> Reset dom -> Reset dom -- | Output reset will be asserted when both input resets are asserted. -- This function is considered unsafe because it can be used on domains -- with components with asynchronous resets, where use of this function -- can introduce glitches triggering a reset. unsafeAndReset :: forall dom. KnownDomain dom => Reset dom -> Reset dom -> Reset dom -- | Output reset will be asserted when either one of the input resets is -- asserted orReset :: forall dom. HasSynchronousReset dom => Reset dom -> Reset dom -> Reset dom -- | Output reset will be asserted when either one of the input resets is -- asserted. This function is considered unsafe because it can be used on -- domains with components with asynchronous resets, where use of this -- function can introduce glitches triggering a reset. unsafeOrReset :: forall dom. KnownDomain dom => Reset dom -> Reset dom -> Reset dom -- | A reset signal belonging to a domain called dom. -- -- The underlying representation of resets is Bool. data Reset (dom :: Domain) -- | Reset generator for simulation purposes. Asserts the reset for a -- single cycle. -- -- To be used like: -- --
--   rstSystem = resetGen @System
--   
-- -- See tbClockGen for example usage. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGen :: forall dom. KnownDomain dom => Reset dom -- | Reset generator for simulation purposes. Asserts the reset for the -- first n cycles. -- -- To be used like: -- --
--   rstSystem5 = resetGen @System d5
--   
-- -- Example usage: -- --
--   >>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
--   [True,True,True,False,False,False,False]
--   
-- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom -- | Get ResetKind from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetKind @dom of
--       SAsynchronous -> foo
--       SSynchronous -> bar
--   
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync -- | Reset generator for use in simulation, for the System clock -- domain. Asserts the reset for a single cycle. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
systemResetGen :: Reset System -- | unsafeToReset is unsafe. For asynchronous resets it is unsafe -- because it can introduce combinatorial loops. In case of synchronous -- resets it can lead to meta-stability issues in the presence of -- asynchronous resets. -- -- NB: You probably want to use unsafeFromActiveLow or -- unsafeFromActiveHigh. unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom -- | unsafeFromReset is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- -- NB: You probably want to use unsafeToActiveLow or -- unsafeToActiveHigh. unsafeFromReset :: Reset dom -> Signal dom Bool -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveLow instead. This function -- will be removed in Clash 1.12. unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveLow instead. This function -- will be removed in Clash 1.12. unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Generic clock related utilities. module Clash.Clocks -- | NB: The documentation only shows instances up to 3 -- output clocks. By default, instances up to and including 18 -- clocks will exist. class Clocks t where { type family ClocksCxt t :: Constraint; type family NumOutClocks t :: Nat; } clocks :: (Clocks t, KnownDomain domIn, ClocksCxt t) => Clock domIn -> Reset domIn -> t -- | NB: The documentation only shows instances up to 3 -- output clocks. By default, instances up to and including 18 -- clocks will exist. class ClocksSync t where { type family ClocksSyncClocksInst t (domIn :: Domain) :: Type; type family ClocksResetSynchronizerCxt t :: Constraint; } clocksResetSynchronizer :: (ClocksSync t, KnownDomain domIn, ClocksResetSynchronizerCxt t) => ClocksSyncClocksInst t domIn -> Clock domIn -> t type ClocksSyncCxt t (domIn :: Domain) = (KnownDomain domIn, ClocksSync t, ClocksResetSynchronizerCxt t, Clocks (ClocksSyncClocksInst t domIn), ClocksCxt (ClocksSyncClocksInst t domIn)) type NumOutClocksSync t (domIn :: Domain) = NumOutClocks (ClocksSyncClocksInst t domIn) instance Clash.Clocks.Internal.ClocksSync (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Reset c1) instance Clash.Clocks.Internal.ClocksSync (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Reset c1, Clash.Signal.Internal.Clock c2, Clash.Signal.Internal.Reset c2) instance Clash.Clocks.Internal.ClocksSync (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Reset c1, Clash.Signal.Internal.Clock c2, Clash.Signal.Internal.Reset c2, Clash.Signal.Internal.Clock c3, Clash.Signal.Internal.Reset c3) instance Clash.Clocks.Internal.Clocks (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Signal pllLock GHC.Types.Bool) instance Clash.Clocks.Internal.Clocks (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Clock c2, Clash.Signal.Internal.Signal pllLock GHC.Types.Bool) instance Clash.Clocks.Internal.Clocks (Clash.Signal.Internal.Clock c1, Clash.Signal.Internal.Clock c2, Clash.Signal.Internal.Clock c3, Clash.Signal.Internal.Signal pllLock GHC.Types.Bool) -- | This module contains functions for instantiating clock generators on -- Xilinx FPGA's. -- -- We suggest you use a clock generator even if your oscillator runs at -- the frequency you want to run your circuit at. -- -- A clock generator generates a stable clock signal for your design at a -- configurable frequency. A clock generator in an FPGA is frequently -- referred to as a PLL (Phase-Locked Loop). However, Xilinx -- differentiates between several types of clock generator -- implementations in their FPGAs and uses the term PLL to refer to one -- specific type, so we choose to use the more generic term clock -- generator here. -- -- For most use cases, you would create two or more synthesis domains -- describing the oscillator input and the domains you wish to use in -- your design, and use the regular functions below to generate -- the clocks and resets of the design from the oscillator input. There -- are use cases not covered by this simpler approach, and the unsafe -- functions are provided as a means to build advanced reset managers -- for the output domains. module Clash.Xilinx.ClockGen -- | Instantiate a Xilinx MMCM clock generator corresponding to the Xilinx -- "Clock Wizard" with 1 single-ended reference clock input and a reset -- input, and 1 to 7 output clocks and a locked output. -- -- This function incorporates resetSynchronizers to convert the -- locked output port into proper Reset signals for the -- output domains which will keep the circuit in reset while the clock is -- still stabilizing. clockWizard :: forall t domIn. (HasAsynchronousReset domIn, ClocksSyncCxt t domIn, NumOutClocksSync t domIn <= 7) => Clock domIn -> Reset domIn -> t -- | Instantiate a Xilinx MMCM clock generator corresponding to the Xilinx -- "Clock Wizard" with 1 differential reference clock input and a reset -- input, and 1 to 7 output clocks and a locked output. -- -- This function incorporates resetSynchronizers to convert the -- locked output port into proper Reset signals for the -- output domains which will keep the circuit in reset while the clock is -- still stabilizing. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. clockWizardDifferential :: forall t domIn. (HasAsynchronousReset domIn, ClocksSyncCxt t domIn, NumOutClocksSync t domIn <= 7) => DiffClock domIn -> Reset domIn -> t -- | Instantiate a Xilinx MMCM clock generator corresponding to the Xilinx -- "Clock Wizard" with 1 single-ended reference clock input and a reset -- input, and 1 to 7 output clocks and a locked output. -- -- NB: Because the clock generator reacts asynchronously to the -- incoming reset input, the signal must be glitch-free. unsafeClockWizard :: forall t domIn. (KnownDomain domIn, Clocks t, ClocksCxt t, NumOutClocks t <= 7) => Clock domIn -> Reset domIn -> t -- | Instantiate a Xilinx MMCM clock generator corresponding to the Xilinx -- "Clock Wizard" with 1 differential reference clock input and a reset -- input, and 1 to 7 output clocks and a locked output. -- -- NB: Because the clock generator reacts asynchronously to the -- incoming reset input, the signal must be glitch-free. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. unsafeClockWizardDifferential :: forall t domIn. (KnownDomain domIn, Clocks t, ClocksCxt t, NumOutClocks t <= 7) => DiffClock domIn -> Reset domIn -> t -- | This module contains functions for instantiating clock generators on -- Intel FPGA's. -- -- We suggest you use a clock generator even if your oscillator runs at -- the frequency you want to run your circuit at. -- -- A clock generator generates a stable clock signal for your design at a -- configurable frequency. A clock generator in an FPGA is frequently -- referred to as a PLL (Phase-Locked Loop). Intel also refers to them as -- PLL's in general but because this is not consistently the case among -- FPGA vendors, we choose the more generic term clock generator. -- -- For most use cases, you would create two or more synthesis domains -- describing the oscillator input and the domains you wish to use in -- your design, and use the regular functions below to generate -- the clocks and resets of the design from the oscillator input. There -- are use cases not covered by this simpler approach, and the unsafe -- functions are provided as a means to build advanced reset managers -- for the output domains. module Clash.Intel.ClockGen -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "ALTPLL" IP core (Arria GX, Arria II, Stratix IV, -- Stratix III, Stratix II, Stratix, Cyclone 10 LP, Cyclone IV, Cyclone -- III, Cyclone II, Cyclone) with 1 reference clock input and a reset -- input and 1 to 5 output clocks and a locked output. -- -- This function incorporates resetSynchronizers to convert the -- locked output port into proper Reset signals for the -- output domains which will keep the circuit in reset while the clock is -- still stabilizing. -- -- See also the ALTPLL (Phase-Locked Loop) IP Core User Guide altpllSync :: forall t domIn. (HasAsynchronousReset domIn, ClocksSyncCxt t domIn, NumOutClocksSync t domIn <= 5) => Clock domIn -> Reset domIn -> t -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "Altera PLL" IP core (Arria V, Stratix V, Cyclone V) -- with 1 reference clock input and a reset input and 1 to 18 output -- clocks and a locked output. -- -- This function incorporates resetSynchronizers to convert the -- locked output port into proper Reset signals for the -- output domains which will keep the circuit in reset while the clock is -- still stabilizing. -- -- See also the Altera Phase-Locked Loop (Altera PLL) IP Core User -- Guide alteraPllSync :: forall t domIn. (HasAsynchronousReset domIn, ClocksSyncCxt t domIn, NumOutClocksSync t domIn <= 18) => Clock domIn -> Reset domIn -> t -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "ALTPLL" IP core (Arria GX, Arria II, Stratix IV, -- Stratix III, Stratix II, Stratix, Cyclone 10 LP, Cyclone IV, Cyclone -- III, Cyclone II, Cyclone) with 1 reference clock input and a reset -- input and 1 to 5 output clocks and a locked output. -- -- NB: Because the clock generator reacts asynchronously to the -- incoming reset input, the signal must be glitch-free. -- -- See also the ALTPLL (Phase-Locked Loop) IP Core User Guide unsafeAltpll :: forall t domIn. (KnownDomain domIn, Clocks t, ClocksCxt t, NumOutClocks t <= 5) => Clock domIn -> Reset domIn -> t -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "Altera PLL" IP core (Arria V, Stratix V, Cyclone V) -- with 1 reference clock input and a reset input and 1 to 18 output -- clocks and a locked output. -- -- NB: Because the clock generator reacts asynchronously to the -- incoming reset input, the signal must be glitch-free. -- -- See also the Altera Phase-Locked Loop (Altera PLL) IP Core User -- Guide unsafeAlteraPll :: forall t domIn. (KnownDomain domIn, Clocks t, ClocksCxt t, NumOutClocks t <= 18) => Clock domIn -> Reset domIn -> t -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "ALTPLL" IP core (Arria GX, Arria II, Stratix IV, -- Stratix III, Stratix II, Stratix, Cyclone 10 LP, Cyclone IV, Cyclone -- III, Cyclone II, Cyclone) with 1 reference clock input and a reset -- input and 1 output clock and a locked output. -- -- This function is deprecated because the locked output is an -- asynchronous signal. This means the user is required to add a -- synchronizer and as such this function is unsafe. The common use case -- is now covered by altpllSync and unsafeAltpll offers the -- functionality of this deprecated function for advanced use cases. -- | Deprecated: This function is unsafe. Please see documentation of -- the function for alternatives. altpll :: forall domOut domIn name. (HasAsynchronousReset domIn, KnownDomain domOut) => SSymbol name -> Clock domIn -> Reset domIn -> (Clock domOut, Signal domOut Bool) -- | Instantiate an Intel clock generator corresponding to the -- Intel/Quartus "Altera PLL" IP core (Arria V, Stratix V, Cyclone V) -- with 1 reference clock input and a reset input and 1 to 18 output -- clocks and a locked output. -- -- This function is deprecated because the locked output is an -- asynchronous signal. This means the user is required to add a -- synchronizer and as such this function is unsafe. The common use case -- is now covered by alteraPllSync and unsafeAlteraPll -- offers the functionality of this deprecated function for advanced use -- cases. -- | Deprecated: This function is unsafe. Please see documentation of -- the function for alternatives. alteraPll :: forall t domIn name. (HasAsynchronousReset domIn, Clocks t, ClocksCxt t, NumOutClocks t <= 18) => SSymbol name -> Clock domIn -> Reset domIn -> t -- | Clash has synchronous Signals 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 Signals 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/
--     , _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. -- -- module Clash.Signal -- | Clash has synchronous Signals 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 Signals 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. -- -- -- -- Signals have the type role -- --
--   >>> :i Signal
--   type role Signal nominal representational
--   ...
--   
-- -- as it is safe to coerce the underlying value of a signal, but not safe -- to coerce a signal between different synthesis domains. -- -- See the module documentation of Clash.Signal for more -- information about domains. data Signal (dom :: Domain) a -- | The in part of an inout port. BiSignalIn has the type -- role -- --
--   >>> :i BiSignalIn
--   type role BiSignalIn nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | The out part of an inout port -- -- Wraps (multiple) writing signals. The semantics are such that only one -- of the signals may write at a single time step. -- -- BiSignalOut has the type role -- --
--   >>> :i BiSignalOut
--   type role BiSignalOut nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | Used to specify the default behavior of a "BiSignal", i.e. what -- value is read when no value is being written to it. data BiSignalDefault -- | inout port behaves as if connected to a pull-up resistor PullUp :: BiSignalDefault -- | inout port behaves as if connected to a pull-down resistor PullDown :: BiSignalDefault -- | inout port behaves as if is floating. Reading a -- floating "BiSignal" value in simulation will yield an errorX -- (undefined value). Floating :: BiSignalDefault type Domain = Symbol -- | We either get evidence that this function was instantiated with the -- same domains, or Nothing. sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB) -- | A KnownDomain constraint indicates that a circuit's behavior -- depends on some properties of a domain. See DomainConfiguration -- for more information. class (KnownSymbol dom, KnownNat (DomainPeriod dom)) => KnownDomain (dom :: Domain) where { type family KnownConf dom :: DomainConfiguration; } -- | Returns SDomainConfiguration corresponding to an instance's -- DomainConfiguration. -- -- Example usage: -- --
--   >>> knownDomain @System
--   SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
--   
knownDomain :: KnownDomain dom => SDomainConfiguration dom (KnownConf dom) type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) -- | Determines clock edge memory elements are sensitive to. Not yet -- implemented. data ActiveEdge -- | Elements are sensitive to the rising edge (low-to-high) of the clock. Rising :: ActiveEdge -- | Elements are sensitive to the falling edge (high-to-low) of the clock. Falling :: ActiveEdge -- | Singleton version of ActiveEdge data SActiveEdge (edge :: ActiveEdge) [SRising] :: SActiveEdge 'Rising [SFalling] :: SActiveEdge 'Falling data InitBehavior -- | Power up value of memory elements is unknown. Unknown :: InitBehavior -- | If applicable, power up value of a memory element is defined. Applies -- to registers for example, but not to blockRam. Defined :: InitBehavior data SInitBehavior (init :: InitBehavior) [SUnknown] :: SInitBehavior 'Unknown [SDefined] :: SInitBehavior 'Defined data ResetKind -- | Elements respond asynchronously to changes in their reset -- input. This means that they do not wait for the next active -- clock edge, but respond immediately instead. Common on Intel FPGA -- platforms. Asynchronous :: ResetKind -- | Elements respond synchronously to changes in their reset input. -- This means that changes in their reset input won't take effect until -- the next active clock edge. Common on Xilinx FPGA platforms. Synchronous :: ResetKind -- | Singleton version of ResetKind data SResetKind (resetKind :: ResetKind) [SAsynchronous] :: SResetKind 'Asynchronous [SSynchronous] :: SResetKind 'Synchronous -- | Determines the value for which a reset line is considered "active" data ResetPolarity -- | Reset is considered active if underlying signal is True. ActiveHigh :: ResetPolarity -- | Reset is considered active if underlying signal is False. ActiveLow :: ResetPolarity -- | Singleton version of ResetPolarity data SResetPolarity (polarity :: ResetPolarity) [SActiveHigh] :: SResetPolarity 'ActiveHigh [SActiveLow] :: SResetPolarity 'ActiveLow -- | A domain with a name (Domain). Configures the behavior of -- various aspects of a circuits. See the documentation of this record's -- field types for more information on the options. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. data DomainConfiguration DomainConfiguration :: Domain -> Nat -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> DomainConfiguration -- | Domain name [_name] :: DomainConfiguration -> Domain -- | Period of clock in ps [_period] :: DomainConfiguration -> Nat -- | Active edge of the clock [_activeEdge] :: DomainConfiguration -> ActiveEdge -- | Whether resets are synchronous (edge-sensitive) or asynchronous -- (level-sensitive) [_resetKind] :: DomainConfiguration -> ResetKind -- | Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value [_initBehavior] :: DomainConfiguration -> InitBehavior -- | Whether resets are active high or active low [_resetPolarity] :: DomainConfiguration -> ResetPolarity -- | Singleton version of DomainConfiguration data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) [SDomainConfiguration] :: {sName :: SSymbol dom " Domain name", sPeriod :: SNat period " Period of clock in /ps/", sActiveEdge :: SActiveEdge edge " Active edge of the clock (not yet implemented)", sResetKind :: SResetKind reset " Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)", sInitBehavior :: SInitBehavior init " Whether the initial (or "power up") value of memory elements is unknown/undefined, or configurable to a specific value", sResetPolarity :: SResetPolarity polarity " Whether resets are active high or active low"} -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) -- | Convenience type to help to extract a period from a domain. Example -- usage: -- --
--   myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...
--   
type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) -- | Convenience type to help to extract the active edge from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...
--   
type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) -- | Convenience type to help to extract the reset synchronicity from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) => ...
--   
type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) -- | Convenience type to help to extract the initial value behavior from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...
--   
type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) -- | Convenience type to help to extract the reset polarity from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...
--   
type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) -- | Convenience type to constrain a domain to have synchronous resets. -- Example usage: -- --
--   myFunc :: HasSynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) -- | Convenience type to constrain a domain to have asynchronous resets. -- Example usage: -- --
--   myFunc :: HasAsynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) -- | Convenience type to constrain a domain to have initial values. Example -- usage: -- --
--   myFunc :: HasDefinedInitialValues dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Note that there is no UnknownInitialValues dom as a component -- that works without initial values will also work if it does have them. -- -- Click here for usage hints type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) -- | Gets time in Picoseconds from time in Seconds type Seconds (s :: Nat) = Milliseconds (1000 * s) -- | Gets time in Picoseconds from time in Milliseconds type Milliseconds (ms :: Nat) = Microseconds (1000 * ms) -- | Gets time in Picoseconds from time in Microseconds type Microseconds (us :: Nat) = Nanoseconds (1000 * us) -- | Gets time in Picoseconds from time in Nanoseconds type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns) -- | Gets time in Picoseconds from time in picoseconds, essentially -- id type Picoseconds (ps :: Nat) = ps -- | The domain's clock frequency in hertz, calculated based on the period -- stored in picoseconds. This might lead to rounding errors. type DomainToHz (dom :: Domain) = PeriodToHz (DomainPeriod dom) -- | Converts a frequency in hertz to a period in picoseconds. This might -- lead to rounding errors. type HzToPeriod (hz :: Nat) = Seconds 1 `Div` hz -- | Converts a period in picoseconds to a frequency in hertz. This might -- lead to rounding errors. type PeriodToHz (period :: Nat) = (Seconds 1) `Div` period -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed type PeriodToCycles (dom :: Domain) (period :: Nat) = period `DivRU` DomainPeriod dom -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed. The same as -- PeriodToCycles. type ClockDivider (dom :: Domain) (period :: Nat) = PeriodToCycles dom period -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type System = ("System" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and synchronously to -- changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type XilinxSystem = ("XilinxSystem" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type IntelSystem = ("IntelSystem" :: Domain) -- | Convenience value to allow easy "subclassing" of System domain. Should -- be used in combination with createDomain. For example, if you -- just want to change the period but leave all other settings intact -- use: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
vSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of IntelSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vIntelSystem{vName="Intel10", vPeriod=10}
--   
vIntelSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of XilinxSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}
--   
vXilinxSystem :: VDomainConfiguration -- | Same as SDomainConfiguration but allows for easy updates through -- record update syntax. Should be used in combination with -- vDomain and createDomain. Example: -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
data VDomainConfiguration VDomainConfiguration :: String -> Natural -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> VDomainConfiguration -- | Corresponds to _name on DomainConfiguration [vName] :: VDomainConfiguration -> String -- | Corresponds to _period on DomainConfiguration [vPeriod] :: VDomainConfiguration -> Natural -- | Corresponds to _activeEdge on DomainConfiguration [vActiveEdge] :: VDomainConfiguration -> ActiveEdge -- | Corresponds to _resetKind on DomainConfiguration [vResetKind] :: VDomainConfiguration -> ResetKind -- | Corresponds to _initBehavior on DomainConfiguration [vInitBehavior] :: VDomainConfiguration -> InitBehavior -- | Corresponds to _resetPolarity on DomainConfiguration [vResetPolarity] :: VDomainConfiguration -> ResetPolarity -- | Convert SDomainConfiguration to VDomainConfiguration. -- Should be used in combination with createDomain only. vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration -- | Convenience method to express new domains in terms of others. -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
-- -- The function will create two extra identifiers. The first: -- --
--   type System10 = ..
--   
-- -- You can use that as the dom to Clocks/Resets/Enables/Signals. For -- example: Signal System10 Int. Additionally, it will create a -- VDomainConfiguration that you can use in later calls to -- createDomain: -- --
--   vSystem10 = knownVDomain @System10
--   
-- -- It will also make System10 an instance of KnownDomain. -- -- If either identifier is already in scope it will not be generated a -- second time. Note: This can be useful for example when documenting a -- new domain: -- --
--   -- | Here is some documentation for CustomDomain
--   type CustomDomain = ("CustomDomain" :: Domain)
--   
--   -- | Here is some documentation for vCustomDomain
--   createDomain vSystem{vName="CustomDomain"}
--   
createDomain :: VDomainConfiguration -> Q [Dec] -- | Like 'knownDomain but yields a VDomainConfiguration. Should -- only be used in combination with createDomain. knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration -- | Get the clock period from a KnownDomain context clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period -- | Get ActiveEdge from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case activeEdge @dom of
--       SRising -> foo
--       SFalling -> bar
--   
activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge -- | Get ResetKind from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetKind @dom of
--       SAsynchronous -> foo
--       SSynchronous -> bar
--   
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync -- | Get InitBehavior from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case initBehavior @dom of
--       SDefined -> foo
--       SUnknown -> bar
--   
initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init -- | Get ResetPolarity from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetPolarity @dom of
--       SActiveHigh -> foo
--       SActiveLow -> bar
--   
resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity -- | A clock signal belonging to a domain named dom. data Clock (dom :: Domain) -- | A differential clock signal belonging to a domain named dom. -- The clock input of a design with such an input has two ports which are -- in antiphase. The first input is the positive phase, the second the -- negative phase. When using makeTopEntity, the names of the -- inputs will end in _p and _n respectively. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. data DiffClock (dom :: Domain) -- | Calculate the frequency in Hz, given the period in ps -- -- I.e., to calculate the clock frequency of a clock with a period of -- 5000 ps: -- --
--   >>> periodToHz 5000
--   2.0e8
--   
-- -- Note that if p in periodToHz (fromIntegral p) -- is negative, fromIntegral will give an Underflow -- :: ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Ratio -- Natural. To get the old behavior of this function, use a type -- application: -- --
--   >>> periodToHz @(Ratio Natural) 5000
--   200000000 % 1
--   
-- -- NB: This function is not synthesizable periodToHz :: (HasCallStack, Fractional a) => Natural -> a -- | Calculate the period in ps, given a frequency in Hz -- -- I.e., to calculate the clock period for a circuit to run at 240 MHz we -- get -- --
--   >>> hzToPeriod 240e6
--   4166
--   
-- -- If the value hzToPeriod is applied to is not of the type -- Ratio Natural, you can use hzToPeriod -- (realToFrac f). Note that if f is negative, -- realToFrac will give an Underflow :: -- ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Natural. To -- get the old behavior of this function, use a type application: -- --
--   >>> hzToPeriod @Natural 240e6
--   4166
--   
-- -- hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a -- | Implicit version of unsafeSynchronizer. unsafeSynchronizer :: forall dom1 dom2 a. (HiddenClock dom1, HiddenClock dom2) => Signal dom1 a -> Signal dom2 a -- | A reset signal belonging to a domain called dom. -- -- The underlying representation of resets is Bool. data Reset (dom :: Domain) -- | unsafeToReset is unsafe. For asynchronous resets it is unsafe -- because it can introduce combinatorial loops. In case of synchronous -- resets it can lead to meta-stability issues in the presence of -- asynchronous resets. -- -- NB: You probably want to use unsafeFromActiveLow or -- unsafeFromActiveHigh. unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom -- | unsafeFromReset is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- -- NB: You probably want to use unsafeToActiveLow or -- unsafeToActiveHigh. unsafeFromReset :: Reset dom -> Signal dom Bool -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Convert between different types of reset, adding a synchronizer in -- case it needs to convert from an asynchronous to a synchronous reset. convertReset :: forall domA domB. (HiddenClock domA, HiddenClock domB) => Reset domA -> Reset domB -- | The resetSynchronizer will synchronize an incoming reset according to -- whether the domain is synchronous or asynchronous. -- -- For asynchronous resets this synchronizer ensures the reset will only -- be de-asserted synchronously but it can still be asserted -- asynchronously. The reset assert is immediate, but reset de-assertion -- is delayed by two cycles. -- -- Normally, asynchronous resets can be both asynchronously asserted and -- de-asserted. Asynchronous de-assertion can induce meta-stability in -- the component which is being reset. To ensure this doesn't happen, -- resetSynchronizer ensures that de-assertion of a reset happens -- synchronously. Assertion of the reset remains asynchronous. -- -- Note that asynchronous assertion does not induce meta-stability in the -- component whose reset is asserted. However, when a component "A" in -- another clock or reset domain depends on the value of a component "B" -- being reset, then asynchronous assertion of the reset of component "B" -- can induce meta-stability in component "A". To prevent this from -- happening you need to use a proper synchronizer, for example one of -- the synchronizers in Clash.Explicit.Synchronizer. -- -- For synchronous resets this function ensures that the reset is -- asserted and de-asserted synchronously. Both the assertion and -- de-assertion of the reset are delayed by two cycles. -- --

Example 1

-- -- The circuit below detects a rising bit (i.e., a transition from 0 to -- 1) in a given argument. It takes a reset that is not synchronized to -- any of the other incoming signals and synchronizes it using -- resetSynchronizer. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk asyncRst key1 =
--     withClockResetEnable clk rst enableGen leds
--    where
--     rst   = resetSynchronizer clk asyncRst
--     key1R = isRising 1 key1
--     leds  = mealy blinkerT (1, False, 0) key1R
--   
-- --

Example 2

-- -- Similar to Example 1 this circuit detects a rising bit (i.e., a -- transition from 0 to 1) in a given argument. It takes a clock that is -- not stable yet and a reset signal that is not synchronized to any -- other signals. It stabilizes the clock and then synchronizes the reset -- signal. -- -- Note that the function altpllSync provides this functionality -- in a convenient form, obviating the need for -- resetSynchronizer for this use case. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk rst key1 =
--       let  (pllOut,pllStable) = unsafeAltpll clk rst
--            rstSync            = resetSynchronizer pllOut (unsafeFromActiveLow pllStable)
--       in   exposeClockResetEnable leds pllOut rstSync enableGen
--     where
--       key1R  = isRising 1 key1
--       leds   = mealy blinkerT (1, False, 0) key1R
--   
-- --

Implementation details

-- -- resetSynchronizer implements the following circuit for -- asynchronous domains: -- --
--                                   rst
--   --------------------------------------+
--                       |                 |
--                  +----v----+       +----v----+
--     deasserted   |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
-- -- This corresponds to figure 3d at -- https://www.embedded.com/asynchronous-reset-synchronization-and-distribution-challenges-and-solutions/ -- -- For synchronous domains two sequential dflipflops are used: -- --
--                  +---------+       +---------+
--     rst          |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Reset dom -- | Filter glitches from reset signals by only triggering a reset after it -- has been asserted for glitchlessPeriod cycles. Similarly, it -- will stay asserted until a glitchlessPeriod number of -- deasserted cycles have been observed. -- -- This circuit can only be used on platforms supporting initial values. -- This restriction can be worked around by using -- unsafeResetGlitchFilter but this is not recommended. -- -- On platforms without initial values, you should instead use -- resetGlitchFilterWithReset with an additional power-on reset, -- or holdReset if filtering is only needed on deassertion. -- -- At power-on, the reset will be asserted. If the filtered reset input -- remains unasserted, the output reset will deassert after -- glitchlessPeriod clock cycles. -- -- If resetGlitchFilter is used in a domain with asynchronous -- resets (Asynchronous), resetGlitchFilter will first -- synchronize the reset input with dualFlipFlopSynchronizer. -- --

Example 1

-- --
--   >>> let sampleResetN n = sampleN n . unsafeToActiveHigh
--   
--   >>> let resetFromList = unsafeFromActiveHigh . fromList
--   
--   >>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True, True]
--   
--   >>> sampleResetN 12 (resetGlitchFilter d2 (clockGen @XilinxSystem) rst)
--   [True,True,True,True,False,False,False,False,False,True,True,True]
--   
resetGlitchFilter :: forall dom glitchlessPeriod. (HasCallStack, HasDefinedInitialValues dom, 1 <= glitchlessPeriod) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom -- | Hold reset for a number of cycles relative to an implicit reset -- signal. -- -- Example: -- --
--   >>> sampleN @System 8 (unsafeToActiveHigh (holdReset (SNat @2)))
--   [True,True,True,False,False,False,False,False]
--   
-- -- holdReset holds the reset for an additional 2 clock cycles for -- a total of 3 clock cycles where the reset is asserted. holdReset :: forall dom m. HiddenClockResetEnable dom => SNat m -> Reset dom -- | A signal of booleans, indicating whether a component is enabled. No -- special meaning is implied, it's up to the component itself to decide -- how to respond to its enable line. It is used throughout Clash as a -- global enable signal. data Enable dom -- | Convert a signal of bools to an Enable construct toEnable :: Signal dom Bool -> Enable dom -- | Convert Enable construct to its underlying representation: a -- signal of bools. fromEnable :: Enable dom -> Signal dom Bool -- | Enable generator for some domain. Is simply always True. enableGen :: Enable dom -- | A constraint that indicates the component has a hidden -- Clock -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenClock dom = (Hidden (HiddenClockName dom) (Clock dom), KnownDomain dom) -- | Hide the Clock argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideClock :: forall dom r. HiddenClock dom => (Clock dom -> r) -> r -- | Expose a hidden Clock argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClock dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a clock of a component working on multiple -- domains (such as the first example), use exposeSpecificClock. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClock reg clockGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeClock to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClock @System reg clockGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeClock :: forall dom r. WithSingleDomain dom r => (HiddenClock dom => r) -> KnownDomain dom => Clock dom -> r -- | Connect an explicit Clock to a function with a hidden -- Clock. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClock dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a clock to a component working on multiple -- domains (such as the first example), use withSpecificClock. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClock clockGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withClock to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClock @System clockGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withClock :: forall dom r. WithSingleDomain dom r => KnownDomain dom => Clock dom -> (HiddenClock dom => r) -> r -- | Expose a hidden Clock argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeClock, callers should -- explicitly state what the clock domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificClock can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificClock @System reg clockGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificClock @dom reg clockGen
--   
exposeSpecificClock :: forall dom r. WithSpecificDomain dom r => (HiddenClock dom => r) -> KnownDomain dom => Clock dom -> r -- | Connect an explicit Clock to a function with a hidden -- Clock. This function can be used on components with multiple -- domains. As opposed to withClock, callers should explicitly -- state what the clock domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificClock can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificClock @System clockGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificClock @dom clockGen reg
--   
withSpecificClock :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Clock dom -> (HiddenClock dom => r) -> r -- | Connect a hidden Clock to an argument where a normal -- Clock argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasClock :: forall dom. HiddenClock dom => Clock dom -- | A constraint that indicates the component needs a Reset -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenReset dom = (Hidden (HiddenResetName dom) (Reset dom), KnownDomain dom) -- | Hide the Reset argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideReset :: forall dom r. HiddenReset dom => (Reset dom -> r) -> r -- | Expose a hidden Reset argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenReset dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a reset of a component working on multiple -- domains (such as the first example), use exposeSpecificReset. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeReset reg resetGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeReset to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeReset @System reg resetGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeReset :: forall dom r. WithSingleDomain dom r => (HiddenReset dom => r) -> KnownDomain dom => Reset dom -> r -- | Connect an explicit Reset to a function with a hidden -- Reset. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenReset dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a reset to a component working on multiple -- domains (such as the first example), use withSpecificReset. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withReset resetGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withReset to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withReset @System resetGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withReset :: forall dom r. WithSingleDomain dom r => KnownDomain dom => Reset dom -> (HiddenReset dom => r) -> r -- | Expose a hidden Reset argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeReset, callers should -- explicitly state what the reset domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificReset can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificReset @System reg resetGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificReset @dom reg resetGen
--   
exposeSpecificReset :: forall dom r. WithSpecificDomain dom r => (HiddenReset dom => r) -> KnownDomain dom => Reset dom -> r -- | Connect an explicit Reset to a function with a hidden -- Reset. This function can be used on components with multiple -- domains. As opposed to withReset, callers should explicitly -- state what the reset domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificReset can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificReset @System resetGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificReset @dom resetGen reg
--   
withSpecificReset :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Reset dom -> (HiddenReset dom => r) -> r -- | Connect a hidden Reset to an argument where a normal -- Reset argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasReset :: forall dom. HiddenReset dom => Reset dom -- | A constraint that indicates the component needs an -- Enable -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenEnable dom = (Hidden (HiddenEnableName dom) (Enable dom), KnownDomain dom) -- | Hide the Enable argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideEnable :: forall dom r. HiddenEnable dom => (Enable dom -> r) -> r -- | Expose a hidden Enable argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a enable of a component working on multiple -- domains (such as the first example), use exposeSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeEnable reg enableGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeEnable @System reg enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeEnable :: forall dom r. WithSingleDomain dom r => (HiddenEnable dom => r) -> KnownDomain dom => Enable dom -> r -- | Connect an explicit Enable to a function with a hidden -- Enable. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a enable to a component working on multiple -- domains (such as the first example), use withSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withEnable enableGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withEnable to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withEnable @System enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withEnable :: forall dom r. KnownDomain dom => WithSingleDomain dom r => Enable dom -> (HiddenEnable dom => r) -> r -- | Expose a hidden Enable argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeEnable, callers should -- explicitly state what the enable domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificEnable @System reg enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificEnable @dom reg enableGen
--   
exposeSpecificEnable :: forall dom r. WithSpecificDomain dom r => (HiddenEnable dom => r) -> KnownDomain dom => Enable dom -> r -- | Connect an explicit Enable to a function with a hidden -- Enable. This function can be used on components with multiple -- domains. As opposed to withEnable, callers should explicitly -- state what the enable domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificEnable @System enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificEnable @dom enableGen reg
--   
withSpecificEnable :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Enable dom -> (HiddenEnable dom => r) -> r -- | Connect a hidden Enable to an argument where a normal -- Enable argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasEnable :: forall dom. HiddenEnable dom => Enable dom -- | A constraint that indicates the component needs a Clock, -- a Reset, and an Enable belonging to the same -- dom. -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenClockResetEnable dom = (HiddenClock dom, HiddenReset dom, HiddenEnable dom) -- | Hide the Clock, Reset, and Enable arguments of a -- component, so they can be routed implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideClockResetEnable :: forall dom r. HiddenClockResetEnable dom => (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) -> r -- | Expose hidden Clock, Reset, and Enable arguments -- of a component, so they can be applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a clock, reset, and enable of a component -- working on multiple domains (such as the first example), use -- exposeSpecificClockResetEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClockResetEnable reg clockGen resetGen enableGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeClockResetEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClockResetEnable @System reg clockGen resetGen enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Usage in a testbench context: -- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst en
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--       en             = enableGen
--   
exposeClockResetEnable :: forall dom r. WithSingleDomain dom r => (HiddenClockResetEnable dom => r) -> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r -- | Connect an explicit Clock, Reset, and Enable to a -- function with a hidden Clock, Reset, and Enable. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a clock, reset, and enable to a component -- working on multiple domains (such as the first example), use -- withSpecificClockResetEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClockResetEnable clockGen resetGen enableGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withClockResetEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClockResetEnable @System clockGen resetGen enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withClockResetEnable :: forall dom r. KnownDomain dom => WithSingleDomain dom r => Clock dom -> Reset dom -> Enable dom -> (HiddenClockResetEnable dom => r) -> r -- | Expose hidden Clock, Reset, and Enable arguments -- of a component, so they can be applied explicitly. This function can -- be used on components with multiple domains. As opposed to -- exposeClockResetEnable, callers should explicitly state what -- the domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificClockResetEnable can only be used when it can -- find the specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificClockResetEnable @System reg clockGen resetGen enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificClockResetEnable @dom reg clockGen resetGen enableGen
--   
exposeSpecificClockResetEnable :: forall dom r. WithSpecificDomain dom r => (HiddenClockResetEnable dom => r) -> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r -- | Connect an explicit Clock, Reset, and Enable to a -- function with hidden Clock, Reset, and Enable -- arguments. This function can be used on components with multiple -- domains. As opposed to withClockResetEnable, callers should -- explicitly state what the domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificClockResetEnable can only be used when it can find -- the specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificClockResetEnable @System clockGen resetGen enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificClockResetEnable @dom clockGen resetGen enableGen reg
--   
withSpecificClockResetEnable :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Clock dom -> Reset dom -> Enable dom -> (HiddenClockResetEnable dom => r) -> r -- | A constraint that indicates the component needs a Clock, -- a Reset, and an Enable belonging to the System -- domain. -- -- Click here to read more about hidden clocks, resets, and -- enables type SystemClockResetEnable = (Hidden (HiddenClockName System) (Clock System), Hidden (HiddenResetName System) (Reset System), Hidden (HiddenEnableName System) (Enable System)) -- | Merge enable signal with signal of bools by applying the boolean AND -- operation. -- -- NB: The component given to andEnable as an argument needs an -- explicit type signature. Please read Monomorphism restriction -- leads to surprising behavior. -- -- The component whose enable is modified will only be enabled when both -- the encompassing HiddenEnable and the Signal -- dom Bool are asserted. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to merge an enable of a component working on multiple -- domains (such as the first example), use andSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> f en = andEnable en reg
--   
--   >>> sampleN @System 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
-- -- Force andEnable to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> f en = andEnable @System en reg
--   
--   >>> sampleN 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
andEnable :: forall dom r. HiddenEnable dom => WithSingleDomain dom r => Signal dom Bool -> (HiddenEnable dom => r) -> r -- | Merge enable signal with signal of bools by applying the boolean AND -- operation. -- -- NB: The component given to andSpecificEnable as an argument -- needs an explicit type signature. Please read Monomorphism -- restriction leads to surprising behavior. -- -- The component whose enable is modified will only be enabled when both -- the encompassing HiddenEnable and the Signal -- dom Bool are asserted. -- -- This function can be used on components with multiple domains. As -- opposed to andEnable, callers should explicitly state what the -- enable domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- andSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> f en = andSpecificEnable @System en reg
--   
--   >>> sampleN 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   f en = andSpecificEnable @dom en reg
--   
andSpecificEnable :: forall dom r. (HiddenEnable dom, WithSpecificDomain dom r) => Signal dom Bool -> (HiddenEnable dom => r) -> r -- | Special version of delay that doesn't take enable signals of -- any kind. Initial value will be undefined. dflipflop :: forall dom a. (HiddenClock dom, NFDataX a) => Signal dom a -> Signal dom a -- | delay dflt s delays the values in -- Signal s for once cycle, the value at time 0 is -- dflt. -- --
--   >>> sampleN @System 3 (delay 0 (fromList [1,2,3,4]))
--   [0,1,2]
--   
delay :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom a -> Signal dom a -- | Version of delay that only updates when its second argument is -- a Just value. -- --
--   >>> let input = fromList [Just 1, Just 2, Nothing, Nothing, Just 5, Just 6, Just (7::Int)]
--   
--   >>> sampleN @System 7 (delayMaybe 0 input)
--   [0,1,2,2,2,5,6]
--   
delayMaybe :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom (Maybe a) -> Signal dom a -- | Version of delay that only updates when its second argument is -- asserted. -- --
--   >>> let input = fromList [1,2,3,4,5,6,7::Int]
--   
--   >>> let enable = fromList [True,True,False,False,True,True,True]
--   
--   >>> sampleN @System 7 (delayEn 0 enable input)
--   [0,1,2,2,2,5,6]
--   
delayEn :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | register i s delays the values in Signal -- s for one cycle, and sets the value at time 0 to i -- --
--   >>> sampleN @System 5 (register 8 (fromList [1,1,2,3,4]))
--   [8,8,1,2,3]
--   
register :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom a -> Signal dom a infixr 3 `register` -- | Version of register that only updates its content when its -- second argument is a Just value. So given: -- --
--   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 (+))
--   
-- -- We get: -- --
--   >>> sampleN @System 9 sometimes1
--   [Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]
--   
--   >>> sampleN @System 9 countSometimes
--   [0,0,0,1,1,2,2,3,3]
--   
regMaybe :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom (Maybe a) -> Signal dom a infixr 3 `regMaybe` -- | Version of register that only updates its content when its -- second argument is asserted. So given: -- --
--   oscillate = register False (not <$> oscillate)
--   count     = regEn 0 oscillate (count + 1)
--   
-- -- We get: -- --
--   >>> sampleN @System 9 oscillate
--   [False,False,True,False,True,False,True,False,True]
--   
--   >>> sampleN @System 9 count
--   [0,0,0,1,1,2,2,3,3]
--   
regEn :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | The above type is a generalization for: -- --
--   mux :: Signal Bool -> Signal a -> Signal a -> Signal a
--   
-- -- A multiplexer. Given "mux b t f", output t -- when b is True, and f when b is -- False. mux :: Applicative f => f Bool -> f a -> f a -> f a -- | Clock generator for simulations. Do not use this clock -- generator for the testBench function, use tbClockGen -- instead. -- -- To be used like: -- --
--   clkSystem = clockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. clockGen :: KnownDomain dom => Clock dom -- | Reset generator for simulation purposes. Asserts the reset for a -- single cycle. -- -- To be used like: -- --
--   rstSystem = resetGen @System
--   
-- -- See tbClockGen for example usage. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGen :: forall dom. KnownDomain dom => Reset dom -- | Reset generator for simulation purposes. Asserts the reset for the -- first n cycles. -- -- To be used like: -- --
--   rstSystem5 = resetGen @System d5
--   
-- -- Example usage: -- --
--   >>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
--   [True,True,True,False,False,False,False]
--   
-- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom -- | Clock generator for the System clock domain. -- -- NB: Should only be used for simulation, and not for the -- testBench function. For the testBench function, used -- tbSystemClockGen systemClockGen :: Clock System -- | Reset generator for use in simulation, for the System clock -- domain. Asserts the reset for a single cycle. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
systemResetGen :: Reset System -- | The above type is a generalization for: -- --
--   (.&&.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (&&) that returns a Signal of -- Bool (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 .&&. -- | The above type is a generalization for: -- --
--   (.||.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (||) that returns a Signal of -- Bool (.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 .||. -- | Isomorphism between a Signal of a product type (e.g. a tuple) -- and a product type of Signals. -- -- Instances of Bundle must satisfy the following laws: -- --
--   bundle . unbundle = id
--   unbundle . bundle = id
--   
-- -- By default, bundle and unbundle, are defined as the -- identity, that is, writing: -- --
--   data D = A | B
--   
--   instance Bundle D
--   
-- -- is the same as: -- --
--   data D = A | B
--   
--   instance Bundle D where
--     type Unbundled clk D = Signal clk D
--     bundle   s = s
--     unbundle s = s
--   
-- -- For custom product types you'll have to write the instance manually: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b }
--   
--   instance Bundle (Pair a b) where
--     type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b)
--   
--     -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b)
--     bundle   (MkPair as bs) = MkPair <$> as <*> bs
--   
--     -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b)
--     unbundle pairs = MkPair (getA <$> pairs) (getB <$> pairs)
--   
class Bundle a where { type family Unbundled (dom :: Domain) a = res | res -> dom a; type Unbundled dom a = Signal dom a; } -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: Bundle a => Unbundled dom a -> Signal dom a -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: (Bundle a, Signal dom a ~ Unbundled dom a) => Unbundled dom a -> Signal dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: Bundle a => Signal dom a -> Unbundled dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: (Bundle a, Unbundled dom a ~ Signal dom a) => Signal dom a -> Unbundled dom a -- | See TaggedEmptyTuple data EmptyTuple EmptyTuple :: EmptyTuple -- | Helper type to emulate the "old" behavior of Bundle's unit instance. -- I.e., the instance for Bundle () used to be defined as: -- --
--   class Bundle () where
--     bundle   :: () -> Signal dom ()
--     unbundle :: Signal dom () -> ()
--   
-- -- In order to have sensible type inference, the Bundle class -- specifies that the argument type of bundle should uniquely -- identify the result type, and vice versa for unbundle. The type -- signatures in the snippet above don't though, as () doesn't -- uniquely map to a specific domain. In other words, domain -- should occur in both the argument and result of both functions. -- -- TaggedEmptyTuple tackles this by carrying the domain in its -- type. The bundle and unbundle instance now looks like: -- --
--   class Bundle EmptyTuple where
--     bundle   :: TaggedEmptyTuple dom -> Signal dom EmptyTuple
--     unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
--   
-- -- dom is now mentioned both the argument and result for both -- bundle and unbundle. data TaggedEmptyTuple (dom :: Domain) TaggedEmptyTuple :: TaggedEmptyTuple (dom :: Domain) -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate @System (register 8) [1, 2, 3]
--   [8,1,2,3...
--   ...
--   
-- -- Where System denotes the domain to simulate on. The -- reset line is asserted for a single cycle. The first value is -- therefore supplied twice to the circuit: once while reset is high, and -- once directly after. The first output value (the value produced -- while the reset is asserted) is dropped. -- -- If you only want to simulate a finite number of samples, see -- simulateN. If you need the reset line to be asserted for more -- than one cycle or if you need a custom reset value, see -- simulateWithReset and simulateWithResetN. -- -- NB: This function is not synthesizable simulate :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Simulate a (Unbundled a -> Unbundled b) -- function given a list of samples of type a -- --
--   >>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b] -- | Same as simulate, but only sample the first Int output -- values. -- -- NB: This function is not synthesizable simulateN :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulate, but with the reset line asserted for n -- cycles. Similar to simulate, simulateWithReset will drop -- the output values produced while the reset is asserted. While the -- reset is asserted, the reset value a is supplied to the -- circuit. simulateWithReset :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulateWithReset, but only sample the first Int -- output values. simulateWithResetN :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Simulate a component until it matches a condition -- -- If the given component has not yet been given a clock, reset, or -- enable line, runUntil will supply them. The reset will be -- asserted for a single cycle. -- -- It prints a message of the form -- --
--   Signal sampled for N cycles until value X
--   
-- -- NB: This function is not synthesizable -- --

Example with test bench

-- -- A common usage is with a test bench using outputVerifier. -- -- NB: Since this uses assert, when using clashi, -- read the note at Clash.Explicit.Testbench#assert-clashi. -- --
--   import Clash.Prelude
--   import Clash.Explicit.Testbench
--   
--   topEntity
--     :: Signal System Int
--     -> Signal System Int
--   topEntity = id
--   
--   testBench
--     :: Signal System Bool
--   testBench = done
--    where
--     testInput = stimuliGenerator clk rst $(listToVecTH [1 :: Int .. 10])
--     expectedOutput =
--       outputVerifier' clk rst $(listToVecTH $ [1 :: Int .. 9] <> [42])
--     done = expectedOutput $ topEntity testInput
--     clk = tbSystemClockGen (not <$> done)
--     rst = systemResetGen
--   
-- --
--   > runUntil id testBench
--   
--   
--   cycle(<Clock: System>): 10, outputVerifier
--   expected value: 42, not equal to actual value: 10
--   Signal sampled for 11 cycles until value True
--   
-- -- When you need to verify multiple test benches, the following -- invocations come in handy: -- --
--   > mapM_ (runUntil id) [ testBenchA, testBenchB ]
--   
-- -- or when the test benches are in different clock domains: -- --
--   testBenchA :: Signal DomA Bool
--   testBenchB :: Signal DomB Bool
--   
-- --
--   > sequence_ [ runUntil id testBenchA, runUntil id testBenchB ]
--   
runUntil :: forall dom a. (KnownDomain dom, NFDataX a, ShowX a) => (a -> Bool) -> (HiddenClockResetEnable dom => Signal dom a) -> IO () -- | Lazily simulate a (Signal a -> Signal -- b) function given a list of samples of type a -- --
--   >>> simulate @System (register 8) [1, 2, 3]
--   [8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate_lazy :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Lazily simulate a (Unbundled a -> -- Unbundled b) function given a list of samples of type -- a -- --
--   >>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB_lazy :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b] -- | Build an Automaton from a function over Signals. -- -- NB: Consumption of continuation of the Automaton must be -- affine; that is, you can only apply the continuation associated with a -- particular element at most once. signalAutomaton :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> Automaton (->) a b -- | Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sample will supply them. The reset will be -- asserted for a single cycle. sample will not drop the value -- produced by the circuit while the reset was asserted. If you want -- this, or if you want more than a single cycle reset, consider using -- sampleWithReset. -- -- NB: This function is not synthesizable sample :: forall dom a. (KnownDomain dom, NFDataX a) => (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN @System 3 s == [s0, s1, s2]
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sampleN will supply them. The reset will be -- asserted for a single cycle. sampleN will not drop the value -- produced by the circuit while the reset was asserted. If you want -- this, or if you want more than a single cycle reset, consider using -- sampleWithResetN. -- -- NB: This function is not synthesizable sampleN :: forall dom a. (KnownDomain dom, NFDataX a) => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get an infinite list of samples from a Signal, while asserting -- the reset line for m clock cycles. sampleWithReset does -- not return the first m cycles, i.e., when the reset is -- asserted. -- -- NB: This function is not synthesizable sampleWithReset :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get a list of n samples from a Signal, while asserting -- the reset line for m clock cycles. sampleWithReset does -- not return the first m cycles, i.e., while the reset is -- asserted. -- -- NB: This function is not synthesizable sampleWithResetN :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5])
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList :: NFDataX a => [a] -> Signal dom a -- | Like fromList, but resets on reset and has a defined reset -- value. -- --
--   >>> let rst = unsafeFromActiveHigh (fromList [True, True, False, False, True, False])
--   
--   >>> let res = withReset rst (fromListWithReset Nothing [Just 'a', Just 'b', Just 'c'])
--   
--   >>> sampleN @System 6 res
--   [Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
--   
-- -- NB: This function is not synthesizable fromListWithReset :: forall dom a. (HiddenReset dom, NFDataX a) => a -> [a] -> Signal dom a -- | Lazily get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sample_lazy will supply them. The reset will be -- asserted for a single cycle. sample_lazy will not drop the -- value produced by the circuit while the reset was asserted. -- -- NB: This function is not synthesizable sample_lazy :: forall dom a. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Lazily get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN @System 3 s == [s0, s1, s2]
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sampleN_lazy will supply them. The reset will be -- asserted for a single cycle. sampleN_lazy will not drop the -- value produced by the circuit while the reset was asserted. -- -- NB: This function is not synthesizable sampleN_lazy :: forall dom a. KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList_lazy :: [a] -> Signal dom a -- | testFor n s tests the signal s for n cycles. -- -- NB: This function is not synthesizable testFor :: KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom Bool) -> Property -- | The above type is a generalization for: -- --
--   (.==.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (==) that returns a Signal of -- Bool (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 .==. -- | The above type is a generalization for: -- --
--   (./=.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (/=) that returns a Signal of -- Bool (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 ./=. -- | The above type is a generalization for: -- --
--   (.<.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<) that returns a Signal of -- Bool (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<. -- | The above type is a generalization for: -- --
--   (.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<=) that returns a Signal of -- Bool (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<=. -- | The above type is a generalization for: -- --
--   (.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>=) that returns a Signal of -- Bool (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>=. -- | The above type is a generalization for: -- --
--   (.>.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>) that returns a Signal of -- Bool (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>. -- | Converts the out part of a BiSignal to an in part. -- In simulation it checks whether multiple components are writing and -- will error accordingly. Make sure this is only called ONCE for every -- BiSignal. veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n -- | Read the value from an inout port readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a -- | Write to an inout port writeToBiSignal :: (HasCallStack, BitPack a, NFDataX a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a) -- | Combine several inout signals into one. mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m type HiddenClockName dom = AppendSymbol dom "_clk" type HiddenResetName dom = AppendSymbol dom "_rst" type HiddenEnableName dom = AppendSymbol dom "_en" -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveLow instead. This function -- will be removed in Clash 1.12. unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveLow instead. This function -- will be removed in Clash 1.12. unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | See Clash.Explicit.Verification for an introduction. -- -- The verification API is currently experimental and subject to change. module Clash.Verification data Assertion (dom :: Domain) -- | A property is a temporal or basic assertion that's specified to either -- used as an _assert_ or _cover_ statement. See assert and -- cover. data Property (dom :: Domain) -- | Render target for HDL data RenderAs -- | Property Specification Language PSL :: RenderAs -- | SystemVerilog Assertions SVA :: RenderAs -- | Use SVA for SystemVerilog, PSL for others AutoRenderAs :: RenderAs -- | Yosys Formal Extensions for Verilog and SystemVerilog. See: -- https://symbiyosys.readthedocs.io/en/latest/verilog.html and -- https://symbiyosys.readthedocs.io/en/latest/verific.html -- -- Falls back to PSL for VHDL, however currently Clash's PSL syntax isn't -- suported by GHDL+SymbiYosys; YosysFormal :: RenderAs -- | Convert a signal to a cv expression with a name hint. Clash will try -- its best to use this name in the rendered assertion, but might run -- into collisions. You can skip using name altogether. Clash will -- then try its best to get a readable name from context. name :: Text -> Signal dom Bool -> Assertion dom -- | For using a literal (either True or False) in assertions lit :: Bool -> Assertion dom -- | Truth table for not: -- --
--   a     | not a
--   ------------
--   True  | False
--   False | True
--   
not :: AssertionValue dom a => a -> Assertion dom -- | Truth table for and: -- --
--   a     | b     | a `and` b
--   --------------|----------
--   False | False | False
--   False | True  | False
--   True  | False | False
--   True  | True  | True
--   
and :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for or: -- --
--   a     | b     | a `or` b
--   --------------|---------
--   False | False | False
--   False | True  | True
--   True  | False | True
--   True  | True  | True
--   
or :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for implies: -- --
--   a     | b     | a `implies` b
--   --------------|--------------
--   False | False | True
--   False | True  | True
--   True  | False | False
--   True  | True  | True
--   
implies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Truth table for next: -- --
--   a[n]  | a[n+1] | a `implies` next a
--   ---------------|-------------------
--   False | False  | True
--   False | True   | True
--   True  | False  | False
--   True  | True   | True
--   
-- -- where a[n] represents the value of a at cycle n and -- a[n+1] represents the value of a at cycle -- n+1. Cycle n is an arbitrary cycle. next :: AssertionValue dom a => a -> Assertion dom -- | Truth table for nextN: -- --
--   a[n]  | a[n+m] | a `implies` next m a
--   ---------------|---------------------
--   False | False  | True
--   False | True   | True
--   True  | False  | False
--   True  | True   | True
--   
-- -- where a[n] represents the value of a at cycle n and -- a[n+m] represents the value of a at cycle n+m. Cycle -- n is an arbitrary cycle. nextN :: AssertionValue dom a => Word -> a -> Assertion dom -- | Same as a && next b but with a nice syntax. E.g., -- a && next b could be written as a before -- b. Might be read as "a happens one cycle before b". before :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Same as a implies next b but with a nice syntax. E.g., -- a implies next b could be written as a -- timplies b. Might be read as "a at cycle n implies b at -- cycle n+1". timplies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Same as implies but strictly temporal. timpliesOverlapping :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom -- | Specify assertion should _always_ hold always :: AssertionValue dom a => a -> Assertion dom -- | Specify assertion should _never_ hold (not supported by SVA) never :: AssertionValue dom a => a -> Assertion dom -- | Specify assertion should _eventually_ hold eventually :: AssertionValue dom a => a -> Assertion dom -- | Check whether given assertion always holds. Results can be collected -- with check. assert :: AssertionValue dom a => a -> Property dom -- | Check whether given assertion holds for at least a single cycle. -- Results can be collected with check. cover :: AssertionValue dom a => a -> Property dom check :: (KnownDomain dom, HiddenClock dom, HiddenReset dom) => Text -> RenderAs -> Property dom -> Signal dom AssertionResult checkI :: (KnownDomain dom, HiddenClock dom, HiddenReset dom) => Text -> RenderAs -> Property dom -> Signal dom a -> Signal dom a -- | Print assertions in HDL hideAssertion :: Signal dom AssertionResult -> Signal dom a -> Signal dom a module Clash.Verification.DSL (|&|) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 5 |&| (|||) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 4 ||| (~>) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 0 ~> (|=>) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 1 |=> (|->) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 1 |-> (#|#) :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom infixr 3 #|# module Clash.Signal.Delayed -- | A synchronized signal with samples of type a, synchronized to -- clock clk, that has accumulated delay amount of -- samples delay along its path. -- -- DSignal has the type role -- --
--   >>> :i DSignal
--   type role DSignal nominal nominal representational
--   ...
--   
-- -- as it is safe to coerce the values in the signal, but not safe to -- coerce the synthesis domain or delay in the signal. data DSignal (dom :: Domain) (delay :: Nat) a -- | Delay a DSignal for d periods. -- --
--   delay3
--     :: HiddenClockResetEnable dom
--     => DSignal dom n Int
--     -> DSignal dom (n + 3) Int
--   delay3 = delayed (-1 :> -1 :> -1 :> Nil)
--   
-- --
--   >>> sampleN @System 7 (toSignal (delay3 (dfromList [0..])))
--   [-1,-1,-1,-1,1,2,3]
--   
delayed :: (KnownNat d, HiddenClockResetEnable dom, NFDataX a) => Vec d a -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d periods, where d is -- derived from the context. -- --
--   delay2
--     :: HiddenClockResetEnable dom
--     => Int
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delay2 = delayedI
--   
-- --
--   >>> sampleN @System 7 (toSignal (delay2 (-1) (dfromList [0..])))
--   [-1,-1,-1,1,2,3,4]
--   
-- -- Or d can be specified using type application: -- --
--   >>> :t delayedI @3
--   delayedI @3
--     :: (...
--         ...
--         ...
--         ...) =>
--        a -> DSignal dom n a -> DSignal dom (n + 3) a
--   
delayedI :: (KnownNat d, NFDataX a, HiddenClockResetEnable dom) => a -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d cycles, the value at time 0..d-1 -- is a. -- --
--   delayN2
--     :: ( HiddenClock dom
--        , HiddenEnable dom )
--     => Int
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delayN2 = delayN d2
--   
-- --
--   >>> printX $ sampleN @System 6 (toSignal (delayN2 (-1) (dfromList [1..])))
--   [-1,-1,1,2,3,4]
--   
delayN :: forall dom a d n. (HiddenClock dom, HiddenEnable dom, NFDataX a) => SNat d -> a -> DSignal dom n a -> DSignal dom (n + d) a -- | Delay a DSignal for d cycles, where d is -- derived from the context. The value at time 0..d-1 is a default value. -- --
--   delayI2
--     :: ( HiddenClock dom
--        , HiddenEnable dom )
--     => Int
--     -> DSignal dom n Int
--     -> DSignal dom (n + 2) Int
--   delayI2 = delayI
--   
-- --
--   >>> sampleN @System 6 (toSignal (delayI2 (-1) (dfromList [1..])))
--   [-1,-1,1,2,3,4]
--   
-- -- You can also use type application to do the same: -- --
--   >>> sampleN @System 6 (toSignal (delayI @2 (-1) (dfromList [1..])))
--   [-1,-1,1,2,3,4]
--   
delayI :: forall d n a dom. (HiddenClock dom, HiddenEnable dom, NFDataX a, KnownNat d) => a -> DSignal dom n a -> DSignal dom (n + d) a -- | Tree fold over a Vec of DSignals with a combinatorial -- function, and delaying delay cycles after each application. -- Values at times 0..(delay*k)-1 are set to a default. -- --
--   countingSignals :: Vec 4 (DSignal dom 0 Int)
--   countingSignals = repeat (dfromList [0..])
--   
-- --
--   >>> printX $ sampleN @System 6 (toSignal (delayedFold d1 (-1) (+) countingSignals))
--   [-1,-2,0,4,8,12]
--   
-- --
--   >>> printX $ sampleN @System 8 (toSignal (delayedFold d2 (-1) (*) countingSignals))
--   [-1,-1,1,1,0,1,16,81]
--   
delayedFold :: forall dom n delay k a. (HiddenClock dom, HiddenEnable dom, NFDataX a, KnownNat delay, KnownNat k) => SNat delay -> a -> (a -> a -> a) -> Vec (2 ^ k) (DSignal dom n a) -> DSignal dom (n + (delay * k)) a -- | Feed the delayed result of a function back to its input: -- --
--   mac
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = feedback (mac' x y)
--     where
--       mac'
--         :: DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> DSignal dom 0 Int
--         -> (DSignal dom 0 Int, DSignal dom 1 Int)
--       mac' a b acc = let acc' = a * b + acc
--                      in  (acc, delayedI clk rst en 0 acc')
--   
-- --
--   >>> sampleN 7 (toSignal (mac systemClockGen systemResetGen enableGen (dfromList [0..]) (dfromList [0..])))
--   [0,0,1,5,14,30,55]
--   
feedback :: (DSignal dom n a -> (DSignal dom n a, DSignal dom ((n + m) + 1) a)) -> DSignal dom n a -- | Signals are not delayed fromSignal :: Signal dom a -> DSignal dom 0 a -- | Strip a DSignal of its delay information. toSignal :: DSignal dom delay a -> Signal dom a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList :: NFDataX a => [a] -> DSignal dom 0 a -- | Create a DSignal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (toSignal (dfromList [1,2,3,4,5]))
--   [1,2]
--   
-- -- NB: This function is not synthesizable dfromList_lazy :: [a] -> DSignal dom 0 a -- | EXPERIMENTAL -- -- Unsafely convert a Signal to a DSignal with an -- arbitrary delay. -- -- NB: Should only be used to interface with functions specified -- in terms of Signal. unsafeFromSignal :: Signal dom a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the future in the present. Often -- required When writing a circuit that requires feedback from itself. -- --
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--     -> DSignal dom 0 Int
--   mac clk rst en x y = acc'
--     where
--       acc' = (x * y) + antiDelay d1 acc
--       acc  = delayedI clk rst en 0 acc'
--   
antiDelay :: SNat d -> DSignal dom (n + d) a -> DSignal dom n a -- | EXPERIMENTAL -- -- Access a delayed signal from the past in the present. In -- contrast with delayed and friends forward does not insert any -- logic. This means using this function violates the delay invariant of -- DSignal. This is sometimes useful when combining unrelated -- delayed signals where inserting logic is not wanted or when -- abstracting over internal delayed signals where the internal delay -- information should not be leaked. -- -- For example, the circuit below returns a sequence of numbers as a pair -- but the internal delay information between the elements of the pair -- should not leak into the type. -- --
--   numbers
--     :: forall dom
--      . KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> DSignal dom 5 (Int, Int)
--   numbers clk rst en = DB.bundle (forward d1 s1, s2)
--     where
--       s1 :: DSignal dom 4 Int
--       s1 = delayed clk rst en (100 :> 10 :> 5 :> 1 :> Nil) (pure 200)
--       s2 :: DSignal dom 5 Int
--       s2 = fmap (2*) $ delayN d1 0 en clk s1
--   
-- --
--   >>> sampleN 8 (toSignal (numbers systemClockGen systemResetGen enableGen))
--   [(1,0),(1,2),(5,2),(10,10),(100,20),(200,200),(200,400),(200,400)]
--   
forward :: SNat d -> DSignal dom n a -> DSignal dom (n + d) a module Clash.Signal.Delayed.Bundle -- | Isomorphism between a DSignal of a product type (e.g. a tuple) -- and a product type of DSignals. -- -- Instances of Bundle must satisfy the following laws: -- --
--   bundle . unbundle = id
--   unbundle . bundle = id
--   
-- -- By default, bundle and unbundle, are defined as the -- identity, that is, writing: -- --
--   data D = A | B
--   
--   instance Bundle D
--   
-- -- is the same as: -- --
--   data D = A | B
--   
--   instance Bundle D where
--     type Unbundled dom delay D = DSignal dom delay D
--     bundle   s = s
--     unbundle s = s
--   
class Bundle a where { type family Unbundled (dom :: Domain) (d :: Nat) a = res | res -> dom d a; type Unbundled dom d a = DSignal dom d a; } -- | Example: -- --
--   bundle :: (DSignal dom d a, DSignal dom d b) -> DSignal dom d (a,b)
--   
-- -- However: -- --
--   bundle :: DSignal dom Bit -> DSignal dom Bit
--   
bundle :: Bundle a => Unbundled dom d a -> DSignal dom d a -- | Example: -- --
--   bundle :: (DSignal dom d a, DSignal dom d b) -> DSignal dom d (a,b)
--   
-- -- However: -- --
--   bundle :: DSignal dom Bit -> DSignal dom Bit
--   
bundle :: (Bundle a, DSignal dom d a ~ Unbundled dom d a) => Unbundled dom d a -> DSignal dom d a -- | Example: -- --
--   unbundle :: DSignal dom d (a,b) -> (DSignal dom d a, DSignal dom d b)
--   
-- -- However: -- --
--   unbundle :: DSignal dom Bit -> DSignal dom Bit
--   
unbundle :: Bundle a => DSignal dom d a -> Unbundled dom d a -- | Example: -- --
--   unbundle :: DSignal dom d (a,b) -> (DSignal dom d a, DSignal dom d b)
--   
-- -- However: -- --
--   unbundle :: DSignal dom Bit -> DSignal dom Bit
--   
unbundle :: (Bundle a, Unbundled dom d a ~ DSignal dom d a) => DSignal dom d a -> Unbundled dom d a -- | See TaggedEmptyTuple data EmptyTuple EmptyTuple :: EmptyTuple -- | Same as TaggedEmptyTuple in Clash.Signal.Bundle, but -- adapted for DSignal. data TaggedEmptyTuple (dom :: Domain) (d :: Nat) TaggedEmptyTuple :: TaggedEmptyTuple (dom :: Domain) (d :: Nat) instance Clash.Signal.Delayed.Bundle.Bundle Clash.Signal.Bundle.EmptyTuple instance Clash.Signal.Delayed.Bundle.Bundle () instance Clash.Signal.Delayed.Bundle.Bundle GHC.Types.Bool instance Clash.Signal.Delayed.Bundle.Bundle GHC.Integer.Type.Integer instance Clash.Signal.Delayed.Bundle.Bundle GHC.Types.Int instance Clash.Signal.Delayed.Bundle.Bundle GHC.Types.Float instance Clash.Signal.Delayed.Bundle.Bundle GHC.Types.Double instance Clash.Signal.Delayed.Bundle.Bundle (GHC.Maybe.Maybe a) instance Clash.Signal.Delayed.Bundle.Bundle (Data.Either.Either a b) instance Clash.Signal.Delayed.Bundle.Bundle Clash.Sized.Internal.BitVector.Bit instance Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Internal.Index.Index n) instance Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Internal.Signed.Signed n) instance Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Internal.Unsigned.Unsigned n) instance Clash.Signal.Delayed.Bundle.Bundle (a, b) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c, d) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c, d, e) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c, d, e, f) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c, d, e, f, g) instance Clash.Signal.Delayed.Bundle.Bundle (a, b, c, d, e, f, g, h) instance GHC.TypeNats.KnownNat n => Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.Vector.Vec n a) instance GHC.TypeNats.KnownNat d => Clash.Signal.Delayed.Bundle.Bundle (Clash.Sized.RTree.RTree d a) -- | Synchronizer circuits for safe clock domain crossings module Clash.Prelude.Synchronizer -- | Synchronizer based on two sequentially connected flip-flops. -- -- dualFlipFlopSynchronizer :: (NFDataX a, HiddenClock dom1, HiddenClockResetEnable dom2) => a -> Signal dom1 a -> Signal dom2 a -- | Synchronizer implemented as a FIFO around an asynchronous RAM. Based -- on the design described in Clash.Tutorial#multiclock, which is -- itself based on the design described in -- http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf. -- -- NB: This synchronizer can be used for -- word-synchronization. asyncFIFOSynchronizer :: (HiddenClockResetEnable rdom, HiddenClockResetEnable wdom, 2 <= addrSize, NFDataX a) => SNat addrSize -> Signal rdom Bool -> Signal wdom (Maybe a) -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool) -- |

Initializing a ROM with a data file

-- -- ROMs initialized with a data file. The BNF grammar for this data file -- is simple: -- --
--   FILE = LINE+
--   LINE = BIT+
--   BIT  = '0'
--        | '1'
--   
-- -- Consecutive LINEs correspond to consecutive memory addresses -- starting at 0. For example, a data file memory.bin -- containing the 9-bit unsigned numbers 7 to 13 looks -- like: -- --
--   000000111
--   000001000
--   000001001
--   000001010
--   000001011
--   000001100
--   000001101
--   
-- -- Such a file can be produced with memFile: -- --
--   writeFile "memory.bin" (memFile Nothing [7 :: Unsigned 9 .. 13])
--   
-- -- We can instantiate a synchronous ROM using the contents of the file -- above like so: -- --
--   f :: (HiddenClock dom, HiddenEnable dom)
--      => Signal dom (Unsigned 3)
--      -> Signal dom (Unsigned 9)
--   f rd = unpack <$> romFile d7 "memory.bin" rd
--   
-- -- And see that it works as expected: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ f (fromList [3..5])
--   [10,11,12]
--   
-- -- However, we can also interpret the same data as a tuple of a 6-bit -- unsigned number, and a 3-bit signed number: -- --
--   g :: (HiddenClock dom, HiddenEnable dom)
--     => Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 6,Signed 3)
--   g rd = unpack <$> romFile d7 "memory.bin" rd
--   
-- -- And then we would see: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ g (fromList [3..5])
--   [(1,2),(1,3)(1,-4)]
--   
module Clash.Prelude.ROM.File -- | An asynchronous/combinational ROM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n) => FilePath -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- romFile :: (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, Enum addr) => SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- -- TODO: table -- --

See also:

-- -- romFilePow2 :: forall n m dom. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom) => FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Convert data to the String contents of a memory file. -- -- -- --

Example

-- -- The Maybe datatype has don't care bits, where the actual -- value does not matter. But the bits need a defined value in the -- memory. Either 0 or 1 can be used, and both are valid representations -- of the data. -- --
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8]
--   
--   >>> mapM_ (putStrLn . show . pack) es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> putStr (memFile (Just 0) es)
--   000000000
--   100000111
--   100001000
--   
--   >>> putStr (memFile (Just 1) es)
--   011111111
--   100000111
--   100001000
--   
memFile :: forall a f. (BitPack a, Foldable f, HasCallStack) => Maybe Bit -> f a -> String -- | asyncRomFile primitive asyncRomFile# :: KnownNat m => SNat n -> FilePath -> Int -> BitVector m -- |

Efficient bundling of ROM content with the compiled code

-- -- Leveraging Template Haskell, the content for the ROM components in -- this module is stored alongside the compiled Haskell code. It covers -- use cases where passing the initial content as a Vec turns out -- to be problematically slow. -- -- The data is stored efficiently, with very little overhead (worst-case -- 7%, often no overhead at all). -- -- Unlike Clash.Prelude.ROM.File, Clash.Prelude.ROM.Blob -- generates practically the same HDL as Clash.Prelude.ROM and is -- compatible with all tools consuming the generated HDL. module Clash.Prelude.ROM.Blob -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRomBlob :: Enum addr => MemBlob n m -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomBlobPow2 :: KnownNat n => MemBlob (2 ^ n) m -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr) => MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | asyncRomBlob primitive asyncRomBlob# :: forall m n. MemBlob n m -> Int -> BitVector m -- | ROMs module Clash.Prelude.ROM -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRom :: (KnownNat n, Enum addr, NFDataX a) => Vec n a -> addr -> a -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomPow2 :: (KnownNat n, NFDataX a) => Vec (2 ^ n) a -> Unsigned n -> a -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: forall dom n m a. (NFDataX a, KnownNat n, KnownNat m, HiddenClock dom, HiddenEnable dom) => Vec n a -> Signal dom (Unsigned m) -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: forall dom n a. (KnownNat n, NFDataX a, HiddenClock dom, HiddenEnable dom) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | asyncRom primitive asyncRom# :: forall n a. (KnownNat n, NFDataX a) => Vec n a -> Int -> a -- | RAM primitives with a combinational read port module Clash.Prelude.RAM -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => SNat n -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: (KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | Whereas the output of a Mealy machine depends on current -- transition, the output of a Moore machine depends on the -- previous state. -- -- Moore machines are strictly less expressive, but may impose laxer -- timing requirements. module Clash.Prelude.Moore -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> Int        -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: HiddenClockResetEnable dom
--     => Signal dom (Int, Int)
--     -> Signal dom Int
--   mac = moore mac id 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14,30,...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore macT id 0 (bundle (a,x))
--       s2 = moore macT id 0 (bundle (b,y))
--   
moore :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB t o 0 (a,b)
--       (i2,b2) = mooreB t o 3 (c,i1)
--   
mooreB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine without any output logic medvedev :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> s) -> s -> Signal dom i -> Signal dom s -- | A version of medvedev that does automatic Bundleing medvedevB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle s) => (s -> i -> s) -> s -> Unbundled dom i -> Unbundled dom s -- | Whereas the output of a Moore machine depends on the previous -- state, the output of a Mealy machine depends on current -- transition. -- -- Mealy machines are strictly more expressive, but may impose stricter -- timing requirements. module Clash.Prelude.Mealy -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac :: HiddenClockResetEnable dom  => Signal dom (Int, Int) -> Signal dom Int
--   mac = mealy macT 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy macT 0 (bundle (a,x))
--       s2 = mealy macT 0 (bundle (b,y))
--   
mealy :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | Create a synchronous function from a combinational function describing -- a mealy machine using the state monad. This can be particularly useful -- when combined with lenses or optics to replicate imperative -- algorithms. -- --
--   data DelayState = DelayState
--     { _history    :: Vec 4 Int
--     , _untilValid :: Index 4
--     }
--     deriving (Generic, NFDataX)
--   makeLenses ''DelayState
--   
--   initialDelayState = DelayState (repeat 0) maxBound
--   
--   delayS :: Int -> State DelayState (Maybe Int)
--   delayS n = do
--     history   %= (n +>>)
--     remaining <- use untilValid
--     if remaining > 0
--     then do
--        untilValid -= 1
--        return Nothing
--      else do
--        out <- uses history last
--        return (Just out)
--   
--   delayTop :: HiddenClockResetEnable dom  => Signal dom Int -> Signal dom (Maybe Int)
--   delayTop = mealyS delayS initialDelayState
--   
-- --
--   >>> L.take 7 $ simulate @System delayTop [1,2,3,4,5,6,7,8]
--   [Nothing,Nothing,Nothing,Just 1,Just 2,Just 3,Just 4]
--   ...
--   
mealyS :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s o) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB f 0 (a,b)
--       (i2,b2) = mealyB f 3 (c,i1)
--   
mealyB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | A version of mealyS that does automatic Bundleing, see -- mealyB for details. mealySB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o -- | Infix version of mealyB (<^>) :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | Self-synchronizing circuits based on data-flow principles. -- | Deprecated: Module will be removed in Clash 1.10 in favor of -- clash-protocols. See: -- https://github.com/clash-lang/clash-protocols/. module Clash.Prelude.DataFlow -- | Dataflow circuit with bidirectional synchronization channels. -- -- In the forward direction we assert validity of the data. -- In the backward direction we assert that the circuit is -- ready to receive new data. A circuit adhering to the -- DataFlow type should: -- -- -- -- The DataFlow type is defined as: -- --
--   newtype DataFlow' dom iEn oEn i o
--     = DF
--     { df :: Signal dom i     -- Incoming data
--          -> Signal dom iEn   -- Flagged with /valid/ bits @iEn@.
--          -> Signal dom oEn   -- Incoming back-pressure, /ready/ edge.
--          -> ( Signal dom o   -- Outgoing data.
--             , Signal dom oEn -- Flagged with /valid/ bits @oEn@.
--             , Signal dom iEn -- Outgoing back-pressure, /ready/ edge.
--             )
--     }
--   
-- -- where: -- -- -- -- We define several composition operators for our DataFlow -- circuits: -- -- -- -- When you look at the types of the above operators it becomes clear why -- we parametrize in the types of the synchronization channels. newtype DataFlow dom iEn oEn i o DF :: (Signal dom i -> Signal dom iEn -> Signal dom oEn -> (Signal dom o, Signal dom oEn, Signal dom iEn)) -> DataFlow dom iEn oEn i o -- | Create an ordinary circuit from a DataFlow circuit [df] :: DataFlow dom iEn oEn i o -> Signal dom i -> Signal dom iEn -> Signal dom oEn -> (Signal dom o, Signal dom oEn, Signal dom iEn) -- | Dataflow circuit synchronized to the systemClockGen. type -- DataFlow iEn oEn i o = DataFlow' systemClockGen iEn oEn i o -- -- Create a DataFlow circuit from a circuit description with the -- appropriate type: -- --
--   Signal dom i        -- Incoming data.
--   -> Signal dom Bool  -- Flagged with a single /valid/ bit.
--   -> Signal dom Bool  -- Incoming back-pressure, /ready/ bit.
--   -> ( Signal dom o   -- Outgoing data.
--      , Signal dom oEn -- Flagged with a single /valid/ bit.
--      , Signal dom iEn -- Outgoing back-pressure, /ready/ bit.
--      )
--   
-- -- A circuit adhering to the DataFlow type should: -- -- liftDF :: (Signal dom i -> Signal dom Bool -> Signal dom Bool -> (Signal dom o, Signal dom Bool, Signal dom Bool)) -> DataFlow dom Bool Bool i o -- | Create a DataFlow circuit where the given function f -- operates on the data, and the synchronization channels are passed -- unaltered. pureDF :: (i -> o) -> DataFlow dom Bool Bool i o -- | Create a DataFlow circuit from a Mealy machine description as -- those of Clash.Prelude.Mealy mealyDF :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> DataFlow dom Bool Bool i o -- | Create a DataFlow circuit from a Moore machine description as -- those of Clash.Prelude.Moore mooreDF :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> DataFlow dom Bool Bool i o -- | Create a FIFO buffer adhering to the DataFlow protocol. Can be -- filled with initial content. -- -- To create a FIFO of size 4, with two initial values 2 and 3 you would -- write: -- --
--   fifo4 = fifoDF d4 (2 :> 3 :> Nil)
--   
fifoDF :: forall addrSize m n a dom. (KnownDomain dom, NFDataX a, KnownNat addrSize, KnownNat n, KnownNat m, (m + n) ~ (2 ^ addrSize)) => Clock dom -> Reset dom -> Enable dom -> SNat (m + n) -> Vec m a -> DataFlow dom Bool Bool a a -- | Identity circuit -- idDF :: DataFlow dom en en a a -- | Sequential composition of two DataFlow circuits. -- seqDF :: DataFlow dom aEn bEn a b -> DataFlow dom bEn cEn b c -> DataFlow dom aEn cEn a c -- | Apply the circuit to the first halve of the communication channels, -- leave the second halve unchanged. -- firstDF :: DataFlow dom aEn bEn a b -> DataFlow dom (aEn, cEn) (bEn, cEn) (a, c) (b, c) -- | Swap the two communication channels. -- swapDF :: DataFlow dom (aEn, bEn) (bEn, aEn) (a, b) (b, a) -- | Apply the circuit to the second halve of the communication channels, -- leave the first halve unchanged. -- secondDF :: DataFlow dom aEn bEn a b -> DataFlow dom (cEn, aEn) (cEn, bEn) (c, a) (c, b) -- | Compose two DataFlow circuits in parallel. -- parDF :: DataFlow dom aEn bEn a b -> DataFlow dom cEn dEn c d -> DataFlow dom (aEn, cEn) (bEn, dEn) (a, c) (b, d) -- | Compose n DataFlow circuits in parallel. parNDF :: KnownNat n => Vec n (DataFlow dom aEn bEn a b) -> DataFlow dom (Vec n aEn) (Vec n bEn) (Vec n a) (Vec n b) -- | Feed back the second halve of the communication channel. The feedback -- loop is buffered by a fifoDF circuit. -- -- So given a circuit h with two synchronization channels: -- --
--   h :: DataFlow (Bool,Bool) (Bool,Bool) (a,d) (b,d)
--   
-- -- Feeding back the d part (including its synchronization -- channels) results in: -- --
--   loopDF d4 Nil h
--   
-- -- -- When you have a circuit h', with only a single -- synchronization channel: -- --
--   h' :: DataFlow Bool Bool (a,d) (b,d)
--   
-- -- and you want to compose h' in a feedback loop, the following -- will not work: -- --
--   f `seqDF` (loopDF d4 Nil h') `seqDF` g
--   
-- -- The circuits f, h, and g, must operate in -- lock-step because the h' circuit only has a single -- synchronization channel. Consequently, there should only be progress -- when all three circuits are producing valid data and all three -- circuits are ready to receive new data. We need to compose -- h' with the lockStep and stepLock functions to -- achieve the lock-step operation. -- --
--   f `seqDF` (lockStep `seqDF` loopDF d4 Nil h' `seqDF` stepLock) `seqDF` g
--   
-- loopDF :: (KnownDomain dom, NFDataX d, KnownNat m, KnownNat n, KnownNat addrSize, (m + n) ~ (2 ^ addrSize)) => Clock dom -> Reset dom -> Enable dom -> SNat (m + n) -> Vec m d -> DataFlow dom (Bool, Bool) (Bool, Bool) (a, d) (b, d) -> DataFlow dom Bool Bool a b -- | Feed back the second halve of the communication channel. Unlike -- loopDF, the feedback loop is not buffered. loopDF_nobuf :: DataFlow dom (Bool, Bool) (Bool, Bool) (a, d) (b, d) -> DataFlow dom Bool Bool a b -- | Reduce or extend the synchronization granularity of parallel -- compositions. class LockStep a b -- | Reduce the synchronization granularity to a single Boolean -- value. -- -- Given: -- --
--   f :: DataFlow Bool Bool a b
--   g :: DataFlow Bool Bool c d
--   h :: DataFlow Bool Bool (b,d) (p,q)
--   
-- -- We cannot simply write: -- --
--   (f `parDF` g) `seqDF` h
--   
-- -- because, f `parDF` g, has type, DataFlow -- (Bool,Bool) (Bool,Bool) (a,c) (b,d), which does not match the -- expected synchronization granularity of h. We need a circuit -- in between that has the type: -- --
--   DataFlow (Bool,Bool) Bool (b,d) (b,d)
--   
-- -- Simply &&-ing the valid signals in the forward -- direction, and duplicating the ready signal in the backward -- direction is however not enough. We also need to make sure that -- f does not update its output when g's output is -- invalid and visa versa, as h can only consume its input when -- both f and g are producing valid data. g's -- ready port is hence only asserted when h is ready and -- f is producing valid data. And f's ready port -- is only asserted when h is ready and g is producing -- valid data. f and g will hence be proceeding in -- lock-step. -- -- The lockStep function ensures that all synchronization signals -- are properly connected: -- --
--   (f `parDF` g) `seqDF` lockStep `seqDF` h
--   
-- -- -- Note 1: ensure that the components that you are synchronizing -- have buffered/delayed ready and valid signals, or -- lockStep has the potential to introduce combinational loops. -- You can do this by placing fifoDFs on the parallel channels. -- Extending the above example, you would write: -- --
--   ((f `seqDF` fifoDF d4 Nil) `parDF` (g `seqDF` fifoDF d4 Nil)) `seqDF` lockStep `seqDF` h
--   
-- -- Note 2: lockStep works for arbitrarily nested tuples. -- That is: -- --
--   p :: DataFlow Bool Bool ((b,d),d) z
--   
--   q :: DataFlow ((Bool,Bool),Bool) ((Bool,Bool),Bool) ((a,c),c) ((b,d),d)
--   q = f `parDF` g `parDF` g
--   
--   r = q `seqDF` lockStep `seqDF` p
--   
-- -- Does the right thing. lockStep :: LockStep a b => DataFlow dom a Bool b b -- | Extend the synchronization granularity from a single Boolean -- value. -- -- Given: -- --
--   f :: DataFlow Bool Bool a b
--   g :: DataFlow Bool Bool c d
--   h :: DataFlow Bool Bool (p,q) (a,c)
--   
-- -- We cannot simply write: -- --
--   h `seqDF` (f `parDF` g)
--   
-- -- because, f `parDF` g, has type, DataFlow -- (Bool,Bool) (Bool,Bool) (a,c) (b,d), which does not match the -- expected synchronization granularity of h. We need a circuit -- in between that has the type: -- --
--   DataFlow Bool (Bool,Bool) (a,c) (a,c)
--   
-- -- Simply &&-ing the ready signals in the backward -- direction, and duplicating the valid signal in the forward -- direction is however not enough. We need to make sure that f -- does not consume values when g is not ready and visa -- versa, because h cannot update the values of its output tuple -- independently. f's valid port is hence only asserted -- when h is valid and g is ready to receive new -- values. g's valid port is only asserted when -- h is valid and f is ready to receive new values. -- f and g will hence be proceeding in -- lock-step. -- -- The stepLock function ensures that all synchronization signals -- are properly connected: -- --
--   h `seqDF` stepLock `seqDF` (f `parDF` g)
--   
-- -- -- Note 1: ensure that the components that you are synchronizing -- have buffered/delayed ready and valid signals, or -- stepLock has the potential to introduce combinational loops. -- You can do this by placing fifoDFs on the parallel channels. -- Extending the above example, you would write: -- --
--   h `seqDF` stepLock `seqDF` ((fifoDF d4 Nil `seqDF` f) `parDF` (fifoDF d4 Nil `seqDF` g))
--   
-- -- Note 2: stepLock works for arbitrarily nested tuples. -- That is: -- --
--   p :: DataFlow Bool Bool z ((a,c),c)
--   
--   q :: DataFlow ((Bool,Bool),Bool) ((Bool,Bool),Bool) ((a,c),c) ((b,d),d)
--   q = f `parDF` g `parDF` g
--   
--   r = p `seqDF` stepLock `seqDF` q
--   
-- -- Does the right thing. stepLock :: LockStep a b => DataFlow dom Bool a b b instance Clash.Prelude.DataFlow.LockStep GHC.Types.Bool c instance (Clash.Prelude.DataFlow.LockStep a x, Clash.Prelude.DataFlow.LockStep b y) => Clash.Prelude.DataFlow.LockStep (a, b) (x, y) instance (Clash.Prelude.DataFlow.LockStep en a, GHC.TypeNats.KnownNat n) => Clash.Prelude.DataFlow.LockStep (Clash.Sized.Vector.Vec n en) (Clash.Sized.Vector.Vec n a) -- |

Initializing a block RAM with a data file

-- -- Block RAM primitives that can be initialized with a data file. The BNF -- grammar for this data file is simple: -- --
--   FILE = LINE+
--   LINE = BIT+
--   BIT  = '0'
--        | '1'
--   
-- -- Consecutive LINEs correspond to consecutive memory addresses -- starting at 0. For example, a data file memory.bin -- containing the 9-bit unsigned numbers 7 to 13 looks -- like: -- --
--   000000111
--   000001000
--   000001001
--   000001010
--   000001011
--   000001100
--   000001101
--   
-- -- Such a file can be produced with memFile: -- --
--   writeFile "memory.bin" (memFile Nothing [7 :: Unsigned 9 .. 13])
--   
-- -- We can instantiate a block RAM using the contents of the file above -- like so: -- --
--   f :: (HiddenClock dom, HiddenEnable dom)
--     => Signal dom (Unsigned 3)
--     -> Signal dom (Unsigned 9)
--   f rd = unpack <$> blockRamFile d7 "memory.bin" rd (pure Nothing)
--   
-- -- In the example above, we basically treat the block RAM as a -- synchronous ROM. We can see that it works as expected: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ f (fromList [3..5])
--   [10,11,12]
--   
-- -- However, we can also interpret the same data as a tuple of a 6-bit -- unsigned number, and a 3-bit signed number: -- --
--   g :: (HiddenClock dom, HiddenEnable dom)
--      => Signal dom (Unsigned 3)
--      -> Signal dom (Unsigned 6,Signed 3)
--   g clk rd = unpack <$> blockRamFile d7 "memory.bin" rd (pure Nothing)
--   
-- -- And then we would see: -- --
--   >>> import qualified Data.List as L
--   >>> L.tail $ sampleN 4 $ g (fromList [3..5])
--   [(1,2),(1,3)(1,-4)]
--   
module Clash.Prelude.BlockRam.File -- | Create a block RAM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFile :: (KnownNat m, Enum addr, NFDataX addr, HiddenClock dom, HiddenEnable dom, HasCallStack) => SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFilePow2 :: forall dom n m. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack) => FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Convert data to the String contents of a memory file. -- -- -- --

Example

-- -- The Maybe datatype has don't care bits, where the actual -- value does not matter. But the bits need a defined value in the -- memory. Either 0 or 1 can be used, and both are valid representations -- of the data. -- --
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8]
--   
--   >>> mapM_ (putStrLn . show . pack) es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> putStr (memFile (Just 0) es)
--   000000000
--   100000111
--   100001000
--   
--   >>> putStr (memFile (Just 1) es)
--   011111111
--   100000111
--   100001000
--   
memFile :: forall a f. (BitPack a, Foldable f, HasCallStack) => Maybe Bit -> f a -> String -- |

Efficient bundling of initial RAM content with the compiled -- code

-- -- Leveraging Template Haskell, the initial content for the block RAM -- components in this module is stored alongside the compiled Haskell -- code. It covers use cases where passing the initial content as a -- Vec turns out to be problematically slow. -- -- The data is stored efficiently, with very little overhead (worst-case -- 7%, often no overhead at all). -- -- Unlike Clash.Prelude.BlockRam.File, -- Clash.Prelude.BlockRam.Blob generates practically the same HDL -- as Clash.Prelude.BlockRam and is compatible with all tools -- consuming the generated HDL. module Clash.Prelude.BlockRam.Blob -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr, NFDataX addr) => MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | Block RAM primitives -- --

Using RAMs

-- -- We will show a rather elaborate example on how you can, and why you -- might want to use blockRams. We will build a "small" CPU + -- Memory + Program ROM where we will slowly evolve to using -- blockRams. Note that the code is not meant as a de-facto -- standard on how to do CPU design in Clash. -- -- We start with the definition of the Instructions, Register names and -- machine codes: -- --
--   {-# LANGUAGE RecordWildCards, TupleSections, DeriveAnyClass #-}
--   
--   module CPU where
--   
--   import Clash.Prelude
--   
--   type InstrAddr = Unsigned 8
--   type MemAddr   = Unsigned 5
--   type Value     = Signed 8
--   
--   data Instruction
--     = Compute Operator Reg Reg Reg
--     | Branch Reg Value
--     | Jump Value
--     | Load MemAddr Reg
--     | Store Reg MemAddr
--     | Nop
--     deriving (Eq, Show, Generic, NFDataX)
--   
--   data Reg
--     = Zero
--     | PC
--     | RegA
--     | RegB
--     | RegC
--     | RegD
--     | RegE
--     deriving (Eq, Show, Enum, Generic, NFDataX)
--   
--   data Operator = Add | Sub | Incr | Imm | CmpGt
--     deriving (Eq, Show, Generic, NFDataX)
--   
--   data MachCode
--     = MachCode
--     { inputX  :: Reg
--     , inputY  :: Reg
--     , result  :: Reg
--     , aluCode :: Operator
--     , ldReg   :: Reg
--     , rdAddr  :: MemAddr
--     , wrAddrM :: Maybe MemAddr
--     , jmpM    :: Maybe Value
--     }
--   
--   nullCode =
--     MachCode
--       { inputX = Zero
--       , inputY = Zero
--       , result = Zero
--       , aluCode = Imm
--       , ldReg = Zero
--       , rdAddr = 0
--       , wrAddrM = Nothing
--       , jmpM = Nothing
--       }
--   
-- -- Next we define the CPU and its ALU: -- --
--   cpu
--     :: Vec 7 Value          -- ^ Register bank
--     -> (Value,Instruction)  -- ^ (Memory output, Current instruction)
--     -> ( Vec 7 Value
--        , (MemAddr, Maybe (MemAddr,Value), InstrAddr)
--        )
--   cpu regbank (memOut, instr) =
--     (regbank', (rdAddr, (,aluOut) <$> wrAddrM, bitCoerce ipntr))
--    where
--     -- Current instruction pointer
--     ipntr = regbank !! PC
--   
--     -- Decoder
--     (MachCode {..}) = case instr of
--       Compute op rx ry res -> nullCode {inputX=rx,inputY=ry,result=res,aluCode=op}
--       Branch cr a          -> nullCode {inputX=cr,jmpM=Just a}
--       Jump a               -> nullCode {aluCode=Incr,jmpM=Just a}
--       Load a r             -> nullCode {ldReg=r,rdAddr=a}
--       Store r a            -> nullCode {inputX=r,wrAddrM=Just a}
--       Nop                  -> nullCode
--   
--     -- ALU
--     regX   = regbank !! inputX
--     regY   = regbank !! inputY
--     aluOut = alu aluCode regX regY
--   
--     -- next instruction
--     nextPC =
--       case jmpM of
--         Just a | aluOut /= 0 -> ipntr + a
--         _                    -> ipntr + 1
--   
--     -- update registers
--     regbank' = replace Zero   0
--              $ replace PC     nextPC
--              $ replace result aluOut
--              $ replace ldReg  memOut
--              $ regbank
--   
--   alu Add   x y = x + y
--   alu Sub   x y = x - y
--   alu Incr  x _ = x + 1
--   alu Imm   x _ = x
--   alu CmpGt x y = if x > y then 1 else 0
--   
-- -- We initially create a memory out of simple registers: -- --
--   dataMem
--     :: HiddenClockResetEnable dom
--     => Signal dom MemAddr
--     -- ^ Read address
--     -> Signal dom (Maybe (MemAddr,Value))
--     -- ^ (write address, data in)
--     -> Signal dom Value
--     -- ^ data out
--   dataMem rd wrM =
--     mealy dataMemT (replicate d32 0) (bundle (rd,wrM))
--    where
--     dataMemT mem (rd,wrM) = (mem',dout)
--       where
--         dout = mem !! rd
--         mem' =
--           case wrM of
--             Just (wr,din) -> replace wr din mem
--             _             -> mem
--   
-- -- And then connect everything: -- --
--   system
--     :: ( KnownNat n
--        , HiddenClockResetEnable dom
--        )
--     => Vec n Instruction
--     -> Signal dom Value
--   system instrs = memOut
--    where
--     memOut = dataMem rdAddr dout
--     (rdAddr, dout, ipntr) = mealyB cpu (replicate d7 0) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- Create a simple program that calculates the GCD of 4 and 6: -- --
--   -- Compute GCD of 4 and 6
--   prog = -- 0 := 4
--          Compute Incr Zero RegA RegA :>
--          replicate d3 (Compute Incr RegA Zero RegA) ++
--          Store RegA 0 :>
--          -- 1 := 6
--          Compute Incr Zero RegA RegA :>
--          replicate d5 (Compute Incr RegA Zero RegA) ++
--          Store RegA 1 :>
--          -- A := 4
--          Load 0 RegA :>
--          -- B := 6
--          Load 1 RegB :>
--          -- start
--          Compute CmpGt RegA RegB RegC :>
--          Branch RegC 4 :>
--          Compute CmpGt RegB RegA RegC :>
--          Branch RegC 4 :>
--          Jump 5 :>
--          -- (a > b)
--          Compute Sub RegA RegB RegA :>
--          Jump (-6) :>
--          -- (b > a)
--          Compute Sub RegB RegA RegB :>
--          Jump (-8) :>
--          -- end
--          Store RegA 2 :>
--          Load 2 RegC :>
--          Nil
--   
-- -- And test our system: -- --
--   >>> sampleN @System 32 (system prog)
--   [0,0,0,0,0,0,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- -- to see that our system indeed calculates that the GCD of 6 and 4 is 2. -- --

Improvement 1: using asyncRam

-- -- As you can see, it's fairly straightforward to build a memory using -- registers and read (!!) and write (replace) logic. This -- might however not result in the most efficient hardware structure, -- especially when building an ASIC. -- -- Instead it is preferable to use the asyncRam function which has -- the potential to be translated to a more efficient structure: -- --
--   system2
--     :: ( KnownNat n
--        , HiddenClockResetEnable dom  )
--     => Vec n Instruction
--     -> Signal dom Value
--   system2 instrs = memOut
--    where
--     memOut = asyncRam d32 rdAddr dout
--     (rdAddr,dout,ipntr) = mealyB cpu (replicate d7 0) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- Again, we can simulate our system and see that it works. This time -- however, we need to disregard the first few output samples, because -- the initial content of an asyncRam is undefined, and -- consequently, the first few output samples are also undefined. -- We use the utility function printX to conveniently filter out -- the undefinedness and replace it with the string "undefined" -- in the first few leading outputs. -- --
--   >>> printX $ sampleN @System 32 (system2 prog)
--   [undefined,undefined,undefined,undefined,undefined,undefined,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- --

Improvement 2: using blockRam

-- -- Finally we get to using blockRam. On FPGAs, asyncRam -- will be implemented in terms of LUTs, and therefore take up logic -- resources. FPGAs also have large(r) memory structures called block -- RAMs, which are preferred, especially as the memories we need for -- our application get bigger. The blockRam function will be -- translated to such a block RAM. -- -- One important aspect of block RAMs is that they have a -- synchronous read port, meaning that, unlike the behavior of -- asyncRam, given a read address r at time t, -- the value v in the RAM at address r is only -- available at time t+1. -- -- For us that means we need to change the design of our CPU. Right now, -- upon a load instruction we generate a read address for the memory, and -- the value at that read address is immediately available to be put in -- the register bank. Because we will be using a block RAM, the value is -- delayed until the next cycle. Thus, we will need to also delay the -- register address to which the memory address is loaded: -- --
--   cpu2
--     :: (Vec 7 Value,Reg)    -- ^ (Register bank, Load reg addr)
--     -> (Value,Instruction)  -- ^ (Memory output, Current instruction)
--     -> ( (Vec 7 Value, Reg)
--        , (MemAddr, Maybe (MemAddr,Value), InstrAddr)
--        )
--   cpu2 (regbank,ldRegD) (memOut,instr) =
--     ((regbank', ldRegD'), (rdAddr, (,aluOut) <$> wrAddrM, bitCoerce ipntr))
--    where
--     -- Current instruction pointer
--     ipntr = regbank !! PC
--   
--     -- Decoder
--     (MachCode {..}) = case instr of
--       Compute op rx ry res -> nullCode {inputX=rx,inputY=ry,result=res,aluCode=op}
--       Branch cr a          -> nullCode {inputX=cr,jmpM=Just a}
--       Jump a               -> nullCode {aluCode=Incr,jmpM=Just a}
--       Load a r             -> nullCode {ldReg=r,rdAddr=a}
--       Store r a            -> nullCode {inputX=r,wrAddrM=Just a}
--       Nop                  -> nullCode
--   
--     -- ALU
--     regX   = regbank !! inputX
--     regY   = regbank !! inputY
--     aluOut = alu aluCode regX regY
--   
--     -- next instruction
--     nextPC =
--       case jmpM of
--         Just a | aluOut /= 0 -> ipntr + a
--         _                    -> ipntr + 1
--   
--     -- update registers
--     ldRegD'  = ldReg  -- Delay the ldReg by 1 cycle
--     regbank' = replace Zero   0
--              $ replace PC     nextPC
--              $ replace result aluOut
--              $ replace ldRegD memOut
--              $ regbank
--   
-- -- We can now finally instantiate our system with a blockRam: -- --
--   system3
--     :: (KnownNat n
--        , HiddenClockResetEnable dom  )
--     => Vec n Instruction
--     -> Signal dom Value
--   system3 instrs = memOut
--    where
--     memOut = blockRam (replicate d32 0) rdAddr dout
--     (rdAddr,dout,ipntr) = mealyB cpu2 ((replicate d7 0),Zero) (memOut,instr)
--     instr  = asyncRom instrs <$> ipntr
--   
-- -- We are, however, not done. We will also need to update our program. -- The reason being that values that we try to load in our registers -- won't be loaded into the register until the next cycle. This is a -- problem when the next instruction immediately depends on this memory -- value. In our case, this was only the case when we loaded the value -- 6, which was stored at address 1, into -- RegB. Our updated program is thus: -- --
--   prog2 = -- 0 := 4
--          Compute Incr Zero RegA RegA :>
--          replicate d3 (Compute Incr RegA Zero RegA) ++
--          Store RegA 0 :>
--          -- 1 := 6
--          Compute Incr Zero RegA RegA :>
--          replicate d5 (Compute Incr RegA Zero RegA) ++
--          Store RegA 1 :>
--          -- A := 4
--          Load 0 RegA :>
--          -- B := 6
--          Load 1 RegB :>
--          Nop :> -- Extra NOP
--          -- start
--          Compute CmpGt RegA RegB RegC :>
--          Branch RegC 4 :>
--          Compute CmpGt RegB RegA RegC :>
--          Branch RegC 4 :>
--          Jump 5 :>
--          -- (a > b)
--          Compute Sub RegA RegB RegA :>
--          Jump (-6) :>
--          -- (b > a)
--          Compute Sub RegB RegA RegB :>
--          Jump (-8) :>
--          -- end
--          Store RegA 2 :>
--          Load 2 RegC :>
--          Nil
--   
-- -- When we simulate our system we see that it works. This time again, we -- need to disregard the first sample, because the initial output of a -- blockRam is undefined. We use the utility function -- printX to conveniently filter out the undefinedness and replace -- it with the string "undefined". -- --
--   >>> printX $ sampleN @System 34 (system3 prog2)
--   [undefined,0,0,0,0,0,0,4,4,4,4,4,4,4,4,6,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,2]
--   
-- -- This concludes the short introduction to using blockRam. module Clash.Prelude.BlockRam -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: HiddenClock dom
--     => Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 = blockRam (replicate d40 1)
--   
blockRam :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, Enum addr, NFDataX addr) => Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: HiddenClock dom
--     => Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 = blockRamPow2 (replicate d32 1)
--   
blockRamPow2 :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, KnownNat n) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | A version of blockRam that has no default values set. May be -- cleared to an arbitrary state using a reset function. blockRamU :: forall n dom a r addr. (HasCallStack, HiddenClockResetEnable dom, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => ResetStrategy r -> SNat n -> (Index n -> a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | A version of blockRam that is initialized with the same value -- on all memory positions blockRam1 :: forall n dom a r addr. (HasCallStack, HiddenClockResetEnable dom, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => ResetStrategy r -> SNat n -> a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a data ResetStrategy (r :: Bool) [ClearOnReset] :: ResetStrategy 'True [NoClearOnReset] :: ResetStrategy 'False -- | Create a read-after-write block RAM from a read-before-write one -- --
--   >>> :t readNew (blockRam (0 :> 1 :> Nil))
--   readNew (blockRam (0 :> 1 :> Nil))
--     :: ...
--        ...
--        ...
--        ...
--        ... =>
--        Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a
--   
readNew :: (HiddenClockResetEnable dom, NFDataX a, Eq addr) => (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs dom1 dom2 a. (HasCallStack, KnownNat nAddrs, HiddenClock dom1, HiddenClock dom2, NFDataX a) => Signal dom1 (RamOp nAddrs a) -> Signal dom2 (RamOp nAddrs a) -> (Signal dom1 a, Signal dom2 a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a module Clash.Explicit.Testbench -- | Compares the first two Signals for equality and logs a warning -- when they are not equal. The second Signal is considered the -- expected value. This function simply returns the third Signal -- unaltered as its result. This function is used by -- outputVerifier. -- --

Usage in clashi

-- -- NB: When simulating a component that uses assert in -- clashi, usually, the warnings are only logged the first time -- the component is simulated. Issuing :reload in -- clashi will discard the cached result of the computation, and -- warnings will once again be emitted. -- -- NB: This function can be used in synthesizable designs. assert :: (KnownDomain dom, Eq a, ShowX a) => Clock dom -> Reset dom -> String -> Signal dom a -> Signal dom a -> Signal dom b -> Signal dom b -- | The same as assert, but can handle don't care bits in its -- expected value. assertBitVector :: (KnownDomain dom, KnownNat n) => Clock dom -> Reset dom -> String -> Signal dom (BitVector n) -> Signal dom (BitVector n) -> Signal dom b -> Signal dom b -- | Ignore signal for a number of cycles, while outputting a static value. ignoreFor :: forall dom n a. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> SNat n -> a -> Signal dom a -> Signal dom a -- | Example: -- --
--   testInput
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Signal dom Int
--   testInput clk rst = stimuliGenerator clk rst $(listToVecTH [(1::Int),3..21])
--   
-- --
--   >>> sampleN 14 (testInput systemClockGen resetGen)
--   [1,1,3,5,7,9,11,13,15,17,19,21,21,21]
--   
stimuliGenerator :: forall l dom a. (KnownNat l, KnownDomain dom) => Clock dom -> Reset dom -> Vec l a -> Signal dom a -- | Clock generator to be used in the testBench function. -- -- To be used like: -- --
--   clkSystem en = tbClockGen @System en
--   
-- --

Example

-- --
--   module Example where
--   
--   import Clash.Explicit.Prelude
--   import Clash.Explicit.Testbench
--   
--   -- Fast domain: twice as fast as "Slow"
--   createDomain vSystem{vName="Fast", vPeriod=10}
--   
--   -- Slow domain: twice as slow as "Fast"
--   createDomain vSystem{vName="Slow", vPeriod=20}
--   
--   topEntity
--     :: Clock "Fast"
--     -> Reset "Fast"
--     -> Enable "Fast"
--     -> Clock "Slow"
--     -> Signal "Fast" (Unsigned 8)
--     -> Signal "Slow" (Unsigned 8, Unsigned 8)
--   topEntity clk1 rst1 en1 clk2 i =
--     let h = register clk1 rst1 en1 0 (register clk1 rst1 en1 0 i)
--         l = register clk1 rst1 en1 0 i
--     in  unsafeSynchronizer clk1 clk2 (bundle (h, l))
--   
--   testBench
--     :: Signal "Slow" Bool
--   testBench = done
--     where
--       testInput      = stimuliGenerator clkA1 rstA1 $(listToVecTH [1::Unsigned 8,2,3,4,5,6,7,8])
--       expectedOutput = outputVerifier   clkB2 rstB2 $(listToVecTH [(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)])
--       done           = expectedOutput (topEntity clkA1 rstA1 enableGen clkB2 testInput)
--       notDone        = not <$> done
--       clkA1          = tbClockGen @"Fast" (unsafeSynchronizer clkB2 clkA1 notDone)
--       clkB2          = tbClockGen @"Slow" notDone
--       rstA1          = resetGen @"Fast"
--       rstB2          = resetGen @"Slow"
--   
tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom -- | Enable signal that's always enabled. Because it has a blackbox -- definition this enable signal is opaque to other blackboxes. It will -- therefore never be optimized away. tbEnableGen :: Enable tag -- | Clock generator for the System clock domain. -- -- NB: Can be used in the testBench function -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
tbSystemClockGen :: Signal System Bool -> Clock System -- | Convert a single-ended clock to a differential clock -- -- The tbClockGen function generates a single-ended clock. This -- function will output the two phases of a differential clock -- corresponding to that single-ended clock. -- -- This function is only meant to be used in the testBench -- function, not to create a differential output in hardware. -- -- Example: -- --
--   clk = clockToDiffClock $ tbClockGen (not <$> done)
--   
clockToDiffClock :: KnownDomain dom => Clock dom -> DiffClock dom -- | Compare a signal (coming from a circuit) to a vector of samples. If a -- sample from the signal is not equal to the corresponding sample in the -- vector, print to stderr and continue testing. This function is -- synthesizable in the sense that HDL simulators will run it. If -- testDom and circuitDom refer to the same domain, it -- can also be synthesized into hardware. -- -- NB: This function uses assert. When simulating this -- function in clashi, read the note. -- -- Example: -- --
--   expectedOutput
--     :: Clock dom -> Reset dom
--     -> Signal dom Int -> Signal dom Bool
--   expectedOutput clk rst = outputVerifier clk rst $(listToVecTH ([70,99,2,3,4,5,7,8,9,10]::[Int]))
--   
-- --
--   >>> import qualified Data.List as List
--   
--   >>> sampleN 12 (expectedOutput systemClockGen resetGen (fromList (0:[0..10] List.++ [10,10,10])))
--   
--   cycle(<Clock: System>): 0, outputVerifier
--   expected value: 70, not equal to actual value: 0
--   [False
--   cycle(<Clock: System>): 1, outputVerifier
--   expected value: 70, not equal to actual value: 0
--   ,False
--   cycle(<Clock: System>): 2, outputVerifier
--   expected value: 99, not equal to actual value: 1
--   ,False,False,False,False,False
--   cycle(<Clock: System>): 7, outputVerifier
--   expected value: 7, not equal to actual value: 6
--   ,False
--   cycle(<Clock: System>): 8, outputVerifier
--   expected value: 8, not equal to actual value: 7
--   ,False
--   cycle(<Clock: System>): 9, outputVerifier
--   expected value: 9, not equal to actual value: 8
--   ,False
--   cycle(<Clock: System>): 10, outputVerifier
--   expected value: 10, not equal to actual value: 9
--   ,False,True]
--   
-- -- If you're working with BitVectors containing don't care bits -- you should use outputVerifierBitVector. outputVerifier :: forall l a testDom circuitDom. (KnownNat l, KnownDomain testDom, KnownDomain circuitDom, Eq a, ShowX a, 1 <= l) => Clock testDom -> Clock circuitDom -> Reset testDom -> Vec l a -> Signal circuitDom a -> Signal testDom Bool -- | Same as outputVerifier but used in cases where the test bench -- domain and the domain of the circuit under test are the same. outputVerifier' :: forall l a dom. (KnownNat l, KnownDomain dom, Eq a, ShowX a, 1 <= l) => Clock dom -> Reset dom -> Vec l a -> Signal dom a -> Signal dom Bool -- | Same as outputVerifier, but can handle don't care bits in its -- expected values. outputVerifierBitVector :: forall l n testDom circuitDom. (KnownNat l, KnownNat n, KnownDomain testDom, KnownDomain circuitDom, 1 <= l) => Clock testDom -> Clock circuitDom -> Reset testDom -> Vec l (BitVector n) -> Signal circuitDom (BitVector n) -> Signal testDom Bool -- | Same as outputVerifier', but can handle don't care bits in its -- expected values. outputVerifierBitVector' :: forall l n dom. (KnownNat l, KnownNat n, KnownDomain dom, 1 <= l) => Clock dom -> Reset dom -> Vec l (BitVector n) -> Signal dom (BitVector n) -> Signal dom Bool -- | Same as tbClockGen, but returns two clocks on potentially -- different domains. To be used in situations where the test circuit -- potentially operates on a different clock than the device under test. biTbClockGen :: forall testDom circuitDom. (KnownDomain testDom, KnownDomain circuitDom) => Signal testDom Bool -> (Clock testDom, Clock circuitDom) -- | Cross clock domains in a way that is unsuitable for hardware but good -- enough for simulation. -- -- It's equal to unsafeSynchronizer but will warn when used -- outside of a test bench. outputVerifier uses this function when -- it needs to cross between clock domains, which will render it -- unsuitable for synthesis, but good enough for simulating the generated -- HDL. unsafeSimSynchronizer :: forall dom1 dom2 a. (KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Signal dom1 a -> Signal dom2 a outputVerifierWith :: forall l a testDom circuitDom. (KnownNat l, KnownDomain testDom, KnownDomain circuitDom, Eq a, ShowX a, 1 <= l) => (Clock testDom -> Reset testDom -> Signal testDom a -> Signal testDom a -> Signal testDom Bool -> Signal testDom Bool) -> Clock testDom -> Clock circuitDom -> Reset testDom -> Vec l a -> Signal circuitDom a -> Signal testDom Bool module Clash.Prelude.Testbench -- | Compares the first two Signals for equality and logs a warning -- when they are not equal. The second Signal is considered the -- expected value. This function simply returns the third Signal -- unaltered as its result. This function is used by -- outputVerifier'. -- --

Usage in clashi

-- -- NB: When simulating a component that uses assert in -- clashi, usually, the warnings are only logged the first time -- the component is simulated. Issuing :reload in -- clashi will discard the cached result of the computation, and -- warnings will once again be emitted. -- -- NB: This function can be used in synthesizable designs. assert :: (Eq a, ShowX a, HiddenClock dom, HiddenReset dom) => String -> Signal dom a -> Signal dom a -> Signal dom b -> Signal dom b -- | The same as assert, but can handle don't care bits in its -- expected value. assertBitVector :: (KnownNat n, HiddenClock dom, HiddenReset dom) => String -> Signal dom (BitVector n) -> Signal dom (BitVector n) -> Signal dom b -> Signal dom b -- | Ignore signal for a number of cycles, while outputting a static value. ignoreFor :: HiddenClockResetEnable dom => SNat n -> a -> Signal dom a -> Signal dom a -- | Compare a signal (coming from a circuit) to a vector of samples. If a -- sample from the signal is not equal to the corresponding sample in the -- vector, print to stderr and continue testing. This function is -- synthesizable in the sense that HDL simulators will run it. -- -- NB: This function uses assert. When simulating this -- function in clashi, read the note. -- -- Example: -- --
--   expectedOutput
--     :: HiddenClockResetEnable dom
--     -> Signal dom Int -> Signal dom Bool
--   expectedOutput = outputVerifier' $(listToVecTH ([70,99,2,3,4,5,7,8,9,10]::[Int]))
--   
-- --
--   >>> import qualified Data.List as List
--   
--   >>> sampleN @System 12 (expectedOutput (fromList (0:[0..10] List.++ [10,10,10])))
--   
--   cycle(<Clock: System>): 0, outputVerifier
--   expected value: 70, not equal to actual value: 0
--   [False
--   cycle(<Clock: System>): 1, outputVerifier
--   expected value: 70, not equal to actual value: 0
--   ,False
--   cycle(<Clock: System>): 2, outputVerifier
--   expected value: 99, not equal to actual value: 1
--   ,False,False,False,False,False
--   cycle(<Clock: System>): 7, outputVerifier
--   expected value: 7, not equal to actual value: 6
--   ,False
--   cycle(<Clock: System>): 8, outputVerifier
--   expected value: 8, not equal to actual value: 7
--   ,False
--   cycle(<Clock: System>): 9, outputVerifier
--   expected value: 9, not equal to actual value: 8
--   ,False
--   cycle(<Clock: System>): 10, outputVerifier
--   expected value: 10, not equal to actual value: 9
--   ,False,True]
--   
-- -- If you're working with BitVectors containing don't care bits -- you should use outputVerifierBitVector'. outputVerifier' :: (KnownNat l, Eq a, ShowX a, HiddenClock dom, HiddenReset dom, 1 <= l) => Vec l a -> Signal dom a -> Signal dom Bool -- | Same as outputVerifier', but can handle don't care bits in its -- expected values. outputVerifierBitVector' :: (KnownNat l, KnownNat n, HiddenClock dom, HiddenReset dom, 1 <= l) => Vec l (BitVector n) -> Signal dom (BitVector n) -> Signal dom Bool -- | Example: -- --
--   testInput
--     :: HiddenClockResetEnable dom
--     => Signal dom Int
--   testInput = stimuliGenerator $(listToVecTH [(1::Int),3..21])
--   
-- --
--   >>> sampleN @System 13 testInput
--   [1,1,3,5,7,9,11,13,15,17,19,21,21]
--   
stimuliGenerator :: (KnownNat l, HiddenClock dom, HiddenReset dom) => Vec l a -> Signal dom a -- | Clock generator to be used in the testBench function. -- -- To be used like: -- --
--   clkSystem en = tbClockGen @System en
--   
-- --

Example

-- --
--   module Example where
--   
--   import Clash.Explicit.Prelude
--   import Clash.Explicit.Testbench
--   
--   -- Fast domain: twice as fast as "Slow"
--   createDomain vSystem{vName="Fast", vPeriod=10}
--   
--   -- Slow domain: twice as slow as "Fast"
--   createDomain vSystem{vName="Slow", vPeriod=20}
--   
--   topEntity
--     :: Clock "Fast"
--     -> Reset "Fast"
--     -> Enable "Fast"
--     -> Clock "Slow"
--     -> Signal "Fast" (Unsigned 8)
--     -> Signal "Slow" (Unsigned 8, Unsigned 8)
--   topEntity clk1 rst1 en1 clk2 i =
--     let h = register clk1 rst1 en1 0 (register clk1 rst1 en1 0 i)
--         l = register clk1 rst1 en1 0 i
--     in  unsafeSynchronizer clk1 clk2 (bundle (h, l))
--   
--   testBench
--     :: Signal "Slow" Bool
--   testBench = done
--     where
--       testInput      = stimuliGenerator clkA1 rstA1 $(listToVecTH [1::Unsigned 8,2,3,4,5,6,7,8])
--       expectedOutput = outputVerifier   clkB2 rstB2 $(listToVecTH [(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)])
--       done           = expectedOutput (topEntity clkA1 rstA1 enableGen clkB2 testInput)
--       notDone        = not <$> done
--       clkA1          = tbClockGen @"Fast" (unsafeSynchronizer clkB2 clkA1 notDone)
--       clkB2          = tbClockGen @"Slow" notDone
--       rstA1          = resetGen @"Fast"
--       rstB2          = resetGen @"Slow"
--   
tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom -- | Enable signal that's always enabled. Because it has a blackbox -- definition this enable signal is opaque to other blackboxes. It will -- therefore never be optimized away. tbEnableGen :: Enable tag -- | Clock generator for the System clock domain. -- -- NB: Can be used in the testBench function -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
tbSystemClockGen :: Signal System Bool -> Clock System -- | Convert a single-ended clock to a differential clock -- -- The tbClockGen function generates a single-ended clock. This -- function will output the two phases of a differential clock -- corresponding to that single-ended clock. -- -- This function is only meant to be used in the testBench -- function, not to create a differential output in hardware. -- -- Example: -- --
--   clk = clockToDiffClock $ tbClockGen (not <$> done)
--   
clockToDiffClock :: KnownDomain dom => Clock dom -> DiffClock dom module Clash.Class.Counter.Internal -- | Counter is a class that composes multiple counters into a -- single one. It is similar to odometers found in olds cars, once all -- counters reach their maximum they reset to zero - i.e. odometer -- rollover. See countSucc and countPred for API usage -- examples. -- -- Example use case: when driving a monitor through VGA you would like to -- keep track at least two counters: one counting a horizontal position, -- and one vertical. Perhaps a fancy VGA driver would also like to keep -- track of the number of drawn frames. To do so, the three counters are -- setup with different types. On each round of the horizontal -- counter the vertical counter should be increased. On each round -- of the vertical counter the frame counter should be increased. With -- this class you could simply use the type: -- --
--   (FrameCount, VerticalCount, HorizontalCount)
--   
-- -- and have countSucc work as described. class Counter a -- | Value counter wraps around to on a countSuccOverflow overflow countMin :: Counter a => a -- | Value counter wraps around to on a countSuccOverflow overflow countMin :: (Counter a, Bounded a) => a -- | Value counter wraps around to on a countPredOverflow overflow countMax :: Counter a => a -- | Value counter wraps around to on a countPredOverflow overflow countMax :: (Counter a, Bounded a) => a -- | Gets the successor of a. If it overflows, the first part of -- the tuple will be set to True and the second part wraps around to -- countMin. countSuccOverflow :: Counter a => a -> (Bool, a) -- | Gets the successor of a. If it overflows, the first part of -- the tuple will be set to True and the second part wraps around to -- countMin. countSuccOverflow :: (Counter a, Eq a, Enum a, Bounded a) => a -> (Bool, a) -- | Gets the predecessor of a. If it underflows, the first part -- of the tuple will be set to True and the second part wraps around to -- countMax. countPredOverflow :: Counter a => a -> (Bool, a) -- | Gets the predecessor of a. If it underflows, the first part -- of the tuple will be set to True and the second part wraps around to -- countMax. countPredOverflow :: (Counter a, Eq a, Enum a, Bounded a) => a -> (Bool, a) instance (Clash.Class.Counter.Internal.Counter a0, Clash.Class.Counter.Internal.Counter a1, Clash.Class.Counter.Internal.Counter a2) => Clash.Class.Counter.Internal.Counter (a0, a1, a2) instance Clash.Class.Counter.Internal.Counter a => Clash.Class.Counter.Internal.Counter (Data.Functor.Identity.Identity a) instance (1 GHC.TypeNats.<= n, GHC.TypeNats.KnownNat n) => Clash.Class.Counter.Internal.Counter (Clash.Sized.Internal.Index.Index n) instance GHC.TypeNats.KnownNat n => Clash.Class.Counter.Internal.Counter (Clash.Sized.Internal.Unsigned.Unsigned n) instance GHC.TypeNats.KnownNat n => Clash.Class.Counter.Internal.Counter (Clash.Sized.Internal.Signed.Signed n) instance GHC.TypeNats.KnownNat n => Clash.Class.Counter.Internal.Counter (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Class.Counter.Internal.Counter GHC.Types.Bool instance Clash.Class.Counter.Internal.Counter Clash.Sized.Internal.BitVector.Bit instance Clash.Class.Counter.Internal.Counter GHC.Types.Int instance Clash.Class.Counter.Internal.Counter GHC.Int.Int8 instance Clash.Class.Counter.Internal.Counter GHC.Int.Int16 instance Clash.Class.Counter.Internal.Counter GHC.Int.Int32 instance Clash.Class.Counter.Internal.Counter GHC.Int.Int64 instance Clash.Class.Counter.Internal.Counter GHC.Types.Word instance Clash.Class.Counter.Internal.Counter GHC.Word.Word8 instance Clash.Class.Counter.Internal.Counter GHC.Word.Word16 instance Clash.Class.Counter.Internal.Counter GHC.Word.Word32 instance Clash.Class.Counter.Internal.Counter GHC.Word.Word64 instance Clash.Class.Counter.Internal.Counter a => Clash.Class.Counter.Internal.Counter (GHC.Maybe.Maybe a) instance (Clash.Class.Counter.Internal.Counter a, Clash.Class.Counter.Internal.Counter b) => Clash.Class.Counter.Internal.Counter (Data.Either.Either a b) instance (Clash.Class.Counter.Internal.Counter a0, Clash.Class.Counter.Internal.Counter a1) => Clash.Class.Counter.Internal.Counter (a0, a1) -- | Utilities for wrapping counters consisting of multiple individual -- counters module Clash.Class.Counter -- | Counter is a class that composes multiple counters into a -- single one. It is similar to odometers found in olds cars, once all -- counters reach their maximum they reset to zero - i.e. odometer -- rollover. See countSucc and countPred for API usage -- examples. -- -- Example use case: when driving a monitor through VGA you would like to -- keep track at least two counters: one counting a horizontal position, -- and one vertical. Perhaps a fancy VGA driver would also like to keep -- track of the number of drawn frames. To do so, the three counters are -- setup with different types. On each round of the horizontal -- counter the vertical counter should be increased. On each round -- of the vertical counter the frame counter should be increased. With -- this class you could simply use the type: -- --
--   (FrameCount, VerticalCount, HorizontalCount)
--   
-- -- and have countSucc work as described. class Counter a -- | Value counter wraps around to on a countSuccOverflow overflow countMin :: Counter a => a -- | Value counter wraps around to on a countSuccOverflow overflow countMin :: (Counter a, Bounded a) => a -- | Value counter wraps around to on a countPredOverflow overflow countMax :: Counter a => a -- | Value counter wraps around to on a countPredOverflow overflow countMax :: (Counter a, Bounded a) => a -- | Gets the successor of a. If it overflows, the first part of -- the tuple will be set to True and the second part wraps around to -- countMin. countSuccOverflow :: Counter a => a -> (Bool, a) -- | Gets the successor of a. If it overflows, the first part of -- the tuple will be set to True and the second part wraps around to -- countMin. countSuccOverflow :: (Counter a, Eq a, Enum a, Bounded a) => a -> (Bool, a) -- | Gets the predecessor of a. If it underflows, the first part -- of the tuple will be set to True and the second part wraps around to -- countMax. countPredOverflow :: Counter a => a -> (Bool, a) -- | Gets the predecessor of a. If it underflows, the first part -- of the tuple will be set to True and the second part wraps around to -- countMax. countPredOverflow :: (Counter a, Eq a, Enum a, Bounded a) => a -> (Bool, a) -- | Successor of a counter. -- -- Examples: -- --
--   >>> type T = (Unsigned 2, Unsigned 2)
--   
--   >>> countSucc @T (1, 1)
--   (1,2)
--   
--   >>> countSucc @T (1, 2)
--   (1,3)
--   
--   >>> countSucc @T (1, 3)
--   (2,0)
--   
--   >>> countSucc @T (3, 3)
--   (0,0)
--   
--   >>> countSucc @(Index 9, Index 2) (0, 1)
--   (1,0)
--   
--   >>> countSucc @(Either (Index 9) (Index 9)) (Left 8)
--   Right 0
--   
countSucc :: Counter a => a -> a -- | Predecessor of a counter -- -- Examples: -- --
--   >>> type T = (Unsigned 2, Unsigned 2)
--   
--   >>> countPred @T (1, 2)
--   (1,1)
--   
--   >>> countPred @T (1, 3)
--   (1,2)
--   
--   >>> countPred @T (2, 0)
--   (1,3)
--   
--   >>> countPred @T (0, 0)
--   (3,3)
--   
--   >>> countPred @(Index 9, Index 2) (1, 0)
--   (0,1)
--   
--   >>> countPred @(Either (Index 9) (Index 9)) (Right 0)
--   Left 8
--   
countPred :: Counter a => a -> a module Clash.Class.AutoReg.Internal -- | autoReg is a "smart" version of register. It does two -- things: -- --
    --
  1. It splits product types over their fields. For example, given a -- 3-tuple, the corresponding HDL will end up with three instances of a -- register (or more if the three fields can be split up similarly).
  2. --
  3. Given a data type where a constructor indicates (parts) of the -- data will (not) be updated a given cycle, it will split the data in -- two parts. The first part will contain the "always interesting" parts -- (the constructor bits). The second holds the "potentially -- uninteresting" data (the rest). Both parts will be stored in separate -- registers. The register holding the "potentially uninteresting" part -- will only be enabled if the constructor bits indicate they're -- interesting.
  4. --
-- -- The most important example of this is Maybe. Consider Maybe -- (Signed 16); when viewed as bits, a Nothing would look -- like: -- --
--   >>> pack @(Maybe (Signed 16)) Nothing
--   0b0_...._...._...._....
--   
-- -- and Just -- --
--   >>> pack @(Maybe (Signed 16)) (Just 3)
--   0b1_0000_0000_0000_0011
--   
-- -- In the first case, Nothing, we don't particularly care about updating -- the register holding the Signed 16 field, as they'll be -- unknown anyway. We can therefore deassert its enable line. -- -- Making Clash lay it out like this increases the chances of synthesis -- tools clock gating the registers, saving energy. -- -- This version of autoReg will split the given data type up -- recursively. For example, given a :: Maybe (Maybe Int, Maybe -- Int), a total of five registers will be rendered. Both the -- "interesting" and "uninteresting" enable lines of the inner Maybe -- types will be controlled by the outer one, in addition to the inner -- parts controlling their "uninteresting" parts as described in (2). -- -- The default implementation is just register. If you don't need -- or want the special features of AutoReg, you can use that by -- writing an empty instance. -- --
--   data MyDataType = ...
--   instance AutoReg MyDataType
--   
-- -- If you have a product type you can use deriveAutoReg to derive -- an instance. class NFDataX a => AutoReg a -- | For documentation see class AutoReg. -- -- This is the version with explicit clock/reset/enable inputs, -- Clash.Prelude exports an implicit version of this: -- autoReg autoReg :: (AutoReg a, HasCallStack, KnownDomain dom) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a -- | Automatically derives an AutoReg instance for a product type -- -- Usage: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b } deriving (Generic, NFDataX)
--   data Tup3 a b c = MkTup3 { getAB :: Pair a b, getC :: c } deriving (Generic, NFDataX)
--   deriveAutoReg ''Pair
--   deriveAutoReg ''Tup3
--   
-- -- NB: Because of the way template haskell works the order here -- matters, if you try to deriveAutoReg ''Tup3 before -- Pair it will complain about missing an instance AutoReg -- (Pair a b). deriveAutoReg :: Name -> DecsQ deriveAutoRegTuples :: [Int] -> DecsQ instance Clash.Class.AutoReg.Internal.AutoReg () instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Bool instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Double instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Float instance Clash.Class.AutoReg.Internal.AutoReg Foreign.C.Types.CUShort instance Clash.Class.AutoReg.Internal.AutoReg Numeric.Half.Internal.Half instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Char instance Clash.Class.AutoReg.Internal.AutoReg GHC.Integer.Type.Integer instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Int instance Clash.Class.AutoReg.Internal.AutoReg GHC.Int.Int8 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Int.Int16 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Int.Int32 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Int.Int64 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Types.Word instance Clash.Class.AutoReg.Internal.AutoReg GHC.Word.Word8 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Word.Word16 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Word.Word32 instance Clash.Class.AutoReg.Internal.AutoReg GHC.Word.Word64 instance Clash.Class.AutoReg.Internal.AutoReg Clash.Sized.Internal.BitVector.Bit instance GHC.TypeNats.KnownNat n => Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Internal.BitVector.BitVector n) instance Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Internal.Signed.Signed n) instance Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Internal.Unsigned.Unsigned n) instance Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Internal.Index.Index n) instance Clash.XException.NFDataX (rep (int GHC.TypeNats.+ frac)) => Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Fixed.Fixed rep int frac) instance Clash.Class.AutoReg.Internal.AutoReg a => Clash.Class.AutoReg.Internal.AutoReg (GHC.Maybe.Maybe a) instance (GHC.TypeNats.KnownNat n, Clash.Class.AutoReg.Internal.AutoReg a) => Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.Vector.Vec n a) instance (GHC.TypeNats.KnownNat d, Clash.Class.AutoReg.Internal.AutoReg a) => Clash.Class.AutoReg.Internal.AutoReg (Clash.Sized.RTree.RTree d a) module Clash.Class.AutoReg -- | autoReg is a "smart" version of register. It does two -- things: -- --
    --
  1. It splits product types over their fields. For example, given a -- 3-tuple, the corresponding HDL will end up with three instances of a -- register (or more if the three fields can be split up similarly).
  2. --
  3. Given a data type where a constructor indicates (parts) of the -- data will (not) be updated a given cycle, it will split the data in -- two parts. The first part will contain the "always interesting" parts -- (the constructor bits). The second holds the "potentially -- uninteresting" data (the rest). Both parts will be stored in separate -- registers. The register holding the "potentially uninteresting" part -- will only be enabled if the constructor bits indicate they're -- interesting.
  4. --
-- -- The most important example of this is Maybe. Consider Maybe -- (Signed 16); when viewed as bits, a Nothing would look -- like: -- --
--   >>> pack @(Maybe (Signed 16)) Nothing
--   0b0_...._...._...._....
--   
-- -- and Just -- --
--   >>> pack @(Maybe (Signed 16)) (Just 3)
--   0b1_0000_0000_0000_0011
--   
-- -- In the first case, Nothing, we don't particularly care about updating -- the register holding the Signed 16 field, as they'll be -- unknown anyway. We can therefore deassert its enable line. -- -- Making Clash lay it out like this increases the chances of synthesis -- tools clock gating the registers, saving energy. -- -- This version of autoReg will split the given data type up -- recursively. For example, given a :: Maybe (Maybe Int, Maybe -- Int), a total of five registers will be rendered. Both the -- "interesting" and "uninteresting" enable lines of the inner Maybe -- types will be controlled by the outer one, in addition to the inner -- parts controlling their "uninteresting" parts as described in (2). -- -- The default implementation is just register. If you don't need -- or want the special features of AutoReg, you can use that by -- writing an empty instance. -- --
--   data MyDataType = ...
--   instance AutoReg MyDataType
--   
-- -- If you have a product type you can use deriveAutoReg to derive -- an instance. class NFDataX a => AutoReg a -- | For documentation see class AutoReg. -- -- This is the version with explicit clock/reset/enable inputs, -- Clash.Prelude exports an implicit version of this: -- autoReg autoReg :: (AutoReg a, HasCallStack, KnownDomain dom) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a -- | Automatically derives an AutoReg instance for a product type -- -- Usage: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b } deriving (Generic, NFDataX)
--   data Tup3 a b c = MkTup3 { getAB :: Pair a b, getC :: c } deriving (Generic, NFDataX)
--   deriveAutoReg ''Pair
--   deriveAutoReg ''Tup3
--   
-- -- NB: Because of the way template haskell works the order here -- matters, if you try to deriveAutoReg ''Tup3 before -- Pair it will complain about missing an instance AutoReg -- (Pair a b). deriveAutoReg :: Name -> DecsQ module Clash.Class.Exp -- | Type class implementing exponentiation with explicitly resizing -- results. class Exp a type family ExpResult a (n :: Nat) -- | Exponentiation with known exponent. (^) :: Exp a => a -> SNat n -> ExpResult a n instance GHC.TypeNats.KnownNat m => Clash.Class.Exp.Exp (Clash.Sized.Internal.Index.Index m) instance GHC.TypeNats.KnownNat m => Clash.Class.Exp.Exp (Clash.Sized.Internal.Signed.Signed m) instance GHC.TypeNats.KnownNat m => Clash.Class.Exp.Exp (Clash.Sized.Internal.Unsigned.Unsigned m) module Clash.Num.Zeroing -- | A zeroing number type is one where all operations return zero if they -- go out of bounds for the underlying type. -- -- Numbers can be converted to zero by default using toZeroing. data Zeroing a fromZeroing :: Zeroing a -> a toZeroing :: SaturatingNum a => a -> Zeroing a instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Num.Zeroing.Zeroing a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Num.Zeroing.Zeroing a) instance Clash.Class.Parity.Parity a => Clash.Class.Parity.Parity (Clash.Num.Zeroing.Zeroing a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Num.Zeroing.Zeroing a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Num.Zeroing.Zeroing a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Num.Zeroing.Zeroing a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Num.Zeroing.Zeroing a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Clash.Num.Zeroing.Zeroing a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Num.Zeroing.Zeroing a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Clash.Num.Zeroing.Zeroing a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Clash.Num.Zeroing.Zeroing a) instance Data.Bits.Bits a => Data.Bits.Bits (Clash.Num.Zeroing.Zeroing a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Num.Zeroing.Zeroing a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Num.Zeroing.Zeroing a) instance Clash.Class.Resize.Resize f => Clash.Class.Resize.Resize (Data.Functor.Compose.Compose Clash.Num.Zeroing.Zeroing f) instance (GHC.Enum.Bounded a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Num.Num (Clash.Num.Zeroing.Zeroing a) instance (GHC.Enum.Enum a, Clash.Class.Num.SaturatingNum a) => GHC.Enum.Enum (Clash.Num.Zeroing.Zeroing a) instance (GHC.Real.Real a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Real (Clash.Num.Zeroing.Zeroing a) instance (GHC.Real.Integral a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Integral (Clash.Num.Zeroing.Zeroing a) instance (GHC.Real.Fractional a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Fractional (Clash.Num.Zeroing.Zeroing a) instance (GHC.Real.RealFrac a, Clash.Class.Num.SaturatingNum a) => GHC.Real.RealFrac (Clash.Num.Zeroing.Zeroing a) module Clash.Num.Wrapping -- | A wrapping number type is one where all operations wrap between -- minBound and maxBound (and vice-versa) if the result goes out of -- bounds for the underlying type. -- -- Numbers can be converted to wrap by default using toWrapping. newtype Wrapping a Wrapping :: a -> Wrapping a [fromWrapping] :: Wrapping a -> a toWrapping :: SaturatingNum a => a -> Wrapping a instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Num.Wrapping.Wrapping a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Num.Wrapping.Wrapping a) instance Clash.Class.Parity.Parity a => Clash.Class.Parity.Parity (Clash.Num.Wrapping.Wrapping a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Num.Wrapping.Wrapping a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Num.Wrapping.Wrapping a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Num.Wrapping.Wrapping a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Num.Wrapping.Wrapping a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Clash.Num.Wrapping.Wrapping a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Num.Wrapping.Wrapping a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Clash.Num.Wrapping.Wrapping a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Clash.Num.Wrapping.Wrapping a) instance Data.Bits.Bits a => Data.Bits.Bits (Clash.Num.Wrapping.Wrapping a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Num.Wrapping.Wrapping a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Num.Wrapping.Wrapping a) instance Clash.Class.Resize.Resize f => Clash.Class.Resize.Resize (Data.Functor.Compose.Compose Clash.Num.Wrapping.Wrapping f) instance Clash.Class.Num.SaturatingNum a => GHC.Num.Num (Clash.Num.Wrapping.Wrapping a) instance (GHC.Enum.Enum a, Clash.Class.Num.SaturatingNum a) => GHC.Enum.Enum (Clash.Num.Wrapping.Wrapping a) instance (GHC.Real.Real a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Real (Clash.Num.Wrapping.Wrapping a) instance (GHC.Real.Integral a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Integral (Clash.Num.Wrapping.Wrapping a) instance (GHC.Real.Fractional a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Fractional (Clash.Num.Wrapping.Wrapping a) instance (GHC.Real.RealFrac a, Clash.Class.Num.SaturatingNum a) => GHC.Real.RealFrac (Clash.Num.Wrapping.Wrapping a) module Clash.Num.Saturating -- | A saturating number type is one where all operations saturate at the -- bounds of the underlying type, i.e. operations which overflow return -- maxBound and operations that underflow return minBound. -- -- Numbers can be converted to saturate by default using -- toSaturating. data Saturating a fromSaturating :: Saturating a -> a toSaturating :: SaturatingNum a => a -> Saturating a instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Num.Saturating.Saturating a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Num.Saturating.Saturating a) instance Clash.Class.Parity.Parity a => Clash.Class.Parity.Parity (Clash.Num.Saturating.Saturating a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Num.Saturating.Saturating a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Num.Saturating.Saturating a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Num.Saturating.Saturating a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Num.Saturating.Saturating a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Clash.Num.Saturating.Saturating a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Num.Saturating.Saturating a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Clash.Num.Saturating.Saturating a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Clash.Num.Saturating.Saturating a) instance Data.Bits.Bits a => Data.Bits.Bits (Clash.Num.Saturating.Saturating a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Num.Saturating.Saturating a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Num.Saturating.Saturating a) instance Clash.Class.Resize.Resize f => Clash.Class.Resize.Resize (Data.Functor.Compose.Compose Clash.Num.Saturating.Saturating f) instance (GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Num.Num (Clash.Num.Saturating.Saturating a) instance (GHC.Enum.Enum a, Clash.Class.Num.SaturatingNum a) => GHC.Enum.Enum (Clash.Num.Saturating.Saturating a) instance (GHC.Real.Real a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Real (Clash.Num.Saturating.Saturating a) instance (GHC.Real.Integral a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Integral (Clash.Num.Saturating.Saturating a) instance (GHC.Real.Fractional a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Fractional (Clash.Num.Saturating.Saturating a) instance (GHC.Classes.Ord a, GHC.Real.RealFrac a, Clash.Class.Num.SaturatingNum a) => GHC.Real.RealFrac (Clash.Num.Saturating.Saturating a) module Clash.Num.Overflowing -- | An overflowing number behaves similarly to a Wrapping number, -- but also includes an overflow status flag which can be used to more -- easily check if an overflow has occurred. -- -- Numbers can be converted to be Overflowing using -- toOverflowing. data Overflowing a -- | Retrieve the value fromOverflowing :: Overflowing a -> a -- | True when a computation has overflowed hasOverflowed :: Overflowing a -> Bool toOverflowing :: a -> Overflowing a -- | Reset the overflow status flag to False. clearOverflow :: Overflowing a -> Overflowing a instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Num.Overflowing.Overflowing a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Num.Overflowing.Overflowing a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Num.Overflowing.Overflowing a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Num.Overflowing.Overflowing a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Num.Overflowing.Overflowing a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Num.Overflowing.Overflowing a) instance GHC.Generics.Generic (Clash.Num.Overflowing.Overflowing a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Num.Overflowing.Overflowing a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Num.Overflowing.Overflowing a) instance (Clash.Class.BitPack.Internal.BitPack a, GHC.TypeNats.KnownNat (Clash.Class.BitPack.Internal.BitSize a GHC.TypeNats.+ 1)) => Clash.Class.BitPack.Internal.BitPack (Clash.Num.Overflowing.Overflowing a) instance Clash.Class.Parity.Parity a => Clash.Class.Parity.Parity (Clash.Num.Overflowing.Overflowing a) instance (GHC.Enum.Bounded a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Num.Num (Clash.Num.Overflowing.Overflowing a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Clash.Num.Overflowing.Overflowing a) instance (GHC.Enum.Enum a, GHC.Classes.Eq a, Clash.Class.Num.SaturatingNum a) => GHC.Enum.Enum (Clash.Num.Overflowing.Overflowing a) instance (GHC.Real.Real a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Real (Clash.Num.Overflowing.Overflowing a) instance (GHC.Real.Integral a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Integral (Clash.Num.Overflowing.Overflowing a) instance (GHC.Real.Fractional a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Fractional (Clash.Num.Overflowing.Overflowing a) instance (GHC.Real.RealFrac a, Clash.Class.Num.SaturatingNum a) => GHC.Real.RealFrac (Clash.Num.Overflowing.Overflowing a) module Clash.Num.Erroring -- | An erroring number type is one where all operations return a -- XExecption if they would go out of bounds for the underlying -- type. -- -- Numbers can be converted to error by default using toErroring. data Erroring a fromErroring :: Erroring a -> a toErroring :: SaturatingNum a => a -> Erroring a instance Clash.XException.ShowX a => Clash.XException.ShowX (Clash.Num.Erroring.Erroring a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Num.Erroring.Erroring a) instance Clash.Class.Parity.Parity a => Clash.Class.Parity.Parity (Clash.Num.Erroring.Erroring a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Clash.Num.Erroring.Erroring a) instance Clash.XException.NFDataX a => Clash.XException.NFDataX (Clash.Num.Erroring.Erroring a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Num.Erroring.Erroring a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Num.Erroring.Erroring a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Clash.Num.Erroring.Erroring a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Num.Erroring.Erroring a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Clash.Num.Erroring.Erroring a) instance Clash.Class.BitPack.Internal.BitPack a => Clash.Class.BitPack.Internal.BitPack (Clash.Num.Erroring.Erroring a) instance Data.Bits.Bits a => Data.Bits.Bits (Clash.Num.Erroring.Erroring a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Num.Erroring.Erroring a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Clash.Num.Erroring.Erroring a) instance Clash.Class.Resize.Resize f => Clash.Class.Resize.Resize (Data.Functor.Compose.Compose Clash.Num.Erroring.Erroring f) instance (GHC.Enum.Bounded a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Num.Num (Clash.Num.Erroring.Erroring a) instance (GHC.Enum.Enum a, Clash.Class.Num.SaturatingNum a) => GHC.Enum.Enum (Clash.Num.Erroring.Erroring a) instance (GHC.Real.Real a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Real (Clash.Num.Erroring.Erroring a) instance (GHC.Real.Integral a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Integral (Clash.Num.Erroring.Erroring a) instance (GHC.Real.Fractional a, GHC.Classes.Ord a, Clash.Class.Num.SaturatingNum a) => GHC.Real.Fractional (Clash.Num.Erroring.Erroring a) instance (GHC.Real.RealFrac a, Clash.Class.Num.SaturatingNum a) => GHC.Real.RealFrac (Clash.Num.Erroring.Erroring a) -- | TopEntity annotations allow us to control hierarchy and naming -- aspects of the Clash compiler. We have the Synthesize and -- TestBench annotation. -- --

Synthesize annotation

-- -- The Synthesize annotation allows us to: -- -- -- -- Functions with a Synthesize annotation must adhere to the -- following restrictions: -- -- -- -- Also take the following into account when using Synthesize -- annotations. -- -- -- -- Finally, the root module, the module which you pass as an argument to -- the Clash compiler must either have: -- -- -- -- You apply Synthesize annotations to functions using an -- ANN pragma: -- --
--   {-# ANN f (Synthesize {t_name = ..., ...  }) #-}
--   f x = ...
--   
-- -- For example, given the following specification: -- --
--   module Blinker where
--   
--   import Clash.Prelude
--   import Clash.Intel.ClockGen
--   
--   -- Define a synthesis domain with a clock with a period of 20000 /ps/. Signal
--   -- coming from the reset button is low when pressed, and high when not pressed.
--   createDomain
--     vSystem{vName="DomInput", vPeriod=20000, vResetPolarity=ActiveLow}
--   -- Define a synthesis domain with a clock with a period of 50000 /ps/.
--   createDomain vSystem{vName="Dom50", vPeriod=50000}
--   
--   topEntity
--     :: Clock DomInput
--     -> Reset DomInput
--     -> Enable Dom50
--     -> Signal Dom50 Bit
--     -> Signal Dom50 (BitVector 8)
--   topEntity clk20 rstBtn enaBtn modeBtn =
--     exposeClockResetEnable
--       (mealy blinkerT initialStateBlinkerT . isRising 1)
--       clk50
--       rst50
--       enaBtn
--       modeBtn
--    where
--     -- Start with the first LED turned on, in rotate mode, with the counter on zero
--     initialStateBlinkerT = (1, False, 0)
--   
--     -- Instantiate a PLL: this stabilizes the incoming clock signal and releases
--     -- the reset output when the signal is stable. We're also using it to
--     -- transform an incoming clock signal running at 20 MHz to a clock signal
--     -- running at 50 MHz. Since the signature of topEntity already specifies the
--     -- Dom50 domain, we don't need any type signatures to specify the domain here.
--     (clk50, rst50) = altpllSync clk20 rstBtn
--   
--   blinkerT
--     :: (BitVector 8, Bool, Index 16650001)
--     -> Bool
--     -> ((BitVector 8, Bool, Index 16650001), BitVector 8)
--   blinkerT (leds,mode,cntr) key1R = ((leds',mode',cntr'),leds)
--     where
--       -- clock frequency = 50e6  (50 MHz)
--       -- led update rate = 333e-3 (every 333ms)
--       cnt_max = 16650000 -- 50e6 * 333e-3
--   
--       cntr' | cntr == cnt_max = 0
--             | otherwise       = cntr + 1
--   
--       mode' | key1R     = not mode
--             | otherwise = mode
--   
--       leds' | cntr == 0 = if mode then complement leds
--                                   else rotateL leds 1
--             | otherwise = leds
--   
-- -- The Clash compiler would normally generate the following -- topEntity.vhdl file: -- --
--   -- Automatically generated VHDL-93
--   library IEEE;
--   use IEEE.STD_LOGIC_1164.ALL;
--   use IEEE.NUMERIC_STD.ALL;
--   use IEEE.MATH_REAL.ALL;
--   use std.textio.all;
--   use work.all;
--   use work.Blinker_topEntity_types.all;
--   
--   entity topEntity is
--     port(-- clock
--          clk20   : in Blinker_topEntity_types.clk_DomInput;
--          -- reset
--          rstBtn  : in Blinker_topEntity_types.rst_DomInput;
--          -- enable
--          enaBtn  : in Blinker_topEntity_types.en_Dom50;
--          modeBtn : in std_logic;
--          result  : out std_logic_vector(7 downto 0));
--   end;
--   
--   architecture structural of topEntity is
--     ...
--   end;
--   
-- -- However, if we add the following Synthesize annotation in the -- file: -- --
--   {-# ANN topEntity
--     (Synthesize
--       { t_name   = "blinker"
--       , t_inputs = [ PortName "CLOCK_50"
--                    , PortName "KEY0"
--                    , PortName "KEY1"
--                    , PortName "KEY2" ]
--       , t_output = PortName "LED"
--       }) #-}
--   
-- -- The Clash compiler will generate the following blinker.vhdl -- file instead: -- --
--   -- Automatically generated VHDL-93
--   library IEEE;
--   use IEEE.STD_LOGIC_1164.ALL;
--   use IEEE.NUMERIC_STD.ALL;
--   use IEEE.MATH_REAL.ALL;
--   use std.textio.all;
--   use work.all;
--   use work.blinker_types.all;
--   
--   entity blinker is
--     port(-- clock
--          CLOCK_50 : in blinker_types.clk_DomInput;
--          -- reset
--          KEY0     : in blinker_types.rst_DomInput;
--          -- enable
--          KEY1     : in blinker_types.en_Dom50;
--          KEY2     : in std_logic;
--          LED      : out std_logic_vector(7 downto 0));
--   end;
--   
--   architecture structural of blinker is
--     ...
--   end;
--   
-- -- Where we now have: -- -- -- -- See the documentation of Synthesize for the meaning of all its -- fields. -- --

TestBench annotation

-- -- Tell what binder is the test bench for a Synthesize-annotated -- binder. -- --
--   entityBeingTested :: ...
--   entityBeingTested = ...
--   {-# NOINLINE entityBeingTested #-}
--   {-# ANN entityBeingTested (defSyn "entityBeingTested") #-}
--   
--   
--   myTestBench :: Signal System Bool
--   myTestBench = ... entityBeingTested ...
--   {-# NOINLINE myTestBench #-}
--   {-# ANN myTestBench (TestBench 'entityBeingTested) #-}
--   
-- -- The TestBench annotation actually already implies a -- Synthesize annotation on the device under test, so the -- defSyn in the example could have been omitted. We recommend you -- supply defSyn explicitly nonetheless. In any case, it will -- still need the NOINLINE annotation. module Clash.Annotations.TopEntity -- | TopEntity annotation data TopEntity -- | Instruct the Clash compiler to use this top-level function as a -- separately synthesizable component. Synthesize :: String -> [PortName] -> PortName -> TopEntity -- | The name the top-level component should have, put in a correspondingly -- named file. [t_name] :: TopEntity -> String -- | List of names that are assigned in-order to the inputs of the -- component. [t_inputs] :: TopEntity -> [PortName] -- | Name assigned in-order to the outputs of the component. As a Haskell -- function can only truly return a single value -- with multiple values -- "wrapped" by a tuple -- this field is not a list, but a single -- PortName. Use PortProduct to give -- names to the individual components of the output tuple. [t_output] :: TopEntity -> PortName -- | Tell what binder is the TestBench for a -- Synthesize-annotated binder. -- --
--   {-# NOINLINE myTestBench #-}
--   {-# ANN myTestBench (TestBench 'entityBeingTested) #-}
--   
TestBench :: Name -> TopEntity -- | Give port names for arguments/results. -- -- Give a data type and function: -- --
--   data T = MkT Int Bool
--   
--   {-# ANN f (defSyn "f") #-}
--   f :: Int -> T -> (T,Bool)
--   f a b = ...
--   
-- -- Clash would normally generate the following VHDL entity: -- --
--   entity f is
--     port(a      : in signed(63 downto 0);
--          b_0    : in signed(63 downto 0);
--          b_1    : in boolean;
--          result : out std_logic_vector(65 downto 0));
--   end;
--   
-- -- However, we can change this by using PortNames. So by: -- --
--   {-# ANN f
--      (Synthesize
--         { t_name   = "f"
--         , t_inputs = [ PortName "a"
--                      , PortName "b" ]
--         , t_output = PortName "res" }) #-}
--   f :: Int -> T -> (T,Bool)
--   f a b = ...
--   
-- -- we get: -- --
--   entity f is
--     port(a   : in signed(63 downto 0);
--          b   : in std_logic_vector(64 downto 0);
--          res : out std_logic_vector(65 downto 0));
--   end;
--   
-- -- If we want to name fields for tuples/records we have to use -- PortProduct -- --
--   {-# ANN f
--      (Synthesize
--         { t_name   = "f"
--         , t_inputs = [ PortName "a"
--                      , PortProduct "" [ PortName "b", PortName "c" ] ]
--         , t_output = PortProduct "res" [PortName "q"] }) #-}
--   f :: Int -> T -> (T,Bool)
--   f a b = ...
--   
-- -- So that we get: -- --
--   entity f is
--     port(a     : in signed(63 downto 0);
--          b     : in signed(63 downto 0);
--          c     : in boolean;
--          res_q : out std_logic_vector(64 downto 0);
--          res_1 : out boolean);
--   end;
--   
-- -- Notice how we didn't name the second field of the result, and the -- second output port got PortProduct name, "res", as a prefix for -- its name. data PortName -- | You want a port, with the given name, for the entire argument/type -- -- You can use an empty String ,"" , in case you want an -- auto-generated name. PortName :: String -> PortName -- | You want to assign ports to fields of a product argument/type -- -- The first argument of PortProduct is the name of: -- --
    --
  1. The signal/wire to which the individual ports are aggregated.
  2. --
  3. The prefix for any unnamed ports below the PortProduct
  4. --
-- -- You can use an empty String ,"" , in case you want an -- auto-generated name. PortProduct :: String -> [PortName] -> PortName -- | Default Synthesize annotation which has no specified names for -- the input and output ports. -- --
--   >>> defSyn "foo"
--   Synthesize {t_name = "foo", t_inputs = [], t_output = PortName ""}
--   
defSyn :: String -> TopEntity instance Language.Haskell.TH.Syntax.Lift Clash.Annotations.TopEntity.PortName instance GHC.Generics.Generic Clash.Annotations.TopEntity.PortName instance GHC.Show.Show Clash.Annotations.TopEntity.PortName instance Data.Data.Data Clash.Annotations.TopEntity.PortName instance GHC.Classes.Eq Clash.Annotations.TopEntity.PortName instance GHC.Generics.Generic Clash.Annotations.TopEntity.TopEntity instance GHC.Show.Show Clash.Annotations.TopEntity.TopEntity instance Data.Data.Data Clash.Annotations.TopEntity.TopEntity instance GHC.Classes.Eq Clash.Annotations.TopEntity.TopEntity instance Language.Haskell.TH.Syntax.Lift Clash.Annotations.TopEntity.TopEntity -- | This is the Safe API only of -- Clash.Explicit.Prelude -- -- This module defines the explicitly clocked counterparts of the -- functions defined in Clash.Prelude. module Clash.Explicit.Prelude.Safe -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   import qualified Data.List as L
--   
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = mealy clk rst en macT 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy clk rst en macT 0 (bundle (a,x))
--       s2 = mealy clk rst en macT 0 (bundle (b,y))
--   
mealy :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool,Int) -> (Int,(Int,Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy clk rst en f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy clk rst en f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB clk rst en f 0 (a,b)
--       (i2,b2) = mealyB clk rst en f 3 (c,i1)
--   
mealyB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = moore clk rst en macT id 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore clk rst en macT id 0 (bundle (a,x))
--       s2 = moore clk rst en macT id 0 (bundle (b,y))
--   
moore :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore clk rst en t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore clk rst en t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB clk rst en t o 0 (a,b)
--       (i2,b2) = mooreB clk rst en t o 3 (c,i1)
--   
mooreB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a register function for product-type like signals (e.g. -- (Signal a, Signal b)) -- --
--   rP :: Clock dom -> Reset dom -> Enable dom
--      -> (Signal dom Int, Signal dom Int)
--      -> (Signal dom Int, Signal dom Int)
--   rP clk rst en = registerB clk rst en (8,8)
--   
-- --
--   >>> simulateB (rP systemClockGen systemResetGen enableGen) [(1,1),(1,1),(2,2),(3,3)] :: [(Int,Int)]
--   [(8,8),(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
registerB :: (KnownDomain dom, NFDataX a, Bundle a) => Clock dom -> Reset dom -> Enable dom -> a -> Unbundled dom a -> Unbundled dom a -- | Synchronizer based on two sequentially connected flip-flops. -- -- dualFlipFlopSynchronizer :: (NFDataX a, KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Reset dom2 -> Enable dom2 -> a -> Signal dom1 a -> Signal dom2 a -- | Synchronizer implemented as a FIFO around a synchronous RAM. Based on -- the design described in Clash.Tutorial#multiclock, which is -- itself based on the design described in -- http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf. -- However, this FIFO uses a synchronous dual-ported RAM which, unlike -- those designs using RAM with an asynchronous read port, is nearly -- guaranteed to actually synthesize into one of the dual-ported RAMs -- found on most FPGAs. -- -- NB: This synchronizer can be used for -- word-synchronization. NB: This synchronizer will only -- work safely when you set up the proper bus skew and maximum delay -- constraints inside your synthesis tool for the clock domain crossings -- of the gray pointers. asyncFIFOSynchronizer :: (KnownDomain wdom, KnownDomain rdom, 2 <= addrSize, NFDataX a) => SNat addrSize -> Clock wdom -> Clock rdom -> Reset wdom -> Reset rdom -> Enable wdom -> Enable rdom -> Signal rdom Bool -> Signal wdom (Maybe a) -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool) -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRom :: (KnownNat n, Enum addr, NFDataX a) => Vec n a -> addr -> a -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomPow2 :: (KnownNat n, NFDataX a) => Vec (2 ^ n) a -> Unsigned n -> a -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: (KnownDomain dom, KnownNat n, NFDataX a, Enum addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: (KnownDomain dom, KnownNat n, NFDataX a) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRomBlob :: Enum addr => MemBlob n m -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomBlobPow2 :: KnownNat n => MemBlob (2 ^ n) m -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (KnownDomain dom, Enum addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> SNat n -> Signal rdom addr -> Signal wdom (Maybe (addr, a)) -> Signal rdom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: forall wdom rdom n a. (KnownNat n, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> Signal rdom (Unsigned n) -> Signal wdom (Maybe (Unsigned n, a)) -> Signal rdom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: Clock  dom
--     -> Enable  dom
--     -> Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 clk en = blockRam clk en (replicate d40 1)
--   
blockRam :: (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: Clock dom
--     -> Enable dom
--     -> Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 clk en = blockRamPow2 clk en (replicate d32 1)
--   
blockRamPow2 :: (KnownDomain dom, HasCallStack, NFDataX a, KnownNat n) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (KnownDomain dom, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | Create a read-after-write block RAM from a read-before-write one readNew :: (KnownDomain dom, NFDataX a, Eq addr) => Clock dom -> Reset dom -> Enable dom -> (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs domA domB a. (HasCallStack, KnownNat nAddrs, KnownDomain domA, KnownDomain domB, NFDataX a) => Clock domA -> Clock domB -> Signal domA (RamOp nAddrs a) -> Signal domB (RamOp nAddrs a) -> (Signal domA a, Signal domB a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a -- | Give a pulse when the Signal goes from minBound to -- maxBound isRising :: (KnownDomain dom, NFDataX a, Bounded a, Eq a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom Bool -- | Give a pulse when the Signal goes from maxBound to -- minBound isFalling :: (KnownDomain dom, NFDataX a, Bounded a, Eq a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom Bool -- | Give a pulse every n clock cycles. This is a useful helper -- function when combined with functions like regEn or -- mux, in order to delay a register by a known amount. riseEvery :: forall dom n. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> SNat n -> Signal dom Bool -- | Oscillate a Bool for a given number of cycles, given -- the starting state. oscillate :: forall dom n. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Bool -> SNat n -> Signal dom Bool -- | Fixed size vectors. -- -- data Vec :: Nat -> Type -> Type [Nil] :: Vec 0 a [Cons] :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the head of a vector. -- --
--   >>> 3:>4:>5:>Nil
--   3 :> 4 :> 5 :> Nil
--   
--   >>> let x = 3:>4:>5:>Nil
--   
--   >>> :t x
--   x :: Num a => Vec 3 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (x :> y :> _) = x + y
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   7
--   
-- -- Also in conjunctions with (:<): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:>) :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the tail of a vector. -- --
--   >>> (3:>4:>5:>Nil) :< 1
--   3 :> 4 :> 5 :> 1 :> Nil
--   
--   >>> let x = (3:>4:>5:>Nil) :< 1
--   
--   >>> :t x
--   x :: Num a => Vec 4 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (_ :< y :< x) = y + x
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   13
--   
-- -- Also in conjunctions with (:>): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:<) :: Vec n a -> a -> Vec (n + 1) a infixr 5 :> infixl 5 :< infixr 5 `Cons` -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a vector, reduces -- the vector using the binary operator, from left to right: -- --
--   foldl f z (x1 :> x2 :> ... :> xn :> Nil) == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   foldl f z Nil                            == z
--   
-- --
--   >>> foldl (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldl :: forall b a n. (b -> a -> b) -> b -> Vec n a -> b -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a vector, reduces -- the vector using the binary operator, from right to left: -- --
--   foldr f z (x1 :> ... :> xn1 :> xn :> Nil) == x1 `f` (... (xn1 `f` (xn `f` z))...)
--   foldr r z Nil                             == z
--   
-- --
--   >>> foldr (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   1.875
--   
-- -- "foldr f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldr :: (a -> b -> b) -> b -> Vec n a -> b -- | "map f xs" is the vector obtained by applying f -- to each element of xs, i.e., -- --
--   map f (x1 :> x2 :>  ... :> xn :> Nil) == (f x1 :> f x2 :> ... :> f xn :> Nil)
--   
-- -- and corresponds to the following circuit layout: -- map :: (a -> b) -> Vec n a -> Vec n b -- | Convert a BitVector to a Vec of Bits. -- --
--   >>> let x = 6 :: BitVector 8
--   
--   >>> x
--   0b0000_0110
--   
--   >>> bv2v x
--   0 :> 0 :> 0 :> 0 :> 0 :> 1 :> 1 :> 0 :> Nil
--   
bv2v :: KnownNat n => BitVector n -> Vec n Bit -- | To be used as the motive p for dfold, when the f -- in "dfold p f" is a variation on (:>), e.g.: -- --
--   map' :: forall n a b . KnownNat n => (a -> b) -> Vec n a -> Vec n b
--   map' f = dfold (Proxy @(VCons b)) (_ x xs -> f x :> xs)
--   
data VCons (a :: Type) (f :: TyFun Nat Type) :: Type traverse# :: forall a f b n. Applicative f => (a -> f b) -> Vec n a -> f (Vec n b) -- | Create a vector of one element -- --
--   >>> singleton 5
--   5 :> Nil
--   
singleton :: a -> Vec 1 a -- | Extract the first element of a vector -- --
--   >>> head (1:>2:>3:>Nil)
--   1
--   
-- --
--   >>> head Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘head’, namely ‘Nil’
--         In the expression: head Nil
--         In an equation for ‘it’: it = head Nil
--   
head :: Vec (n + 1) a -> a -- | Extract the elements after the head of a vector -- --
--   >>> tail (1:>2:>3:>Nil)
--   2 :> 3 :> Nil
--   
-- --
--   >>> tail Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘tail’, namely ‘Nil’
--         In the expression: tail Nil
--         In an equation for ‘it’: it = tail Nil
--   
tail :: Vec (n + 1) a -> Vec n a -- | Extract the last element of a vector -- --
--   >>> last (1:>2:>3:>Nil)
--   3
--   
-- --
--   >>> last Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘last’, namely ‘Nil’
--         In the expression: last Nil
--         In an equation for ‘it’: it = last Nil
--   
last :: Vec (n + 1) a -> a -- | Extract all the elements of a vector except the last element -- --
--   >>> init (1:>2:>3:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> init Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘init’, namely ‘Nil’
--         In the expression: init Nil
--         In an equation for ‘it’: it = init Nil
--   
init :: Vec (n + 1) a -> Vec n a -- | Shift in elements to the head of a vector, bumping out elements at the -- tail. The result is a tuple containing: -- -- -- --
--   >>> shiftInAt0 (1 :> 2 :> 3 :> 4 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> 0 :> 1 :> 2 :> Nil,3 :> 4 :> Nil)
--   
--   >>> shiftInAt0 (1 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> Nil,0 :> 1 :> Nil)
--   
shiftInAt0 :: KnownNat n => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift in element to the tail of a vector, bumping out elements at the -- head. The result is a tuple containing: -- -- -- --
--   >>> shiftInAtN (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> Nil)
--   (3 :> 4 :> 5 :> 6 :> Nil,1 :> 2 :> Nil)
--   
--   >>> shiftInAtN (1 :> Nil) (2 :> 3 :> Nil)
--   (3 :> Nil,1 :> 2 :> Nil)
--   
shiftInAtN :: KnownNat m => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Add an element to the head of a vector, and extract all but the last -- element. -- --
--   >>> 1 +>> (3:>4:>5:>Nil)
--   1 :> 3 :> 4 :> Nil
--   
--   >>> 1 +>> Nil
--   Nil
--   
(+>>) :: KnownNat n => a -> Vec n a -> Vec n a infixr 4 +>> -- | Add an element to the tail of a vector, and extract all but the first -- element. -- --
--   >>> (3:>4:>5:>Nil) <<+ 1
--   4 :> 5 :> 1 :> Nil
--   
--   >>> Nil <<+ 1
--   Nil
--   
(<<+) :: Vec n a -> a -> Vec n a infixl 4 <<+ -- | Shift m elements out from the head of a vector, filling up the -- tail with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFrom0 d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (3 :> 4 :> 5 :> 0 :> 0 :> Nil,1 :> 2 :> Nil)
--   
shiftOutFrom0 :: (Default a, KnownNat m) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Shift m elements out from the tail of a vector, filling up the -- head with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFromN d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (0 :> 0 :> 1 :> 2 :> 3 :> Nil,4 :> 5 :> Nil)
--   
shiftOutFromN :: (Default a, KnownNat n) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Append two vectors. -- --
--   >>> (1:>2:>3:>Nil) ++ (7:>8:>Nil)
--   1 :> 2 :> 3 :> 7 :> 8 :> Nil
--   
(++) :: Vec n a -> Vec m a -> Vec (n + m) a infixr 5 ++ -- | Split a vector into two vectors at the given point. -- --
--   >>> splitAt (SNat :: SNat 3) (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
--   >>> splitAt d3 (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
splitAt :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector into two vectors where the length of the two is -- determined by the context. -- --
--   >>> splitAtI (1:>2:>3:>7:>8:>Nil) :: (Vec 2 Int, Vec 3 Int)
--   (1 :> 2 :> Nil,3 :> 7 :> 8 :> Nil)
--   
splitAtI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) -- | Concatenate a vector of vectors. -- --
--   >>> concat ((1:>2:>3:>Nil) :> (4:>5:>6:>Nil) :> (7:>8:>9:>Nil) :> (10:>11:>12:>Nil) :> Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil
--   
concat :: Vec n (Vec m a) -> Vec (n * m) a -- | Map a function over all the elements of a vector and concatentate the -- resulting vectors. -- --
--   >>> concatMap (replicate d3) (1:>2:>3:>Nil)
--   1 :> 1 :> 1 :> 2 :> 2 :> 2 :> 3 :> 3 :> 3 :> Nil
--   
concatMap :: (a -> Vec m b) -> Vec n a -> Vec (n * m) b -- | Split a vector of (n * m) elements into a vector of "vectors of length -- m", where the length m is given. -- --
--   >>> unconcat d4 (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil) :> (5 :> 6 :> 7 :> 8 :> Nil) :> (9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) -- | Split a vector of (n * m) elements into a vector of "vectors of -- length m", where the length m is determined by the -- context. -- --
--   >>> unconcatI (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil) :: Vec 2 (Vec 6 Int)
--   (1 :> 2 :> 3 :> 4 :> 5 :> 6 :> Nil) :> (7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) -- | Merge two vectors, alternating their elements, i.e., -- --
--   >>> merge (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> 7 :> 8 :> Nil)
--   1 :> 5 :> 2 :> 6 :> 3 :> 7 :> 4 :> 8 :> Nil
--   
merge :: KnownNat n => Vec n a -> Vec n a -> Vec (2 * n) a -- | The elements in a vector in reverse order. -- --
--   >>> reverse (1:>2:>3:>4:>Nil)
--   4 :> 3 :> 2 :> 1 :> Nil
--   
reverse :: Vec n a -> Vec n a -- | Apply a function of every element of a vector and its index. -- --
--   >>> :t imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   imap (+) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Index 4)
--   
--   >>> imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   2 :> 3 :> *** Exception: X: Clash.Sized.Index: result 4 is out of bounds: [0..3]
--   ...
--   
--   >>> imap (\i a -> extend (bitCoerce i) + a) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Unsigned 8)
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- imap :: forall n a b. KnownNat n => (Index n -> a -> b) -> Vec n a -> Vec n b -- | Zip two vectors with a functions that also takes the elements' -- indices. -- --
--   >>> izipWith (\i a b -> i + a + b) (2 :> 2 :> Nil)  (3 :> 3:> Nil)
--   *** Exception: X: Clash.Sized.Index: result 3 is out of bounds: [0..1]
--   ...
--   
--   >>> izipWith (\i a b -> extend (bitCoerce i) + a + b) (2 :> 2 :> Nil) (3 :> 3 :> Nil) :: Vec 2 (Unsigned 8)
--   5 :> 6 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- -- -- NB: izipWith is strict in its second argument, -- and lazy in its third. This matters when izipWith is -- used in a recursive setting. See lazyV for more information. izipWith :: KnownNat n => (Index n -> a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | Right fold (function applied to each element and its index) -- --
--   >>> let findLeftmost x xs = ifoldr (\i a b -> if a == x then Just i else b) Nothing xs
--   
--   >>> findLeftmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> findLeftmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldr f z xs" corresponds to the following circuit -- layout: -- ifoldr :: KnownNat n => (Index n -> a -> b -> b) -> b -> Vec n a -> b -- | Left fold (function applied to each element and its index) -- --
--   >>> let findRightmost x xs = ifoldl (\a i b -> if b == x then Just i else a) Nothing xs
--   
--   >>> findRightmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 4
--   
--   >>> findRightmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldl f z xs" corresponds to the following circuit -- layout: -- ifoldl :: KnownNat n => (a -> Index n -> b -> a) -> a -> Vec n b -> a -- | Generate a vector of indices. -- --
--   >>> indices d4
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indices :: KnownNat n => SNat n -> Vec n (Index n) -- | Generate a vector of indices, where the length of the vector is -- determined by the context. -- --
--   >>> indicesI :: Vec 4 (Index 4)
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indicesI :: KnownNat n => Vec n (Index n) -- | "findIndex p xs" returns the index of the first -- element of xs satisfying the predicate p, or -- Nothing if there is no such element. -- --
--   >>> findIndex (> 3) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 3
--   
--   >>> findIndex (> 8) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
findIndex :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe (Index n) -- | "elemIndex a xs" returns the index of the first -- element which is equal (by ==) to the query element a, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> elemIndex 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
elemIndex :: (KnownNat n, Eq a) => a -> Vec n a -> Maybe (Index n) -- | zipWith generalizes zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "zipWith (+)" applied to two vectors produces -- the vector of corresponding sums. -- --
--   zipWith f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) == (f x1 y1 :> f x2 y2 :> ... :> f xn yn :> Nil)
--   
-- -- "zipWith f xs ys" corresponds to the following circuit -- layout: -- -- -- NB: zipWith is strict in its second argument, and -- lazy in its third. This matters when zipWith is used in -- a recursive setting. See lazyV for more information. zipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | zipWith3 generalizes zip3 by zipping with the function -- given as the first argument, instead of a tupling function. -- --
--   zipWith3 f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) (z1 :> z2 :> ... :> zn :> Nil) == (f x1 y1 z1 :> f x2 y2 z2 :> ... :> f xn yn zn :> Nil)
--   
-- -- "zipWith3 f xs ys zs" corresponds to the following -- circuit layout: -- -- -- NB: zipWith3 is strict in its second argument, -- and lazy in its third and fourth. This matters when -- zipWith3 is used in a recursive setting. See lazyV for -- more information. zipWith3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d zipWith4 :: (a -> b -> c -> d -> e) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n h -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldr1 f (x1 :> ... :> xn2 :> xn1 :> xn :> Nil) == x1 `f` (... (xn2 `f` (xn1 `f` xn))...)
--   foldr1 f (x1 :> Nil)                            == x1
--   foldr1 f Nil                                    == TYPE ERROR
--   
-- --
--   >>> foldr1 (/) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   1.875
--   
-- -- "foldr1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldl1 f (x1 :> x2 :> x3 :> ... :> xn :> Nil) == (...((x1 `f` x2) `f` x3) `f`...) `f` xn
--   foldl1 f (x1 :> Nil)                          == x1
--   foldl1 f Nil                                  == TYPE ERROR
--   
-- --
--   >>> foldl1 (/) (1 :> 5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | fold is a variant of foldr1 and foldl1, but -- instead of reducing from right to left, or left to right, it reduces a -- vector using a tree-like structure. The depth, or delay, of the -- structure produced by "fold f xs", is hence -- O(log_2(length xs)), and not O(length -- xs). -- -- NB: The binary operator "f" in "fold f -- xs" must be associative. -- --
--   fold f (x1 :> x2 :> ... :> xn1 :> xn :> Nil) == ((x1 `f` x2) `f` ...) `f` (... `f` (xn1 `f` xn))
--   fold f (x1 :> Nil)                           == x1
--   fold f Nil                                   == TYPE ERROR
--   
-- --
--   >>> fold (+) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   15
--   
-- -- "fold f xs" corresponds to the following circuit -- layout: -- fold :: forall n a. (a -> a -> a) -> Vec (n + 1) a -> a -- | scanl is similar to foldl, but returns a vector of -- successive reduced values from the left: -- --
--   scanl f z (x1 :> x2 :> ... :> Nil) == z :> (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> scanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   0 :> 5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "scanl f z xs" corresponds to the following circuit -- layout: -- -- -- scanl :: (b -> a -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanl with no seed value -- --
--   >>> scanl1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> -1 :> -4 :> -8 :> Nil
--   
scanl1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | scanr with no seed value -- --
--   >>> scanr1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   -2 :> 3 :> -1 :> 4 :> Nil
--   
scanr1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | postscanl is a variant of scanl where the first result -- is dropped: -- --
--   postscanl f z (x1 :> x2 :> ... :> Nil) == (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> postscanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "postscanl f z xs" corresponds to the following -- circuit layout: -- postscanl :: (b -> a -> b) -> b -> Vec n a -> Vec n b -- | scanr is similar to foldr, but returns a vector of -- successive reduced values from the right: -- --
--   scanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> z :> Nil
--   
-- --
--   >>> scanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> 0 :> Nil
--   
-- -- "scanr f z xs" corresponds to the following circuit -- layout: -- -- -- scanr :: (a -> b -> b) -> b -> Vec n a -> Vec (n + 1) b -- | postscanr is a variant of scanr that where the last -- result is dropped: -- --
--   postscanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> Nil
--   
-- --
--   >>> postscanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> Nil
--   
-- -- "postscanr f z xs" corresponds to the following -- circuit layout: -- postscanr :: (a -> b -> b) -> b -> Vec n a -> Vec n b -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumL (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,1 :> 2 :> 4 :> 7 :> Nil)
--   
-- -- "mapAccumL f acc xs" corresponds to the following -- circuit layout: -- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumR (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,10 :> 8 :> 5 :> 1 :> Nil)
--   
-- -- "mapAccumR f acc xs" corresponds to the following -- circuit layout: -- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | zip takes two vectors and returns a vector of corresponding -- pairs. -- --
--   >>> zip (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil)
--   (1,4) :> (2,3) :> (3,2) :> (4,1) :> Nil
--   
zip :: Vec n a -> Vec n b -> Vec n (a, b) -- | zip3 takes three vectors and returns a vector of corresponding -- triplets. -- --
--   >>> zip3 (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil) (5:>6:>7:>8:>Nil)
--   (1,4,5) :> (2,3,6) :> (3,2,7) :> (4,1,8) :> Nil
--   
zip3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) -- | zip4 takes four vectors and returns a list of quadruples, -- analogous to zip. zip4 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n (a, b, c, d) -- | zip5 takes five vectors and returns a list of five-tuples, -- analogous to zip. zip5 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n (a, b, c, d, e) -- | zip6 takes six vectors and returns a list of six-tuples, -- analogous to zip. zip6 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n (a, b, c, d, e, f) -- | zip7 takes seven vectors and returns a list of seven-tuples, -- analogous to zip. zip7 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n (a, b, c, d, e, f, g) -- | unzip transforms a vector of pairs into a vector of first -- components and a vector of second components. -- --
--   >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
--   
unzip :: Vec n (a, b) -> (Vec n a, Vec n b) -- | unzip3 transforms a vector of triplets into a vector of first -- components, a vector of second components, and a vector of third -- components. -- --
--   >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
--   
unzip3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) -- | unzip4 takes a vector of quadruples and returns four vectors, -- analogous to unzip. unzip4 :: Vec n (a, b, c, d) -> (Vec n a, Vec n b, Vec n c, Vec n d) -- | unzip5 takes a vector of five-tuples and returns five vectors, -- analogous to unzip. unzip5 :: Vec n (a, b, c, d, e) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e) -- | unzip6 takes a vector of six-tuples and returns six vectors, -- analogous to unzip. unzip6 :: Vec n (a, b, c, d, e, f) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f) -- | unzip7 takes a vector of seven-tuples and returns seven -- vectors, analogous to unzip. unzip7 :: Vec n (a, b, c, d, e, f, g) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f, Vec n g) -- | "xs !! n" returns the n'th element of -- xs. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> (1:>2:>3:>4:>5:>Nil) !! 4
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! (length (1:>2:>3:>4:>5:>Nil) - 1)
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 1
--   2
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 4
--   ...
--   
(!!) :: (KnownNat n, Enum i) => Vec n a -> i -> a -- | The length of a Vector as an Int value. -- --
--   >>> length (6 :> 7 :> 8 :> Nil)
--   3
--   
length :: KnownNat n => Vec n a -> Int -- | "replace n a xs" returns the vector xs where -- the n'th element is replaced by a. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> replace 3 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 7 :> 5 :> Nil
--   
--   >>> replace 0 7 (1:>2:>3:>4:>5:>Nil)
--   7 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
--   >>> replace 9 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 4
--   ...
--   
replace :: (KnownNat n, Enum i) => i -> a -> Vec n a -> Vec n a -- | "take n xs" returns the n-length prefix of -- xs. -- --
--   >>> take (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d3               (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d0               (1:>2:>Nil)
--   Nil
--   
-- --
--   >>> take d4               (1:>2:>Nil)
--   
--   <interactive>:...
--       • Couldn't match type ‘4 + n0’ with ‘2’
--         Expected type: Vec (4 + n0) a
--           Actual type: Vec (1 + 1) a
--         The type variable ‘n0’ is ambiguous
--       • In the second argument of ‘take’, namely ‘(1 :> 2 :> Nil)’
--         In the expression: take d4 (1 :> 2 :> Nil)
--         In an equation for ‘it’: it = take d4 (1 :> 2 :> Nil)
--   
take :: SNat m -> Vec (m + n) a -> Vec m a -- | "takeI xs" returns the prefix of xs as demanded -- by the context. -- --
--   >>> takeI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   1 :> 2 :> Nil
--   
takeI :: KnownNat m => Vec (m + n) a -> Vec m a -- | "drop n xs" returns the suffix of xs after the -- first n elements. -- --
--   >>> drop (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d3               (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d0               (1:>2:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> drop d4               (1:>2:>Nil)
--   
--   <interactive>:...: error:...
--       • Couldn't match...type ‘4 + n0...
--         The type variable ‘n0’ is ambiguous
--       • In the first argument of ‘print’, namely ‘it’
--         In a stmt of an interactive GHCi command: print it
--   
drop :: SNat m -> Vec (m + n) a -> Vec n a -- | "dropI xs" returns the suffix of xs as demanded -- by the context. -- --
--   >>> dropI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   4 :> 5 :> Nil
--   
dropI :: KnownNat m => Vec (m + n) a -> Vec n a -- | "at n xs" returns n'th element of xs -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> at (SNat :: SNat 1) (1:>2:>3:>4:>5:>Nil)
--   2
--   
--   >>> at d1               (1:>2:>3:>4:>5:>Nil)
--   2
--   
at :: SNat m -> Vec (m + (n + 1)) a -> a -- | "select f s n xs" selects n elements with -- step-size s and offset f from xs. -- --
--   >>> select (SNat :: SNat 1) (SNat :: SNat 2) (SNat :: SNat 3) (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
--   >>> select d1 d2 d3 (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
select :: CmpNat (i + s) (s * n) ~ 'GT => SNat f -> SNat s -> SNat n -> Vec (f + i) a -> Vec n a -- | "selectI f s xs" selects as many elements as demanded -- by the context with step-size s and offset f from -- xs. -- --
--   >>> selectI d1 d2 (1:>2:>3:>4:>5:>6:>7:>8:>Nil) :: Vec 2 Int
--   2 :> 4 :> Nil
--   
selectI :: (CmpNat (i + s) (s * n) ~ 'GT, KnownNat n) => SNat f -> SNat s -> Vec (f + i) a -> Vec n a -- | "replicate n a" returns a vector that has n -- copies of a. -- --
--   >>> replicate (SNat :: SNat 3) 6
--   6 :> 6 :> 6 :> Nil
--   
--   >>> replicate d3 6
--   6 :> 6 :> 6 :> Nil
--   
replicate :: SNat n -> a -> Vec n a -- | "repeat a" creates a vector with as many copies of -- a as demanded by the context. -- --
--   >>> repeat 6 :: Vec 5 Int
--   6 :> 6 :> 6 :> 6 :> 6 :> Nil
--   
repeat :: KnownNat n => a -> Vec n a -- | "iterate n f x" returns a vector starting with -- x followed by n repeated applications of f to -- x. -- --
--   iterate (SNat :: SNat 4) f x == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   iterate d4 f x               == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> iterate d4 (+1) 1
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- "iterate n f z" corresponds to the following circuit -- layout: -- iterate :: SNat n -> (a -> a) -> a -> Vec n a -- | "iterateI f x" returns a vector starting with -- x followed by n repeated applications of f -- to x, where n is determined by the context. -- --
--   iterateI f x :: Vec 3 a == (x :> f x :> f (f x) :> Nil)
--   
-- --
--   >>> iterateI (+1) 1 :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- -- "iterateI f z" corresponds to the following circuit -- layout: -- iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a -- | "unfoldr n f s" builds a vector of length n -- from a seed value s, where every element a is -- created by successive calls of f on s. Unlike -- unfoldr from Data.List the generating function -- f cannot dictate the length of the resulting vector, it must -- be statically known. -- -- a simple use of unfoldr: -- --
--   >>> unfoldr d10 (\s -> (s,s-1)) 10
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldr :: SNat n -> (s -> (a, s)) -> s -> Vec n a -- | "unfoldrI f s" builds a vector from a seed value -- s, where every element a is created by successive -- calls of f on s; the length of the vector is -- inferred from the context. Unlike unfoldr from Data.List -- the generating function f cannot dictate the length of the -- resulting vector, it must be statically known. -- -- a simple use of unfoldrI: -- --
--   >>> unfoldrI (\s -> (s,s-1)) 10 :: Vec 10 Int
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldrI :: KnownNat n => (s -> (a, s)) -> s -> Vec n a -- | "generate n f x" returns a vector with n -- repeated applications of f to x. -- --
--   generate (SNat :: SNat 4) f x == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   generate d4 f x               == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   
-- --
--   >>> generate d4 (+1) 1
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "generate n f z" corresponds to the following circuit -- layout: -- generate :: SNat n -> (a -> a) -> a -> Vec n a -- | "generateI f x" returns a vector with n -- repeated applications of f to x, where n is -- determined by the context. -- --
--   generateI f x :: Vec 3 a == (f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> generateI (+1) 1 :: Vec 3 Int
--   2 :> 3 :> 4 :> Nil
--   
-- -- "generateI f z" corresponds to the following circuit -- layout: -- generateI :: KnownNat n => (a -> a) -> a -> Vec n a -- | Transpose a matrix: go from row-major to column-major -- --
--   >>> let xss = (1:>2:>Nil):>(3:>4:>Nil):>(5:>6:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> Nil) :> (3 :> 4 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
--   >>> transpose xss
--   (1 :> 3 :> 5 :> Nil) :> (2 :> 4 :> 6 :> Nil) :> Nil
--   
transpose :: KnownNat n => Vec m (Vec n a) -> Vec n (Vec m a) -- | 1-dimensional stencil computations -- -- "stencil1d stX f xs", where xs has stX + -- n elements, applies the stencil computation f on: n + -- 1 overlapping (1D) windows of length stX, drawn from -- xs. The resulting vector has n + 1 elements. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t stencil1d d2 sum xs
--   stencil1d d2 sum xs :: Num b => Vec 5 b
--   
--   >>> stencil1d d2 sum xs
--   3 :> 5 :> 7 :> 9 :> 11 :> Nil
--   
stencil1d :: KnownNat n => SNat (stX + 1) -> (Vec (stX + 1) a -> b) -> Vec ((stX + n) + 1) a -> Vec (n + 1) b -- | 2-dimensional stencil computations -- -- "stencil2d stY stX f xss", where xss is a -- matrix of stY + m rows of stX + n elements, applies the -- stencil computation f on: (m + 1) * (n + 1) overlapping -- (2D) windows of stY rows of stX elements, drawn from -- xss. The result matrix has m + 1 rows of n + 1 -- elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
-- --
--   >>> :t stencil2d d2 d2 (sum . map sum) xss
--   stencil2d d2 d2 (sum . map sum) xss :: Num b => Vec 3 (Vec 3 b)
--   
-- --
--   >>> stencil2d d2 d2 (sum . map sum) xss
--   (14 :> 18 :> 22 :> Nil) :> (30 :> 34 :> 38 :> Nil) :> (46 :> 50 :> 54 :> Nil) :> Nil
--   
stencil2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> (Vec (stY + 1) (Vec (stX + 1) a) -> b) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) b) -- | "windows1d stX xs", where the vector xs has -- stX + n elements, returns a vector of n + 1 overlapping -- (1D) windows of xs of length stX. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t windows1d d2 xs
--   windows1d d2 xs :: Num a => Vec 5 (Vec 2 a)
--   
--   >>> windows1d d2 xs
--   (1 :> 2 :> Nil) :> (2 :> 3 :> Nil) :> (3 :> 4 :> Nil) :> (4 :> 5 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
windows1d :: KnownNat n => SNat (stX + 1) -> Vec ((stX + n) + 1) a -> Vec (n + 1) (Vec (stX + 1) a) -- | "windows2d stY stX xss", where matrix xss has -- stY + m rows of stX + n, returns a matrix of m+1 -- rows of n+1 elements. The elements of this new matrix are the -- overlapping (2D) windows of xss, where every window has -- stY rows of stX elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
--   >>> :t windows2d d2 d2 xss
--   windows2d d2 d2 xss :: Num a => Vec 3 (Vec 3 (Vec 2 (Vec 2 a)))
--   
--   >>> windows2d d2 d2 xss
--   (((1 :> 2 :> Nil) :> (5 :> 6 :> Nil) :> Nil) :> ((2 :> 3 :> Nil) :> (6 :> 7 :> Nil) :> Nil) :> ((3 :> 4 :> Nil) :> (7 :> 8 :> Nil) :> Nil) :> Nil) :> (((5 :> 6 :> Nil) :> (9 :> 10 :> Nil) :> Nil) :> ((6 :> 7 :> Nil) :> (10 :> 11 :> Nil) :> Nil) :> ((7 :> 8 :> Nil) :> (11 :> 12 :> Nil) :> Nil) :> Nil) :> (((9 :> 10 :> Nil) :> (13 :> 14 :> Nil) :> Nil) :> ((10 :> 11 :> Nil) :> (14 :> 15 :> Nil) :> Nil) :> ((11 :> 12 :> Nil) :> (15 :> 16 :> Nil) :> Nil) :> Nil) :> Nil
--   
windows2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) (Vec (stY + 1) (Vec (stX + 1) a))) -- | Forward permutation specified by an index mapping, ix. The -- result vector is initialized by the given defaults, def, and an -- further values that are permuted into the result are added to the -- current value using the given combination function, f. -- -- The combination function must be associative and -- commutative. permute :: (Enum i, KnownNat n, KnownNat m) => (a -> a -> a) -> Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "backpermute xs is" is equivalent to "map -- (xs !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> backpermute input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
backpermute :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | Copy elements from the source vector, xs, to the destination -- vector according to an index mapping is. This is a forward -- permute operation where a to vector encodes an input to output -- index mapping. Output elements for indices that are not mapped assume -- the value in the default vector def. -- -- For example: -- --
--   >>> let defVec = 0:>0:>0:>0:>0:>0:>0:>0:>0:>Nil
--   
--   >>> let to = 1:>3:>7:>2:>5:>8:>Nil
--   
--   >>> let input = 1:>9:>6:>4:>4:>2:>5:>Nil
--   
--   >>> scatter defVec to input
--   0 :> 1 :> 4 :> 9 :> 0 :> 4 :> 0 :> 6 :> 2 :> Nil
--   
-- -- NB: If the same index appears in the index mapping more than -- once, the latest mapping is chosen. scatter :: (Enum i, KnownNat n, KnownNat m) => Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "gather xs is" is equivalent to "map (xs -- !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> gather input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
gather :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | "interleave d xs" creates a vector: -- --
--   <x_0,x_d,x_(2d),...,x_1,x_(d+1),x_(2d+1),...,x_(d-1),x_(2d-1),x_(3d-1)>
--   
-- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> Nil
--   
--   >>> interleave d3 xs
--   1 :> 4 :> 7 :> 2 :> 5 :> 8 :> 3 :> 6 :> 9 :> Nil
--   
interleave :: (KnownNat n, KnownNat d) => SNat d -> Vec (n * d) a -> Vec (d * n) a -- | Dynamically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeft xs 1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
--   >>> rotateLeft xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateLeft xs (-1)
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateLeftS if you want to rotate left by a -- static amount. rotateLeft :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Dynamically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRight xs 1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
--   >>> rotateRight xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateRight xs (-1)
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateRightS if you want to rotate right by a -- static amount. rotateRight :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Statically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeftS xs d1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateLeft if you want to rotate left by a -- dynamic amount. rotateLeftS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Statically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRightS xs d1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateRight if you want to rotate right by a -- dynamic amount. rotateRightS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Convert a vector to a list. -- --
--   >>> toList (1:>2:>3:>Nil)
--   [1,2,3]
--   
-- -- NB: This function is not synthesizable toList :: Vec n a -> [a] -- | Create a vector literal from a list literal. -- --
--   $(listToVecTH [1::Signed 8,2,3,4,5]) == (8:>2:>3:>4:>5:>Nil) :: Vec 5 (Signed 8)
--   
-- --
--   >>> [1 :: Signed 8,2,3,4,5]
--   [1,2,3,4,5]
--   
--   >>> $(listToVecTH [1::Signed 8,2,3,4,5])
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
listToVecTH :: Lift a => [a] -> ExpQ -- | Vector as a Proxy for Nat asNatProxy :: Vec n a -> Proxy n -- | Length of a Vector as an SNat value lengthS :: KnownNat n => Vec n a -> SNat n -- | What you should use when your vector functions are too strict in their -- arguments. -- --

doctests setup

-- --
--   >>> let compareSwapL a b = if a < b then (a,b) else (b,a)
--   
--   >>> :{
--   let sortVL :: (Ord a, KnownNat (n + 1)) => Vec ((n + 1) + 1) a -> Vec ((n + 1) + 1) a
--       sortVL xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith compareSwapL (lazyV lefts) rights
--   :}
--   
-- --
--   >>> :{
--   let sortV_flip xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith (flip compareSwapL) rights lefts
--   :}
--   
-- --

Example usage

-- -- For example: -- --
--   -- Bubble sort for 1 iteration
--   sortV xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL lefts rights
--   
--   -- Compare and swap
--   compareSwapL a b = if a < b then (a,b)
--                               else (b,a)
--   
-- -- Will not terminate because zipWith is too strict in its second -- argument. -- -- In this case, adding lazyV on zipWiths second argument: -- --
--   sortVL xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL (lazyV lefts) rights
--   
-- -- Results in a successful computation: -- --
--   >>> sortVL (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: There is also a solution using flip, but it slightly -- obfuscates the meaning of the code: -- --
--   sortV_flip xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith (flip compareSwapL) rights lefts
--   
-- --
--   >>> sortV_flip (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
lazyV :: KnownNat n => Vec n a -> Vec n a -- | A dependently typed fold. -- --

doctests setup

-- --
--   >>> :seti -fplugin GHC.TypeLits.Normalise
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply (Append m a) l = Vec (l + m) a
--   
--   >>> let append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- --

Example usage

-- -- Using lists, we can define append (a.k.a. -- Data.List.++) in terms of -- Data.List.foldr: -- --
--   >>> import qualified Data.List
--   
--   >>> let append xs ys = Data.List.foldr (:) ys xs
--   
--   >>> append [1,2] [3,4]
--   [1,2,3,4]
--   
-- -- However, when we try to do the same for Vec, by defining -- append' in terms of Clash.Sized.Vector.foldr: -- --
--   append' xs ys = foldr (:>) ys xs
--   
-- -- we get a type error: -- --
--   >>> let append' xs ys = foldr (:>) ys xs
--   
--   <interactive>:...
--       • Occurs check: cannot construct the infinite type: ... ~ ... + 1
--         Expected type: a -> Vec ... a -> Vec ... a
--           Actual type: a -> Vec ... a -> Vec (... + 1) a
--       • In the first argument of ‘foldr’, namely ‘(:>)’
--         In the expression: foldr (:>) ys xs
--         In an equation for ‘append'’: append' xs ys = foldr (:>) ys xs
--       • Relevant bindings include
--           ys :: Vec ... a (bound at ...)
--           append' :: Vec n a -> Vec ... a -> Vec ... a
--             (bound at ...)
--   
-- -- The reason is that the type of foldr is: -- --
--   >>> :t foldr
--   foldr :: (a -> b -> b) -> b -> Vec n a -> b
--   
-- -- While the type of (:>) is: -- --
--   >>> :t (:>)
--   (:>) :: a -> Vec n a -> Vec (n + 1) a
--   
-- -- We thus need a fold function that can handle the growing -- vector type: dfold. Compared to foldr, dfold -- takes an extra parameter, called the motive, that allows the -- folded function to have an argument and result type that -- depends on the current length of the vector. Using -- dfold, we can now correctly define append': -- --
--   import Data.Singletons
--   import Data.Proxy
--   
--   data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   type instance Apply (Append m a) l = Vec (l + m) a
--   
--   append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- -- We now see that append' has the appropriate type: -- --
--   >>> :t append'
--   append' :: KnownNat k => Vec k a -> Vec m a -> Vec (k + m) a
--   
-- -- And that it works: -- --
--   >>> append' (1 :> 2 :> Nil) (3 :> 4 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: "dfold m f z xs" creates a linear -- structure, which has a depth, or delay, of O(length -- xs). Look at dtfold for a dependently typed fold -- that produces a structure with a depth of O(log_2(length -- xs)). dfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (forall l. SNat l -> a -> (p @@ l) -> p @@ (l + 1)) -> (p @@ 0) -> Vec k a -> p @@ k -- | A combination of dfold and fold: a dependently -- typed fold that reduces a vector in a tree-like structure. -- --

doctests setup

-- --
--   >>> :seti -XUndecidableInstances
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data IIndex (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply IIndex l = Index ((2^l)+1)
--   
--   >>> :{
--   let populationCount' :: (KnownNat k, KnownNat (2^k)) => BitVector (2^k) -> Index ((2^k)+1)
--       populationCount' bv = dtfold (Proxy @IIndex)
--                                    fromIntegral
--                                    (\_ x y -> add x y)
--                                    (bv2v bv)
--   :}
--   
-- --

Example usage

-- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- sum, because it gives a nice (log2(n)) tree-structure -- of adders: -- --
--   populationCount :: (KnownNat (n+1), KnownNat (n+2))
--                   => BitVector (n+1) -> Index (n+2)
--   populationCount = sum . map fromIntegral . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (n+2) -> Index (n+2) -> Index (n+2).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of addes: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (n+1), KnownNat (n+2))
--                        => BitVector (n+1) -> Index (n+2)
--       populationCount' = fold add . map fromIntegral . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘((n + 2) + (n + 2)) - 1’ with ‘n + 2’
--         Expected type: Index (n + 2) -> Index (n + 2) -> Index (n + 2)
--           Actual type: Index (n + 2)
--                        -> Index (n + 2) -> AResult (Index (n + 2)) (Index (n + 2))
--       • In the first argument of ‘fold’, namely ‘add’
--         In the first argument of ‘(.)’, namely ‘fold add’
--         In the expression: fold add . map fromIntegral . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (n + 1) -> Index (n + 2)
--             (bound at ...)
--   
-- -- because fold expects a function of type "a -> a -> -- a", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   import Data.Proxy
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = dtfold (Proxy @IIndex)
--                                fromIntegral
--                                (\_ x y -> add x y)
--                                (bv2v bv)
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
-- -- Some final remarks: -- -- -- -- NB: The depth, or delay, of the structure produced by -- "dtfold m f g xs" is O(log_2(length -- xs)). dtfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> Vec (2 ^ k) a -> p @@ k -- | Specialised version of dfold that builds a triangular -- computational structure. -- --

doctests setup

-- --
--   >>> let compareSwap a b = if a > b then (a,b) else (b,a)
--   
--   >>> let insert y xs = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   
--   >>> let insertionSort = vfold (const insert)
--   
-- --

Example usage

-- --
--   compareSwap a b = if a > b then (a,b) else (b,a)
--   insert y xs     = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   insertionSort   = vfold (const insert)
--   
-- -- Builds a triangular structure of compare and swaps to sort a row. -- --
--   >>> insertionSort (7 :> 3 :> 9 :> 1 :> Nil)
--   1 :> 3 :> 7 :> 9 :> Nil
--   
-- -- The circuit layout of insertionSort, build using -- vfold, is: -- vfold :: forall k a b. KnownNat k => (forall l. SNat l -> a -> Vec l b -> Vec (l + 1) b) -> Vec k a -> Vec k b -- | The largest element of a non-empty vector maximum :: Ord a => Vec (n + 1) a -> a -- | The least element of a non-empty vector minimum :: Ord a => Vec (n + 1) a -> a -- | Apply a function to every element of a vector and the element's -- position (as an SNat value) in the vector. -- --
--   >>> let rotateMatrix = smap (flip rotateRightS)
--   
--   >>> let xss = (1:>2:>3:>Nil):>(1:>2:>3:>Nil):>(1:>2:>3:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> Nil
--   
--   >>> rotateMatrix xss
--   (1 :> 2 :> 3 :> Nil) :> (3 :> 1 :> 2 :> Nil) :> (2 :> 3 :> 1 :> Nil) :> Nil
--   
smap :: forall k a b. KnownNat k => (forall l. SNat l -> a -> b) -> Vec k a -> Vec k b concatBitVector# :: forall n m. (KnownNat n, KnownNat m) => Vec n (BitVector m) -> BitVector (n * m) unconcatBitVector# :: forall n m. (KnownNat n, KnownNat m) => BitVector (n * m) -> Vec n (BitVector m) -- | Convert a Vec of Bits to a BitVector. -- --
--   >>> let x = (0:>0:>0:>1:>0:>0:>1:>0:>Nil) :: Vec 8 Bit
--   
--   >>> x
--   0 :> 0 :> 0 :> 1 :> 0 :> 0 :> 1 :> 0 :> Nil
--   
--   >>> v2bv x
--   0b0001_0010
--   
v2bv :: KnownNat n => Vec n Bit -> BitVector n -- | Evaluate all elements of a vector to WHNF, returning the second -- argument seqV :: KnownNat n => Vec n a -> b -> b infixr 0 `seqV` -- | Evaluate all elements of a vector to WHNF forceV :: KnownNat n => Vec n a -> Vec n a -- | Evaluate all elements of a vector to WHNF, returning the second -- argument. Does not propagate XExceptions. seqVX :: KnownNat n => Vec n a -> b -> b infixr 0 `seqVX` -- | Evaluate all elements of a vector to WHNF. Does not propagate -- XExceptions. forceVX :: KnownNat n => Vec n a -> Vec n a -- | Representable types of kind *. This class is derivable in GHC -- with the DeriveGeneric flag on. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class Generic a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) -- | This is the Safe API only of Clash.Prelude -- -- Clash is a functional hardware description language that borrows both -- its syntax and semantics from the functional programming language -- Haskell. The merits of using a functional language to describe -- hardware comes from the fact that combinational circuits can be -- directly modeled as mathematical functions and that functional -- languages lend themselves very well at describing and (de-)composing -- mathematical functions. -- -- This package provides: -- -- -- -- To use the library: -- -- -- -- For now, Clash.Prelude is also the best starting point for -- exploring the library. A preliminary version of a tutorial can be -- found in Clash.Tutorial. Some circuit examples can be found in -- Clash.Examples. module Clash.Prelude.Safe -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac :: HiddenClockResetEnable dom  => Signal dom (Int, Int) -> Signal dom Int
--   mac = mealy macT 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy macT 0 (bundle (a,x))
--       s2 = mealy macT 0 (bundle (b,y))
--   
mealy :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | Create a synchronous function from a combinational function describing -- a mealy machine using the state monad. This can be particularly useful -- when combined with lenses or optics to replicate imperative -- algorithms. -- --
--   data DelayState = DelayState
--     { _history    :: Vec 4 Int
--     , _untilValid :: Index 4
--     }
--     deriving (Generic, NFDataX)
--   makeLenses ''DelayState
--   
--   initialDelayState = DelayState (repeat 0) maxBound
--   
--   delayS :: Int -> State DelayState (Maybe Int)
--   delayS n = do
--     history   %= (n +>>)
--     remaining <- use untilValid
--     if remaining > 0
--     then do
--        untilValid -= 1
--        return Nothing
--      else do
--        out <- uses history last
--        return (Just out)
--   
--   delayTop :: HiddenClockResetEnable dom  => Signal dom Int -> Signal dom (Maybe Int)
--   delayTop = mealyS delayS initialDelayState
--   
-- --
--   >>> L.take 7 $ simulate @System delayTop [1,2,3,4,5,6,7,8]
--   [Nothing,Nothing,Nothing,Just 1,Just 2,Just 3,Just 4]
--   ...
--   
mealyS :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s o) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB f 0 (a,b)
--       (i2,b2) = mealyB f 3 (c,i1)
--   
mealyB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | A version of mealyS that does automatic Bundleing, see -- mealyB for details. mealySB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o -- | Infix version of mealyB (<^>) :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> Int        -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: HiddenClockResetEnable dom
--     => Signal dom (Int, Int)
--     -> Signal dom Int
--   mac = moore mac id 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14,30,...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore macT id 0 (bundle (a,x))
--       s2 = moore macT id 0 (bundle (b,y))
--   
moore :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB t o 0 (a,b)
--       (i2,b2) = mooreB t o 3 (c,i1)
--   
mooreB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a register function for product-type like signals (e.g. -- '(Signal a, Signal b)') -- --
--   rP :: HiddenClockResetEnable dom
--      => (Signal dom Int, Signal dom Int)
--      -> (Signal dom Int, Signal dom Int)
--   rP = registerB (8,8)
--   
-- --
--   >>> simulateB @System rP [(1,1),(2,2),(3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
registerB :: (HiddenClockResetEnable dom, NFDataX a, Bundle a) => a -> Unbundled dom a -> Unbundled dom a infixr 3 `registerB` -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRom :: (KnownNat n, Enum addr, NFDataX a) => Vec n a -> addr -> a -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomPow2 :: (KnownNat n, NFDataX a) => Vec (2 ^ n) a -> Unsigned n -> a -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: forall dom n m a. (NFDataX a, KnownNat n, KnownNat m, HiddenClock dom, HiddenEnable dom) => Vec n a -> Signal dom (Unsigned m) -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: forall dom n a. (KnownNat n, NFDataX a, HiddenClock dom, HiddenEnable dom) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRomBlob :: Enum addr => MemBlob n m -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomBlobPow2 :: KnownNat n => MemBlob (2 ^ n) m -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr) => MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => SNat n -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: (KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: HiddenClock dom
--     => Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 = blockRam (replicate d40 1)
--   
blockRam :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, Enum addr, NFDataX addr) => Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: HiddenClock dom
--     => Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 = blockRamPow2 (replicate d32 1)
--   
blockRamPow2 :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, KnownNat n) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr, NFDataX addr) => MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | Create a read-after-write block RAM from a read-before-write one -- --
--   >>> :t readNew (blockRam (0 :> 1 :> Nil))
--   readNew (blockRam (0 :> 1 :> Nil))
--     :: ...
--        ...
--        ...
--        ...
--        ... =>
--        Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a
--   
readNew :: (HiddenClockResetEnable dom, NFDataX a, Eq addr) => (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs dom1 dom2 a. (HasCallStack, KnownNat nAddrs, HiddenClock dom1, HiddenClock dom2, NFDataX a) => Signal dom1 (RamOp nAddrs a) -> Signal dom2 (RamOp nAddrs a) -> (Signal dom1 a, Signal dom2 a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a -- | Give a pulse when the Signal goes from minBound to -- maxBound isRising :: (HiddenClockResetEnable dom, NFDataX a, Bounded a, Eq a) => a -> Signal dom a -> Signal dom Bool -- | Give a pulse when the Signal goes from maxBound to -- minBound isFalling :: (HiddenClockResetEnable dom, NFDataX a, Bounded a, Eq a) => a -> Signal dom a -> Signal dom Bool -- | Give a pulse every n clock cycles. This is a useful helper -- function when combined with functions like regEn or -- mux, in order to delay a register by a known amount. -- -- To be precise: the given signal will be False for the -- next n-1 cycles, followed by a single True -- value: -- --
--   >>> Prelude.last (sampleN @System 1025 (riseEvery d1024)) == True
--   True
--   
--   >>> Prelude.or (sampleN @System 1024 (riseEvery d1024)) == False
--   True
--   
-- -- For example, to update a counter once every 10 million cycles: -- --
--   counter = regEn 0 (riseEvery (SNat :: SNat 10000000)) (counter + 1)
--   
riseEvery :: HiddenClockResetEnable dom => SNat n -> Signal dom Bool -- | Oscillate a Bool for a given number of cycles. This is -- a convenient function when combined with something like -- regEn, as it allows you to easily hold a register -- value for a given number of cycles. The input Bool -- determines what the initial value is. -- -- To oscillate on an interval of 5 cycles: -- --
--   >>> sampleN @System 11 (oscillate False d5)
--   [False,False,False,False,False,False,True,True,True,True,True]
--   
-- -- To oscillate between True and False: -- --
--   >>> sampleN @System 11 (oscillate False d1)
--   [False,False,True,False,True,False,True,False,True,False,True]
--   
-- -- An alternative definition for the above could be: -- --
--   >>> let osc' = register False (not <$> osc')
--   
--   >>> sampleN @System 200 (oscillate False d1) == sampleN @System 200 osc'
--   True
--   
oscillate :: HiddenClockResetEnable dom => Bool -> SNat n -> Signal dom Bool -- | Fixed size vectors. -- -- data Vec :: Nat -> Type -> Type [Nil] :: Vec 0 a [Cons] :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the head of a vector. -- --
--   >>> 3:>4:>5:>Nil
--   3 :> 4 :> 5 :> Nil
--   
--   >>> let x = 3:>4:>5:>Nil
--   
--   >>> :t x
--   x :: Num a => Vec 3 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (x :> y :> _) = x + y
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   7
--   
-- -- Also in conjunctions with (:<): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:>) :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the tail of a vector. -- --
--   >>> (3:>4:>5:>Nil) :< 1
--   3 :> 4 :> 5 :> 1 :> Nil
--   
--   >>> let x = (3:>4:>5:>Nil) :< 1
--   
--   >>> :t x
--   x :: Num a => Vec 4 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (_ :< y :< x) = y + x
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   13
--   
-- -- Also in conjunctions with (:>): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:<) :: Vec n a -> a -> Vec (n + 1) a infixr 5 :> infixl 5 :< infixr 5 `Cons` -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a vector, reduces -- the vector using the binary operator, from left to right: -- --
--   foldl f z (x1 :> x2 :> ... :> xn :> Nil) == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   foldl f z Nil                            == z
--   
-- --
--   >>> foldl (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldl :: forall b a n. (b -> a -> b) -> b -> Vec n a -> b -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a vector, reduces -- the vector using the binary operator, from right to left: -- --
--   foldr f z (x1 :> ... :> xn1 :> xn :> Nil) == x1 `f` (... (xn1 `f` (xn `f` z))...)
--   foldr r z Nil                             == z
--   
-- --
--   >>> foldr (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   1.875
--   
-- -- "foldr f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldr :: (a -> b -> b) -> b -> Vec n a -> b -- | "map f xs" is the vector obtained by applying f -- to each element of xs, i.e., -- --
--   map f (x1 :> x2 :>  ... :> xn :> Nil) == (f x1 :> f x2 :> ... :> f xn :> Nil)
--   
-- -- and corresponds to the following circuit layout: -- map :: (a -> b) -> Vec n a -> Vec n b -- | Convert a BitVector to a Vec of Bits. -- --
--   >>> let x = 6 :: BitVector 8
--   
--   >>> x
--   0b0000_0110
--   
--   >>> bv2v x
--   0 :> 0 :> 0 :> 0 :> 0 :> 1 :> 1 :> 0 :> Nil
--   
bv2v :: KnownNat n => BitVector n -> Vec n Bit -- | To be used as the motive p for dfold, when the f -- in "dfold p f" is a variation on (:>), e.g.: -- --
--   map' :: forall n a b . KnownNat n => (a -> b) -> Vec n a -> Vec n b
--   map' f = dfold (Proxy @(VCons b)) (_ x xs -> f x :> xs)
--   
data VCons (a :: Type) (f :: TyFun Nat Type) :: Type traverse# :: forall a f b n. Applicative f => (a -> f b) -> Vec n a -> f (Vec n b) -- | Create a vector of one element -- --
--   >>> singleton 5
--   5 :> Nil
--   
singleton :: a -> Vec 1 a -- | Extract the first element of a vector -- --
--   >>> head (1:>2:>3:>Nil)
--   1
--   
-- --
--   >>> head Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘head’, namely ‘Nil’
--         In the expression: head Nil
--         In an equation for ‘it’: it = head Nil
--   
head :: Vec (n + 1) a -> a -- | Extract the elements after the head of a vector -- --
--   >>> tail (1:>2:>3:>Nil)
--   2 :> 3 :> Nil
--   
-- --
--   >>> tail Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘tail’, namely ‘Nil’
--         In the expression: tail Nil
--         In an equation for ‘it’: it = tail Nil
--   
tail :: Vec (n + 1) a -> Vec n a -- | Extract the last element of a vector -- --
--   >>> last (1:>2:>3:>Nil)
--   3
--   
-- --
--   >>> last Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘last’, namely ‘Nil’
--         In the expression: last Nil
--         In an equation for ‘it’: it = last Nil
--   
last :: Vec (n + 1) a -> a -- | Extract all the elements of a vector except the last element -- --
--   >>> init (1:>2:>3:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> init Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘init’, namely ‘Nil’
--         In the expression: init Nil
--         In an equation for ‘it’: it = init Nil
--   
init :: Vec (n + 1) a -> Vec n a -- | Shift in elements to the head of a vector, bumping out elements at the -- tail. The result is a tuple containing: -- -- -- --
--   >>> shiftInAt0 (1 :> 2 :> 3 :> 4 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> 0 :> 1 :> 2 :> Nil,3 :> 4 :> Nil)
--   
--   >>> shiftInAt0 (1 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> Nil,0 :> 1 :> Nil)
--   
shiftInAt0 :: KnownNat n => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift in element to the tail of a vector, bumping out elements at the -- head. The result is a tuple containing: -- -- -- --
--   >>> shiftInAtN (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> Nil)
--   (3 :> 4 :> 5 :> 6 :> Nil,1 :> 2 :> Nil)
--   
--   >>> shiftInAtN (1 :> Nil) (2 :> 3 :> Nil)
--   (3 :> Nil,1 :> 2 :> Nil)
--   
shiftInAtN :: KnownNat m => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Add an element to the head of a vector, and extract all but the last -- element. -- --
--   >>> 1 +>> (3:>4:>5:>Nil)
--   1 :> 3 :> 4 :> Nil
--   
--   >>> 1 +>> Nil
--   Nil
--   
(+>>) :: KnownNat n => a -> Vec n a -> Vec n a infixr 4 +>> -- | Add an element to the tail of a vector, and extract all but the first -- element. -- --
--   >>> (3:>4:>5:>Nil) <<+ 1
--   4 :> 5 :> 1 :> Nil
--   
--   >>> Nil <<+ 1
--   Nil
--   
(<<+) :: Vec n a -> a -> Vec n a infixl 4 <<+ -- | Shift m elements out from the head of a vector, filling up the -- tail with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFrom0 d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (3 :> 4 :> 5 :> 0 :> 0 :> Nil,1 :> 2 :> Nil)
--   
shiftOutFrom0 :: (Default a, KnownNat m) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Shift m elements out from the tail of a vector, filling up the -- head with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFromN d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (0 :> 0 :> 1 :> 2 :> 3 :> Nil,4 :> 5 :> Nil)
--   
shiftOutFromN :: (Default a, KnownNat n) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Append two vectors. -- --
--   >>> (1:>2:>3:>Nil) ++ (7:>8:>Nil)
--   1 :> 2 :> 3 :> 7 :> 8 :> Nil
--   
(++) :: Vec n a -> Vec m a -> Vec (n + m) a infixr 5 ++ -- | Split a vector into two vectors at the given point. -- --
--   >>> splitAt (SNat :: SNat 3) (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
--   >>> splitAt d3 (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
splitAt :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector into two vectors where the length of the two is -- determined by the context. -- --
--   >>> splitAtI (1:>2:>3:>7:>8:>Nil) :: (Vec 2 Int, Vec 3 Int)
--   (1 :> 2 :> Nil,3 :> 7 :> 8 :> Nil)
--   
splitAtI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) -- | Concatenate a vector of vectors. -- --
--   >>> concat ((1:>2:>3:>Nil) :> (4:>5:>6:>Nil) :> (7:>8:>9:>Nil) :> (10:>11:>12:>Nil) :> Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil
--   
concat :: Vec n (Vec m a) -> Vec (n * m) a -- | Map a function over all the elements of a vector and concatentate the -- resulting vectors. -- --
--   >>> concatMap (replicate d3) (1:>2:>3:>Nil)
--   1 :> 1 :> 1 :> 2 :> 2 :> 2 :> 3 :> 3 :> 3 :> Nil
--   
concatMap :: (a -> Vec m b) -> Vec n a -> Vec (n * m) b -- | Split a vector of (n * m) elements into a vector of "vectors of length -- m", where the length m is given. -- --
--   >>> unconcat d4 (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil) :> (5 :> 6 :> 7 :> 8 :> Nil) :> (9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) -- | Split a vector of (n * m) elements into a vector of "vectors of -- length m", where the length m is determined by the -- context. -- --
--   >>> unconcatI (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil) :: Vec 2 (Vec 6 Int)
--   (1 :> 2 :> 3 :> 4 :> 5 :> 6 :> Nil) :> (7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) -- | Merge two vectors, alternating their elements, i.e., -- --
--   >>> merge (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> 7 :> 8 :> Nil)
--   1 :> 5 :> 2 :> 6 :> 3 :> 7 :> 4 :> 8 :> Nil
--   
merge :: KnownNat n => Vec n a -> Vec n a -> Vec (2 * n) a -- | The elements in a vector in reverse order. -- --
--   >>> reverse (1:>2:>3:>4:>Nil)
--   4 :> 3 :> 2 :> 1 :> Nil
--   
reverse :: Vec n a -> Vec n a -- | Apply a function of every element of a vector and its index. -- --
--   >>> :t imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   imap (+) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Index 4)
--   
--   >>> imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   2 :> 3 :> *** Exception: X: Clash.Sized.Index: result 4 is out of bounds: [0..3]
--   ...
--   
--   >>> imap (\i a -> extend (bitCoerce i) + a) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Unsigned 8)
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- imap :: forall n a b. KnownNat n => (Index n -> a -> b) -> Vec n a -> Vec n b -- | Zip two vectors with a functions that also takes the elements' -- indices. -- --
--   >>> izipWith (\i a b -> i + a + b) (2 :> 2 :> Nil)  (3 :> 3:> Nil)
--   *** Exception: X: Clash.Sized.Index: result 3 is out of bounds: [0..1]
--   ...
--   
--   >>> izipWith (\i a b -> extend (bitCoerce i) + a + b) (2 :> 2 :> Nil) (3 :> 3 :> Nil) :: Vec 2 (Unsigned 8)
--   5 :> 6 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- -- -- NB: izipWith is strict in its second argument, -- and lazy in its third. This matters when izipWith is -- used in a recursive setting. See lazyV for more information. izipWith :: KnownNat n => (Index n -> a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | Right fold (function applied to each element and its index) -- --
--   >>> let findLeftmost x xs = ifoldr (\i a b -> if a == x then Just i else b) Nothing xs
--   
--   >>> findLeftmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> findLeftmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldr f z xs" corresponds to the following circuit -- layout: -- ifoldr :: KnownNat n => (Index n -> a -> b -> b) -> b -> Vec n a -> b -- | Left fold (function applied to each element and its index) -- --
--   >>> let findRightmost x xs = ifoldl (\a i b -> if b == x then Just i else a) Nothing xs
--   
--   >>> findRightmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 4
--   
--   >>> findRightmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldl f z xs" corresponds to the following circuit -- layout: -- ifoldl :: KnownNat n => (a -> Index n -> b -> a) -> a -> Vec n b -> a -- | Generate a vector of indices. -- --
--   >>> indices d4
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indices :: KnownNat n => SNat n -> Vec n (Index n) -- | Generate a vector of indices, where the length of the vector is -- determined by the context. -- --
--   >>> indicesI :: Vec 4 (Index 4)
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indicesI :: KnownNat n => Vec n (Index n) -- | "findIndex p xs" returns the index of the first -- element of xs satisfying the predicate p, or -- Nothing if there is no such element. -- --
--   >>> findIndex (> 3) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 3
--   
--   >>> findIndex (> 8) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
findIndex :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe (Index n) -- | "elemIndex a xs" returns the index of the first -- element which is equal (by ==) to the query element a, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> elemIndex 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
elemIndex :: (KnownNat n, Eq a) => a -> Vec n a -> Maybe (Index n) -- | zipWith generalizes zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "zipWith (+)" applied to two vectors produces -- the vector of corresponding sums. -- --
--   zipWith f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) == (f x1 y1 :> f x2 y2 :> ... :> f xn yn :> Nil)
--   
-- -- "zipWith f xs ys" corresponds to the following circuit -- layout: -- -- -- NB: zipWith is strict in its second argument, and -- lazy in its third. This matters when zipWith is used in -- a recursive setting. See lazyV for more information. zipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | zipWith3 generalizes zip3 by zipping with the function -- given as the first argument, instead of a tupling function. -- --
--   zipWith3 f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) (z1 :> z2 :> ... :> zn :> Nil) == (f x1 y1 z1 :> f x2 y2 z2 :> ... :> f xn yn zn :> Nil)
--   
-- -- "zipWith3 f xs ys zs" corresponds to the following -- circuit layout: -- -- -- NB: zipWith3 is strict in its second argument, -- and lazy in its third and fourth. This matters when -- zipWith3 is used in a recursive setting. See lazyV for -- more information. zipWith3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d zipWith4 :: (a -> b -> c -> d -> e) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n h -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldr1 f (x1 :> ... :> xn2 :> xn1 :> xn :> Nil) == x1 `f` (... (xn2 `f` (xn1 `f` xn))...)
--   foldr1 f (x1 :> Nil)                            == x1
--   foldr1 f Nil                                    == TYPE ERROR
--   
-- --
--   >>> foldr1 (/) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   1.875
--   
-- -- "foldr1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldl1 f (x1 :> x2 :> x3 :> ... :> xn :> Nil) == (...((x1 `f` x2) `f` x3) `f`...) `f` xn
--   foldl1 f (x1 :> Nil)                          == x1
--   foldl1 f Nil                                  == TYPE ERROR
--   
-- --
--   >>> foldl1 (/) (1 :> 5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | fold is a variant of foldr1 and foldl1, but -- instead of reducing from right to left, or left to right, it reduces a -- vector using a tree-like structure. The depth, or delay, of the -- structure produced by "fold f xs", is hence -- O(log_2(length xs)), and not O(length -- xs). -- -- NB: The binary operator "f" in "fold f -- xs" must be associative. -- --
--   fold f (x1 :> x2 :> ... :> xn1 :> xn :> Nil) == ((x1 `f` x2) `f` ...) `f` (... `f` (xn1 `f` xn))
--   fold f (x1 :> Nil)                           == x1
--   fold f Nil                                   == TYPE ERROR
--   
-- --
--   >>> fold (+) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   15
--   
-- -- "fold f xs" corresponds to the following circuit -- layout: -- fold :: forall n a. (a -> a -> a) -> Vec (n + 1) a -> a -- | scanl is similar to foldl, but returns a vector of -- successive reduced values from the left: -- --
--   scanl f z (x1 :> x2 :> ... :> Nil) == z :> (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> scanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   0 :> 5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "scanl f z xs" corresponds to the following circuit -- layout: -- -- -- scanl :: (b -> a -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanl with no seed value -- --
--   >>> scanl1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> -1 :> -4 :> -8 :> Nil
--   
scanl1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | scanr with no seed value -- --
--   >>> scanr1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   -2 :> 3 :> -1 :> 4 :> Nil
--   
scanr1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | postscanl is a variant of scanl where the first result -- is dropped: -- --
--   postscanl f z (x1 :> x2 :> ... :> Nil) == (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> postscanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "postscanl f z xs" corresponds to the following -- circuit layout: -- postscanl :: (b -> a -> b) -> b -> Vec n a -> Vec n b -- | scanr is similar to foldr, but returns a vector of -- successive reduced values from the right: -- --
--   scanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> z :> Nil
--   
-- --
--   >>> scanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> 0 :> Nil
--   
-- -- "scanr f z xs" corresponds to the following circuit -- layout: -- -- -- scanr :: (a -> b -> b) -> b -> Vec n a -> Vec (n + 1) b -- | postscanr is a variant of scanr that where the last -- result is dropped: -- --
--   postscanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> Nil
--   
-- --
--   >>> postscanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> Nil
--   
-- -- "postscanr f z xs" corresponds to the following -- circuit layout: -- postscanr :: (a -> b -> b) -> b -> Vec n a -> Vec n b -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumL (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,1 :> 2 :> 4 :> 7 :> Nil)
--   
-- -- "mapAccumL f acc xs" corresponds to the following -- circuit layout: -- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumR (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,10 :> 8 :> 5 :> 1 :> Nil)
--   
-- -- "mapAccumR f acc xs" corresponds to the following -- circuit layout: -- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | zip takes two vectors and returns a vector of corresponding -- pairs. -- --
--   >>> zip (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil)
--   (1,4) :> (2,3) :> (3,2) :> (4,1) :> Nil
--   
zip :: Vec n a -> Vec n b -> Vec n (a, b) -- | zip3 takes three vectors and returns a vector of corresponding -- triplets. -- --
--   >>> zip3 (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil) (5:>6:>7:>8:>Nil)
--   (1,4,5) :> (2,3,6) :> (3,2,7) :> (4,1,8) :> Nil
--   
zip3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) -- | zip4 takes four vectors and returns a list of quadruples, -- analogous to zip. zip4 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n (a, b, c, d) -- | zip5 takes five vectors and returns a list of five-tuples, -- analogous to zip. zip5 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n (a, b, c, d, e) -- | zip6 takes six vectors and returns a list of six-tuples, -- analogous to zip. zip6 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n (a, b, c, d, e, f) -- | zip7 takes seven vectors and returns a list of seven-tuples, -- analogous to zip. zip7 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n (a, b, c, d, e, f, g) -- | unzip transforms a vector of pairs into a vector of first -- components and a vector of second components. -- --
--   >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
--   
unzip :: Vec n (a, b) -> (Vec n a, Vec n b) -- | unzip3 transforms a vector of triplets into a vector of first -- components, a vector of second components, and a vector of third -- components. -- --
--   >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
--   
unzip3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) -- | unzip4 takes a vector of quadruples and returns four vectors, -- analogous to unzip. unzip4 :: Vec n (a, b, c, d) -> (Vec n a, Vec n b, Vec n c, Vec n d) -- | unzip5 takes a vector of five-tuples and returns five vectors, -- analogous to unzip. unzip5 :: Vec n (a, b, c, d, e) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e) -- | unzip6 takes a vector of six-tuples and returns six vectors, -- analogous to unzip. unzip6 :: Vec n (a, b, c, d, e, f) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f) -- | unzip7 takes a vector of seven-tuples and returns seven -- vectors, analogous to unzip. unzip7 :: Vec n (a, b, c, d, e, f, g) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f, Vec n g) -- | "xs !! n" returns the n'th element of -- xs. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> (1:>2:>3:>4:>5:>Nil) !! 4
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! (length (1:>2:>3:>4:>5:>Nil) - 1)
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 1
--   2
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 4
--   ...
--   
(!!) :: (KnownNat n, Enum i) => Vec n a -> i -> a -- | The length of a Vector as an Int value. -- --
--   >>> length (6 :> 7 :> 8 :> Nil)
--   3
--   
length :: KnownNat n => Vec n a -> Int -- | "replace n a xs" returns the vector xs where -- the n'th element is replaced by a. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> replace 3 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 7 :> 5 :> Nil
--   
--   >>> replace 0 7 (1:>2:>3:>4:>5:>Nil)
--   7 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
--   >>> replace 9 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 4
--   ...
--   
replace :: (KnownNat n, Enum i) => i -> a -> Vec n a -> Vec n a -- | "take n xs" returns the n-length prefix of -- xs. -- --
--   >>> take (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d3               (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d0               (1:>2:>Nil)
--   Nil
--   
-- --
--   >>> take d4               (1:>2:>Nil)
--   
--   <interactive>:...
--       • Couldn't match type ‘4 + n0’ with ‘2’
--         Expected type: Vec (4 + n0) a
--           Actual type: Vec (1 + 1) a
--         The type variable ‘n0’ is ambiguous
--       • In the second argument of ‘take’, namely ‘(1 :> 2 :> Nil)’
--         In the expression: take d4 (1 :> 2 :> Nil)
--         In an equation for ‘it’: it = take d4 (1 :> 2 :> Nil)
--   
take :: SNat m -> Vec (m + n) a -> Vec m a -- | "takeI xs" returns the prefix of xs as demanded -- by the context. -- --
--   >>> takeI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   1 :> 2 :> Nil
--   
takeI :: KnownNat m => Vec (m + n) a -> Vec m a -- | "drop n xs" returns the suffix of xs after the -- first n elements. -- --
--   >>> drop (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d3               (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d0               (1:>2:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> drop d4               (1:>2:>Nil)
--   
--   <interactive>:...: error:...
--       • Couldn't match...type ‘4 + n0...
--         The type variable ‘n0’ is ambiguous
--       • In the first argument of ‘print’, namely ‘it’
--         In a stmt of an interactive GHCi command: print it
--   
drop :: SNat m -> Vec (m + n) a -> Vec n a -- | "dropI xs" returns the suffix of xs as demanded -- by the context. -- --
--   >>> dropI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   4 :> 5 :> Nil
--   
dropI :: KnownNat m => Vec (m + n) a -> Vec n a -- | "at n xs" returns n'th element of xs -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> at (SNat :: SNat 1) (1:>2:>3:>4:>5:>Nil)
--   2
--   
--   >>> at d1               (1:>2:>3:>4:>5:>Nil)
--   2
--   
at :: SNat m -> Vec (m + (n + 1)) a -> a -- | "select f s n xs" selects n elements with -- step-size s and offset f from xs. -- --
--   >>> select (SNat :: SNat 1) (SNat :: SNat 2) (SNat :: SNat 3) (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
--   >>> select d1 d2 d3 (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
select :: CmpNat (i + s) (s * n) ~ 'GT => SNat f -> SNat s -> SNat n -> Vec (f + i) a -> Vec n a -- | "selectI f s xs" selects as many elements as demanded -- by the context with step-size s and offset f from -- xs. -- --
--   >>> selectI d1 d2 (1:>2:>3:>4:>5:>6:>7:>8:>Nil) :: Vec 2 Int
--   2 :> 4 :> Nil
--   
selectI :: (CmpNat (i + s) (s * n) ~ 'GT, KnownNat n) => SNat f -> SNat s -> Vec (f + i) a -> Vec n a -- | "replicate n a" returns a vector that has n -- copies of a. -- --
--   >>> replicate (SNat :: SNat 3) 6
--   6 :> 6 :> 6 :> Nil
--   
--   >>> replicate d3 6
--   6 :> 6 :> 6 :> Nil
--   
replicate :: SNat n -> a -> Vec n a -- | "repeat a" creates a vector with as many copies of -- a as demanded by the context. -- --
--   >>> repeat 6 :: Vec 5 Int
--   6 :> 6 :> 6 :> 6 :> 6 :> Nil
--   
repeat :: KnownNat n => a -> Vec n a -- | "iterate n f x" returns a vector starting with -- x followed by n repeated applications of f to -- x. -- --
--   iterate (SNat :: SNat 4) f x == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   iterate d4 f x               == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> iterate d4 (+1) 1
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- "iterate n f z" corresponds to the following circuit -- layout: -- iterate :: SNat n -> (a -> a) -> a -> Vec n a -- | "iterateI f x" returns a vector starting with -- x followed by n repeated applications of f -- to x, where n is determined by the context. -- --
--   iterateI f x :: Vec 3 a == (x :> f x :> f (f x) :> Nil)
--   
-- --
--   >>> iterateI (+1) 1 :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- -- "iterateI f z" corresponds to the following circuit -- layout: -- iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a -- | "unfoldr n f s" builds a vector of length n -- from a seed value s, where every element a is -- created by successive calls of f on s. Unlike -- unfoldr from Data.List the generating function -- f cannot dictate the length of the resulting vector, it must -- be statically known. -- -- a simple use of unfoldr: -- --
--   >>> unfoldr d10 (\s -> (s,s-1)) 10
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldr :: SNat n -> (s -> (a, s)) -> s -> Vec n a -- | "unfoldrI f s" builds a vector from a seed value -- s, where every element a is created by successive -- calls of f on s; the length of the vector is -- inferred from the context. Unlike unfoldr from Data.List -- the generating function f cannot dictate the length of the -- resulting vector, it must be statically known. -- -- a simple use of unfoldrI: -- --
--   >>> unfoldrI (\s -> (s,s-1)) 10 :: Vec 10 Int
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldrI :: KnownNat n => (s -> (a, s)) -> s -> Vec n a -- | "generate n f x" returns a vector with n -- repeated applications of f to x. -- --
--   generate (SNat :: SNat 4) f x == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   generate d4 f x               == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   
-- --
--   >>> generate d4 (+1) 1
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "generate n f z" corresponds to the following circuit -- layout: -- generate :: SNat n -> (a -> a) -> a -> Vec n a -- | "generateI f x" returns a vector with n -- repeated applications of f to x, where n is -- determined by the context. -- --
--   generateI f x :: Vec 3 a == (f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> generateI (+1) 1 :: Vec 3 Int
--   2 :> 3 :> 4 :> Nil
--   
-- -- "generateI f z" corresponds to the following circuit -- layout: -- generateI :: KnownNat n => (a -> a) -> a -> Vec n a -- | Transpose a matrix: go from row-major to column-major -- --
--   >>> let xss = (1:>2:>Nil):>(3:>4:>Nil):>(5:>6:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> Nil) :> (3 :> 4 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
--   >>> transpose xss
--   (1 :> 3 :> 5 :> Nil) :> (2 :> 4 :> 6 :> Nil) :> Nil
--   
transpose :: KnownNat n => Vec m (Vec n a) -> Vec n (Vec m a) -- | 1-dimensional stencil computations -- -- "stencil1d stX f xs", where xs has stX + -- n elements, applies the stencil computation f on: n + -- 1 overlapping (1D) windows of length stX, drawn from -- xs. The resulting vector has n + 1 elements. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t stencil1d d2 sum xs
--   stencil1d d2 sum xs :: Num b => Vec 5 b
--   
--   >>> stencil1d d2 sum xs
--   3 :> 5 :> 7 :> 9 :> 11 :> Nil
--   
stencil1d :: KnownNat n => SNat (stX + 1) -> (Vec (stX + 1) a -> b) -> Vec ((stX + n) + 1) a -> Vec (n + 1) b -- | 2-dimensional stencil computations -- -- "stencil2d stY stX f xss", where xss is a -- matrix of stY + m rows of stX + n elements, applies the -- stencil computation f on: (m + 1) * (n + 1) overlapping -- (2D) windows of stY rows of stX elements, drawn from -- xss. The result matrix has m + 1 rows of n + 1 -- elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
-- --
--   >>> :t stencil2d d2 d2 (sum . map sum) xss
--   stencil2d d2 d2 (sum . map sum) xss :: Num b => Vec 3 (Vec 3 b)
--   
-- --
--   >>> stencil2d d2 d2 (sum . map sum) xss
--   (14 :> 18 :> 22 :> Nil) :> (30 :> 34 :> 38 :> Nil) :> (46 :> 50 :> 54 :> Nil) :> Nil
--   
stencil2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> (Vec (stY + 1) (Vec (stX + 1) a) -> b) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) b) -- | "windows1d stX xs", where the vector xs has -- stX + n elements, returns a vector of n + 1 overlapping -- (1D) windows of xs of length stX. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t windows1d d2 xs
--   windows1d d2 xs :: Num a => Vec 5 (Vec 2 a)
--   
--   >>> windows1d d2 xs
--   (1 :> 2 :> Nil) :> (2 :> 3 :> Nil) :> (3 :> 4 :> Nil) :> (4 :> 5 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
windows1d :: KnownNat n => SNat (stX + 1) -> Vec ((stX + n) + 1) a -> Vec (n + 1) (Vec (stX + 1) a) -- | "windows2d stY stX xss", where matrix xss has -- stY + m rows of stX + n, returns a matrix of m+1 -- rows of n+1 elements. The elements of this new matrix are the -- overlapping (2D) windows of xss, where every window has -- stY rows of stX elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
--   >>> :t windows2d d2 d2 xss
--   windows2d d2 d2 xss :: Num a => Vec 3 (Vec 3 (Vec 2 (Vec 2 a)))
--   
--   >>> windows2d d2 d2 xss
--   (((1 :> 2 :> Nil) :> (5 :> 6 :> Nil) :> Nil) :> ((2 :> 3 :> Nil) :> (6 :> 7 :> Nil) :> Nil) :> ((3 :> 4 :> Nil) :> (7 :> 8 :> Nil) :> Nil) :> Nil) :> (((5 :> 6 :> Nil) :> (9 :> 10 :> Nil) :> Nil) :> ((6 :> 7 :> Nil) :> (10 :> 11 :> Nil) :> Nil) :> ((7 :> 8 :> Nil) :> (11 :> 12 :> Nil) :> Nil) :> Nil) :> (((9 :> 10 :> Nil) :> (13 :> 14 :> Nil) :> Nil) :> ((10 :> 11 :> Nil) :> (14 :> 15 :> Nil) :> Nil) :> ((11 :> 12 :> Nil) :> (15 :> 16 :> Nil) :> Nil) :> Nil) :> Nil
--   
windows2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) (Vec (stY + 1) (Vec (stX + 1) a))) -- | Forward permutation specified by an index mapping, ix. The -- result vector is initialized by the given defaults, def, and an -- further values that are permuted into the result are added to the -- current value using the given combination function, f. -- -- The combination function must be associative and -- commutative. permute :: (Enum i, KnownNat n, KnownNat m) => (a -> a -> a) -> Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "backpermute xs is" is equivalent to "map -- (xs !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> backpermute input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
backpermute :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | Copy elements from the source vector, xs, to the destination -- vector according to an index mapping is. This is a forward -- permute operation where a to vector encodes an input to output -- index mapping. Output elements for indices that are not mapped assume -- the value in the default vector def. -- -- For example: -- --
--   >>> let defVec = 0:>0:>0:>0:>0:>0:>0:>0:>0:>Nil
--   
--   >>> let to = 1:>3:>7:>2:>5:>8:>Nil
--   
--   >>> let input = 1:>9:>6:>4:>4:>2:>5:>Nil
--   
--   >>> scatter defVec to input
--   0 :> 1 :> 4 :> 9 :> 0 :> 4 :> 0 :> 6 :> 2 :> Nil
--   
-- -- NB: If the same index appears in the index mapping more than -- once, the latest mapping is chosen. scatter :: (Enum i, KnownNat n, KnownNat m) => Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "gather xs is" is equivalent to "map (xs -- !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> gather input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
gather :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | "interleave d xs" creates a vector: -- --
--   <x_0,x_d,x_(2d),...,x_1,x_(d+1),x_(2d+1),...,x_(d-1),x_(2d-1),x_(3d-1)>
--   
-- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> Nil
--   
--   >>> interleave d3 xs
--   1 :> 4 :> 7 :> 2 :> 5 :> 8 :> 3 :> 6 :> 9 :> Nil
--   
interleave :: (KnownNat n, KnownNat d) => SNat d -> Vec (n * d) a -> Vec (d * n) a -- | Dynamically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeft xs 1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
--   >>> rotateLeft xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateLeft xs (-1)
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateLeftS if you want to rotate left by a -- static amount. rotateLeft :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Dynamically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRight xs 1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
--   >>> rotateRight xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateRight xs (-1)
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateRightS if you want to rotate right by a -- static amount. rotateRight :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Statically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeftS xs d1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateLeft if you want to rotate left by a -- dynamic amount. rotateLeftS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Statically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRightS xs d1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateRight if you want to rotate right by a -- dynamic amount. rotateRightS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Convert a vector to a list. -- --
--   >>> toList (1:>2:>3:>Nil)
--   [1,2,3]
--   
-- -- NB: This function is not synthesizable toList :: Vec n a -> [a] -- | Create a vector literal from a list literal. -- --
--   $(listToVecTH [1::Signed 8,2,3,4,5]) == (8:>2:>3:>4:>5:>Nil) :: Vec 5 (Signed 8)
--   
-- --
--   >>> [1 :: Signed 8,2,3,4,5]
--   [1,2,3,4,5]
--   
--   >>> $(listToVecTH [1::Signed 8,2,3,4,5])
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
listToVecTH :: Lift a => [a] -> ExpQ -- | Vector as a Proxy for Nat asNatProxy :: Vec n a -> Proxy n -- | Length of a Vector as an SNat value lengthS :: KnownNat n => Vec n a -> SNat n -- | What you should use when your vector functions are too strict in their -- arguments. -- --

doctests setup

-- --
--   >>> let compareSwapL a b = if a < b then (a,b) else (b,a)
--   
--   >>> :{
--   let sortVL :: (Ord a, KnownNat (n + 1)) => Vec ((n + 1) + 1) a -> Vec ((n + 1) + 1) a
--       sortVL xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith compareSwapL (lazyV lefts) rights
--   :}
--   
-- --
--   >>> :{
--   let sortV_flip xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith (flip compareSwapL) rights lefts
--   :}
--   
-- --

Example usage

-- -- For example: -- --
--   -- Bubble sort for 1 iteration
--   sortV xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL lefts rights
--   
--   -- Compare and swap
--   compareSwapL a b = if a < b then (a,b)
--                               else (b,a)
--   
-- -- Will not terminate because zipWith is too strict in its second -- argument. -- -- In this case, adding lazyV on zipWiths second argument: -- --
--   sortVL xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL (lazyV lefts) rights
--   
-- -- Results in a successful computation: -- --
--   >>> sortVL (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: There is also a solution using flip, but it slightly -- obfuscates the meaning of the code: -- --
--   sortV_flip xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith (flip compareSwapL) rights lefts
--   
-- --
--   >>> sortV_flip (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
lazyV :: KnownNat n => Vec n a -> Vec n a -- | A dependently typed fold. -- --

doctests setup

-- --
--   >>> :seti -fplugin GHC.TypeLits.Normalise
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply (Append m a) l = Vec (l + m) a
--   
--   >>> let append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- --

Example usage

-- -- Using lists, we can define append (a.k.a. -- Data.List.++) in terms of -- Data.List.foldr: -- --
--   >>> import qualified Data.List
--   
--   >>> let append xs ys = Data.List.foldr (:) ys xs
--   
--   >>> append [1,2] [3,4]
--   [1,2,3,4]
--   
-- -- However, when we try to do the same for Vec, by defining -- append' in terms of Clash.Sized.Vector.foldr: -- --
--   append' xs ys = foldr (:>) ys xs
--   
-- -- we get a type error: -- --
--   >>> let append' xs ys = foldr (:>) ys xs
--   
--   <interactive>:...
--       • Occurs check: cannot construct the infinite type: ... ~ ... + 1
--         Expected type: a -> Vec ... a -> Vec ... a
--           Actual type: a -> Vec ... a -> Vec (... + 1) a
--       • In the first argument of ‘foldr’, namely ‘(:>)’
--         In the expression: foldr (:>) ys xs
--         In an equation for ‘append'’: append' xs ys = foldr (:>) ys xs
--       • Relevant bindings include
--           ys :: Vec ... a (bound at ...)
--           append' :: Vec n a -> Vec ... a -> Vec ... a
--             (bound at ...)
--   
-- -- The reason is that the type of foldr is: -- --
--   >>> :t foldr
--   foldr :: (a -> b -> b) -> b -> Vec n a -> b
--   
-- -- While the type of (:>) is: -- --
--   >>> :t (:>)
--   (:>) :: a -> Vec n a -> Vec (n + 1) a
--   
-- -- We thus need a fold function that can handle the growing -- vector type: dfold. Compared to foldr, dfold -- takes an extra parameter, called the motive, that allows the -- folded function to have an argument and result type that -- depends on the current length of the vector. Using -- dfold, we can now correctly define append': -- --
--   import Data.Singletons
--   import Data.Proxy
--   
--   data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   type instance Apply (Append m a) l = Vec (l + m) a
--   
--   append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- -- We now see that append' has the appropriate type: -- --
--   >>> :t append'
--   append' :: KnownNat k => Vec k a -> Vec m a -> Vec (k + m) a
--   
-- -- And that it works: -- --
--   >>> append' (1 :> 2 :> Nil) (3 :> 4 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: "dfold m f z xs" creates a linear -- structure, which has a depth, or delay, of O(length -- xs). Look at dtfold for a dependently typed fold -- that produces a structure with a depth of O(log_2(length -- xs)). dfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (forall l. SNat l -> a -> (p @@ l) -> p @@ (l + 1)) -> (p @@ 0) -> Vec k a -> p @@ k -- | A combination of dfold and fold: a dependently -- typed fold that reduces a vector in a tree-like structure. -- --

doctests setup

-- --
--   >>> :seti -XUndecidableInstances
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data IIndex (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply IIndex l = Index ((2^l)+1)
--   
--   >>> :{
--   let populationCount' :: (KnownNat k, KnownNat (2^k)) => BitVector (2^k) -> Index ((2^k)+1)
--       populationCount' bv = dtfold (Proxy @IIndex)
--                                    fromIntegral
--                                    (\_ x y -> add x y)
--                                    (bv2v bv)
--   :}
--   
-- --

Example usage

-- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- sum, because it gives a nice (log2(n)) tree-structure -- of adders: -- --
--   populationCount :: (KnownNat (n+1), KnownNat (n+2))
--                   => BitVector (n+1) -> Index (n+2)
--   populationCount = sum . map fromIntegral . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (n+2) -> Index (n+2) -> Index (n+2).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of addes: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (n+1), KnownNat (n+2))
--                        => BitVector (n+1) -> Index (n+2)
--       populationCount' = fold add . map fromIntegral . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘((n + 2) + (n + 2)) - 1’ with ‘n + 2’
--         Expected type: Index (n + 2) -> Index (n + 2) -> Index (n + 2)
--           Actual type: Index (n + 2)
--                        -> Index (n + 2) -> AResult (Index (n + 2)) (Index (n + 2))
--       • In the first argument of ‘fold’, namely ‘add’
--         In the first argument of ‘(.)’, namely ‘fold add’
--         In the expression: fold add . map fromIntegral . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (n + 1) -> Index (n + 2)
--             (bound at ...)
--   
-- -- because fold expects a function of type "a -> a -> -- a", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   import Data.Proxy
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = dtfold (Proxy @IIndex)
--                                fromIntegral
--                                (\_ x y -> add x y)
--                                (bv2v bv)
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
-- -- Some final remarks: -- -- -- -- NB: The depth, or delay, of the structure produced by -- "dtfold m f g xs" is O(log_2(length -- xs)). dtfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> Vec (2 ^ k) a -> p @@ k -- | Specialised version of dfold that builds a triangular -- computational structure. -- --

doctests setup

-- --
--   >>> let compareSwap a b = if a > b then (a,b) else (b,a)
--   
--   >>> let insert y xs = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   
--   >>> let insertionSort = vfold (const insert)
--   
-- --

Example usage

-- --
--   compareSwap a b = if a > b then (a,b) else (b,a)
--   insert y xs     = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   insertionSort   = vfold (const insert)
--   
-- -- Builds a triangular structure of compare and swaps to sort a row. -- --
--   >>> insertionSort (7 :> 3 :> 9 :> 1 :> Nil)
--   1 :> 3 :> 7 :> 9 :> Nil
--   
-- -- The circuit layout of insertionSort, build using -- vfold, is: -- vfold :: forall k a b. KnownNat k => (forall l. SNat l -> a -> Vec l b -> Vec (l + 1) b) -> Vec k a -> Vec k b -- | The largest element of a non-empty vector maximum :: Ord a => Vec (n + 1) a -> a -- | The least element of a non-empty vector minimum :: Ord a => Vec (n + 1) a -> a -- | Apply a function to every element of a vector and the element's -- position (as an SNat value) in the vector. -- --
--   >>> let rotateMatrix = smap (flip rotateRightS)
--   
--   >>> let xss = (1:>2:>3:>Nil):>(1:>2:>3:>Nil):>(1:>2:>3:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> Nil
--   
--   >>> rotateMatrix xss
--   (1 :> 2 :> 3 :> Nil) :> (3 :> 1 :> 2 :> Nil) :> (2 :> 3 :> 1 :> Nil) :> Nil
--   
smap :: forall k a b. KnownNat k => (forall l. SNat l -> a -> b) -> Vec k a -> Vec k b concatBitVector# :: forall n m. (KnownNat n, KnownNat m) => Vec n (BitVector m) -> BitVector (n * m) unconcatBitVector# :: forall n m. (KnownNat n, KnownNat m) => BitVector (n * m) -> Vec n (BitVector m) -- | Convert a Vec of Bits to a BitVector. -- --
--   >>> let x = (0:>0:>0:>1:>0:>0:>1:>0:>Nil) :: Vec 8 Bit
--   
--   >>> x
--   0 :> 0 :> 0 :> 1 :> 0 :> 0 :> 1 :> 0 :> Nil
--   
--   >>> v2bv x
--   0b0001_0010
--   
v2bv :: KnownNat n => Vec n Bit -> BitVector n -- | Evaluate all elements of a vector to WHNF, returning the second -- argument seqV :: KnownNat n => Vec n a -> b -> b infixr 0 `seqV` -- | Evaluate all elements of a vector to WHNF forceV :: KnownNat n => Vec n a -> Vec n a -- | Evaluate all elements of a vector to WHNF, returning the second -- argument. Does not propagate XExceptions. seqVX :: KnownNat n => Vec n a -> b -> b infixr 0 `seqVX` -- | Evaluate all elements of a vector to WHNF. Does not propagate -- XExceptions. forceVX :: KnownNat n => Vec n a -> Vec n a -- | Representable types of kind *. This class is derivable in GHC -- with the DeriveGeneric flag on. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class Generic a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) -- | This module can automatically generate TopEntity definitions from -- Clash.NamedTypes annotations. Annotations involving data/type -- families must be inspected for correctness. Not all cases can be -- handled with automatic generation due to the difficulty of type -- manipulation in template Haskell. In particular annotations -- inside the following is unlikely to work: -- -- -- -- See Clash.Tests.TopEntityGeneration for more examples. -- --
--   import Clash.Annotations.TH
--   
--   data Named
--     = Named
--     { name1 :: "named1" ::: BitVector 3
--     , name2 :: "named2" ::: BitVector 5
--     }
--   
--   topEntity :: "tup1" ::: Signal System (Int, Bool)
--             -> "tup2" ::: (Signal System Int, Signal System Bool)
--             -> "tup3" ::: Signal System ("int":::Int, "bool":::Bool)
--             -> "tup4" ::: ("int":::Signal System Int, "bool":::Signal System Bool)
--             -> "custom" ::: Signal System Named
--             -> "outTup" ::: Signal System ("outint":::Int, "outbool":::Bool)
--   topEntity = undefined
--   makeTopEntity 'topEntity
--   -- ===>
--   --  
--   
module Clash.Annotations.TH -- | Automatically create a TopEntity for a given -- Name. The name of the generated RTL entity will be the -- name of the function that has been specified; e.g. -- makeTopEntity 'foobar will generate a foobar -- module. -- -- The function arguments and return values of the function specified by -- the given Name must be annotated with -- (:::). This annotation provides the given name of the -- port. makeTopEntity :: Name -> DecsQ -- | Automatically create a TopEntity for a given -- Name, using the given String to -- specify the name of the generated RTL entity. -- -- The function arguments and return values of the function specified by -- the given Name must be annotated with -- (:::). This annotation provides the given name of the -- port. makeTopEntityWithName :: Name -> String -> DecsQ -- | Wrap a TopEntity expression in an annotation pragma makeTopEntityWithName' :: Name -> Maybe String -> DecQ -- | Return a typed expression for a TopEntity of a given -- (Name, Type). buildTopEntity :: Maybe String -> (Name, Type) -> TExpQ TopEntity -- | Return a typed 'Maybe TopEntity' expression given a Name. This -- will return an TExp of Nothing if TopEntity -- generation failed. maybeBuildTopEntity :: Maybe String -> Name -> Q (TExp (Maybe TopEntity)) -- | Turn the Name of a value to a (Name, -- Type) getNameBinding :: Name -> Q (Name, Type) instance Data.Traversable.Traversable Clash.Annotations.TH.TypeF instance Data.Foldable.Foldable Clash.Annotations.TH.TypeF instance GHC.Base.Functor Clash.Annotations.TH.TypeF instance GHC.Base.Functor Clash.Annotations.TH.Naming instance GHC.Classes.Eq Clash.Annotations.TH.ClockType instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Clash.Annotations.TH.Naming a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Clash.Annotations.TH.Naming a) instance Data.Functor.Foldable.Recursive Language.Haskell.TH.Syntax.Type instance Data.Functor.Foldable.Corecursive Language.Haskell.TH.Syntax.Type -- | This module contains: -- -- module Clash.Annotations.BitRepresentation.Deriving deriveAnnotation :: Derivator -> Q Type -> Q [Dec] -- | Derives BitPack instances for given type. Will account for custom bit -- representation annotations in the module where the splice is ran. Note -- that the generated instance might conflict with existing -- implementations (for example, an instance for Maybe a exists, -- yielding conflicts for any alternative implementations). -- -- Usage: -- --
--   data Color = R | G | B
--   {-# ANN module (DataReprAnn
--                     $(liftQ [t|Color|])
--                     2
--                     [ ConstrRepr 'R 0b11 0b00 []
--                     , ConstrRepr 'G 0b11 0b01 []
--                     , ConstrRepr 'B 0b11 0b10 []
--                     ]) #-}
--   deriveBitPack [t| Color |]
--   
--   data MaybeColor = JustColor Color
--                   | NothingColor deriving (Generic,BitPack)
--   
-- -- NB: Because of the way template haskell works the order here -- matters, if you try to derive MaybeColor before deriveBitPack Color it -- will complain about missing an instance BitSize Color. deriveBitPack :: Q Type -> Q [Dec] -- | Derives bit representation corresponding to the default manner in -- which Clash stores types. deriveDefaultAnnotation :: Q Type -> Q [Dec] derivePackedAnnotation :: Q Type -> Q [Dec] -- | Derive a compactly represented version of Maybe a. derivePackedMaybeAnnotation :: DataReprAnn -> Q [Dec] -- | Derives bit representation corresponding to the default manner in -- which BlueSpec stores types. deriveBlueSpecAnnotation :: Q Type -> Q [Dec] -- | Derives bit representation corresponding to the default manner in -- which Clash stores types. defaultDerivator :: Derivator -- | Derives bit representation corresponding to the default manner in -- which BlueSpec stores types. blueSpecDerivator :: Derivator -- | This derivator tries to distribute its constructor bits over space -- left by the difference in constructor sizes. Example: -- --
--   type SmallInt = Unsigned 2
--   
--   data Train
--      = Passenger SmallInt
--      | Freight SmallInt SmallInt
--      | Maintenance
--      | Toy
--   
-- -- The packed representation of this data type needs only a single -- constructor bit. The first bit discriminates between Freight -- and non-Freight constructors. All other constructors do not -- use their last two bits; the packed representation will store the rest -- of the constructor bits there. packedDerivator :: Derivator packedMaybeDerivator :: DataReprAnn -> Derivator -- | Simple derivators change the (default) way Clash stores data types. It -- assumes no overlap between constructors and fields. simpleDerivator :: ConstructorType -> FieldsType -> Derivator -- | In Haskell apply the first argument to the second argument, in HDL -- just return the second argument. -- -- This is used in the generated pack/unpack to not do anything in HDL. dontApplyInHDL :: (a -> b) -> a -> b -- | Indicates how to pack constructor for simpleDerivator data ConstructorType -- | First constructor will be encoded as 0b0, the second as 0b1, the third -- as 0b10, etc. Binary :: ConstructorType -- | Reserve a single bit for each constructor marker. OneHot :: ConstructorType -- | Indicates how to pack (constructor) fields for simpleDerivator data FieldsType -- | Store fields of different constructors at (possibly) overlapping bit -- positions. That is, a data type with two constructors with each two -- fields of each one bit will take two bits for its whole -- representation (plus constructor bits). Overlap is left-biased, i.e. -- don't care bits are padded to the right. -- -- This is the default behavior of Clash. OverlapL :: FieldsType -- | Store fields of different constructors at (possibly) overlapping bit -- positions. That is, a data type with two constructors with each two -- fields of each one bit will take two bits for its whole -- representation (plus constructor bits). Overlap is right biased, i.e. -- don't care bits are padded between between the constructor bits and -- the field bits. OverlapR :: FieldsType -- | Store fields of different constructs at non-overlapping positions. -- That is, a data type with two constructors with each two fields of -- each one bit will take four bits for its whole representation -- (plus constructor bits). Wide :: FieldsType -- | A derivator derives a bit representation given a type type Derivator = Type -> Q DataReprAnnExp -- | DataReprAnn as template haskell expression type DataReprAnnExp = Exp instance Language.Haskell.TH.Syntax.Lift Clash.Annotations.BitRepresentation.Deriving.BitMaskOrigin instance Data.Data.Data Clash.Annotations.BitRepresentation.Deriving.BitMaskOrigin instance GHC.Show.Show Clash.Annotations.BitRepresentation.Deriving.BitMaskOrigin instance Control.DeepSeq.NFData Clash.Annotations.BitRepresentation.Deriving.Bit' instance GHC.Generics.Generic Clash.Annotations.BitRepresentation.Deriving.Bit' instance GHC.Classes.Eq Clash.Annotations.BitRepresentation.Deriving.Bit' instance GHC.Show.Show Clash.Annotations.BitRepresentation.Deriving.Bit' -- | Utilities for tracing signals and dumping them in various ways. -- Example usage: -- --
--   import Clash.Prelude hiding (writeFile)
--   import Data.Text.IO  (writeFile)
--   
--   -- | Count and wrap around
--   subCounter :: SystemClockResetEnable => Signal System (Index 3)
--   subCounter = traceSignal1 "sub" counter
--     where
--       counter =
--         register 0 (fmap succ' counter)
--   
--       succ' c
--         | c == maxBound = 0
--         | otherwise     = c + 1
--   
--   -- | Count, but only when my subcounter is wrapping around
--   mainCounter :: SystemClockResetEnable => Signal System (Signed 64)
--   mainCounter = traceSignal1 "main" counter
--     where
--       counter =
--         register 0 (fmap succ' $ bundle (subCounter,counter))
--   
--       succ' (sc, c)
--         | sc == maxBound = c + 1
--         | otherwise      = c
--   
--   -- | Collect traces, and dump them to a VCD file.
--   main :: IO ()
--   main = do
--     let cntrOut = exposeClockResetEnable mainCounter systemClockGen systemResetGen enableGen
--     vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]
--     case vcd of
--       Left msg ->
--         error msg
--       Right contents ->
--         writeFile "mainCounter.vcd" contents
--   
module Clash.Signal.Trace -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceSignal1 :: (BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceVecSignal1 :: (KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceSignal :: forall dom a. (KnownDomain dom, BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceVecSignal :: forall dom a n. (KnownDomain dom, KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Produce a four-state VCD (Value Change Dump) according to IEEE -- 1364-{1995,2001}. This function fails if a trace name contains either -- non-printable or non-VCD characters. -- -- Due to lazy evaluation, the created VCD files might not contain all -- the traces you were expecting. You therefore have to provide a list of -- names you definately want to be dumped in the VCD file. -- -- For example: -- --
--   vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]
--   
-- -- Evaluates cntrOut long enough in order for to guarantee that -- the main, and sub traces end up in the generated VCD -- file. dumpVCD :: NFDataX a => (Int, Int) -> Signal dom a -> [String] -> IO (Either String Text) -- | Dump a number of samples to a replayable bytestring. dumpReplayable :: forall a dom. NFDataX a => Int -> Signal dom a -> String -> IO ByteString -- | Take a serialized signal (dumped with dumpReplayable) and -- convert it back into a signal. Will error if dumped type does not -- match requested type. The first value in the signal that fails to -- decode will stop the decoding process and yield an error. Not that -- this always happens if you evaluate more values than were originally -- dumped. replay :: forall a dom n. (Typeable a, NFDataX a, BitPack a, KnownNat n, n ~ BitSize a) => ByteString -> Either String (Signal dom a) type Period = Int type Changed = Bool type Value = (Natural, Natural) type Width = Int type TraceMap = Map String (TypeRepBS, Period, Width, [Value]) -- | Serialized TypeRep we need to store for dumpReplayable / replay type TypeRepBS = ByteString -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. traceSignal# :: forall dom a. (BitPack a, NFDataX a, Typeable a) => IORef TraceMap -> Int -> String -> Signal dom a -> IO (Signal dom a) -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. traceVecSignal# :: forall dom n a. (KnownNat n, BitPack a, NFDataX a, Typeable a) => IORef TraceMap -> Int -> String -> Signal dom (Vec (n + 1) a) -> IO (Signal dom (Vec (n + 1) a)) -- | Same as dumpVCD, but supplied with a custom tracemap dumpVCD# :: NFDataX a => IORef TraceMap -> (Int, Int) -> Signal dom a -> [String] -> IO (Either String Text) -- | Same as dumpVCD, but supplied with a custom tracemap and a -- custom timestamp dumpVCD## :: (Int, Int) -> TraceMap -> UTCTime -> Either String Text -- | Keep evaluating given signal until all trace names are present. waitForTraces# :: NFDataX a => IORef TraceMap -> Signal dom a -> [String] -> IO () -- | Map of traces used by the non-internal trace and dumpvcd functions. traceMap# :: IORef TraceMap -- | This module defines the explicitly clocked counterparts of the -- functions defined in Clash.Prelude. module Clash.Explicit.Prelude -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   import qualified Data.List as L
--   
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = mealy clk rst en macT 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy clk rst en macT 0 (bundle (a,x))
--       s2 = mealy clk rst en macT 0 (bundle (b,y))
--   
mealy :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | Create a synchronous function from a combinational function describing -- a mealy machine using the state monad. This can be particularly useful -- when combined with lenses or optics to replicate imperative -- algorithms. -- --
--   data DelayState = DelayState
--     { _history    :: Vec 4 Int
--     , _untilValid :: Index 4
--     }
--     deriving (Generic, NFDataX)
--   makeLenses ''DelayState
--   
--   initialDelayState = DelayState (repeat 0) maxBound
--   
--   delayS :: Int -> State DelayState (Maybe Int)
--   delayS n = do
--     history   %= (n +>>)
--     remaining <- use untilValid
--     if remaining > 0
--     then do
--        untilValid -= 1
--        return Nothing
--      else do
--        out <- uses history last
--        return (Just out)
--   
--   delayTop ::KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int -> Signal dom (Maybe Int))
--   delayTop clk rst en = mealyS clk rst en delayS initialDelayState
--   
-- --
--   >>> L.take 7 $ simulate (delayTop systemClockGen systemResetGen enableGen) [-100,1,2,3,4,5,6,7,8]
--   [Nothing,Nothing,Nothing,Nothing,Just 1,Just 2,Just 3]
--   
mealyS :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool,Int) -> (Int,(Int,Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy clk rst en f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy clk rst en f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB clk rst en f 0 (a,b)
--       (i2,b2) = mealyB clk rst en f 3 (c,i1)
--   
mealyB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | A version of mealyS that does automatic Bundleing, see -- mealyB for details. mealySB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> Signal dom (Int, Int)
--     -> Signal dom Int
--   mac clk rst en = moore clk rst en macT id 0
--   
-- --
--   >>> simulate (mac systemClockGen systemResetGen enableGen) [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Enable dom
--     -> (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac clk rst en (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore clk rst en macT id 0 (bundle (a,x))
--       s2 = moore clk rst en macT id 0 (bundle (b,y))
--   
moore :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore clk rst en t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore clk rst en t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g clk rst en a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB clk rst en t o 0 (a,b)
--       (i2,b2) = mooreB clk rst en t o 3 (c,i1)
--   
mooreB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a register function for product-type like signals (e.g. -- (Signal a, Signal b)) -- --
--   rP :: Clock dom -> Reset dom -> Enable dom
--      -> (Signal dom Int, Signal dom Int)
--      -> (Signal dom Int, Signal dom Int)
--   rP clk rst en = registerB clk rst en (8,8)
--   
-- --
--   >>> simulateB (rP systemClockGen systemResetGen enableGen) [(1,1),(1,1),(2,2),(3,3)] :: [(Int,Int)]
--   [(8,8),(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
registerB :: (KnownDomain dom, NFDataX a, Bundle a) => Clock dom -> Reset dom -> Enable dom -> a -> Unbundled dom a -> Unbundled dom a -- | Synchronizer based on two sequentially connected flip-flops. -- -- dualFlipFlopSynchronizer :: (NFDataX a, KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Reset dom2 -> Enable dom2 -> a -> Signal dom1 a -> Signal dom2 a -- | Synchronizer implemented as a FIFO around a synchronous RAM. Based on -- the design described in Clash.Tutorial#multiclock, which is -- itself based on the design described in -- http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf. -- However, this FIFO uses a synchronous dual-ported RAM which, unlike -- those designs using RAM with an asynchronous read port, is nearly -- guaranteed to actually synthesize into one of the dual-ported RAMs -- found on most FPGAs. -- -- NB: This synchronizer can be used for -- word-synchronization. NB: This synchronizer will only -- work safely when you set up the proper bus skew and maximum delay -- constraints inside your synthesis tool for the clock domain crossings -- of the gray pointers. asyncFIFOSynchronizer :: (KnownDomain wdom, KnownDomain rdom, 2 <= addrSize, NFDataX a) => SNat addrSize -> Clock wdom -> Clock rdom -> Reset wdom -> Reset rdom -> Enable wdom -> Enable rdom -> Signal rdom Bool -> Signal wdom (Maybe a) -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool) -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRom :: (KnownNat n, Enum addr, NFDataX a) => Vec n a -> addr -> a -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomPow2 :: (KnownNat n, NFDataX a) => Vec (2 ^ n) a -> Unsigned n -> a -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: (KnownDomain dom, KnownNat n, NFDataX a, Enum addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: (KnownDomain dom, KnownNat n, NFDataX a) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRomBlob :: Enum addr => MemBlob n m -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomBlobPow2 :: KnownNat n => MemBlob (2 ^ n) m -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (KnownDomain dom, Enum addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | An asynchronous/combinational ROM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n) => FilePath -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- romFile :: (KnownNat m, Enum addr, KnownDomain dom) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- -- TODO: table -- --

See also:

-- -- romFilePow2 :: forall dom n m. (KnownNat m, KnownNat n, KnownDomain dom) => Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> SNat n -> Signal rdom addr -> Signal wdom (Maybe (addr, a)) -> Signal rdom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: forall wdom rdom n a. (KnownNat n, HasCallStack, KnownDomain wdom, KnownDomain rdom, NFDataX a) => Clock wdom -> Clock rdom -> Enable wdom -> Signal rdom (Unsigned n) -> Signal wdom (Maybe (Unsigned n, a)) -> Signal rdom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: Clock  dom
--     -> Enable  dom
--     -> Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 clk en = blockRam clk en (replicate d40 1)
--   
blockRam :: (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: Clock dom
--     -> Enable dom
--     -> Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 clk en = blockRamPow2 clk en (replicate d32 1)
--   
blockRamPow2 :: (KnownDomain dom, HasCallStack, NFDataX a, KnownNat n) => Clock dom -> Enable dom -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | A version of blockRam that has no default values set. May be -- cleared to an arbitrary state using a reset function. blockRamU :: forall n dom a r addr. (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => Clock dom -> Reset dom -> Enable dom -> ResetStrategy r -> SNat n -> (Index n -> a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | A version of blockRam that is initialized with the same value -- on all memory positions blockRam1 :: forall n dom a r addr. (KnownDomain dom, HasCallStack, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => Clock dom -> Reset dom -> Enable dom -> ResetStrategy r -> SNat n -> a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a data ResetStrategy (r :: Bool) [ClearOnReset] :: ResetStrategy 'True [NoClearOnReset] :: ResetStrategy 'False -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (KnownDomain dom, Enum addr, NFDataX addr) => Clock dom -> Enable dom -> MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (KnownDomain dom, KnownNat n) => Clock dom -> Enable dom -> MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | Create a block RAM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFile :: (KnownDomain dom, KnownNat m, Enum addr, NFDataX addr, HasCallStack) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFilePow2 :: forall dom n m. (KnownDomain dom, KnownNat m, KnownNat n, HasCallStack) => Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Create a read-after-write block RAM from a read-before-write one readNew :: (KnownDomain dom, NFDataX a, Eq addr) => Clock dom -> Reset dom -> Enable dom -> (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs domA domB a. (HasCallStack, KnownNat nAddrs, KnownDomain domA, KnownDomain domB, NFDataX a) => Clock domA -> Clock domB -> Signal domA (RamOp nAddrs a) -> Signal domB (RamOp nAddrs a) -> (Signal domA a, Signal domB a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a -- | Give a window over a Signal -- -- @ window4 window :: (KnownNat n, KnownDomain dom, NFDataX a, Default a) => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Vec (n + 1) (Signal dom a) -- | Give a delayed window over a Signal -- --
--   windowD3
--     :: KnownDomain dom
--     -> Clock dom
--     -> Enable dom
--     -> Reset dom
--     -> Signal dom Int
--     -> Vec 3 (Signal dom Int)
--   windowD3 = windowD
--   
-- --
--   >>> simulateB (windowD3 systemClockGen resetGen enableGen) [1::Int,1,2,3,4] :: [Vec 3 Int]
--   [0 :> 0 :> 0 :> Nil,0 :> 0 :> 0 :> Nil,1 :> 0 :> 0 :> Nil,2 :> 1 :> 0 :> Nil,3 :> 2 :> 1 :> Nil,4 :> 3 :> 2 :> Nil,...
--   ...
--   
windowD :: (KnownNat n, NFDataX a, Default a, KnownDomain dom) => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Vec (n + 1) (Signal dom a) -- | Give a pulse when the Signal goes from minBound to -- maxBound isRising :: (KnownDomain dom, NFDataX a, Bounded a, Eq a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom Bool -- | Give a pulse when the Signal goes from maxBound to -- minBound isFalling :: (KnownDomain dom, NFDataX a, Bounded a, Eq a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom Bool -- | Give a pulse every n clock cycles. This is a useful helper -- function when combined with functions like regEn or -- mux, in order to delay a register by a known amount. riseEvery :: forall dom n. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> SNat n -> Signal dom Bool -- | Oscillate a Bool for a given number of cycles, given -- the starting state. oscillate :: forall dom n. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Bool -> SNat n -> Signal dom Bool -- | Compares the first two Signals for equality and logs a warning -- when they are not equal. The second Signal is considered the -- expected value. This function simply returns the third Signal -- unaltered as its result. This function is used by -- outputVerifier. -- --

Usage in clashi

-- -- NB: When simulating a component that uses assert in -- clashi, usually, the warnings are only logged the first time -- the component is simulated. Issuing :reload in -- clashi will discard the cached result of the computation, and -- warnings will once again be emitted. -- -- NB: This function can be used in synthesizable designs. assert :: (KnownDomain dom, Eq a, ShowX a) => Clock dom -> Reset dom -> String -> Signal dom a -> Signal dom a -> Signal dom b -> Signal dom b -- | Example: -- --
--   testInput
--     :: KnownDomain dom
--     => Clock dom
--     -> Reset dom
--     -> Signal dom Int
--   testInput clk rst = stimuliGenerator clk rst $(listToVecTH [(1::Int),3..21])
--   
-- --
--   >>> sampleN 14 (testInput systemClockGen resetGen)
--   [1,1,3,5,7,9,11,13,15,17,19,21,21,21]
--   
stimuliGenerator :: forall l dom a. (KnownNat l, KnownDomain dom) => Clock dom -> Reset dom -> Vec l a -> Signal dom a -- | Same as outputVerifier but used in cases where the test bench -- domain and the domain of the circuit under test are the same. outputVerifier' :: forall l a dom. (KnownNat l, KnownDomain dom, Eq a, ShowX a, 1 <= l) => Clock dom -> Reset dom -> Vec l a -> Signal dom a -> Signal dom Bool -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceSignal1 :: (BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceVecSignal1 :: (KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceSignal :: forall dom a. (KnownDomain dom, BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceVecSignal :: forall dom a n. (KnownDomain dom, KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Produce a four-state VCD (Value Change Dump) according to IEEE -- 1364-{1995,2001}. This function fails if a trace name contains either -- non-printable or non-VCD characters. -- -- Due to lazy evaluation, the created VCD files might not contain all -- the traces you were expecting. You therefore have to provide a list of -- names you definately want to be dumped in the VCD file. -- -- For example: -- --
--   vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]
--   
-- -- Evaluates cntrOut long enough in order for to guarantee that -- the main, and sub traces end up in the generated VCD -- file. dumpVCD :: NFDataX a => (Int, Int) -> Signal dom a -> [String] -> IO (Either String Text) -- | Fixed size vectors. -- -- data Vec :: Nat -> Type -> Type [Nil] :: Vec 0 a [Cons] :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the head of a vector. -- --
--   >>> 3:>4:>5:>Nil
--   3 :> 4 :> 5 :> Nil
--   
--   >>> let x = 3:>4:>5:>Nil
--   
--   >>> :t x
--   x :: Num a => Vec 3 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (x :> y :> _) = x + y
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   7
--   
-- -- Also in conjunctions with (:<): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:>) :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the tail of a vector. -- --
--   >>> (3:>4:>5:>Nil) :< 1
--   3 :> 4 :> 5 :> 1 :> Nil
--   
--   >>> let x = (3:>4:>5:>Nil) :< 1
--   
--   >>> :t x
--   x :: Num a => Vec 4 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (_ :< y :< x) = y + x
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   13
--   
-- -- Also in conjunctions with (:>): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:<) :: Vec n a -> a -> Vec (n + 1) a infixr 5 :> infixl 5 :< infixr 5 `Cons` -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a vector, reduces -- the vector using the binary operator, from left to right: -- --
--   foldl f z (x1 :> x2 :> ... :> xn :> Nil) == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   foldl f z Nil                            == z
--   
-- --
--   >>> foldl (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldl :: forall b a n. (b -> a -> b) -> b -> Vec n a -> b -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a vector, reduces -- the vector using the binary operator, from right to left: -- --
--   foldr f z (x1 :> ... :> xn1 :> xn :> Nil) == x1 `f` (... (xn1 `f` (xn `f` z))...)
--   foldr r z Nil                             == z
--   
-- --
--   >>> foldr (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   1.875
--   
-- -- "foldr f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldr :: (a -> b -> b) -> b -> Vec n a -> b -- | "map f xs" is the vector obtained by applying f -- to each element of xs, i.e., -- --
--   map f (x1 :> x2 :>  ... :> xn :> Nil) == (f x1 :> f x2 :> ... :> f xn :> Nil)
--   
-- -- and corresponds to the following circuit layout: -- map :: (a -> b) -> Vec n a -> Vec n b -- | Convert a BitVector to a Vec of Bits. -- --
--   >>> let x = 6 :: BitVector 8
--   
--   >>> x
--   0b0000_0110
--   
--   >>> bv2v x
--   0 :> 0 :> 0 :> 0 :> 0 :> 1 :> 1 :> 0 :> Nil
--   
bv2v :: KnownNat n => BitVector n -> Vec n Bit -- | To be used as the motive p for dfold, when the f -- in "dfold p f" is a variation on (:>), e.g.: -- --
--   map' :: forall n a b . KnownNat n => (a -> b) -> Vec n a -> Vec n b
--   map' f = dfold (Proxy @(VCons b)) (_ x xs -> f x :> xs)
--   
data VCons (a :: Type) (f :: TyFun Nat Type) :: Type traverse# :: forall a f b n. Applicative f => (a -> f b) -> Vec n a -> f (Vec n b) -- | Create a vector of one element -- --
--   >>> singleton 5
--   5 :> Nil
--   
singleton :: a -> Vec 1 a -- | Extract the first element of a vector -- --
--   >>> head (1:>2:>3:>Nil)
--   1
--   
-- --
--   >>> head Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘head’, namely ‘Nil’
--         In the expression: head Nil
--         In an equation for ‘it’: it = head Nil
--   
head :: Vec (n + 1) a -> a -- | Extract the elements after the head of a vector -- --
--   >>> tail (1:>2:>3:>Nil)
--   2 :> 3 :> Nil
--   
-- --
--   >>> tail Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘tail’, namely ‘Nil’
--         In the expression: tail Nil
--         In an equation for ‘it’: it = tail Nil
--   
tail :: Vec (n + 1) a -> Vec n a -- | Extract the last element of a vector -- --
--   >>> last (1:>2:>3:>Nil)
--   3
--   
-- --
--   >>> last Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘last’, namely ‘Nil’
--         In the expression: last Nil
--         In an equation for ‘it’: it = last Nil
--   
last :: Vec (n + 1) a -> a -- | Extract all the elements of a vector except the last element -- --
--   >>> init (1:>2:>3:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> init Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘init’, namely ‘Nil’
--         In the expression: init Nil
--         In an equation for ‘it’: it = init Nil
--   
init :: Vec (n + 1) a -> Vec n a -- | Shift in elements to the head of a vector, bumping out elements at the -- tail. The result is a tuple containing: -- -- -- --
--   >>> shiftInAt0 (1 :> 2 :> 3 :> 4 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> 0 :> 1 :> 2 :> Nil,3 :> 4 :> Nil)
--   
--   >>> shiftInAt0 (1 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> Nil,0 :> 1 :> Nil)
--   
shiftInAt0 :: KnownNat n => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift in element to the tail of a vector, bumping out elements at the -- head. The result is a tuple containing: -- -- -- --
--   >>> shiftInAtN (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> Nil)
--   (3 :> 4 :> 5 :> 6 :> Nil,1 :> 2 :> Nil)
--   
--   >>> shiftInAtN (1 :> Nil) (2 :> 3 :> Nil)
--   (3 :> Nil,1 :> 2 :> Nil)
--   
shiftInAtN :: KnownNat m => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Add an element to the head of a vector, and extract all but the last -- element. -- --
--   >>> 1 +>> (3:>4:>5:>Nil)
--   1 :> 3 :> 4 :> Nil
--   
--   >>> 1 +>> Nil
--   Nil
--   
(+>>) :: KnownNat n => a -> Vec n a -> Vec n a infixr 4 +>> -- | Add an element to the tail of a vector, and extract all but the first -- element. -- --
--   >>> (3:>4:>5:>Nil) <<+ 1
--   4 :> 5 :> 1 :> Nil
--   
--   >>> Nil <<+ 1
--   Nil
--   
(<<+) :: Vec n a -> a -> Vec n a infixl 4 <<+ -- | Shift m elements out from the head of a vector, filling up the -- tail with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFrom0 d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (3 :> 4 :> 5 :> 0 :> 0 :> Nil,1 :> 2 :> Nil)
--   
shiftOutFrom0 :: (Default a, KnownNat m) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Shift m elements out from the tail of a vector, filling up the -- head with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFromN d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (0 :> 0 :> 1 :> 2 :> 3 :> Nil,4 :> 5 :> Nil)
--   
shiftOutFromN :: (Default a, KnownNat n) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Append two vectors. -- --
--   >>> (1:>2:>3:>Nil) ++ (7:>8:>Nil)
--   1 :> 2 :> 3 :> 7 :> 8 :> Nil
--   
(++) :: Vec n a -> Vec m a -> Vec (n + m) a infixr 5 ++ -- | Split a vector into two vectors at the given point. -- --
--   >>> splitAt (SNat :: SNat 3) (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
--   >>> splitAt d3 (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
splitAt :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector into two vectors where the length of the two is -- determined by the context. -- --
--   >>> splitAtI (1:>2:>3:>7:>8:>Nil) :: (Vec 2 Int, Vec 3 Int)
--   (1 :> 2 :> Nil,3 :> 7 :> 8 :> Nil)
--   
splitAtI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) -- | Concatenate a vector of vectors. -- --
--   >>> concat ((1:>2:>3:>Nil) :> (4:>5:>6:>Nil) :> (7:>8:>9:>Nil) :> (10:>11:>12:>Nil) :> Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil
--   
concat :: Vec n (Vec m a) -> Vec (n * m) a -- | Map a function over all the elements of a vector and concatentate the -- resulting vectors. -- --
--   >>> concatMap (replicate d3) (1:>2:>3:>Nil)
--   1 :> 1 :> 1 :> 2 :> 2 :> 2 :> 3 :> 3 :> 3 :> Nil
--   
concatMap :: (a -> Vec m b) -> Vec n a -> Vec (n * m) b -- | Split a vector of (n * m) elements into a vector of "vectors of length -- m", where the length m is given. -- --
--   >>> unconcat d4 (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil) :> (5 :> 6 :> 7 :> 8 :> Nil) :> (9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) -- | Split a vector of (n * m) elements into a vector of "vectors of -- length m", where the length m is determined by the -- context. -- --
--   >>> unconcatI (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil) :: Vec 2 (Vec 6 Int)
--   (1 :> 2 :> 3 :> 4 :> 5 :> 6 :> Nil) :> (7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) -- | Merge two vectors, alternating their elements, i.e., -- --
--   >>> merge (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> 7 :> 8 :> Nil)
--   1 :> 5 :> 2 :> 6 :> 3 :> 7 :> 4 :> 8 :> Nil
--   
merge :: KnownNat n => Vec n a -> Vec n a -> Vec (2 * n) a -- | The elements in a vector in reverse order. -- --
--   >>> reverse (1:>2:>3:>4:>Nil)
--   4 :> 3 :> 2 :> 1 :> Nil
--   
reverse :: Vec n a -> Vec n a -- | Apply a function of every element of a vector and its index. -- --
--   >>> :t imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   imap (+) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Index 4)
--   
--   >>> imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   2 :> 3 :> *** Exception: X: Clash.Sized.Index: result 4 is out of bounds: [0..3]
--   ...
--   
--   >>> imap (\i a -> extend (bitCoerce i) + a) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Unsigned 8)
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- imap :: forall n a b. KnownNat n => (Index n -> a -> b) -> Vec n a -> Vec n b -- | Zip two vectors with a functions that also takes the elements' -- indices. -- --
--   >>> izipWith (\i a b -> i + a + b) (2 :> 2 :> Nil)  (3 :> 3:> Nil)
--   *** Exception: X: Clash.Sized.Index: result 3 is out of bounds: [0..1]
--   ...
--   
--   >>> izipWith (\i a b -> extend (bitCoerce i) + a + b) (2 :> 2 :> Nil) (3 :> 3 :> Nil) :: Vec 2 (Unsigned 8)
--   5 :> 6 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- -- -- NB: izipWith is strict in its second argument, -- and lazy in its third. This matters when izipWith is -- used in a recursive setting. See lazyV for more information. izipWith :: KnownNat n => (Index n -> a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | Right fold (function applied to each element and its index) -- --
--   >>> let findLeftmost x xs = ifoldr (\i a b -> if a == x then Just i else b) Nothing xs
--   
--   >>> findLeftmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> findLeftmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldr f z xs" corresponds to the following circuit -- layout: -- ifoldr :: KnownNat n => (Index n -> a -> b -> b) -> b -> Vec n a -> b -- | Left fold (function applied to each element and its index) -- --
--   >>> let findRightmost x xs = ifoldl (\a i b -> if b == x then Just i else a) Nothing xs
--   
--   >>> findRightmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 4
--   
--   >>> findRightmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldl f z xs" corresponds to the following circuit -- layout: -- ifoldl :: KnownNat n => (a -> Index n -> b -> a) -> a -> Vec n b -> a -- | Generate a vector of indices. -- --
--   >>> indices d4
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indices :: KnownNat n => SNat n -> Vec n (Index n) -- | Generate a vector of indices, where the length of the vector is -- determined by the context. -- --
--   >>> indicesI :: Vec 4 (Index 4)
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indicesI :: KnownNat n => Vec n (Index n) -- | "findIndex p xs" returns the index of the first -- element of xs satisfying the predicate p, or -- Nothing if there is no such element. -- --
--   >>> findIndex (> 3) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 3
--   
--   >>> findIndex (> 8) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
findIndex :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe (Index n) -- | "elemIndex a xs" returns the index of the first -- element which is equal (by ==) to the query element a, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> elemIndex 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
elemIndex :: (KnownNat n, Eq a) => a -> Vec n a -> Maybe (Index n) -- | zipWith generalizes zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "zipWith (+)" applied to two vectors produces -- the vector of corresponding sums. -- --
--   zipWith f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) == (f x1 y1 :> f x2 y2 :> ... :> f xn yn :> Nil)
--   
-- -- "zipWith f xs ys" corresponds to the following circuit -- layout: -- -- -- NB: zipWith is strict in its second argument, and -- lazy in its third. This matters when zipWith is used in -- a recursive setting. See lazyV for more information. zipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | zipWith3 generalizes zip3 by zipping with the function -- given as the first argument, instead of a tupling function. -- --
--   zipWith3 f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) (z1 :> z2 :> ... :> zn :> Nil) == (f x1 y1 z1 :> f x2 y2 z2 :> ... :> f xn yn zn :> Nil)
--   
-- -- "zipWith3 f xs ys zs" corresponds to the following -- circuit layout: -- -- -- NB: zipWith3 is strict in its second argument, -- and lazy in its third and fourth. This matters when -- zipWith3 is used in a recursive setting. See lazyV for -- more information. zipWith3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d zipWith4 :: (a -> b -> c -> d -> e) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n h -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldr1 f (x1 :> ... :> xn2 :> xn1 :> xn :> Nil) == x1 `f` (... (xn2 `f` (xn1 `f` xn))...)
--   foldr1 f (x1 :> Nil)                            == x1
--   foldr1 f Nil                                    == TYPE ERROR
--   
-- --
--   >>> foldr1 (/) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   1.875
--   
-- -- "foldr1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldl1 f (x1 :> x2 :> x3 :> ... :> xn :> Nil) == (...((x1 `f` x2) `f` x3) `f`...) `f` xn
--   foldl1 f (x1 :> Nil)                          == x1
--   foldl1 f Nil                                  == TYPE ERROR
--   
-- --
--   >>> foldl1 (/) (1 :> 5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | fold is a variant of foldr1 and foldl1, but -- instead of reducing from right to left, or left to right, it reduces a -- vector using a tree-like structure. The depth, or delay, of the -- structure produced by "fold f xs", is hence -- O(log_2(length xs)), and not O(length -- xs). -- -- NB: The binary operator "f" in "fold f -- xs" must be associative. -- --
--   fold f (x1 :> x2 :> ... :> xn1 :> xn :> Nil) == ((x1 `f` x2) `f` ...) `f` (... `f` (xn1 `f` xn))
--   fold f (x1 :> Nil)                           == x1
--   fold f Nil                                   == TYPE ERROR
--   
-- --
--   >>> fold (+) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   15
--   
-- -- "fold f xs" corresponds to the following circuit -- layout: -- fold :: forall n a. (a -> a -> a) -> Vec (n + 1) a -> a -- | scanl is similar to foldl, but returns a vector of -- successive reduced values from the left: -- --
--   scanl f z (x1 :> x2 :> ... :> Nil) == z :> (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> scanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   0 :> 5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "scanl f z xs" corresponds to the following circuit -- layout: -- -- -- scanl :: (b -> a -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanl with no seed value -- --
--   >>> scanl1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> -1 :> -4 :> -8 :> Nil
--   
scanl1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | scanr with no seed value -- --
--   >>> scanr1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   -2 :> 3 :> -1 :> 4 :> Nil
--   
scanr1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | postscanl is a variant of scanl where the first result -- is dropped: -- --
--   postscanl f z (x1 :> x2 :> ... :> Nil) == (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> postscanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "postscanl f z xs" corresponds to the following -- circuit layout: -- postscanl :: (b -> a -> b) -> b -> Vec n a -> Vec n b -- | scanr is similar to foldr, but returns a vector of -- successive reduced values from the right: -- --
--   scanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> z :> Nil
--   
-- --
--   >>> scanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> 0 :> Nil
--   
-- -- "scanr f z xs" corresponds to the following circuit -- layout: -- -- -- scanr :: (a -> b -> b) -> b -> Vec n a -> Vec (n + 1) b -- | postscanr is a variant of scanr that where the last -- result is dropped: -- --
--   postscanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> Nil
--   
-- --
--   >>> postscanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> Nil
--   
-- -- "postscanr f z xs" corresponds to the following -- circuit layout: -- postscanr :: (a -> b -> b) -> b -> Vec n a -> Vec n b -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumL (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,1 :> 2 :> 4 :> 7 :> Nil)
--   
-- -- "mapAccumL f acc xs" corresponds to the following -- circuit layout: -- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumR (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,10 :> 8 :> 5 :> 1 :> Nil)
--   
-- -- "mapAccumR f acc xs" corresponds to the following -- circuit layout: -- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | zip takes two vectors and returns a vector of corresponding -- pairs. -- --
--   >>> zip (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil)
--   (1,4) :> (2,3) :> (3,2) :> (4,1) :> Nil
--   
zip :: Vec n a -> Vec n b -> Vec n (a, b) -- | zip3 takes three vectors and returns a vector of corresponding -- triplets. -- --
--   >>> zip3 (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil) (5:>6:>7:>8:>Nil)
--   (1,4,5) :> (2,3,6) :> (3,2,7) :> (4,1,8) :> Nil
--   
zip3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) -- | zip4 takes four vectors and returns a list of quadruples, -- analogous to zip. zip4 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n (a, b, c, d) -- | zip5 takes five vectors and returns a list of five-tuples, -- analogous to zip. zip5 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n (a, b, c, d, e) -- | zip6 takes six vectors and returns a list of six-tuples, -- analogous to zip. zip6 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n (a, b, c, d, e, f) -- | zip7 takes seven vectors and returns a list of seven-tuples, -- analogous to zip. zip7 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n (a, b, c, d, e, f, g) -- | unzip transforms a vector of pairs into a vector of first -- components and a vector of second components. -- --
--   >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
--   
unzip :: Vec n (a, b) -> (Vec n a, Vec n b) -- | unzip3 transforms a vector of triplets into a vector of first -- components, a vector of second components, and a vector of third -- components. -- --
--   >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
--   
unzip3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) -- | unzip4 takes a vector of quadruples and returns four vectors, -- analogous to unzip. unzip4 :: Vec n (a, b, c, d) -> (Vec n a, Vec n b, Vec n c, Vec n d) -- | unzip5 takes a vector of five-tuples and returns five vectors, -- analogous to unzip. unzip5 :: Vec n (a, b, c, d, e) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e) -- | unzip6 takes a vector of six-tuples and returns six vectors, -- analogous to unzip. unzip6 :: Vec n (a, b, c, d, e, f) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f) -- | unzip7 takes a vector of seven-tuples and returns seven -- vectors, analogous to unzip. unzip7 :: Vec n (a, b, c, d, e, f, g) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f, Vec n g) -- | "xs !! n" returns the n'th element of -- xs. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> (1:>2:>3:>4:>5:>Nil) !! 4
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! (length (1:>2:>3:>4:>5:>Nil) - 1)
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 1
--   2
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 4
--   ...
--   
(!!) :: (KnownNat n, Enum i) => Vec n a -> i -> a -- | The length of a Vector as an Int value. -- --
--   >>> length (6 :> 7 :> 8 :> Nil)
--   3
--   
length :: KnownNat n => Vec n a -> Int -- | "replace n a xs" returns the vector xs where -- the n'th element is replaced by a. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> replace 3 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 7 :> 5 :> Nil
--   
--   >>> replace 0 7 (1:>2:>3:>4:>5:>Nil)
--   7 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
--   >>> replace 9 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 4
--   ...
--   
replace :: (KnownNat n, Enum i) => i -> a -> Vec n a -> Vec n a -- | "take n xs" returns the n-length prefix of -- xs. -- --
--   >>> take (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d3               (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d0               (1:>2:>Nil)
--   Nil
--   
-- --
--   >>> take d4               (1:>2:>Nil)
--   
--   <interactive>:...
--       • Couldn't match type ‘4 + n0’ with ‘2’
--         Expected type: Vec (4 + n0) a
--           Actual type: Vec (1 + 1) a
--         The type variable ‘n0’ is ambiguous
--       • In the second argument of ‘take’, namely ‘(1 :> 2 :> Nil)’
--         In the expression: take d4 (1 :> 2 :> Nil)
--         In an equation for ‘it’: it = take d4 (1 :> 2 :> Nil)
--   
take :: SNat m -> Vec (m + n) a -> Vec m a -- | "takeI xs" returns the prefix of xs as demanded -- by the context. -- --
--   >>> takeI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   1 :> 2 :> Nil
--   
takeI :: KnownNat m => Vec (m + n) a -> Vec m a -- | "drop n xs" returns the suffix of xs after the -- first n elements. -- --
--   >>> drop (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d3               (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d0               (1:>2:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> drop d4               (1:>2:>Nil)
--   
--   <interactive>:...: error:...
--       • Couldn't match...type ‘4 + n0...
--         The type variable ‘n0’ is ambiguous
--       • In the first argument of ‘print’, namely ‘it’
--         In a stmt of an interactive GHCi command: print it
--   
drop :: SNat m -> Vec (m + n) a -> Vec n a -- | "dropI xs" returns the suffix of xs as demanded -- by the context. -- --
--   >>> dropI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   4 :> 5 :> Nil
--   
dropI :: KnownNat m => Vec (m + n) a -> Vec n a -- | "at n xs" returns n'th element of xs -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> at (SNat :: SNat 1) (1:>2:>3:>4:>5:>Nil)
--   2
--   
--   >>> at d1               (1:>2:>3:>4:>5:>Nil)
--   2
--   
at :: SNat m -> Vec (m + (n + 1)) a -> a -- | "select f s n xs" selects n elements with -- step-size s and offset f from xs. -- --
--   >>> select (SNat :: SNat 1) (SNat :: SNat 2) (SNat :: SNat 3) (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
--   >>> select d1 d2 d3 (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
select :: CmpNat (i + s) (s * n) ~ 'GT => SNat f -> SNat s -> SNat n -> Vec (f + i) a -> Vec n a -- | "selectI f s xs" selects as many elements as demanded -- by the context with step-size s and offset f from -- xs. -- --
--   >>> selectI d1 d2 (1:>2:>3:>4:>5:>6:>7:>8:>Nil) :: Vec 2 Int
--   2 :> 4 :> Nil
--   
selectI :: (CmpNat (i + s) (s * n) ~ 'GT, KnownNat n) => SNat f -> SNat s -> Vec (f + i) a -> Vec n a -- | "replicate n a" returns a vector that has n -- copies of a. -- --
--   >>> replicate (SNat :: SNat 3) 6
--   6 :> 6 :> 6 :> Nil
--   
--   >>> replicate d3 6
--   6 :> 6 :> 6 :> Nil
--   
replicate :: SNat n -> a -> Vec n a -- | "repeat a" creates a vector with as many copies of -- a as demanded by the context. -- --
--   >>> repeat 6 :: Vec 5 Int
--   6 :> 6 :> 6 :> 6 :> 6 :> Nil
--   
repeat :: KnownNat n => a -> Vec n a -- | "iterate n f x" returns a vector starting with -- x followed by n repeated applications of f to -- x. -- --
--   iterate (SNat :: SNat 4) f x == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   iterate d4 f x               == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> iterate d4 (+1) 1
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- "iterate n f z" corresponds to the following circuit -- layout: -- iterate :: SNat n -> (a -> a) -> a -> Vec n a -- | "iterateI f x" returns a vector starting with -- x followed by n repeated applications of f -- to x, where n is determined by the context. -- --
--   iterateI f x :: Vec 3 a == (x :> f x :> f (f x) :> Nil)
--   
-- --
--   >>> iterateI (+1) 1 :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- -- "iterateI f z" corresponds to the following circuit -- layout: -- iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a -- | "unfoldr n f s" builds a vector of length n -- from a seed value s, where every element a is -- created by successive calls of f on s. Unlike -- unfoldr from Data.List the generating function -- f cannot dictate the length of the resulting vector, it must -- be statically known. -- -- a simple use of unfoldr: -- --
--   >>> unfoldr d10 (\s -> (s,s-1)) 10
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldr :: SNat n -> (s -> (a, s)) -> s -> Vec n a -- | "unfoldrI f s" builds a vector from a seed value -- s, where every element a is created by successive -- calls of f on s; the length of the vector is -- inferred from the context. Unlike unfoldr from Data.List -- the generating function f cannot dictate the length of the -- resulting vector, it must be statically known. -- -- a simple use of unfoldrI: -- --
--   >>> unfoldrI (\s -> (s,s-1)) 10 :: Vec 10 Int
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldrI :: KnownNat n => (s -> (a, s)) -> s -> Vec n a -- | "generate n f x" returns a vector with n -- repeated applications of f to x. -- --
--   generate (SNat :: SNat 4) f x == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   generate d4 f x               == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   
-- --
--   >>> generate d4 (+1) 1
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "generate n f z" corresponds to the following circuit -- layout: -- generate :: SNat n -> (a -> a) -> a -> Vec n a -- | "generateI f x" returns a vector with n -- repeated applications of f to x, where n is -- determined by the context. -- --
--   generateI f x :: Vec 3 a == (f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> generateI (+1) 1 :: Vec 3 Int
--   2 :> 3 :> 4 :> Nil
--   
-- -- "generateI f z" corresponds to the following circuit -- layout: -- generateI :: KnownNat n => (a -> a) -> a -> Vec n a -- | Transpose a matrix: go from row-major to column-major -- --
--   >>> let xss = (1:>2:>Nil):>(3:>4:>Nil):>(5:>6:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> Nil) :> (3 :> 4 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
--   >>> transpose xss
--   (1 :> 3 :> 5 :> Nil) :> (2 :> 4 :> 6 :> Nil) :> Nil
--   
transpose :: KnownNat n => Vec m (Vec n a) -> Vec n (Vec m a) -- | 1-dimensional stencil computations -- -- "stencil1d stX f xs", where xs has stX + -- n elements, applies the stencil computation f on: n + -- 1 overlapping (1D) windows of length stX, drawn from -- xs. The resulting vector has n + 1 elements. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t stencil1d d2 sum xs
--   stencil1d d2 sum xs :: Num b => Vec 5 b
--   
--   >>> stencil1d d2 sum xs
--   3 :> 5 :> 7 :> 9 :> 11 :> Nil
--   
stencil1d :: KnownNat n => SNat (stX + 1) -> (Vec (stX + 1) a -> b) -> Vec ((stX + n) + 1) a -> Vec (n + 1) b -- | 2-dimensional stencil computations -- -- "stencil2d stY stX f xss", where xss is a -- matrix of stY + m rows of stX + n elements, applies the -- stencil computation f on: (m + 1) * (n + 1) overlapping -- (2D) windows of stY rows of stX elements, drawn from -- xss. The result matrix has m + 1 rows of n + 1 -- elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
-- --
--   >>> :t stencil2d d2 d2 (sum . map sum) xss
--   stencil2d d2 d2 (sum . map sum) xss :: Num b => Vec 3 (Vec 3 b)
--   
-- --
--   >>> stencil2d d2 d2 (sum . map sum) xss
--   (14 :> 18 :> 22 :> Nil) :> (30 :> 34 :> 38 :> Nil) :> (46 :> 50 :> 54 :> Nil) :> Nil
--   
stencil2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> (Vec (stY + 1) (Vec (stX + 1) a) -> b) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) b) -- | "windows1d stX xs", where the vector xs has -- stX + n elements, returns a vector of n + 1 overlapping -- (1D) windows of xs of length stX. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t windows1d d2 xs
--   windows1d d2 xs :: Num a => Vec 5 (Vec 2 a)
--   
--   >>> windows1d d2 xs
--   (1 :> 2 :> Nil) :> (2 :> 3 :> Nil) :> (3 :> 4 :> Nil) :> (4 :> 5 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
windows1d :: KnownNat n => SNat (stX + 1) -> Vec ((stX + n) + 1) a -> Vec (n + 1) (Vec (stX + 1) a) -- | "windows2d stY stX xss", where matrix xss has -- stY + m rows of stX + n, returns a matrix of m+1 -- rows of n+1 elements. The elements of this new matrix are the -- overlapping (2D) windows of xss, where every window has -- stY rows of stX elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
--   >>> :t windows2d d2 d2 xss
--   windows2d d2 d2 xss :: Num a => Vec 3 (Vec 3 (Vec 2 (Vec 2 a)))
--   
--   >>> windows2d d2 d2 xss
--   (((1 :> 2 :> Nil) :> (5 :> 6 :> Nil) :> Nil) :> ((2 :> 3 :> Nil) :> (6 :> 7 :> Nil) :> Nil) :> ((3 :> 4 :> Nil) :> (7 :> 8 :> Nil) :> Nil) :> Nil) :> (((5 :> 6 :> Nil) :> (9 :> 10 :> Nil) :> Nil) :> ((6 :> 7 :> Nil) :> (10 :> 11 :> Nil) :> Nil) :> ((7 :> 8 :> Nil) :> (11 :> 12 :> Nil) :> Nil) :> Nil) :> (((9 :> 10 :> Nil) :> (13 :> 14 :> Nil) :> Nil) :> ((10 :> 11 :> Nil) :> (14 :> 15 :> Nil) :> Nil) :> ((11 :> 12 :> Nil) :> (15 :> 16 :> Nil) :> Nil) :> Nil) :> Nil
--   
windows2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) (Vec (stY + 1) (Vec (stX + 1) a))) -- | Forward permutation specified by an index mapping, ix. The -- result vector is initialized by the given defaults, def, and an -- further values that are permuted into the result are added to the -- current value using the given combination function, f. -- -- The combination function must be associative and -- commutative. permute :: (Enum i, KnownNat n, KnownNat m) => (a -> a -> a) -> Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "backpermute xs is" is equivalent to "map -- (xs !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> backpermute input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
backpermute :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | Copy elements from the source vector, xs, to the destination -- vector according to an index mapping is. This is a forward -- permute operation where a to vector encodes an input to output -- index mapping. Output elements for indices that are not mapped assume -- the value in the default vector def. -- -- For example: -- --
--   >>> let defVec = 0:>0:>0:>0:>0:>0:>0:>0:>0:>Nil
--   
--   >>> let to = 1:>3:>7:>2:>5:>8:>Nil
--   
--   >>> let input = 1:>9:>6:>4:>4:>2:>5:>Nil
--   
--   >>> scatter defVec to input
--   0 :> 1 :> 4 :> 9 :> 0 :> 4 :> 0 :> 6 :> 2 :> Nil
--   
-- -- NB: If the same index appears in the index mapping more than -- once, the latest mapping is chosen. scatter :: (Enum i, KnownNat n, KnownNat m) => Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "gather xs is" is equivalent to "map (xs -- !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> gather input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
gather :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | "interleave d xs" creates a vector: -- --
--   <x_0,x_d,x_(2d),...,x_1,x_(d+1),x_(2d+1),...,x_(d-1),x_(2d-1),x_(3d-1)>
--   
-- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> Nil
--   
--   >>> interleave d3 xs
--   1 :> 4 :> 7 :> 2 :> 5 :> 8 :> 3 :> 6 :> 9 :> Nil
--   
interleave :: (KnownNat n, KnownNat d) => SNat d -> Vec (n * d) a -> Vec (d * n) a -- | Dynamically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeft xs 1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
--   >>> rotateLeft xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateLeft xs (-1)
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateLeftS if you want to rotate left by a -- static amount. rotateLeft :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Dynamically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRight xs 1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
--   >>> rotateRight xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateRight xs (-1)
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateRightS if you want to rotate right by a -- static amount. rotateRight :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Statically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeftS xs d1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateLeft if you want to rotate left by a -- dynamic amount. rotateLeftS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Statically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRightS xs d1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateRight if you want to rotate right by a -- dynamic amount. rotateRightS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Convert a vector to a list. -- --
--   >>> toList (1:>2:>3:>Nil)
--   [1,2,3]
--   
-- -- NB: This function is not synthesizable toList :: Vec n a -> [a] -- | Create a vector literal from a list literal. -- --
--   $(listToVecTH [1::Signed 8,2,3,4,5]) == (8:>2:>3:>4:>5:>Nil) :: Vec 5 (Signed 8)
--   
-- --
--   >>> [1 :: Signed 8,2,3,4,5]
--   [1,2,3,4,5]
--   
--   >>> $(listToVecTH [1::Signed 8,2,3,4,5])
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
listToVecTH :: Lift a => [a] -> ExpQ -- | Vector as a Proxy for Nat asNatProxy :: Vec n a -> Proxy n -- | Length of a Vector as an SNat value lengthS :: KnownNat n => Vec n a -> SNat n -- | What you should use when your vector functions are too strict in their -- arguments. -- --

doctests setup

-- --
--   >>> let compareSwapL a b = if a < b then (a,b) else (b,a)
--   
--   >>> :{
--   let sortVL :: (Ord a, KnownNat (n + 1)) => Vec ((n + 1) + 1) a -> Vec ((n + 1) + 1) a
--       sortVL xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith compareSwapL (lazyV lefts) rights
--   :}
--   
-- --
--   >>> :{
--   let sortV_flip xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith (flip compareSwapL) rights lefts
--   :}
--   
-- --

Example usage

-- -- For example: -- --
--   -- Bubble sort for 1 iteration
--   sortV xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL lefts rights
--   
--   -- Compare and swap
--   compareSwapL a b = if a < b then (a,b)
--                               else (b,a)
--   
-- -- Will not terminate because zipWith is too strict in its second -- argument. -- -- In this case, adding lazyV on zipWiths second argument: -- --
--   sortVL xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL (lazyV lefts) rights
--   
-- -- Results in a successful computation: -- --
--   >>> sortVL (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: There is also a solution using flip, but it slightly -- obfuscates the meaning of the code: -- --
--   sortV_flip xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith (flip compareSwapL) rights lefts
--   
-- --
--   >>> sortV_flip (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
lazyV :: KnownNat n => Vec n a -> Vec n a -- | A dependently typed fold. -- --

doctests setup

-- --
--   >>> :seti -fplugin GHC.TypeLits.Normalise
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply (Append m a) l = Vec (l + m) a
--   
--   >>> let append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- --

Example usage

-- -- Using lists, we can define append (a.k.a. -- Data.List.++) in terms of -- Data.List.foldr: -- --
--   >>> import qualified Data.List
--   
--   >>> let append xs ys = Data.List.foldr (:) ys xs
--   
--   >>> append [1,2] [3,4]
--   [1,2,3,4]
--   
-- -- However, when we try to do the same for Vec, by defining -- append' in terms of Clash.Sized.Vector.foldr: -- --
--   append' xs ys = foldr (:>) ys xs
--   
-- -- we get a type error: -- --
--   >>> let append' xs ys = foldr (:>) ys xs
--   
--   <interactive>:...
--       • Occurs check: cannot construct the infinite type: ... ~ ... + 1
--         Expected type: a -> Vec ... a -> Vec ... a
--           Actual type: a -> Vec ... a -> Vec (... + 1) a
--       • In the first argument of ‘foldr’, namely ‘(:>)’
--         In the expression: foldr (:>) ys xs
--         In an equation for ‘append'’: append' xs ys = foldr (:>) ys xs
--       • Relevant bindings include
--           ys :: Vec ... a (bound at ...)
--           append' :: Vec n a -> Vec ... a -> Vec ... a
--             (bound at ...)
--   
-- -- The reason is that the type of foldr is: -- --
--   >>> :t foldr
--   foldr :: (a -> b -> b) -> b -> Vec n a -> b
--   
-- -- While the type of (:>) is: -- --
--   >>> :t (:>)
--   (:>) :: a -> Vec n a -> Vec (n + 1) a
--   
-- -- We thus need a fold function that can handle the growing -- vector type: dfold. Compared to foldr, dfold -- takes an extra parameter, called the motive, that allows the -- folded function to have an argument and result type that -- depends on the current length of the vector. Using -- dfold, we can now correctly define append': -- --
--   import Data.Singletons
--   import Data.Proxy
--   
--   data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   type instance Apply (Append m a) l = Vec (l + m) a
--   
--   append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- -- We now see that append' has the appropriate type: -- --
--   >>> :t append'
--   append' :: KnownNat k => Vec k a -> Vec m a -> Vec (k + m) a
--   
-- -- And that it works: -- --
--   >>> append' (1 :> 2 :> Nil) (3 :> 4 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: "dfold m f z xs" creates a linear -- structure, which has a depth, or delay, of O(length -- xs). Look at dtfold for a dependently typed fold -- that produces a structure with a depth of O(log_2(length -- xs)). dfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (forall l. SNat l -> a -> (p @@ l) -> p @@ (l + 1)) -> (p @@ 0) -> Vec k a -> p @@ k -- | A combination of dfold and fold: a dependently -- typed fold that reduces a vector in a tree-like structure. -- --

doctests setup

-- --
--   >>> :seti -XUndecidableInstances
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data IIndex (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply IIndex l = Index ((2^l)+1)
--   
--   >>> :{
--   let populationCount' :: (KnownNat k, KnownNat (2^k)) => BitVector (2^k) -> Index ((2^k)+1)
--       populationCount' bv = dtfold (Proxy @IIndex)
--                                    fromIntegral
--                                    (\_ x y -> add x y)
--                                    (bv2v bv)
--   :}
--   
-- --

Example usage

-- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- sum, because it gives a nice (log2(n)) tree-structure -- of adders: -- --
--   populationCount :: (KnownNat (n+1), KnownNat (n+2))
--                   => BitVector (n+1) -> Index (n+2)
--   populationCount = sum . map fromIntegral . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (n+2) -> Index (n+2) -> Index (n+2).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of addes: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (n+1), KnownNat (n+2))
--                        => BitVector (n+1) -> Index (n+2)
--       populationCount' = fold add . map fromIntegral . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘((n + 2) + (n + 2)) - 1’ with ‘n + 2’
--         Expected type: Index (n + 2) -> Index (n + 2) -> Index (n + 2)
--           Actual type: Index (n + 2)
--                        -> Index (n + 2) -> AResult (Index (n + 2)) (Index (n + 2))
--       • In the first argument of ‘fold’, namely ‘add’
--         In the first argument of ‘(.)’, namely ‘fold add’
--         In the expression: fold add . map fromIntegral . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (n + 1) -> Index (n + 2)
--             (bound at ...)
--   
-- -- because fold expects a function of type "a -> a -> -- a", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   import Data.Proxy
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = dtfold (Proxy @IIndex)
--                                fromIntegral
--                                (\_ x y -> add x y)
--                                (bv2v bv)
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
-- -- Some final remarks: -- -- -- -- NB: The depth, or delay, of the structure produced by -- "dtfold m f g xs" is O(log_2(length -- xs)). dtfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> Vec (2 ^ k) a -> p @@ k -- | Specialised version of dfold that builds a triangular -- computational structure. -- --

doctests setup

-- --
--   >>> let compareSwap a b = if a > b then (a,b) else (b,a)
--   
--   >>> let insert y xs = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   
--   >>> let insertionSort = vfold (const insert)
--   
-- --

Example usage

-- --
--   compareSwap a b = if a > b then (a,b) else (b,a)
--   insert y xs     = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   insertionSort   = vfold (const insert)
--   
-- -- Builds a triangular structure of compare and swaps to sort a row. -- --
--   >>> insertionSort (7 :> 3 :> 9 :> 1 :> Nil)
--   1 :> 3 :> 7 :> 9 :> Nil
--   
-- -- The circuit layout of insertionSort, build using -- vfold, is: -- vfold :: forall k a b. KnownNat k => (forall l. SNat l -> a -> Vec l b -> Vec (l + 1) b) -> Vec k a -> Vec k b -- | The largest element of a non-empty vector maximum :: Ord a => Vec (n + 1) a -> a -- | The least element of a non-empty vector minimum :: Ord a => Vec (n + 1) a -> a -- | Apply a function to every element of a vector and the element's -- position (as an SNat value) in the vector. -- --
--   >>> let rotateMatrix = smap (flip rotateRightS)
--   
--   >>> let xss = (1:>2:>3:>Nil):>(1:>2:>3:>Nil):>(1:>2:>3:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> Nil
--   
--   >>> rotateMatrix xss
--   (1 :> 2 :> 3 :> Nil) :> (3 :> 1 :> 2 :> Nil) :> (2 :> 3 :> 1 :> Nil) :> Nil
--   
smap :: forall k a b. KnownNat k => (forall l. SNat l -> a -> b) -> Vec k a -> Vec k b concatBitVector# :: forall n m. (KnownNat n, KnownNat m) => Vec n (BitVector m) -> BitVector (n * m) unconcatBitVector# :: forall n m. (KnownNat n, KnownNat m) => BitVector (n * m) -> Vec n (BitVector m) -- | Convert a Vec of Bits to a BitVector. -- --
--   >>> let x = (0:>0:>0:>1:>0:>0:>1:>0:>Nil) :: Vec 8 Bit
--   
--   >>> x
--   0 :> 0 :> 0 :> 1 :> 0 :> 0 :> 1 :> 0 :> Nil
--   
--   >>> v2bv x
--   0b0001_0010
--   
v2bv :: KnownNat n => Vec n Bit -> BitVector n -- | Evaluate all elements of a vector to WHNF, returning the second -- argument seqV :: KnownNat n => Vec n a -> b -> b infixr 0 `seqV` -- | Evaluate all elements of a vector to WHNF forceV :: KnownNat n => Vec n a -> Vec n a -- | Evaluate all elements of a vector to WHNF, returning the second -- argument. Does not propagate XExceptions. seqVX :: KnownNat n => Vec n a -> b -> b infixr 0 `seqVX` -- | Evaluate all elements of a vector to WHNF. Does not propagate -- XExceptions. forceVX :: KnownNat n => Vec n a -> Vec n a -- | Representable types of kind *. This class is derivable in GHC -- with the DeriveGeneric flag on. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class Generic a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) -- | A Lift instance can have any of its values turned into a -- Template Haskell expression. This is needed when a value used within a -- Template Haskell quotation is bound outside the Oxford brackets -- ([| ... |] or [|| ... ||]) but not at the top level. -- As an example: -- --
--   add1 :: Int -> Q (TExp Int)
--   add1 x = [|| x + 1 ||]
--   
-- -- Template Haskell has no way of knowing what value x will take -- on at splice-time, so it requires the type of x to be an -- instance of Lift. -- -- A Lift instance must satisfy $(lift x) ≡ x and -- $$(liftTyped x) ≡ x for all x, where $(...) -- and $$(...) are Template Haskell splices. It is additionally -- expected that lift x ≡ unTypeQ (liftTyped -- x). -- -- Lift instances can be derived automatically by use of the -- -XDeriveLift GHC language extension: -- --
--   {-# LANGUAGE DeriveLift #-}
--   module Foo where
--   
--   import Language.Haskell.TH.Syntax
--   
--   data Bar a = Bar1 a (Bar a) | Bar2 String
--     deriving Lift
--   
-- -- Levity-polymorphic since template-haskell-2.16.0.0. class Lift (t :: TYPE r) -- | Turn a value into a Template Haskell expression, suitable for use in a -- splice. lift :: Lift t => t -> Q Exp -- | Turn a value into a Template Haskell typed expression, suitable for -- use in a typed splice. liftTyped :: Lift t => t -> Q (TExp t) -- | Clash is a functional hardware description language that borrows both -- its syntax and semantics from the functional programming language -- Haskell. The merits of using a functional language to describe -- hardware comes from the fact that combinational circuits can be -- directly modeled as mathematical functions and that functional -- languages lend themselves very well at describing and (de-)composing -- mathematical functions. -- -- This package provides: -- -- -- -- To use the library: -- -- -- -- For now, Clash.Prelude is also the best starting point for -- exploring the library. A preliminary version of a tutorial can be -- found in Clash.Tutorial. Some circuit examples can be found in -- Clash.Examples. module Clash.Prelude -- | Create a synchronous function from a combinational function describing -- a mealy machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> (Int,Int)  -- (Updated state, output)
--   macT s (x,y) = (s',s)
--     where
--       s' = x * y + s
--   
--   mac :: HiddenClockResetEnable dom  => Signal dom (Int, Int) -> Signal dom Int
--   mac = mealy macT 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = mealy macT 0 (bundle (a,x))
--       s2 = mealy macT 0 (bundle (b,y))
--   
mealy :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o -- | Create a synchronous function from a combinational function describing -- a mealy machine using the state monad. This can be particularly useful -- when combined with lenses or optics to replicate imperative -- algorithms. -- --
--   data DelayState = DelayState
--     { _history    :: Vec 4 Int
--     , _untilValid :: Index 4
--     }
--     deriving (Generic, NFDataX)
--   makeLenses ''DelayState
--   
--   initialDelayState = DelayState (repeat 0) maxBound
--   
--   delayS :: Int -> State DelayState (Maybe Int)
--   delayS n = do
--     history   %= (n +>>)
--     remaining <- use untilValid
--     if remaining > 0
--     then do
--        untilValid -= 1
--        return Nothing
--      else do
--        out <- uses history last
--        return (Just out)
--   
--   delayTop :: HiddenClockResetEnable dom  => Signal dom Int -> Signal dom (Maybe Int)
--   delayTop = mealyS delayS initialDelayState
--   
-- --
--   >>> L.take 7 $ simulate @System delayTop [1,2,3,4,5,6,7,8]
--   [Nothing,Nothing,Nothing,Just 1,Just 2,Just 3,Just 4]
--   ...
--   
mealyS :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s o) -> s -> Signal dom i -> Signal dom o -- | A version of mealy that does automatic Bundleing -- -- Given a function f of type: -- --
--   f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
--   
-- -- When we want to make compositions of f in g using -- mealy, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (mealy f 0 (bundle (a,b)))
--       (i2,b2) = unbundle (mealy f 3 (bundle (c,i1)))
--   
-- -- Using mealyB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mealyB f 0 (a,b)
--       (i2,b2) = mealyB f 3 (c,i1)
--   
mealyB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | A version of mealyS that does automatic Bundleing, see -- mealyB for details. mealySB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o -- | Infix version of mealyB (<^>) :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a synchronous function from a combinational function describing -- a moore machine -- --
--   macT
--     :: Int        -- Current state
--     -> (Int,Int)  -- Input
--     -> Int        -- Updated state
--   macT s (x,y) = x * y + s
--   
--   mac
--     :: HiddenClockResetEnable dom
--     => Signal dom (Int, Int)
--     -> Signal dom Int
--   mac = moore mac id 0
--   
-- --
--   >>> simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
--   [0,0,1,5,14,30,...
--   ...
--   
-- -- Synchronous sequential functions can be composed just like their -- combinational counterpart: -- --
--   dualMac
--     :: HiddenClockResetEnable dom
--     => (Signal dom Int, Signal dom Int)
--     -> (Signal dom Int, Signal dom Int)
--     -> Signal dom Int
--   dualMac (a,b) (x,y) = s1 + s2
--     where
--       s1 = moore macT id 0 (bundle (a,x))
--       s2 = moore macT id 0 (bundle (b,y))
--   
moore :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> s) -> (s -> o) -> s -> Signal dom i -> Signal dom o -- | A version of moore that does automatic Bundleing -- -- Given a functions t and o of types: -- --
--   t :: Int -> (Bool, Int) -> Int
--   o :: Int -> (Int, Bool)
--   
-- -- When we want to make compositions of t and o in -- g using moore, we have to write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = unbundle (moore t o 0 (bundle (a,b)))
--       (i2,b2) = unbundle (moore t o 3 (bundle (c,i1)))
--   
-- -- Using mooreB however we can write: -- --
--   g a b c = (b1,b2,i2)
--     where
--       (i1,b1) = mooreB t o 0 (a,b)
--       (i2,b2) = mooreB t o 3 (c,i1)
--   
mooreB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> s) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o -- | Create a register function for product-type like signals (e.g. -- '(Signal a, Signal b)') -- --
--   rP :: HiddenClockResetEnable dom
--      => (Signal dom Int, Signal dom Int)
--      -> (Signal dom Int, Signal dom Int)
--   rP = registerB (8,8)
--   
-- --
--   >>> simulateB @System rP [(1,1),(2,2),(3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
registerB :: (HiddenClockResetEnable dom, NFDataX a, Bundle a) => a -> Unbundled dom a -> Unbundled dom a infixr 3 `registerB` -- | Synchronizer based on two sequentially connected flip-flops. -- -- dualFlipFlopSynchronizer :: (NFDataX a, HiddenClock dom1, HiddenClockResetEnable dom2) => a -> Signal dom1 a -> Signal dom2 a -- | Synchronizer implemented as a FIFO around an asynchronous RAM. Based -- on the design described in Clash.Tutorial#multiclock, which is -- itself based on the design described in -- http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf. -- -- NB: This synchronizer can be used for -- word-synchronization. asyncFIFOSynchronizer :: (HiddenClockResetEnable rdom, HiddenClockResetEnable wdom, 2 <= addrSize, NFDataX a) => SNat addrSize -> Signal rdom Bool -> Signal wdom (Maybe a) -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool) -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRom :: (KnownNat n, Enum addr, NFDataX a) => Vec n a -> addr -> a -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomPow2 :: (KnownNat n, NFDataX a) => Vec (2 ^ n) a -> Unsigned n -> a -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- rom :: forall dom n m a. (NFDataX a, KnownNat n, KnownNat m, HiddenClock dom, HiddenEnable dom) => Vec n a -> Signal dom (Unsigned m) -> Signal dom a -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romPow2 :: forall dom n a. (KnownNat n, NFDataX a, HiddenClock dom, HiddenEnable dom) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom a -- | An asynchronous/combinational ROM with space for n elements -- --

See also:

-- -- asyncRomBlob :: Enum addr => MemBlob n m -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- --

See also:

-- -- asyncRomBlobPow2 :: KnownNat n => MemBlob (2 ^ n) m -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- --

See also:

-- -- romBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr) => MemBlob n m -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- --

See also:

-- -- romBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | An asynchronous/combinational ROM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m -- | An asynchronous/combinational ROM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n) => FilePath -> Unsigned n -> BitVector m -- | A ROM with a synchronous read port, with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- romFile :: (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, Enum addr) => SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) -- | A ROM with a synchronous read port, with space for 2^n -- elements -- -- -- -- TODO: table -- --

See also:

-- -- romFilePow2 :: forall n m dom. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom) => FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) -- | Create a RAM with space for n elements -- -- -- --

See also:

-- -- asyncRam :: (Enum addr, NFDataX addr, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => SNat n -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a RAM with space for 2^n elements -- -- -- --

See also:

-- -- asyncRamPow2 :: (KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack, NFDataX a) => Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram40
--     :: HiddenClock dom
--     => Signal dom (Unsigned 6)
--     -> Signal dom (Maybe (Unsigned 6, Bit))
--     -> Signal dom Bit
--   bram40 = blockRam (replicate d40 1)
--   
blockRam :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, Enum addr, NFDataX addr) => Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- -- --

Example

-- --
--   bram32
--     :: HiddenClock dom
--     => Signal dom (Unsigned 5)
--     -> Signal dom (Maybe (Unsigned 5, Bit))
--     -> Signal dom Bit
--   bram32 = blockRamPow2 (replicate d32 1)
--   
blockRamPow2 :: (HasCallStack, HiddenClock dom, HiddenEnable dom, NFDataX a, KnownNat n) => Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a -- | A version of blockRam that has no default values set. May be -- cleared to an arbitrary state using a reset function. blockRamU :: forall n dom a r addr. (HasCallStack, HiddenClockResetEnable dom, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => ResetStrategy r -> SNat n -> (Index n -> a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | A version of blockRam that is initialized with the same value -- on all memory positions blockRam1 :: forall n dom a r addr. (HasCallStack, HiddenClockResetEnable dom, NFDataX a, Enum addr, NFDataX addr, 1 <= n) => ResetStrategy r -> SNat n -> a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a data ResetStrategy (r :: Bool) [ClearOnReset] :: ResetStrategy 'True [NoClearOnReset] :: ResetStrategy 'False -- | Create a block RAM with space for n elements -- -- -- --

See also:

-- -- blockRamBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr, NFDataX addr) => MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- --

See also:

-- -- blockRamBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Efficient storage of memory content -- -- It holds n words of BitVector m. data MemBlob (n :: Nat) (m :: Nat) -- | Create a MemBlob binding from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- createMemBlob can refer to something defined in the same -- module. -- --

Example

-- --
--   createMemBlob "content" Nothing [15 :: Unsigned 8 .. 17]
--   
--   ram clk en = blockRamBlob clk en content
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> :{
--   createMemBlob "content0" (Just 0) es
--   createMemBlob "content1" (Just 1) es
--   x = 1
--   :}
--   
-- --
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> :{
--   createMemBlob "contentN" Nothing es
--   x = 1
--   :}
--   
--   <interactive>:...: error:...
--       packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--   
-- -- Note how we hinted to clashi that our multi-line command was -- a list of declarations by including a dummy declaration x = -- 1. Without this trick, clashi would expect an expression -- and the Template Haskell would not work. createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ -- | Create a MemBlob from a list of values -- -- Since this uses Template Haskell, nothing in the arguments given to -- memBlobTH can refer to something defined in the same module. -- --

Example

-- --
--   ram clk en = blockRamBlob clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
--   
-- -- The Maybe datatype has don't care bits, where the actual value -- does not matter. But the bits need a defined value in the memory. -- Either 0 or 1 can be used, and both are valid representations of the -- data. -- --
--   >>> import qualified Prelude as P
--   
--   >>> let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
--   
--   >>> content0 = $(memBlobTH (Just 0) es)
--   
--   >>> content1 = $(memBlobTH (Just 1) es)
--   
--   >>> let pr = mapM_ (putStrLn . show)
--   
--   >>> pr $ P.map pack es
--   0b0_...._....
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content0
--   0b0_0000_0000
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> pr $ unpackMemBlob content1
--   0b0_1111_1111
--   0b1_0000_0111
--   0b1_0000_1000
--   
--   >>> $(memBlobTH Nothing es)
--   
--   <interactive>:...: error:...
--       • packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
--       • In the untyped splice: $(memBlobTH Nothing es)
--   
memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ -- | Convert a MemBlob back to a list -- -- NB: Not synthesizable unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m] -- | Create a block RAM with space for n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFile :: (KnownNat m, Enum addr, NFDataX addr, HiddenClock dom, HiddenEnable dom, HasCallStack) => SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m) -- | Create a block RAM with space for 2^n elements -- -- -- -- TODO: table -- --

See also:

-- -- blockRamFilePow2 :: forall dom n m. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack) => FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m) -- | Create a read-after-write block RAM from a read-before-write one -- --
--   >>> :t readNew (blockRam (0 :> 1 :> Nil))
--   readNew (blockRam (0 :> 1 :> Nil))
--     :: ...
--        ...
--        ...
--        ...
--        ... =>
--        Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a
--   
readNew :: (HiddenClockResetEnable dom, NFDataX a, Eq addr) => (Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a) -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a -- | Produces vendor-agnostic HDL that will be inferred as a true dual-port -- block RAM -- -- Any value that is being written on a particular port is also the value -- that will be read on that port, i.e. the same-port read/write behavior -- is: WriteFirst. For mixed-port read/write, when port A writes to the -- address port B reads from, the output of port B is undefined, and vice -- versa. trueDualPortBlockRam :: forall nAddrs dom1 dom2 a. (HasCallStack, KnownNat nAddrs, HiddenClock dom1, HiddenClock dom2, NFDataX a) => Signal dom1 (RamOp nAddrs a) -> Signal dom2 (RamOp nAddrs a) -> (Signal dom1 a, Signal dom2 a) -- | Port operation data RamOp n a -- | Read from address RamRead :: Index n -> RamOp n a -- | Write data to address RamWrite :: Index n -> a -> RamOp n a -- | No operation RamNoOp :: RamOp n a -- | Give a window over a Signal -- --
--   window4 :: HiddenClockResetEnable dom
--           => Signal dom Int -> Vec 4 (Signal dom Int)
--   window4 = window
--   
-- --
--   >>> simulateB @System window4 [1::Int,2,3,4,5] :: [Vec 4 Int]
--   [1 :> 0 :> 0 :> 0 :> Nil,2 :> 1 :> 0 :> 0 :> Nil,3 :> 2 :> 1 :> 0 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 4 :> 3 :> 2 :> Nil,...
--   ...
--   
window :: (HiddenClockResetEnable dom, KnownNat n, Default a, NFDataX a) => Signal dom a -> Vec (n + 1) (Signal dom a) -- | Give a delayed window over a Signal -- --
--   windowD3
--     :: HiddenClockResetEnable dom
--     => Signal dom Int
--     -> Vec 3 (Signal dom Int)
--   windowD3 = windowD
--   
-- --
--   >>> simulateB @System windowD3 [1::Int,2,3,4] :: [Vec 3 Int]
--   [0 :> 0 :> 0 :> Nil,1 :> 0 :> 0 :> Nil,2 :> 1 :> 0 :> Nil,3 :> 2 :> 1 :> Nil,4 :> 3 :> 2 :> Nil,...
--   ...
--   
windowD :: (HiddenClockResetEnable dom, KnownNat n, Default a, NFDataX a) => Signal dom a -> Vec (n + 1) (Signal dom a) -- | Give a pulse when the Signal goes from minBound to -- maxBound isRising :: (HiddenClockResetEnable dom, NFDataX a, Bounded a, Eq a) => a -> Signal dom a -> Signal dom Bool -- | Give a pulse when the Signal goes from maxBound to -- minBound isFalling :: (HiddenClockResetEnable dom, NFDataX a, Bounded a, Eq a) => a -> Signal dom a -> Signal dom Bool -- | Give a pulse every n clock cycles. This is a useful helper -- function when combined with functions like regEn or -- mux, in order to delay a register by a known amount. -- -- To be precise: the given signal will be False for the -- next n-1 cycles, followed by a single True -- value: -- --
--   >>> Prelude.last (sampleN @System 1025 (riseEvery d1024)) == True
--   True
--   
--   >>> Prelude.or (sampleN @System 1024 (riseEvery d1024)) == False
--   True
--   
-- -- For example, to update a counter once every 10 million cycles: -- --
--   counter = regEn 0 (riseEvery (SNat :: SNat 10000000)) (counter + 1)
--   
riseEvery :: HiddenClockResetEnable dom => SNat n -> Signal dom Bool -- | Oscillate a Bool for a given number of cycles. This is -- a convenient function when combined with something like -- regEn, as it allows you to easily hold a register -- value for a given number of cycles. The input Bool -- determines what the initial value is. -- -- To oscillate on an interval of 5 cycles: -- --
--   >>> sampleN @System 11 (oscillate False d5)
--   [False,False,False,False,False,False,True,True,True,True,True]
--   
-- -- To oscillate between True and False: -- --
--   >>> sampleN @System 11 (oscillate False d1)
--   [False,False,True,False,True,False,True,False,True,False,True]
--   
-- -- An alternative definition for the above could be: -- --
--   >>> let osc' = register False (not <$> osc')
--   
--   >>> sampleN @System 200 (oscillate False d1) == sampleN @System 200 osc'
--   True
--   
oscillate :: HiddenClockResetEnable dom => Bool -> SNat n -> Signal dom Bool -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceSignal1 :: (BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Associates the traced signal with a clock period of -- 1, which results in incorrect VCD files when working with -- circuits that have multiple clocks. Use traceSignal when -- working with circuits that have multiple clocks. traceVecSignal1 :: (KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Trace a single signal. Will emit an error if a signal with the same -- name was previously registered. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceSignal :: forall dom a. (KnownDomain dom, BitPack a, NFDataX a, Typeable a) => String -> Signal dom a -> Signal dom a -- | Trace a single vector signal: each element in the vector will show up -- as a different trace. If the trace name already exists, this function -- will emit an error. -- -- NB: Works correctly when creating VCD files from traced signal -- in multi-clock circuits. However traceSignal1 might be more -- convenient to use when the domain of your circuit is polymorphic. traceVecSignal :: forall dom a n. (KnownDomain dom, KnownNat n, BitPack a, NFDataX a, Typeable a) => String -> Signal dom (Vec (n + 1) a) -> Signal dom (Vec (n + 1) a) -- | Produce a four-state VCD (Value Change Dump) according to IEEE -- 1364-{1995,2001}. This function fails if a trace name contains either -- non-printable or non-VCD characters. -- -- Due to lazy evaluation, the created VCD files might not contain all -- the traces you were expecting. You therefore have to provide a list of -- names you definately want to be dumped in the VCD file. -- -- For example: -- --
--   vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]
--   
-- -- Evaluates cntrOut long enough in order for to guarantee that -- the main, and sub traces end up in the generated VCD -- file. dumpVCD :: NFDataX a => (Int, Int) -> Signal dom a -> [String] -> IO (Either String Text) -- | A reset signal belonging to a domain called dom. -- -- The underlying representation of resets is Bool. data Reset (dom :: Domain) -- | A differential clock signal belonging to a domain named dom. -- The clock input of a design with such an input has two ports which are -- in antiphase. The first input is the positive phase, the second the -- negative phase. When using makeTopEntity, the names of the -- inputs will end in _p and _n respectively. -- -- To create a differential clock in a test bench, you can use -- clockToDiffClock. data DiffClock (dom :: Domain) -- | A clock signal belonging to a domain named dom. data Clock (dom :: Domain) -- | A signal of booleans, indicating whether a component is enabled. No -- special meaning is implied, it's up to the component itself to decide -- how to respond to its enable line. It is used throughout Clash as a -- global enable signal. data Enable dom -- | Clash has synchronous Signals 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 Signals 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. -- -- -- -- Signals have the type role -- --
--   >>> :i Signal
--   type role Signal nominal representational
--   ...
--   
-- -- as it is safe to coerce the underlying value of a signal, but not safe -- to coerce a signal between different synthesis domains. -- -- See the module documentation of Clash.Signal for more -- information about domains. data Signal (dom :: Domain) a type Domain = Symbol -- | Same as SDomainConfiguration but allows for easy updates through -- record update syntax. Should be used in combination with -- vDomain and createDomain. Example: -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
data VDomainConfiguration VDomainConfiguration :: String -> Natural -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> VDomainConfiguration -- | Corresponds to _name on DomainConfiguration [vName] :: VDomainConfiguration -> String -- | Corresponds to _period on DomainConfiguration [vPeriod] :: VDomainConfiguration -> Natural -- | Corresponds to _activeEdge on DomainConfiguration [vActiveEdge] :: VDomainConfiguration -> ActiveEdge -- | Corresponds to _resetKind on DomainConfiguration [vResetKind] :: VDomainConfiguration -> ResetKind -- | Corresponds to _initBehavior on DomainConfiguration [vInitBehavior] :: VDomainConfiguration -> InitBehavior -- | Corresponds to _resetPolarity on DomainConfiguration [vResetPolarity] :: VDomainConfiguration -> ResetPolarity -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and synchronously to -- changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type XilinxSystem = ("XilinxSystem" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type IntelSystem = ("IntelSystem" :: Domain) -- | A clock (and reset) dom with clocks running at 100 MHz. Memory -- elements respond to the rising edge of the clock, and asynchronously -- to changes in reset signals. It has defined initial values, and -- active-high resets. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. type System = ("System" :: Domain) -- | A KnownDomain constraint indicates that a circuit's behavior -- depends on some properties of a domain. See DomainConfiguration -- for more information. class (KnownSymbol dom, KnownNat (DomainPeriod dom)) => KnownDomain (dom :: Domain) where { type family KnownConf dom :: DomainConfiguration; } -- | Returns SDomainConfiguration corresponding to an instance's -- DomainConfiguration. -- -- Example usage: -- --
--   >>> knownDomain @System
--   SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
--   
knownDomain :: KnownDomain dom => SDomainConfiguration dom (KnownConf dom) type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) -- | Singleton version of DomainConfiguration data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) [SDomainConfiguration] :: {sName :: SSymbol dom " Domain name", sPeriod :: SNat period " Period of clock in /ps/", sActiveEdge :: SActiveEdge edge " Active edge of the clock (not yet implemented)", sResetKind :: SResetKind reset " Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)", sInitBehavior :: SInitBehavior init " Whether the initial (or "power up") value of memory elements is unknown/undefined, or configurable to a specific value", sResetPolarity :: SResetPolarity polarity " Whether resets are active high or active low"} -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed. The same as -- PeriodToCycles. type ClockDivider (dom :: Domain) (period :: Nat) = PeriodToCycles dom period -- | Converts a period in picoseconds to a frequency in hertz. This might -- lead to rounding errors. type PeriodToHz (period :: Nat) = (Seconds 1) `Div` period -- | Number of clock cycles required at the clock frequency of dom -- before a minimum period has passed type PeriodToCycles (dom :: Domain) (period :: Nat) = period `DivRU` DomainPeriod dom -- | The domain's clock frequency in hertz, calculated based on the period -- stored in picoseconds. This might lead to rounding errors. type DomainToHz (dom :: Domain) = PeriodToHz (DomainPeriod dom) -- | Converts a frequency in hertz to a period in picoseconds. This might -- lead to rounding errors. type HzToPeriod (hz :: Nat) = Seconds 1 `Div` hz -- | Gets time in Picoseconds from time in picoseconds, essentially -- id type Picoseconds (ps :: Nat) = ps -- | Gets time in Picoseconds from time in Nanoseconds type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns) -- | Gets time in Picoseconds from time in Microseconds type Microseconds (us :: Nat) = Nanoseconds (1000 * us) -- | Gets time in Picoseconds from time in Milliseconds type Milliseconds (ms :: Nat) = Microseconds (1000 * ms) -- | Gets time in Picoseconds from time in Seconds type Seconds (s :: Nat) = Milliseconds (1000 * s) -- | Convenience type to help to extract the reset polarity from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...
--   
type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) -- | Convenience type to constrain a domain to have initial values. Example -- usage: -- --
--   myFunc :: HasDefinedInitialValues dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Note that there is no UnknownInitialValues dom as a component -- that works without initial values will also work if it does have them. -- -- Click here for usage hints type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) -- | Convenience type to help to extract the initial value behavior from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...
--   
type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) -- | Convenience type to constrain a domain to have asynchronous resets. -- Example usage: -- --
--   myFunc :: HasAsynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) -- | Convenience type to constrain a domain to have synchronous resets. -- Example usage: -- --
--   myFunc :: HasSynchronousReset dom => ...
--   
-- -- Using this type implies KnownDomain. -- -- Click here for usage hints type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) -- | Convenience type to help to extract the reset synchronicity from a -- domain. Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) => ...
--   
type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) -- | Convenience type to help to extract the active edge from a domain. -- Example usage: -- --
--   myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...
--   
type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) -- | Convenience type to help to extract a period from a domain. Example -- usage: -- --
--   myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...
--   
type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) -- | A domain with a name (Domain). Configures the behavior of -- various aspects of a circuits. See the documentation of this record's -- field types for more information on the options. -- -- See module documentation of Clash.Explicit.Signal for more -- information on how to create custom synthesis domains. data DomainConfiguration DomainConfiguration :: Domain -> Nat -> ActiveEdge -> ResetKind -> InitBehavior -> ResetPolarity -> DomainConfiguration -- | Domain name [_name] :: DomainConfiguration -> Domain -- | Period of clock in ps [_period] :: DomainConfiguration -> Nat -- | Active edge of the clock [_activeEdge] :: DomainConfiguration -> ActiveEdge -- | Whether resets are synchronous (edge-sensitive) or asynchronous -- (level-sensitive) [_resetKind] :: DomainConfiguration -> ResetKind -- | Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value [_initBehavior] :: DomainConfiguration -> InitBehavior -- | Whether resets are active high or active low [_resetPolarity] :: DomainConfiguration -> ResetPolarity data SInitBehavior (init :: InitBehavior) [SUnknown] :: SInitBehavior 'Unknown [SDefined] :: SInitBehavior 'Defined data InitBehavior -- | Power up value of memory elements is unknown. Unknown :: InitBehavior -- | If applicable, power up value of a memory element is defined. Applies -- to registers for example, but not to blockRam. Defined :: InitBehavior -- | Singleton version of ResetPolarity data SResetPolarity (polarity :: ResetPolarity) [SActiveHigh] :: SResetPolarity 'ActiveHigh [SActiveLow] :: SResetPolarity 'ActiveLow -- | Determines the value for which a reset line is considered "active" data ResetPolarity -- | Reset is considered active if underlying signal is True. ActiveHigh :: ResetPolarity -- | Reset is considered active if underlying signal is False. ActiveLow :: ResetPolarity -- | Singleton version of ResetKind data SResetKind (resetKind :: ResetKind) [SAsynchronous] :: SResetKind 'Asynchronous [SSynchronous] :: SResetKind 'Synchronous data ResetKind -- | Elements respond asynchronously to changes in their reset -- input. This means that they do not wait for the next active -- clock edge, but respond immediately instead. Common on Intel FPGA -- platforms. Asynchronous :: ResetKind -- | Elements respond synchronously to changes in their reset input. -- This means that changes in their reset input won't take effect until -- the next active clock edge. Common on Xilinx FPGA platforms. Synchronous :: ResetKind -- | Singleton version of ActiveEdge data SActiveEdge (edge :: ActiveEdge) [SRising] :: SActiveEdge 'Rising [SFalling] :: SActiveEdge 'Falling -- | Determines clock edge memory elements are sensitive to. Not yet -- implemented. data ActiveEdge -- | Elements are sensitive to the rising edge (low-to-high) of the clock. Rising :: ActiveEdge -- | Elements are sensitive to the falling edge (high-to-low) of the clock. Falling :: ActiveEdge -- | Convenience value to allow easy "subclassing" of System domain. Should -- be used in combination with createDomain. For example, if you -- just want to change the period but leave all other settings intact -- use: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
vSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of IntelSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vIntelSystem{vName="Intel10", vPeriod=10}
--   
vIntelSystem :: VDomainConfiguration -- | Convenience value to allow easy "subclassing" of XilinxSystem domain. -- Should be used in combination with createDomain. For example, -- if you just want to change the period but leave all other settings -- intact use: -- --
--   createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}
--   
vXilinxSystem :: VDomainConfiguration -- | Convert SDomainConfiguration to VDomainConfiguration. -- Should be used in combination with createDomain only. vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration -- | Convenience method to express new domains in terms of others. -- --
--   createDomain (knownVDomain @System){vName="System10", vPeriod=10}
--   
-- -- This duplicates the settings in the System domain, replaces the -- name and period, and creates an instance for it. As most users often -- want to update the system domain, a shortcut is available in the form: -- --
--   createDomain vSystem{vName="System10", vPeriod=10}
--   
-- -- The function will create two extra identifiers. The first: -- --
--   type System10 = ..
--   
-- -- You can use that as the dom to Clocks/Resets/Enables/Signals. For -- example: Signal System10 Int. Additionally, it will create a -- VDomainConfiguration that you can use in later calls to -- createDomain: -- --
--   vSystem10 = knownVDomain @System10
--   
-- -- It will also make System10 an instance of KnownDomain. -- -- If either identifier is already in scope it will not be generated a -- second time. Note: This can be useful for example when documenting a -- new domain: -- --
--   -- | Here is some documentation for CustomDomain
--   type CustomDomain = ("CustomDomain" :: Domain)
--   
--   -- | Here is some documentation for vCustomDomain
--   createDomain vSystem{vName="CustomDomain"}
--   
createDomain :: VDomainConfiguration -> Q [Dec] -- | We either get evidence that this function was instantiated with the -- same domains, or Nothing. sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB) -- | Convert Enable construct to its underlying representation: a -- signal of bools. fromEnable :: Enable dom -> Signal dom Bool -- | Convert a signal of bools to an Enable construct toEnable :: Signal dom Bool -> Enable dom -- | Enable generator for some domain. Is simply always True. enableGen :: Enable dom -- | Clock generator for simulations. Do not use this clock -- generator for the testBench function, use tbClockGen -- instead. -- -- To be used like: -- --
--   clkSystem = clockGen @System
--   
-- -- See DomainConfiguration for more information on how to use -- synthesis domains. clockGen :: KnownDomain dom => Clock dom -- | Reset generator for simulation purposes. Asserts the reset for a -- single cycle. -- -- To be used like: -- --
--   rstSystem = resetGen @System
--   
-- -- See tbClockGen for example usage. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGen :: forall dom. KnownDomain dom => Reset dom -- | Reset generator for simulation purposes. Asserts the reset for the -- first n cycles. -- -- To be used like: -- --
--   rstSystem5 = resetGen @System d5
--   
-- -- Example usage: -- --
--   >>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
--   [True,True,True,False,False,False,False]
--   
-- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active high reset. Has no effect if reset is -- already an active high reset. Is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | Convert a reset to an active low reset. Has no effect if reset is -- already an active low reset. It is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeToActiveLow instead. This function -- will be removed in Clash 1.12. unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool -- | unsafeFromReset is unsafe because it can introduce: -- -- -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- -- NB: You probably want to use unsafeToActiveLow or -- unsafeToActiveHigh. unsafeFromReset :: Reset dom -> Signal dom Bool -- | unsafeToReset is unsafe. For asynchronous resets it is unsafe -- because it can introduce combinatorial loops. In case of synchronous -- resets it can lead to meta-stability issues in the presence of -- asynchronous resets. -- -- NB: You probably want to use unsafeFromActiveLow or -- unsafeFromActiveHigh. unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveHigh instead. This function -- will be removed in Clash 1.12. unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active high reset and convert it to -- a reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. -- | Deprecated: Use unsafeFromActiveLow instead. This function -- will be removed in Clash 1.12. unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | Interpret a signal of bools as an active low reset and convert it to a -- reset signal corresponding to the domain's setting. -- -- For asynchronous resets it is unsafe because it can cause -- combinatorial loops. In case of synchronous resets it can lead to -- meta-stability in the presence of asynchronous resets. unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom -- | The above type is a generalization for: -- --
--   (.||.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (||) that returns a Signal of -- Bool (.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 .||. -- | The above type is a generalization for: -- --
--   (.&&.) :: Signal Bool -> Signal Bool -> Signal Bool
--   
-- -- It is a version of (&&) that returns a Signal of -- Bool (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 .&&. -- | The above type is a generalization for: -- --
--   mux :: Signal Bool -> Signal a -> Signal a -> Signal a
--   
-- -- A multiplexer. Given "mux b t f", output t -- when b is True, and f when b is -- False. mux :: Applicative f => f Bool -> f a -> f a -> f a -- | The above type is a generalization for: -- --
--   (.==.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (==) that returns a Signal of -- Bool (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 .==. -- | The above type is a generalization for: -- --
--   (./=.) :: Eq a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (/=) that returns a Signal of -- Bool (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 ./=. -- | The above type is a generalization for: -- --
--   (.<.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<) that returns a Signal of -- Bool (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<. -- | The above type is a generalization for: -- --
--   (.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (<=) that returns a Signal of -- Bool (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .<=. -- | The above type is a generalization for: -- --
--   (.>.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>) that returns a Signal of -- Bool (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>. -- | The above type is a generalization for: -- --
--   (.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool
--   
-- -- It is a version of (>=) that returns a Signal of -- Bool (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 .>=. -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5])
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList :: NFDataX a => [a] -> Signal dom a -- | Create a Signal from a list -- -- Every element in the list will correspond to a value of the signal for -- one clock cycle. -- --
--   >>> sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
--   [1,2]
--   
-- -- NB: This function is not synthesizable fromList_lazy :: [a] -> Signal dom a -- | Calculate the period in ps, given a frequency in Hz -- -- I.e., to calculate the clock period for a circuit to run at 240 MHz we -- get -- --
--   >>> hzToPeriod 240e6
--   4166
--   
-- -- If the value hzToPeriod is applied to is not of the type -- Ratio Natural, you can use hzToPeriod -- (realToFrac f). Note that if f is negative, -- realToFrac will give an Underflow :: -- ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Natural. To -- get the old behavior of this function, use a type application: -- --
--   >>> hzToPeriod @Natural 240e6
--   4166
--   
-- -- hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a -- | Calculate the frequency in Hz, given the period in ps -- -- I.e., to calculate the clock frequency of a clock with a period of -- 5000 ps: -- --
--   >>> periodToHz 5000
--   2.0e8
--   
-- -- Note that if p in periodToHz (fromIntegral p) -- is negative, fromIntegral will give an Underflow -- :: ArithException without a call stack, making debugging -- cumbersome. -- -- Before Clash 1.8, this function always returned a Ratio -- Natural. To get the old behavior of this function, use a type -- application: -- --
--   >>> periodToHz @(Ratio Natural) 5000
--   200000000 % 1
--   
-- -- NB: This function is not synthesizable periodToHz :: (HasCallStack, Fractional a) => Natural -> a -- | Get the clock period from a KnownDomain context clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period -- | Get ActiveEdge from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case activeEdge @dom of
--       SRising -> foo
--       SFalling -> bar
--   
activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge -- | Get ResetKind from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetKind @dom of
--       SAsynchronous -> foo
--       SSynchronous -> bar
--   
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync -- | Get InitBehavior from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case initBehavior @dom of
--       SDefined -> foo
--       SUnknown -> bar
--   
initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init -- | Get ResetPolarity from a KnownDomain context. Example usage: -- --
--   f :: forall dom . KnownDomain dom => ....
--   f a b c =
--     case resetPolarity @dom of
--       SActiveHigh -> foo
--       SActiveLow -> bar
--   
resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity -- | Like 'knownDomain but yields a VDomainConfiguration. Should -- only be used in combination with createDomain. knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration -- | Isomorphism between a Signal of a product type (e.g. a tuple) -- and a product type of Signals. -- -- Instances of Bundle must satisfy the following laws: -- --
--   bundle . unbundle = id
--   unbundle . bundle = id
--   
-- -- By default, bundle and unbundle, are defined as the -- identity, that is, writing: -- --
--   data D = A | B
--   
--   instance Bundle D
--   
-- -- is the same as: -- --
--   data D = A | B
--   
--   instance Bundle D where
--     type Unbundled clk D = Signal clk D
--     bundle   s = s
--     unbundle s = s
--   
-- -- For custom product types you'll have to write the instance manually: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b }
--   
--   instance Bundle (Pair a b) where
--     type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b)
--   
--     -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b)
--     bundle   (MkPair as bs) = MkPair <$> as <*> bs
--   
--     -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b)
--     unbundle pairs = MkPair (getA <$> pairs) (getB <$> pairs)
--   
class Bundle a where { type family Unbundled (dom :: Domain) a = res | res -> dom a; type Unbundled dom a = Signal dom a; } -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: Bundle a => Unbundled dom a -> Signal dom a -- | Example: -- --
--   bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)
--   
-- -- However: -- --
--   bundle :: Signal dom Bit -> Signal dom Bit
--   
bundle :: (Bundle a, Signal dom a ~ Unbundled dom a) => Unbundled dom a -> Signal dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: Bundle a => Signal dom a -> Unbundled dom a -- | Example: -- --
--   unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)
--   
-- -- However: -- --
--   unbundle :: Signal dom Bit -> Signal dom Bit
--   
unbundle :: (Bundle a, Unbundled dom a ~ Signal dom a) => Signal dom a -> Unbundled dom a -- | Helper type to emulate the "old" behavior of Bundle's unit instance. -- I.e., the instance for Bundle () used to be defined as: -- --
--   class Bundle () where
--     bundle   :: () -> Signal dom ()
--     unbundle :: Signal dom () -> ()
--   
-- -- In order to have sensible type inference, the Bundle class -- specifies that the argument type of bundle should uniquely -- identify the result type, and vice versa for unbundle. The type -- signatures in the snippet above don't though, as () doesn't -- uniquely map to a specific domain. In other words, domain -- should occur in both the argument and result of both functions. -- -- TaggedEmptyTuple tackles this by carrying the domain in its -- type. The bundle and unbundle instance now looks like: -- --
--   class Bundle EmptyTuple where
--     bundle   :: TaggedEmptyTuple dom -> Signal dom EmptyTuple
--     unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
--   
-- -- dom is now mentioned both the argument and result for both -- bundle and unbundle. data TaggedEmptyTuple (dom :: Domain) TaggedEmptyTuple :: TaggedEmptyTuple (dom :: Domain) -- | See TaggedEmptyTuple data EmptyTuple EmptyTuple :: EmptyTuple -- | The out part of an inout port -- -- Wraps (multiple) writing signals. The semantics are such that only one -- of the signals may write at a single time step. -- -- BiSignalOut has the type role -- --
--   >>> :i BiSignalOut
--   type role BiSignalOut nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | The in part of an inout port. BiSignalIn has the type -- role -- --
--   >>> :i BiSignalIn
--   type role BiSignalIn nominal nominal nominal
--   ...
--   
-- -- as it is not safe to coerce the default behaviour, synthesis domain or -- width of the data in the signal. data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) -- | Used to specify the default behavior of a "BiSignal", i.e. what -- value is read when no value is being written to it. data BiSignalDefault -- | inout port behaves as if connected to a pull-up resistor PullUp :: BiSignalDefault -- | inout port behaves as if connected to a pull-down resistor PullDown :: BiSignalDefault -- | inout port behaves as if is floating. Reading a -- floating "BiSignal" value in simulation will yield an errorX -- (undefined value). Floating :: BiSignalDefault -- | Read the value from an inout port readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a -- | Combine several inout signals into one. mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m -- | Write to an inout port writeToBiSignal :: (HasCallStack, BitPack a, NFDataX a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a) -- | Converts the out part of a BiSignal to an in part. -- In simulation it checks whether multiple components are writing and -- will error accordingly. Make sure this is only called ONCE for every -- BiSignal. veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n -- | Clock generator for the System clock domain. -- -- NB: Should only be used for simulation, and not for the -- testBench function. For the testBench function, used -- tbSystemClockGen systemClockGen :: Clock System -- | Reset generator for use in simulation, for the System clock -- domain. Asserts the reset for a single cycle. -- -- NB: While this can be used in the testBench function, -- it cannot be synthesized to hardware. -- --

Example

-- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--   
systemResetGen :: Reset System -- | The resetSynchronizer will synchronize an incoming reset according to -- whether the domain is synchronous or asynchronous. -- -- For asynchronous resets this synchronizer ensures the reset will only -- be de-asserted synchronously but it can still be asserted -- asynchronously. The reset assert is immediate, but reset de-assertion -- is delayed by two cycles. -- -- Normally, asynchronous resets can be both asynchronously asserted and -- de-asserted. Asynchronous de-assertion can induce meta-stability in -- the component which is being reset. To ensure this doesn't happen, -- resetSynchronizer ensures that de-assertion of a reset happens -- synchronously. Assertion of the reset remains asynchronous. -- -- Note that asynchronous assertion does not induce meta-stability in the -- component whose reset is asserted. However, when a component "A" in -- another clock or reset domain depends on the value of a component "B" -- being reset, then asynchronous assertion of the reset of component "B" -- can induce meta-stability in component "A". To prevent this from -- happening you need to use a proper synchronizer, for example one of -- the synchronizers in Clash.Explicit.Synchronizer. -- -- For synchronous resets this function ensures that the reset is -- asserted and de-asserted synchronously. Both the assertion and -- de-assertion of the reset are delayed by two cycles. -- --

Example 1

-- -- The circuit below detects a rising bit (i.e., a transition from 0 to -- 1) in a given argument. It takes a reset that is not synchronized to -- any of the other incoming signals and synchronizes it using -- resetSynchronizer. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk asyncRst key1 =
--     withClockResetEnable clk rst enableGen leds
--    where
--     rst   = resetSynchronizer clk asyncRst
--     key1R = isRising 1 key1
--     leds  = mealy blinkerT (1, False, 0) key1R
--   
-- --

Example 2

-- -- Similar to Example 1 this circuit detects a rising bit (i.e., a -- transition from 0 to 1) in a given argument. It takes a clock that is -- not stable yet and a reset signal that is not synchronized to any -- other signals. It stabilizes the clock and then synchronizes the reset -- signal. -- -- Note that the function altpllSync provides this functionality -- in a convenient form, obviating the need for -- resetSynchronizer for this use case. -- --
--   topEntity
--     :: Clock  System
--     -> Reset  System
--     -> Signal System Bit
--     -> Signal System (BitVector 8)
--   topEntity clk rst key1 =
--       let  (pllOut,pllStable) = unsafeAltpll clk rst
--            rstSync            = resetSynchronizer pllOut (unsafeFromActiveLow pllStable)
--       in   exposeClockResetEnable leds pllOut rstSync enableGen
--     where
--       key1R  = isRising 1 key1
--       leds   = mealy blinkerT (1, False, 0) key1R
--   
-- --

Implementation details

-- -- resetSynchronizer implements the following circuit for -- asynchronous domains: -- --
--                                   rst
--   --------------------------------------+
--                       |                 |
--                  +----v----+       +----v----+
--     deasserted   |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
-- -- This corresponds to figure 3d at -- https://www.embedded.com/asynchronous-reset-synchronization-and-distribution-challenges-and-solutions/ -- -- For synchronous domains two sequential dflipflops are used: -- --
--                  +---------+       +---------+
--     rst          |         |       |         |
--   --------------->         +------->         +-------->
--                  |         |       |         |
--              +---|>        |   +---|>        |
--              |   |         |   |   |         |
--              |   +---------+   |   +---------+
--      clk     |                 |
--   -----------------------------+
--   
resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Reset dom -- | Filter glitches from reset signals by only triggering a reset after it -- has been asserted for glitchlessPeriod cycles. Similarly, it -- will stay asserted until a glitchlessPeriod number of -- deasserted cycles have been observed. -- -- This circuit can only be used on platforms supporting initial values. -- This restriction can be worked around by using -- unsafeResetGlitchFilter but this is not recommended. -- -- On platforms without initial values, you should instead use -- resetGlitchFilterWithReset with an additional power-on reset, -- or holdReset if filtering is only needed on deassertion. -- -- At power-on, the reset will be asserted. If the filtered reset input -- remains unasserted, the output reset will deassert after -- glitchlessPeriod clock cycles. -- -- If resetGlitchFilter is used in a domain with asynchronous -- resets (Asynchronous), resetGlitchFilter will first -- synchronize the reset input with dualFlipFlopSynchronizer. -- --

Example 1

-- --
--   >>> let sampleResetN n = sampleN n . unsafeToActiveHigh
--   
--   >>> let resetFromList = unsafeFromActiveHigh . fromList
--   
--   >>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True, True]
--   
--   >>> sampleResetN 12 (resetGlitchFilter d2 (clockGen @XilinxSystem) rst)
--   [True,True,True,True,False,False,False,False,False,True,True,True]
--   
resetGlitchFilter :: forall dom glitchlessPeriod. (HasCallStack, HasDefinedInitialValues dom, 1 <= glitchlessPeriod) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom -- | A constraint that indicates the component needs a Clock, -- a Reset, and an Enable belonging to the System -- domain. -- -- Click here to read more about hidden clocks, resets, and -- enables type SystemClockResetEnable = (Hidden (HiddenClockName System) (Clock System), Hidden (HiddenResetName System) (Reset System), Hidden (HiddenEnableName System) (Enable System)) -- | A constraint that indicates the component needs a Clock, -- a Reset, and an Enable belonging to the same -- dom. -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenClockResetEnable dom = (HiddenClock dom, HiddenReset dom, HiddenEnable dom) -- | A constraint that indicates the component needs an -- Enable -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenEnable dom = (Hidden (HiddenEnableName dom) (Enable dom), KnownDomain dom) -- | A constraint that indicates the component needs a Reset -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenReset dom = (Hidden (HiddenResetName dom) (Reset dom), KnownDomain dom) -- | A constraint that indicates the component has a hidden -- Clock -- -- Click here to read more about hidden clocks, resets, and -- enables type HiddenClock dom = (Hidden (HiddenClockName dom) (Clock dom), KnownDomain dom) -- | Expose a hidden Clock argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClock dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a clock of a component working on multiple -- domains (such as the first example), use exposeSpecificClock. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClock reg clockGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeClock to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClock @System reg clockGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeClock :: forall dom r. WithSingleDomain dom r => (HiddenClock dom => r) -> KnownDomain dom => Clock dom -> r -- | Expose a hidden Clock argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeClock, callers should -- explicitly state what the clock domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificClock can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificClock @System reg clockGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificClock @dom reg clockGen
--   
exposeSpecificClock :: forall dom r. WithSpecificDomain dom r => (HiddenClock dom => r) -> KnownDomain dom => Clock dom -> r -- | Hide the Clock argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideClock :: forall dom r. HiddenClock dom => (Clock dom -> r) -> r -- | Connect an explicit Clock to a function with a hidden -- Clock. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClock dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a clock to a component working on multiple -- domains (such as the first example), use withSpecificClock. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClock clockGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withClock to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClock @System clockGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withClock :: forall dom r. WithSingleDomain dom r => KnownDomain dom => Clock dom -> (HiddenClock dom => r) -> r -- | Connect an explicit Clock to a function with a hidden -- Clock. This function can be used on components with multiple -- domains. As opposed to withClock, callers should explicitly -- state what the clock domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificClock can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificClock @System clockGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificClock @dom clockGen reg
--   
withSpecificClock :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Clock dom -> (HiddenClock dom => r) -> r -- | Connect a hidden Clock to an argument where a normal -- Clock argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasClock :: forall dom. HiddenClock dom => Clock dom -- | Expose a hidden Reset argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenReset dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a reset of a component working on multiple -- domains (such as the first example), use exposeSpecificReset. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeReset reg resetGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeReset to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeReset @System reg resetGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeReset :: forall dom r. WithSingleDomain dom r => (HiddenReset dom => r) -> KnownDomain dom => Reset dom -> r -- | Expose a hidden Reset argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeReset, callers should -- explicitly state what the reset domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificReset can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificReset @System reg resetGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificReset @dom reg resetGen
--   
exposeSpecificReset :: forall dom r. WithSpecificDomain dom r => (HiddenReset dom => r) -> KnownDomain dom => Reset dom -> r -- | Hide the Reset argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideReset :: forall dom r. HiddenReset dom => (Reset dom -> r) -> r -- | Connect an explicit Reset to a function with a hidden -- Reset. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenReset dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a reset to a component working on multiple -- domains (such as the first example), use withSpecificReset. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withReset resetGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withReset to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withReset @System resetGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withReset :: forall dom r. WithSingleDomain dom r => KnownDomain dom => Reset dom -> (HiddenReset dom => r) -> r -- | Connect an explicit Reset to a function with a hidden -- Reset. This function can be used on components with multiple -- domains. As opposed to withReset, callers should explicitly -- state what the reset domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificReset can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificReset @System resetGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificReset @dom resetGen reg
--   
withSpecificReset :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Reset dom -> (HiddenReset dom => r) -> r -- | Connect a hidden Reset to an argument where a normal -- Reset argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasReset :: forall dom. HiddenReset dom => Reset dom -- | Expose a hidden Enable argument of a component, so it can be -- applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a enable of a component working on multiple -- domains (such as the first example), use exposeSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeEnable reg enableGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeEnable @System reg enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
exposeEnable :: forall dom r. WithSingleDomain dom r => (HiddenEnable dom => r) -> KnownDomain dom => Enable dom -> r -- | Expose a hidden Enable argument of a component, so it can be -- applied explicitly. This function can be used on components with -- multiple domains. As opposed to exposeEnable, callers should -- explicitly state what the enable domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificEnable @System reg enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificEnable @dom reg enableGen
--   
exposeSpecificEnable :: forall dom r. WithSpecificDomain dom r => (HiddenEnable dom => r) -> KnownDomain dom => Enable dom -> r -- | Hide the Enable argument of a component, so it can be routed -- implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideEnable :: forall dom r. HiddenEnable dom => (Enable dom -> r) -> r -- | Connect an explicit Enable to a function with a hidden -- Enable. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a enable to a component working on multiple -- domains (such as the first example), use withSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withEnable enableGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withEnable to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withEnable @System enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withEnable :: forall dom r. KnownDomain dom => WithSingleDomain dom r => Enable dom -> (HiddenEnable dom => r) -> r -- | Connect an explicit Enable to a function with a hidden -- Enable. This function can be used on components with multiple -- domains. As opposed to withEnable, callers should explicitly -- state what the enable domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificEnable @System enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificEnable @dom enableGen reg
--   
withSpecificEnable :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Enable dom -> (HiddenEnable dom => r) -> r -- | Connect a hidden Enable to an argument where a normal -- Enable argument was expected. -- -- Click here to read more about hidden clocks, resets, and -- enables hasEnable :: forall dom. HiddenEnable dom => Enable dom -- | Merge enable signal with signal of bools by applying the boolean AND -- operation. -- -- NB: The component given to andEnable as an argument needs an -- explicit type signature. Please read Monomorphism restriction -- leads to surprising behavior. -- -- The component whose enable is modified will only be enabled when both -- the encompassing HiddenEnable and the Signal -- dom Bool are asserted. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to merge an enable of a component working on multiple -- domains (such as the first example), use andSpecificEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> f en = andEnable en reg
--   
--   >>> sampleN @System 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
-- -- Force andEnable to work on System (hence sampleN -- not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> f en = andEnable @System en reg
--   
--   >>> sampleN 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
andEnable :: forall dom r. HiddenEnable dom => WithSingleDomain dom r => Signal dom Bool -> (HiddenEnable dom => r) -> r -- | Merge enable signal with signal of bools by applying the boolean AND -- operation. -- -- NB: The component given to andSpecificEnable as an argument -- needs an explicit type signature. Please read Monomorphism -- restriction leads to surprising behavior. -- -- The component whose enable is modified will only be enabled when both -- the encompassing HiddenEnable and the Signal -- dom Bool are asserted. -- -- This function can be used on components with multiple domains. As -- opposed to andEnable, callers should explicitly state what the -- enable domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- andSpecificEnable can only be used when it can find the -- specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> f en = andSpecificEnable @System en reg
--   
--   >>> sampleN 10 (f (riseEvery d2))
--   [5,5,5,6,6,7,7,8,8,9]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   f en = andSpecificEnable @dom en reg
--   
andSpecificEnable :: forall dom r. (HiddenEnable dom, WithSpecificDomain dom r) => Signal dom Bool -> (HiddenEnable dom => r) -> r -- | Expose hidden Clock, Reset, and Enable arguments -- of a component, so they can be applied explicitly. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to expose a clock, reset, and enable of a component -- working on multiple domains (such as the first example), use -- exposeSpecificClockResetEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClockResetEnable reg clockGen resetGen enableGen
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force exposeClockResetEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = exposeClockResetEnable @System reg clockGen resetGen enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Usage in a testbench context: -- --
--   topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
--   topEntity = concat
--   
--   testBench :: Signal System Bool
--   testBench = done
--     where
--       testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
--       expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
--       done           = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst en
--       clk            = tbSystemClockGen (not <$> done)
--       rst            = systemResetGen
--       en             = enableGen
--   
exposeClockResetEnable :: forall dom r. WithSingleDomain dom r => (HiddenClockResetEnable dom => r) -> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r -- | Expose hidden Clock, Reset, and Enable arguments -- of a component, so they can be applied explicitly. This function can -- be used on components with multiple domains. As opposed to -- exposeClockResetEnable, callers should explicitly state what -- the domain is. See the examples for more information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- exposeSpecificClockResetEnable can only be used when it can -- find the specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = exposeSpecificClockResetEnable @System reg clockGen resetGen enableGen
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = exposeSpecificClockResetEnable @dom reg clockGen resetGen enableGen
--   
exposeSpecificClockResetEnable :: forall dom r. WithSpecificDomain dom r => (HiddenClockResetEnable dom => r) -> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r -- | Hide the Clock, Reset, and Enable arguments of a -- component, so they can be routed implicitly. -- -- Click here to read more about hidden clocks, resets, and -- enables hideClockResetEnable :: forall dom r. HiddenClockResetEnable dom => (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) -> r -- | Connect an explicit Clock, Reset, and Enable to a -- function with a hidden Clock, Reset, and Enable. -- -- This function can only be used on components with a single domain. For -- example, this function will refuse when: -- --
--   r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a
--   
-- -- But will work when: -- --
--   r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a
--   
-- -- If you want to connect a clock, reset, and enable to a component -- working on multiple domains (such as the first example), use -- withSpecificClockResetEnable. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- Usage with a polymorphic domain: -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClockResetEnable clockGen resetGen enableGen reg
--   
--   >>> sampleN @System 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Force withClockResetEnable to work on System (hence -- sampleN not needing an explicit domain later): -- --
--   >>> reg = register 5 (reg + 1)
--   
--   >>> sig = withClockResetEnable @System clockGen resetGen enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
withClockResetEnable :: forall dom r. KnownDomain dom => WithSingleDomain dom r => Clock dom -> Reset dom -> Enable dom -> (HiddenClockResetEnable dom => r) -> r -- | Connect an explicit Clock, Reset, and Enable to a -- function with hidden Clock, Reset, and Enable -- arguments. This function can be used on components with multiple -- domains. As opposed to withClockResetEnable, callers should -- explicitly state what the domain is. See the examples for more -- information. -- -- Click here to read more about hidden clocks, resets, and -- enables -- --

Example

-- -- withSpecificClockResetEnable can only be used when it can find -- the specified domain in r: -- --
--   >>> reg = register @System 5 (reg + 1)
--   
--   >>> sig = withSpecificClockResetEnable @System clockGen resetGen enableGen reg
--   
--   >>> sampleN 10 sig
--   [5,5,6,7,8,9,10,11,12,13]
--   
-- -- Type variables work too, if they are in scope. For example: -- --
--   reg = register @dom 5 (reg + 1)
--   sig = withSpecificClockResetEnable @dom clockGen resetGen enableGen reg
--   
withSpecificClockResetEnable :: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) => Clock dom -> Reset dom -> Enable dom -> (HiddenClockResetEnable dom => r) -> r -- | Special version of delay that doesn't take enable signals of -- any kind. Initial value will be undefined. dflipflop :: forall dom a. (HiddenClock dom, NFDataX a) => Signal dom a -> Signal dom a -- | delay dflt s delays the values in -- Signal s for once cycle, the value at time 0 is -- dflt. -- --
--   >>> sampleN @System 3 (delay 0 (fromList [1,2,3,4]))
--   [0,1,2]
--   
delay :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom a -> Signal dom a -- | Version of delay that only updates when its second argument is -- a Just value. -- --
--   >>> let input = fromList [Just 1, Just 2, Nothing, Nothing, Just 5, Just 6, Just (7::Int)]
--   
--   >>> sampleN @System 7 (delayMaybe 0 input)
--   [0,1,2,2,2,5,6]
--   
delayMaybe :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom (Maybe a) -> Signal dom a -- | Version of delay that only updates when its second argument is -- asserted. -- --
--   >>> let input = fromList [1,2,3,4,5,6,7::Int]
--   
--   >>> let enable = fromList [True,True,False,False,True,True,True]
--   
--   >>> sampleN @System 7 (delayEn 0 enable input)
--   [0,1,2,2,2,5,6]
--   
delayEn :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | register i s delays the values in Signal -- s for one cycle, and sets the value at time 0 to i -- --
--   >>> sampleN @System 5 (register 8 (fromList [1,1,2,3,4]))
--   [8,8,1,2,3]
--   
register :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom a -> Signal dom a infixr 3 `register` -- | Version of register that only updates its content when its -- second argument is a Just value. So given: -- --
--   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 (+))
--   
-- -- We get: -- --
--   >>> sampleN @System 9 sometimes1
--   [Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]
--   
--   >>> sampleN @System 9 countSometimes
--   [0,0,0,1,1,2,2,3,3]
--   
regMaybe :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom (Maybe a) -> Signal dom a infixr 3 `regMaybe` -- | Version of register that only updates its content when its -- second argument is asserted. So given: -- --
--   oscillate = register False (not <$> oscillate)
--   count     = regEn 0 oscillate (count + 1)
--   
-- -- We get: -- --
--   >>> sampleN @System 9 oscillate
--   [False,False,True,False,True,False,True,False,True]
--   
--   >>> sampleN @System 9 count
--   [0,0,0,1,1,2,2,3,3]
--   
regEn :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom Bool -> Signal dom a -> Signal dom a -- | Get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sample will supply them. The reset will be -- asserted for a single cycle. sample will not drop the value -- produced by the circuit while the reset was asserted. If you want -- this, or if you want more than a single cycle reset, consider using -- sampleWithReset. -- -- NB: This function is not synthesizable sample :: forall dom a. (KnownDomain dom, NFDataX a) => (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN @System 3 s == [s0, s1, s2]
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sampleN will supply them. The reset will be -- asserted for a single cycle. sampleN will not drop the value -- produced by the circuit while the reset was asserted. If you want -- this, or if you want more than a single cycle reset, consider using -- sampleWithResetN. -- -- NB: This function is not synthesizable sampleN :: forall dom a. (KnownDomain dom, NFDataX a) => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get an infinite list of samples from a Signal, while asserting -- the reset line for m clock cycles. sampleWithReset does -- not return the first m cycles, i.e., when the reset is -- asserted. -- -- NB: This function is not synthesizable sampleWithReset :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Get a list of n samples from a Signal, while asserting -- the reset line for m clock cycles. sampleWithReset does -- not return the first m cycles, i.e., while the reset is -- asserted. -- -- NB: This function is not synthesizable sampleWithResetN :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Lazily get an infinite list of samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sample s == [s0, s1, s2, s3, ...
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sample_lazy will supply them. The reset will be -- asserted for a single cycle. sample_lazy will not drop the -- value produced by the circuit while the reset was asserted. -- -- NB: This function is not synthesizable sample_lazy :: forall dom a. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Lazily get a list of n samples from a Signal -- -- The elements in the list correspond to the values of the Signal -- at consecutive clock cycles -- --
--   sampleN @System 3 s == [s0, s1, s2]
--   
-- -- If the given component has not yet been given a clock, reset, or -- enable line, sampleN_lazy will supply them. The reset will be -- asserted for a single cycle. sampleN_lazy will not drop the -- value produced by the circuit while the reset was asserted. -- -- NB: This function is not synthesizable sampleN_lazy :: forall dom a. KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a] -- | Simulate a (Signal a -> Signal b) function -- given a list of samples of type a -- --
--   >>> simulate @System (register 8) [1, 2, 3]
--   [8,1,2,3...
--   ...
--   
-- -- Where System denotes the domain to simulate on. The -- reset line is asserted for a single cycle. The first value is -- therefore supplied twice to the circuit: once while reset is high, and -- once directly after. The first output value (the value produced -- while the reset is asserted) is dropped. -- -- If you only want to simulate a finite number of samples, see -- simulateN. If you need the reset line to be asserted for more -- than one cycle or if you need a custom reset value, see -- simulateWithReset and simulateWithResetN. -- -- NB: This function is not synthesizable simulate :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulate, but only sample the first Int output -- values. -- -- NB: This function is not synthesizable simulateN :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulate, but with the reset line asserted for n -- cycles. Similar to simulate, simulateWithReset will drop -- the output values produced while the reset is asserted. While the -- reset is asserted, the reset value a is supplied to the -- circuit. simulateWithReset :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Same as simulateWithReset, but only sample the first Int -- output values. simulateWithResetN :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Lazily simulate a (Signal a -> Signal -- b) function given a list of samples of type a -- --
--   >>> simulate @System (register 8) [1, 2, 3]
--   [8,1,2,3...
--   ...
--   
-- -- NB: This function is not synthesizable simulate_lazy :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b] -- | Simulate a (Unbundled a -> Unbundled b) -- function given a list of samples of type a -- --
--   >>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b] -- | Lazily simulate a (Unbundled a -> -- Unbundled b) function given a list of samples of type -- a -- --
--   >>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
--   [(8,8),(1,1),(2,2),(3,3)...
--   ...
--   
-- -- NB: This function is not synthesizable simulateB_lazy :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b] -- | Simulate a component until it matches a condition -- -- If the given component has not yet been given a clock, reset, or -- enable line, runUntil will supply them. The reset will be -- asserted for a single cycle. -- -- It prints a message of the form -- --
--   Signal sampled for N cycles until value X
--   
-- -- NB: This function is not synthesizable -- --

Example with test bench

-- -- A common usage is with a test bench using outputVerifier. -- -- NB: Since this uses assert, when using clashi, -- read the note at Clash.Explicit.Testbench#assert-clashi. -- --
--   import Clash.Prelude
--   import Clash.Explicit.Testbench
--   
--   topEntity
--     :: Signal System Int
--     -> Signal System Int
--   topEntity = id
--   
--   testBench
--     :: Signal System Bool
--   testBench = done
--    where
--     testInput = stimuliGenerator clk rst $(listToVecTH [1 :: Int .. 10])
--     expectedOutput =
--       outputVerifier' clk rst $(listToVecTH $ [1 :: Int .. 9] <> [42])
--     done = expectedOutput $ topEntity testInput
--     clk = tbSystemClockGen (not <$> done)
--     rst = systemResetGen
--   
-- --
--   > runUntil id testBench
--   
--   
--   cycle(<Clock: System>): 10, outputVerifier
--   expected value: 42, not equal to actual value: 10
--   Signal sampled for 11 cycles until value True
--   
-- -- When you need to verify multiple test benches, the following -- invocations come in handy: -- --
--   > mapM_ (runUntil id) [ testBenchA, testBenchB ]
--   
-- -- or when the test benches are in different clock domains: -- --
--   testBenchA :: Signal DomA Bool
--   testBenchB :: Signal DomB Bool
--   
-- --
--   > sequence_ [ runUntil id testBenchA, runUntil id testBenchB ]
--   
runUntil :: forall dom a. (KnownDomain dom, NFDataX a, ShowX a) => (a -> Bool) -> (HiddenClockResetEnable dom => Signal dom a) -> IO () -- | testFor n s tests the signal s for n cycles. -- -- NB: This function is not synthesizable testFor :: KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom Bool) -> Property -- | Implicit version of unsafeSynchronizer. unsafeSynchronizer :: forall dom1 dom2 a. (HiddenClock dom1, HiddenClock dom2) => Signal dom1 a -> Signal dom2 a -- | Hold reset for a number of cycles relative to an implicit reset -- signal. -- -- Example: -- --
--   >>> sampleN @System 8 (unsafeToActiveHigh (holdReset (SNat @2)))
--   [True,True,True,False,False,False,False,False]
--   
-- -- holdReset holds the reset for an additional 2 clock cycles for -- a total of 3 clock cycles where the reset is asserted. holdReset :: forall dom m. HiddenClockResetEnable dom => SNat m -> Reset dom -- | Like fromList, but resets on reset and has a defined reset -- value. -- --
--   >>> let rst = unsafeFromActiveHigh (fromList [True, True, False, False, True, False])
--   
--   >>> let res = withReset rst (fromListWithReset Nothing [Just 'a', Just 'b', Just 'c'])
--   
--   >>> sampleN @System 6 res
--   [Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
--   
-- -- NB: This function is not synthesizable fromListWithReset :: forall dom a. (HiddenReset dom, NFDataX a) => a -> [a] -> Signal dom a -- | Convert between different types of reset, adding a synchronizer in -- case it needs to convert from an asynchronous to a synchronous reset. convertReset :: forall domA domB. (HiddenClock domA, HiddenClock domB) => Reset domA -> Reset domB -- | Build an Automaton from a function over Signals. -- -- NB: Consumption of continuation of the Automaton must be -- affine; that is, you can only apply the continuation associated with a -- particular element at most once. signalAutomaton :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> Automaton (->) a b -- | Fixed size vectors. -- -- data Vec :: Nat -> Type -> Type [Nil] :: Vec 0 a [Cons] :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the head of a vector. -- --
--   >>> 3:>4:>5:>Nil
--   3 :> 4 :> 5 :> Nil
--   
--   >>> let x = 3:>4:>5:>Nil
--   
--   >>> :t x
--   x :: Num a => Vec 3 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (x :> y :> _) = x + y
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   7
--   
-- -- Also in conjunctions with (:<): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:>) :: a -> Vec n a -> Vec (n + 1) a -- | Add an element to the tail of a vector. -- --
--   >>> (3:>4:>5:>Nil) :< 1
--   3 :> 4 :> 5 :> 1 :> Nil
--   
--   >>> let x = (3:>4:>5:>Nil) :< 1
--   
--   >>> :t x
--   x :: Num a => Vec 4 a
--   
-- -- Can be used as a pattern: -- --
--   >>> let f (_ :< y :< x) = y + x
--   
--   >>> :t f
--   f :: Num a => Vec ((n + 1) + 1) a -> a
--   
--   >>> f (3:>4:>5:>6:>7:>Nil)
--   13
--   
-- -- Also in conjunctions with (:>): -- --
--   >>> let g (a :> b :> (_ :< y :< x)) = a + b +  x + y
--   
--   >>> :t g
--   g :: Num a => Vec ((((n + 1) + 1) + 1) + 1) a -> a
--   
--   >>> g (1:>2:>3:>4:>5:>Nil)
--   12
--   
pattern (:<) :: Vec n a -> a -> Vec (n + 1) a infixr 5 :> infixl 5 :< infixr 5 `Cons` -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a vector, reduces -- the vector using the binary operator, from left to right: -- --
--   foldl f z (x1 :> x2 :> ... :> xn :> Nil) == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   foldl f z Nil                            == z
--   
-- --
--   >>> foldl (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldl :: forall b a n. (b -> a -> b) -> b -> Vec n a -> b -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a vector, reduces -- the vector using the binary operator, from right to left: -- --
--   foldr f z (x1 :> ... :> xn1 :> xn :> Nil) == x1 `f` (... (xn1 `f` (xn `f` z))...)
--   foldr r z Nil                             == z
--   
-- --
--   >>> foldr (/) 1 (5 :> 4 :> 3 :> 2 :> Nil)
--   1.875
--   
-- -- "foldr f z xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr f z xs" produces a linear structure, -- which has a depth, or delay, of O(length xs). Use -- fold if your binary operator f is associative, as -- "fold f xs" produces a structure with a depth of -- O(log_2(length xs)). foldr :: (a -> b -> b) -> b -> Vec n a -> b -- | "map f xs" is the vector obtained by applying f -- to each element of xs, i.e., -- --
--   map f (x1 :> x2 :>  ... :> xn :> Nil) == (f x1 :> f x2 :> ... :> f xn :> Nil)
--   
-- -- and corresponds to the following circuit layout: -- map :: (a -> b) -> Vec n a -> Vec n b -- | Convert a BitVector to a Vec of Bits. -- --
--   >>> let x = 6 :: BitVector 8
--   
--   >>> x
--   0b0000_0110
--   
--   >>> bv2v x
--   0 :> 0 :> 0 :> 0 :> 0 :> 1 :> 1 :> 0 :> Nil
--   
bv2v :: KnownNat n => BitVector n -> Vec n Bit -- | To be used as the motive p for dfold, when the f -- in "dfold p f" is a variation on (:>), e.g.: -- --
--   map' :: forall n a b . KnownNat n => (a -> b) -> Vec n a -> Vec n b
--   map' f = dfold (Proxy @(VCons b)) (_ x xs -> f x :> xs)
--   
data VCons (a :: Type) (f :: TyFun Nat Type) :: Type traverse# :: forall a f b n. Applicative f => (a -> f b) -> Vec n a -> f (Vec n b) -- | Create a vector of one element -- --
--   >>> singleton 5
--   5 :> Nil
--   
singleton :: a -> Vec 1 a -- | Extract the first element of a vector -- --
--   >>> head (1:>2:>3:>Nil)
--   1
--   
-- --
--   >>> head Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘head’, namely ‘Nil’
--         In the expression: head Nil
--         In an equation for ‘it’: it = head Nil
--   
head :: Vec (n + 1) a -> a -- | Extract the elements after the head of a vector -- --
--   >>> tail (1:>2:>3:>Nil)
--   2 :> 3 :> Nil
--   
-- --
--   >>> tail Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘tail’, namely ‘Nil’
--         In the expression: tail Nil
--         In an equation for ‘it’: it = tail Nil
--   
tail :: Vec (n + 1) a -> Vec n a -- | Extract the last element of a vector -- --
--   >>> last (1:>2:>3:>Nil)
--   3
--   
-- --
--   >>> last Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘last’, namely ‘Nil’
--         In the expression: last Nil
--         In an equation for ‘it’: it = last Nil
--   
last :: Vec (n + 1) a -> a -- | Extract all the elements of a vector except the last element -- --
--   >>> init (1:>2:>3:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> init Nil
--   
--   <interactive>:...
--       • Couldn't match type ‘1’ with ‘0’
--         Expected type: Vec (0 + 1) a
--           Actual type: Vec 0 a
--       • In the first argument of ‘init’, namely ‘Nil’
--         In the expression: init Nil
--         In an equation for ‘it’: it = init Nil
--   
init :: Vec (n + 1) a -> Vec n a -- | Shift in elements to the head of a vector, bumping out elements at the -- tail. The result is a tuple containing: -- -- -- --
--   >>> shiftInAt0 (1 :> 2 :> 3 :> 4 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> 0 :> 1 :> 2 :> Nil,3 :> 4 :> Nil)
--   
--   >>> shiftInAt0 (1 :> Nil) ((-1) :> 0 :> Nil)
--   (-1 :> Nil,0 :> 1 :> Nil)
--   
shiftInAt0 :: KnownNat n => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Shift in element to the tail of a vector, bumping out elements at the -- head. The result is a tuple containing: -- -- -- --
--   >>> shiftInAtN (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> Nil)
--   (3 :> 4 :> 5 :> 6 :> Nil,1 :> 2 :> Nil)
--   
--   >>> shiftInAtN (1 :> Nil) (2 :> 3 :> Nil)
--   (3 :> Nil,1 :> 2 :> Nil)
--   
shiftInAtN :: KnownNat m => Vec n a -> Vec m a -> (Vec n a, Vec m a) -- | Add an element to the head of a vector, and extract all but the last -- element. -- --
--   >>> 1 +>> (3:>4:>5:>Nil)
--   1 :> 3 :> 4 :> Nil
--   
--   >>> 1 +>> Nil
--   Nil
--   
(+>>) :: KnownNat n => a -> Vec n a -> Vec n a infixr 4 +>> -- | Add an element to the tail of a vector, and extract all but the first -- element. -- --
--   >>> (3:>4:>5:>Nil) <<+ 1
--   4 :> 5 :> 1 :> Nil
--   
--   >>> Nil <<+ 1
--   Nil
--   
(<<+) :: Vec n a -> a -> Vec n a infixl 4 <<+ -- | Shift m elements out from the head of a vector, filling up the -- tail with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFrom0 d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (3 :> 4 :> 5 :> 0 :> 0 :> Nil,1 :> 2 :> Nil)
--   
shiftOutFrom0 :: (Default a, KnownNat m) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Shift m elements out from the tail of a vector, filling up the -- head with Default values. The result is a tuple containing: -- -- -- --
--   >>> shiftOutFromN d2 ((1 :> 2 :> 3 :> 4 :> 5 :> Nil) :: Vec 5 Integer)
--   (0 :> 0 :> 1 :> 2 :> 3 :> Nil,4 :> 5 :> Nil)
--   
shiftOutFromN :: (Default a, KnownNat n) => SNat m -> Vec (m + n) a -> (Vec (m + n) a, Vec m a) -- | Append two vectors. -- --
--   >>> (1:>2:>3:>Nil) ++ (7:>8:>Nil)
--   1 :> 2 :> 3 :> 7 :> 8 :> Nil
--   
(++) :: Vec n a -> Vec m a -> Vec (n + m) a infixr 5 ++ -- | Split a vector into two vectors at the given point. -- --
--   >>> splitAt (SNat :: SNat 3) (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
--   >>> splitAt d3 (1:>2:>3:>7:>8:>Nil)
--   (1 :> 2 :> 3 :> Nil,7 :> 8 :> Nil)
--   
splitAt :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) -- | Split a vector into two vectors where the length of the two is -- determined by the context. -- --
--   >>> splitAtI (1:>2:>3:>7:>8:>Nil) :: (Vec 2 Int, Vec 3 Int)
--   (1 :> 2 :> Nil,3 :> 7 :> 8 :> Nil)
--   
splitAtI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) -- | Concatenate a vector of vectors. -- --
--   >>> concat ((1:>2:>3:>Nil) :> (4:>5:>6:>Nil) :> (7:>8:>9:>Nil) :> (10:>11:>12:>Nil) :> Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil
--   
concat :: Vec n (Vec m a) -> Vec (n * m) a -- | Map a function over all the elements of a vector and concatentate the -- resulting vectors. -- --
--   >>> concatMap (replicate d3) (1:>2:>3:>Nil)
--   1 :> 1 :> 1 :> 2 :> 2 :> 2 :> 3 :> 3 :> 3 :> Nil
--   
concatMap :: (a -> Vec m b) -> Vec n a -> Vec (n * m) b -- | Split a vector of (n * m) elements into a vector of "vectors of length -- m", where the length m is given. -- --
--   >>> unconcat d4 (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil) :> (5 :> 6 :> 7 :> 8 :> Nil) :> (9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) -- | Split a vector of (n * m) elements into a vector of "vectors of -- length m", where the length m is determined by the -- context. -- --
--   >>> unconcatI (1:>2:>3:>4:>5:>6:>7:>8:>9:>10:>11:>12:>Nil) :: Vec 2 (Vec 6 Int)
--   (1 :> 2 :> 3 :> 4 :> 5 :> 6 :> Nil) :> (7 :> 8 :> 9 :> 10 :> 11 :> 12 :> Nil) :> Nil
--   
unconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) -- | Merge two vectors, alternating their elements, i.e., -- --
--   >>> merge (1 :> 2 :> 3 :> 4 :> Nil) (5 :> 6 :> 7 :> 8 :> Nil)
--   1 :> 5 :> 2 :> 6 :> 3 :> 7 :> 4 :> 8 :> Nil
--   
merge :: KnownNat n => Vec n a -> Vec n a -> Vec (2 * n) a -- | The elements in a vector in reverse order. -- --
--   >>> reverse (1:>2:>3:>4:>Nil)
--   4 :> 3 :> 2 :> 1 :> Nil
--   
reverse :: Vec n a -> Vec n a -- | Apply a function of every element of a vector and its index. -- --
--   >>> :t imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   imap (+) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Index 4)
--   
--   >>> imap (+) (2 :> 2 :> 2 :> 2 :> Nil)
--   2 :> 3 :> *** Exception: X: Clash.Sized.Index: result 4 is out of bounds: [0..3]
--   ...
--   
--   >>> imap (\i a -> extend (bitCoerce i) + a) (2 :> 2 :> 2 :> 2 :> Nil) :: Vec 4 (Unsigned 8)
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- imap :: forall n a b. KnownNat n => (Index n -> a -> b) -> Vec n a -> Vec n b -- | Zip two vectors with a functions that also takes the elements' -- indices. -- --
--   >>> izipWith (\i a b -> i + a + b) (2 :> 2 :> Nil)  (3 :> 3:> Nil)
--   *** Exception: X: Clash.Sized.Index: result 3 is out of bounds: [0..1]
--   ...
--   
--   >>> izipWith (\i a b -> extend (bitCoerce i) + a + b) (2 :> 2 :> Nil) (3 :> 3 :> Nil) :: Vec 2 (Unsigned 8)
--   5 :> 6 :> Nil
--   
-- -- "imap f xs" corresponds to the following circuit -- layout: -- -- -- NB: izipWith is strict in its second argument, -- and lazy in its third. This matters when izipWith is -- used in a recursive setting. See lazyV for more information. izipWith :: KnownNat n => (Index n -> a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | Right fold (function applied to each element and its index) -- --
--   >>> let findLeftmost x xs = ifoldr (\i a b -> if a == x then Just i else b) Nothing xs
--   
--   >>> findLeftmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> findLeftmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldr f z xs" corresponds to the following circuit -- layout: -- ifoldr :: KnownNat n => (Index n -> a -> b -> b) -> b -> Vec n a -> b -- | Left fold (function applied to each element and its index) -- --
--   >>> let findRightmost x xs = ifoldl (\a i b -> if b == x then Just i else a) Nothing xs
--   
--   >>> findRightmost 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 4
--   
--   >>> findRightmost 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
-- -- "ifoldl f z xs" corresponds to the following circuit -- layout: -- ifoldl :: KnownNat n => (a -> Index n -> b -> a) -> a -> Vec n b -> a -- | Generate a vector of indices. -- --
--   >>> indices d4
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indices :: KnownNat n => SNat n -> Vec n (Index n) -- | Generate a vector of indices, where the length of the vector is -- determined by the context. -- --
--   >>> indicesI :: Vec 4 (Index 4)
--   0 :> 1 :> 2 :> 3 :> Nil
--   
indicesI :: KnownNat n => Vec n (Index n) -- | "findIndex p xs" returns the index of the first -- element of xs satisfying the predicate p, or -- Nothing if there is no such element. -- --
--   >>> findIndex (> 3) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 3
--   
--   >>> findIndex (> 8) (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
findIndex :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe (Index n) -- | "elemIndex a xs" returns the index of the first -- element which is equal (by ==) to the query element a, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 3 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Just 1
--   
--   >>> elemIndex 8 (1:>3:>2:>4:>3:>5:>6:>Nil)
--   Nothing
--   
elemIndex :: (KnownNat n, Eq a) => a -> Vec n a -> Maybe (Index n) -- | zipWith generalizes zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, "zipWith (+)" applied to two vectors produces -- the vector of corresponding sums. -- --
--   zipWith f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) == (f x1 y1 :> f x2 y2 :> ... :> f xn yn :> Nil)
--   
-- -- "zipWith f xs ys" corresponds to the following circuit -- layout: -- -- -- NB: zipWith is strict in its second argument, and -- lazy in its third. This matters when zipWith is used in -- a recursive setting. See lazyV for more information. zipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c -- | zipWith3 generalizes zip3 by zipping with the function -- given as the first argument, instead of a tupling function. -- --
--   zipWith3 f (x1 :> x2 :> ... xn :> Nil) (y1 :> y2 :> ... :> yn :> Nil) (z1 :> z2 :> ... :> zn :> Nil) == (f x1 y1 z1 :> f x2 y2 z2 :> ... :> f xn yn zn :> Nil)
--   
-- -- "zipWith3 f xs ys zs" corresponds to the following -- circuit layout: -- -- -- NB: zipWith3 is strict in its second argument, -- and lazy in its third and fourth. This matters when -- zipWith3 is used in a recursive setting. See lazyV for -- more information. zipWith3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d zipWith4 :: (a -> b -> c -> d -> e) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n h -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldr1 f (x1 :> ... :> xn2 :> xn1 :> xn :> Nil) == x1 `f` (... (xn2 `f` (xn1 `f` xn))...)
--   foldr1 f (x1 :> Nil)                            == x1
--   foldr1 f Nil                                    == TYPE ERROR
--   
-- --
--   >>> foldr1 (/) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   1.875
--   
-- -- "foldr1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldr1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty vectors. -- --
--   foldl1 f (x1 :> x2 :> x3 :> ... :> xn :> Nil) == (...((x1 `f` x2) `f` x3) `f`...) `f` xn
--   foldl1 f (x1 :> Nil)                          == x1
--   foldl1 f Nil                                  == TYPE ERROR
--   
-- --
--   >>> foldl1 (/) (1 :> 5 :> 4 :> 3 :> 2 :> Nil)
--   8.333333333333333e-3
--   
-- -- "foldl1 f xs" corresponds to the following circuit -- layout: -- -- -- NB: "foldl1 f z xs" produces a linear -- structure, which has a depth, or delay, of O(length -- xs). Use fold if your binary operator f is -- associative, as "fold f xs" produces a structure with -- a depth of O(log_2(length xs)). foldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a -- | fold is a variant of foldr1 and foldl1, but -- instead of reducing from right to left, or left to right, it reduces a -- vector using a tree-like structure. The depth, or delay, of the -- structure produced by "fold f xs", is hence -- O(log_2(length xs)), and not O(length -- xs). -- -- NB: The binary operator "f" in "fold f -- xs" must be associative. -- --
--   fold f (x1 :> x2 :> ... :> xn1 :> xn :> Nil) == ((x1 `f` x2) `f` ...) `f` (... `f` (xn1 `f` xn))
--   fold f (x1 :> Nil)                           == x1
--   fold f Nil                                   == TYPE ERROR
--   
-- --
--   >>> fold (+) (5 :> 4 :> 3 :> 2 :> 1 :> Nil)
--   15
--   
-- -- "fold f xs" corresponds to the following circuit -- layout: -- fold :: forall n a. (a -> a -> a) -> Vec (n + 1) a -> a -- | scanl is similar to foldl, but returns a vector of -- successive reduced values from the left: -- --
--   scanl f z (x1 :> x2 :> ... :> Nil) == z :> (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> scanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   0 :> 5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "scanl f z xs" corresponds to the following circuit -- layout: -- -- -- scanl :: (b -> a -> b) -> b -> Vec n a -> Vec (n + 1) b -- | scanl with no seed value -- --
--   >>> scanl1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   1 :> -1 :> -4 :> -8 :> Nil
--   
scanl1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | scanr with no seed value -- --
--   >>> scanr1 (-) (1 :> 2 :> 3 :> 4 :> Nil)
--   -2 :> 3 :> -1 :> 4 :> Nil
--   
scanr1 :: KnownNat n => (a -> a -> a) -> Vec (n + 1) a -> Vec (n + 1) a -- | postscanl is a variant of scanl where the first result -- is dropped: -- --
--   postscanl f z (x1 :> x2 :> ... :> Nil) == (z `f` x1) :> ((z `f` x1) `f` x2) :> ... :> Nil
--   
-- --
--   >>> postscanl (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   5 :> 9 :> 12 :> 14 :> Nil
--   
-- -- "postscanl f z xs" corresponds to the following -- circuit layout: -- postscanl :: (b -> a -> b) -> b -> Vec n a -> Vec n b -- | scanr is similar to foldr, but returns a vector of -- successive reduced values from the right: -- --
--   scanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> z :> Nil
--   
-- --
--   >>> scanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> 0 :> Nil
--   
-- -- "scanr f z xs" corresponds to the following circuit -- layout: -- -- -- scanr :: (a -> b -> b) -> b -> Vec n a -> Vec (n + 1) b -- | postscanr is a variant of scanr that where the last -- result is dropped: -- --
--   postscanr f z (... :> xn1 :> xn :> Nil) == ... :> (xn1 `f` (xn `f` z)) :> (xn `f` z) :> Nil
--   
-- --
--   >>> postscanr (+) 0 (5 :> 4 :> 3 :> 2 :> Nil)
--   14 :> 9 :> 5 :> 2 :> Nil
--   
-- -- "postscanr f z xs" corresponds to the following -- circuit layout: -- postscanr :: (a -> b -> b) -> b -> Vec n a -> Vec n b -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumL (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,1 :> 2 :> 4 :> 7 :> Nil)
--   
-- -- "mapAccumL f acc xs" corresponds to the following -- circuit layout: -- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- --
--   >>> mapAccumR (\acc x -> (acc + x,acc + 1)) 0 (1 :> 2 :> 3 :> 4 :> Nil)
--   (10,10 :> 8 :> 5 :> 1 :> Nil)
--   
-- -- "mapAccumR f acc xs" corresponds to the following -- circuit layout: -- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> Vec n x -> (acc, Vec n y) -- | zip takes two vectors and returns a vector of corresponding -- pairs. -- --
--   >>> zip (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil)
--   (1,4) :> (2,3) :> (3,2) :> (4,1) :> Nil
--   
zip :: Vec n a -> Vec n b -> Vec n (a, b) -- | zip3 takes three vectors and returns a vector of corresponding -- triplets. -- --
--   >>> zip3 (1:>2:>3:>4:>Nil) (4:>3:>2:>1:>Nil) (5:>6:>7:>8:>Nil)
--   (1,4,5) :> (2,3,6) :> (3,2,7) :> (4,1,8) :> Nil
--   
zip3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) -- | zip4 takes four vectors and returns a list of quadruples, -- analogous to zip. zip4 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n (a, b, c, d) -- | zip5 takes five vectors and returns a list of five-tuples, -- analogous to zip. zip5 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n (a, b, c, d, e) -- | zip6 takes six vectors and returns a list of six-tuples, -- analogous to zip. zip6 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n (a, b, c, d, e, f) -- | zip7 takes seven vectors and returns a list of seven-tuples, -- analogous to zip. zip7 :: Vec n a -> Vec n b -> Vec n c -> Vec n d -> Vec n e -> Vec n f -> Vec n g -> Vec n (a, b, c, d, e, f, g) -- | unzip transforms a vector of pairs into a vector of first -- components and a vector of second components. -- --
--   >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
--   
unzip :: Vec n (a, b) -> (Vec n a, Vec n b) -- | unzip3 transforms a vector of triplets into a vector of first -- components, a vector of second components, and a vector of third -- components. -- --
--   >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
--   (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
--   
unzip3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) -- | unzip4 takes a vector of quadruples and returns four vectors, -- analogous to unzip. unzip4 :: Vec n (a, b, c, d) -> (Vec n a, Vec n b, Vec n c, Vec n d) -- | unzip5 takes a vector of five-tuples and returns five vectors, -- analogous to unzip. unzip5 :: Vec n (a, b, c, d, e) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e) -- | unzip6 takes a vector of six-tuples and returns six vectors, -- analogous to unzip. unzip6 :: Vec n (a, b, c, d, e, f) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f) -- | unzip7 takes a vector of seven-tuples and returns seven -- vectors, analogous to unzip. unzip7 :: Vec n (a, b, c, d, e, f, g) -> (Vec n a, Vec n b, Vec n c, Vec n d, Vec n e, Vec n f, Vec n g) -- | "xs !! n" returns the n'th element of -- xs. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> (1:>2:>3:>4:>5:>Nil) !! 4
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! (length (1:>2:>3:>4:>5:>Nil) - 1)
--   5
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 1
--   2
--   
--   >>> (1:>2:>3:>4:>5:>Nil) !! 14
--   *** Exception: Clash.Sized.Vector.(!!): index 14 is larger than maximum index 4
--   ...
--   
(!!) :: (KnownNat n, Enum i) => Vec n a -> i -> a -- | The length of a Vector as an Int value. -- --
--   >>> length (6 :> 7 :> 8 :> Nil)
--   3
--   
length :: KnownNat n => Vec n a -> Int -- | "replace n a xs" returns the vector xs where -- the n'th element is replaced by a. -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> replace 3 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 7 :> 5 :> Nil
--   
--   >>> replace 0 7 (1:>2:>3:>4:>5:>Nil)
--   7 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
--   >>> replace 9 7 (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> 4 :> 5 :> *** Exception: Clash.Sized.Vector.replace: index 9 is larger than maximum index 4
--   ...
--   
replace :: (KnownNat n, Enum i) => i -> a -> Vec n a -> Vec n a -- | "take n xs" returns the n-length prefix of -- xs. -- --
--   >>> take (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d3               (1:>2:>3:>4:>5:>Nil)
--   1 :> 2 :> 3 :> Nil
--   
--   >>> take d0               (1:>2:>Nil)
--   Nil
--   
-- --
--   >>> take d4               (1:>2:>Nil)
--   
--   <interactive>:...
--       • Couldn't match type ‘4 + n0’ with ‘2’
--         Expected type: Vec (4 + n0) a
--           Actual type: Vec (1 + 1) a
--         The type variable ‘n0’ is ambiguous
--       • In the second argument of ‘take’, namely ‘(1 :> 2 :> Nil)’
--         In the expression: take d4 (1 :> 2 :> Nil)
--         In an equation for ‘it’: it = take d4 (1 :> 2 :> Nil)
--   
take :: SNat m -> Vec (m + n) a -> Vec m a -- | "takeI xs" returns the prefix of xs as demanded -- by the context. -- --
--   >>> takeI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   1 :> 2 :> Nil
--   
takeI :: KnownNat m => Vec (m + n) a -> Vec m a -- | "drop n xs" returns the suffix of xs after the -- first n elements. -- --
--   >>> drop (SNat :: SNat 3) (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d3               (1:>2:>3:>4:>5:>Nil)
--   4 :> 5 :> Nil
--   
--   >>> drop d0               (1:>2:>Nil)
--   1 :> 2 :> Nil
--   
-- --
--   >>> drop d4               (1:>2:>Nil)
--   
--   <interactive>:...: error:...
--       • Couldn't match...type ‘4 + n0...
--         The type variable ‘n0’ is ambiguous
--       • In the first argument of ‘print’, namely ‘it’
--         In a stmt of an interactive GHCi command: print it
--   
drop :: SNat m -> Vec (m + n) a -> Vec n a -- | "dropI xs" returns the suffix of xs as demanded -- by the context. -- --
--   >>> dropI (1:>2:>3:>4:>5:>Nil) :: Vec 2 Int
--   4 :> 5 :> Nil
--   
dropI :: KnownNat m => Vec (m + n) a -> Vec n a -- | "at n xs" returns n'th element of xs -- -- NB: Vector elements have an ASCENDING subscript starting -- from 0 and ending at length - 1. -- --
--   >>> at (SNat :: SNat 1) (1:>2:>3:>4:>5:>Nil)
--   2
--   
--   >>> at d1               (1:>2:>3:>4:>5:>Nil)
--   2
--   
at :: SNat m -> Vec (m + (n + 1)) a -> a -- | "select f s n xs" selects n elements with -- step-size s and offset f from xs. -- --
--   >>> select (SNat :: SNat 1) (SNat :: SNat 2) (SNat :: SNat 3) (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
--   >>> select d1 d2 d3 (1:>2:>3:>4:>5:>6:>7:>8:>Nil)
--   2 :> 4 :> 6 :> Nil
--   
select :: CmpNat (i + s) (s * n) ~ 'GT => SNat f -> SNat s -> SNat n -> Vec (f + i) a -> Vec n a -- | "selectI f s xs" selects as many elements as demanded -- by the context with step-size s and offset f from -- xs. -- --
--   >>> selectI d1 d2 (1:>2:>3:>4:>5:>6:>7:>8:>Nil) :: Vec 2 Int
--   2 :> 4 :> Nil
--   
selectI :: (CmpNat (i + s) (s * n) ~ 'GT, KnownNat n) => SNat f -> SNat s -> Vec (f + i) a -> Vec n a -- | "replicate n a" returns a vector that has n -- copies of a. -- --
--   >>> replicate (SNat :: SNat 3) 6
--   6 :> 6 :> 6 :> Nil
--   
--   >>> replicate d3 6
--   6 :> 6 :> 6 :> Nil
--   
replicate :: SNat n -> a -> Vec n a -- | "repeat a" creates a vector with as many copies of -- a as demanded by the context. -- --
--   >>> repeat 6 :: Vec 5 Int
--   6 :> 6 :> 6 :> 6 :> 6 :> Nil
--   
repeat :: KnownNat n => a -> Vec n a -- | "iterate n f x" returns a vector starting with -- x followed by n repeated applications of f to -- x. -- --
--   iterate (SNat :: SNat 4) f x == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   iterate d4 f x               == (x :> f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> iterate d4 (+1) 1
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- "iterate n f z" corresponds to the following circuit -- layout: -- iterate :: SNat n -> (a -> a) -> a -> Vec n a -- | "iterateI f x" returns a vector starting with -- x followed by n repeated applications of f -- to x, where n is determined by the context. -- --
--   iterateI f x :: Vec 3 a == (x :> f x :> f (f x) :> Nil)
--   
-- --
--   >>> iterateI (+1) 1 :: Vec 3 Int
--   1 :> 2 :> 3 :> Nil
--   
-- -- "iterateI f z" corresponds to the following circuit -- layout: -- iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a -- | "unfoldr n f s" builds a vector of length n -- from a seed value s, where every element a is -- created by successive calls of f on s. Unlike -- unfoldr from Data.List the generating function -- f cannot dictate the length of the resulting vector, it must -- be statically known. -- -- a simple use of unfoldr: -- --
--   >>> unfoldr d10 (\s -> (s,s-1)) 10
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldr :: SNat n -> (s -> (a, s)) -> s -> Vec n a -- | "unfoldrI f s" builds a vector from a seed value -- s, where every element a is created by successive -- calls of f on s; the length of the vector is -- inferred from the context. Unlike unfoldr from Data.List -- the generating function f cannot dictate the length of the -- resulting vector, it must be statically known. -- -- a simple use of unfoldrI: -- --
--   >>> unfoldrI (\s -> (s,s-1)) 10 :: Vec 10 Int
--   10 :> 9 :> 8 :> 7 :> 6 :> 5 :> 4 :> 3 :> 2 :> 1 :> Nil
--   
unfoldrI :: KnownNat n => (s -> (a, s)) -> s -> Vec n a -- | "generate n f x" returns a vector with n -- repeated applications of f to x. -- --
--   generate (SNat :: SNat 4) f x == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   generate d4 f x               == (f x :> f (f x) :> f (f (f x)) :> f (f (f (f x))) :> Nil)
--   
-- --
--   >>> generate d4 (+1) 1
--   2 :> 3 :> 4 :> 5 :> Nil
--   
-- -- "generate n f z" corresponds to the following circuit -- layout: -- generate :: SNat n -> (a -> a) -> a -> Vec n a -- | "generateI f x" returns a vector with n -- repeated applications of f to x, where n is -- determined by the context. -- --
--   generateI f x :: Vec 3 a == (f x :> f (f x) :> f (f (f x)) :> Nil)
--   
-- --
--   >>> generateI (+1) 1 :: Vec 3 Int
--   2 :> 3 :> 4 :> Nil
--   
-- -- "generateI f z" corresponds to the following circuit -- layout: -- generateI :: KnownNat n => (a -> a) -> a -> Vec n a -- | Transpose a matrix: go from row-major to column-major -- --
--   >>> let xss = (1:>2:>Nil):>(3:>4:>Nil):>(5:>6:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> Nil) :> (3 :> 4 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
--   >>> transpose xss
--   (1 :> 3 :> 5 :> Nil) :> (2 :> 4 :> 6 :> Nil) :> Nil
--   
transpose :: KnownNat n => Vec m (Vec n a) -> Vec n (Vec m a) -- | 1-dimensional stencil computations -- -- "stencil1d stX f xs", where xs has stX + -- n elements, applies the stencil computation f on: n + -- 1 overlapping (1D) windows of length stX, drawn from -- xs. The resulting vector has n + 1 elements. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t stencil1d d2 sum xs
--   stencil1d d2 sum xs :: Num b => Vec 5 b
--   
--   >>> stencil1d d2 sum xs
--   3 :> 5 :> 7 :> 9 :> 11 :> Nil
--   
stencil1d :: KnownNat n => SNat (stX + 1) -> (Vec (stX + 1) a -> b) -> Vec ((stX + n) + 1) a -> Vec (n + 1) b -- | 2-dimensional stencil computations -- -- "stencil2d stY stX f xss", where xss is a -- matrix of stY + m rows of stX + n elements, applies the -- stencil computation f on: (m + 1) * (n + 1) overlapping -- (2D) windows of stY rows of stX elements, drawn from -- xss. The result matrix has m + 1 rows of n + 1 -- elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
-- --
--   >>> :t stencil2d d2 d2 (sum . map sum) xss
--   stencil2d d2 d2 (sum . map sum) xss :: Num b => Vec 3 (Vec 3 b)
--   
-- --
--   >>> stencil2d d2 d2 (sum . map sum) xss
--   (14 :> 18 :> 22 :> Nil) :> (30 :> 34 :> 38 :> Nil) :> (46 :> 50 :> 54 :> Nil) :> Nil
--   
stencil2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> (Vec (stY + 1) (Vec (stX + 1) a) -> b) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) b) -- | "windows1d stX xs", where the vector xs has -- stX + n elements, returns a vector of n + 1 overlapping -- (1D) windows of xs of length stX. -- --
--   >>> let xs = (1:>2:>3:>4:>5:>6:>Nil)
--   
--   >>> :t xs
--   xs :: Num a => Vec 6 a
--   
--   >>> :t windows1d d2 xs
--   windows1d d2 xs :: Num a => Vec 5 (Vec 2 a)
--   
--   >>> windows1d d2 xs
--   (1 :> 2 :> Nil) :> (2 :> 3 :> Nil) :> (3 :> 4 :> Nil) :> (4 :> 5 :> Nil) :> (5 :> 6 :> Nil) :> Nil
--   
windows1d :: KnownNat n => SNat (stX + 1) -> Vec ((stX + n) + 1) a -> Vec (n + 1) (Vec (stX + 1) a) -- | "windows2d stY stX xss", where matrix xss has -- stY + m rows of stX + n, returns a matrix of m+1 -- rows of n+1 elements. The elements of this new matrix are the -- overlapping (2D) windows of xss, where every window has -- stY rows of stX elements. -- --
--   >>> let xss = ((1:>2:>3:>4:>Nil):>(5:>6:>7:>8:>Nil):>(9:>10:>11:>12:>Nil):>(13:>14:>15:>16:>Nil):>Nil)
--   
--   >>> :t xss
--   xss :: Num a => Vec 4 (Vec 4 a)
--   
--   >>> :t windows2d d2 d2 xss
--   windows2d d2 d2 xss :: Num a => Vec 3 (Vec 3 (Vec 2 (Vec 2 a)))
--   
--   >>> windows2d d2 d2 xss
--   (((1 :> 2 :> Nil) :> (5 :> 6 :> Nil) :> Nil) :> ((2 :> 3 :> Nil) :> (6 :> 7 :> Nil) :> Nil) :> ((3 :> 4 :> Nil) :> (7 :> 8 :> Nil) :> Nil) :> Nil) :> (((5 :> 6 :> Nil) :> (9 :> 10 :> Nil) :> Nil) :> ((6 :> 7 :> Nil) :> (10 :> 11 :> Nil) :> Nil) :> ((7 :> 8 :> Nil) :> (11 :> 12 :> Nil) :> Nil) :> Nil) :> (((9 :> 10 :> Nil) :> (13 :> 14 :> Nil) :> Nil) :> ((10 :> 11 :> Nil) :> (14 :> 15 :> Nil) :> Nil) :> ((11 :> 12 :> Nil) :> (15 :> 16 :> Nil) :> Nil) :> Nil) :> Nil
--   
windows2d :: (KnownNat n, KnownNat m) => SNat (stY + 1) -> SNat (stX + 1) -> Vec ((stY + m) + 1) (Vec ((stX + n) + 1) a) -> Vec (m + 1) (Vec (n + 1) (Vec (stY + 1) (Vec (stX + 1) a))) -- | Forward permutation specified by an index mapping, ix. The -- result vector is initialized by the given defaults, def, and an -- further values that are permuted into the result are added to the -- current value using the given combination function, f. -- -- The combination function must be associative and -- commutative. permute :: (Enum i, KnownNat n, KnownNat m) => (a -> a -> a) -> Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "backpermute xs is" is equivalent to "map -- (xs !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> backpermute input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
backpermute :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | Copy elements from the source vector, xs, to the destination -- vector according to an index mapping is. This is a forward -- permute operation where a to vector encodes an input to output -- index mapping. Output elements for indices that are not mapped assume -- the value in the default vector def. -- -- For example: -- --
--   >>> let defVec = 0:>0:>0:>0:>0:>0:>0:>0:>0:>Nil
--   
--   >>> let to = 1:>3:>7:>2:>5:>8:>Nil
--   
--   >>> let input = 1:>9:>6:>4:>4:>2:>5:>Nil
--   
--   >>> scatter defVec to input
--   0 :> 1 :> 4 :> 9 :> 0 :> 4 :> 0 :> 6 :> 2 :> Nil
--   
-- -- NB: If the same index appears in the index mapping more than -- once, the latest mapping is chosen. scatter :: (Enum i, KnownNat n, KnownNat m) => Vec n a -> Vec m i -> Vec (m + k) a -> Vec n a -- | Backwards permutation specified by an index mapping, is, from -- the destination vector specifying which element of the source vector -- xs to read. -- -- "gather xs is" is equivalent to "map (xs -- !!) is". -- -- For example: -- --
--   >>> let input = 1:>9:>6:>4:>4:>2:>0:>1:>2:>Nil
--   
--   >>> let from  = 1:>3:>7:>2:>5:>3:>Nil
--   
--   >>> gather input from
--   9 :> 4 :> 1 :> 6 :> 2 :> 4 :> Nil
--   
gather :: (Enum i, KnownNat n) => Vec n a -> Vec m i -> Vec m a -- | "interleave d xs" creates a vector: -- --
--   <x_0,x_d,x_(2d),...,x_1,x_(d+1),x_(2d+1),...,x_(d-1),x_(2d-1),x_(3d-1)>
--   
-- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> 5 :> 6 :> 7 :> 8 :> 9 :> Nil
--   
--   >>> interleave d3 xs
--   1 :> 4 :> 7 :> 2 :> 5 :> 8 :> 3 :> 6 :> 9 :> Nil
--   
interleave :: (KnownNat n, KnownNat d) => SNat d -> Vec (n * d) a -> Vec (d * n) a -- | Dynamically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeft xs 1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
--   >>> rotateLeft xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateLeft xs (-1)
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateLeftS if you want to rotate left by a -- static amount. rotateLeft :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Dynamically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRight xs 1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
--   >>> rotateRight xs 2
--   3 :> 4 :> 1 :> 2 :> Nil
--   
--   >>> rotateRight xs (-1)
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateRightS if you want to rotate right by a -- static amount. rotateRight :: (Enum i, KnownNat n) => Vec n a -> i -> Vec n a -- | Statically rotate a Vector to the left: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateLeftS xs d1
--   2 :> 3 :> 4 :> 1 :> Nil
--   
-- -- NB: Use rotateLeft if you want to rotate left by a -- dynamic amount. rotateLeftS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Statically rotate a Vector to the right: -- --
--   >>> let xs = 1 :> 2 :> 3 :> 4 :> Nil
--   
--   >>> rotateRightS xs d1
--   4 :> 1 :> 2 :> 3 :> Nil
--   
-- -- NB: Use rotateRight if you want to rotate right by a -- dynamic amount. rotateRightS :: KnownNat n => Vec n a -> SNat d -> Vec n a -- | Convert a vector to a list. -- --
--   >>> toList (1:>2:>3:>Nil)
--   [1,2,3]
--   
-- -- NB: This function is not synthesizable toList :: Vec n a -> [a] -- | Create a vector literal from a list literal. -- --
--   $(listToVecTH [1::Signed 8,2,3,4,5]) == (8:>2:>3:>4:>5:>Nil) :: Vec 5 (Signed 8)
--   
-- --
--   >>> [1 :: Signed 8,2,3,4,5]
--   [1,2,3,4,5]
--   
--   >>> $(listToVecTH [1::Signed 8,2,3,4,5])
--   1 :> 2 :> 3 :> 4 :> 5 :> Nil
--   
listToVecTH :: Lift a => [a] -> ExpQ -- | Vector as a Proxy for Nat asNatProxy :: Vec n a -> Proxy n -- | Length of a Vector as an SNat value lengthS :: KnownNat n => Vec n a -> SNat n -- | What you should use when your vector functions are too strict in their -- arguments. -- --

doctests setup

-- --
--   >>> let compareSwapL a b = if a < b then (a,b) else (b,a)
--   
--   >>> :{
--   let sortVL :: (Ord a, KnownNat (n + 1)) => Vec ((n + 1) + 1) a -> Vec ((n + 1) + 1) a
--       sortVL xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith compareSwapL (lazyV lefts) rights
--   :}
--   
-- --
--   >>> :{
--   let sortV_flip xs = map fst sorted :< (snd (last sorted))
--         where
--           lefts  = head xs :> map snd (init sorted)
--           rights = tail xs
--           sorted = zipWith (flip compareSwapL) rights lefts
--   :}
--   
-- --

Example usage

-- -- For example: -- --
--   -- Bubble sort for 1 iteration
--   sortV xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL lefts rights
--   
--   -- Compare and swap
--   compareSwapL a b = if a < b then (a,b)
--                               else (b,a)
--   
-- -- Will not terminate because zipWith is too strict in its second -- argument. -- -- In this case, adding lazyV on zipWiths second argument: -- --
--   sortVL xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith compareSwapL (lazyV lefts) rights
--   
-- -- Results in a successful computation: -- --
--   >>> sortVL (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: There is also a solution using flip, but it slightly -- obfuscates the meaning of the code: -- --
--   sortV_flip xs = map fst sorted :< (snd (last sorted))
--    where
--      lefts  = head xs :> map snd (init sorted)
--      rights = tail xs
--      sorted = zipWith (flip compareSwapL) rights lefts
--   
-- --
--   >>> sortV_flip (4 :> 1 :> 2 :> 3 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
lazyV :: KnownNat n => Vec n a -> Vec n a -- | A dependently typed fold. -- --

doctests setup

-- --
--   >>> :seti -fplugin GHC.TypeLits.Normalise
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply (Append m a) l = Vec (l + m) a
--   
--   >>> let append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- --

Example usage

-- -- Using lists, we can define append (a.k.a. -- Data.List.++) in terms of -- Data.List.foldr: -- --
--   >>> import qualified Data.List
--   
--   >>> let append xs ys = Data.List.foldr (:) ys xs
--   
--   >>> append [1,2] [3,4]
--   [1,2,3,4]
--   
-- -- However, when we try to do the same for Vec, by defining -- append' in terms of Clash.Sized.Vector.foldr: -- --
--   append' xs ys = foldr (:>) ys xs
--   
-- -- we get a type error: -- --
--   >>> let append' xs ys = foldr (:>) ys xs
--   
--   <interactive>:...
--       • Occurs check: cannot construct the infinite type: ... ~ ... + 1
--         Expected type: a -> Vec ... a -> Vec ... a
--           Actual type: a -> Vec ... a -> Vec (... + 1) a
--       • In the first argument of ‘foldr’, namely ‘(:>)’
--         In the expression: foldr (:>) ys xs
--         In an equation for ‘append'’: append' xs ys = foldr (:>) ys xs
--       • Relevant bindings include
--           ys :: Vec ... a (bound at ...)
--           append' :: Vec n a -> Vec ... a -> Vec ... a
--             (bound at ...)
--   
-- -- The reason is that the type of foldr is: -- --
--   >>> :t foldr
--   foldr :: (a -> b -> b) -> b -> Vec n a -> b
--   
-- -- While the type of (:>) is: -- --
--   >>> :t (:>)
--   (:>) :: a -> Vec n a -> Vec (n + 1) a
--   
-- -- We thus need a fold function that can handle the growing -- vector type: dfold. Compared to foldr, dfold -- takes an extra parameter, called the motive, that allows the -- folded function to have an argument and result type that -- depends on the current length of the vector. Using -- dfold, we can now correctly define append': -- --
--   import Data.Singletons
--   import Data.Proxy
--   
--   data Append (m :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
--   type instance Apply (Append m a) l = Vec (l + m) a
--   
--   append' xs ys = dfold (Proxy :: Proxy (Append m a)) (const (:>)) ys xs
--   
-- -- We now see that append' has the appropriate type: -- --
--   >>> :t append'
--   append' :: KnownNat k => Vec k a -> Vec m a -> Vec (k + m) a
--   
-- -- And that it works: -- --
--   >>> append' (1 :> 2 :> Nil) (3 :> 4 :> Nil)
--   1 :> 2 :> 3 :> 4 :> Nil
--   
-- -- NB: "dfold m f z xs" creates a linear -- structure, which has a depth, or delay, of O(length -- xs). Look at dtfold for a dependently typed fold -- that produces a structure with a depth of O(log_2(length -- xs)). dfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (forall l. SNat l -> a -> (p @@ l) -> p @@ (l + 1)) -> (p @@ 0) -> Vec k a -> p @@ k -- | A combination of dfold and fold: a dependently -- typed fold that reduces a vector in a tree-like structure. -- --

doctests setup

-- --
--   >>> :seti -XUndecidableInstances
--   
--   >>> import Data.Singletons (Apply, Proxy (..), TyFun)
--   
--   >>> data IIndex (f :: TyFun Nat Type) :: Type
--   
--   >>> type instance Apply IIndex l = Index ((2^l)+1)
--   
--   >>> :{
--   let populationCount' :: (KnownNat k, KnownNat (2^k)) => BitVector (2^k) -> Index ((2^k)+1)
--       populationCount' bv = dtfold (Proxy @IIndex)
--                                    fromIntegral
--                                    (\_ x y -> add x y)
--                                    (bv2v bv)
--   :}
--   
-- --

Example usage

-- -- As an example of when you might want to use dtfold we will -- build a population counter: a circuit that counts the number of bits -- set to '1' in a BitVector. Given a vector of n bits, we -- only need we need a data type that can represent the number n: -- Index (n+1). Index k has a range of -- [0 .. k-1] (using ceil(log2(k)) bits), hence we need -- Index n+1. As an initial attempt we will use -- sum, because it gives a nice (log2(n)) tree-structure -- of adders: -- --
--   populationCount :: (KnownNat (n+1), KnownNat (n+2))
--                   => BitVector (n+1) -> Index (n+2)
--   populationCount = sum . map fromIntegral . bv2v
--   
-- -- The "problem" with this description is that all adders have the same -- bit-width, i.e. all adders are of the type: -- --
--   (+) :: Index (n+2) -> Index (n+2) -> Index (n+2).
--   
-- -- This is a "problem" because we could have a more efficient structure: -- one where each layer of adders is precisely wide enough to -- count the number of bits at that layer. That is, at height d we -- want the adder to be of type: -- --
--   Index ((2^d)+1) -> Index ((2^d)+1) -> Index ((2^(d+1))+1)
--   
-- -- We have such an adder in the form of the add function, as -- defined in the instance ExtendingNum instance of Index. -- However, we cannot simply use fold to create a tree-structure -- of addes: -- --
--   >>> :{
--   let populationCount' :: (KnownNat (n+1), KnownNat (n+2))
--                        => BitVector (n+1) -> Index (n+2)
--       populationCount' = fold add . map fromIntegral . bv2v
--   :}
--   
--   <interactive>:...
--       • Couldn't match type ‘((n + 2) + (n + 2)) - 1’ with ‘n + 2’
--         Expected type: Index (n + 2) -> Index (n + 2) -> Index (n + 2)
--           Actual type: Index (n + 2)
--                        -> Index (n + 2) -> AResult (Index (n + 2)) (Index (n + 2))
--       • In the first argument of ‘fold’, namely ‘add’
--         In the first argument of ‘(.)’, namely ‘fold add’
--         In the expression: fold add . map fromIntegral . bv2v
--       • Relevant bindings include
--           populationCount' :: BitVector (n + 1) -> Index (n + 2)
--             (bound at ...)
--   
-- -- because fold expects a function of type "a -> a -> -- a", i.e. a function where the arguments and result all have -- exactly the same type. -- -- In order to accommodate the type of our add, where the result -- is larger than the arguments, we must use a dependently typed fold in -- the form of dtfold: -- --
--   {-# LANGUAGE UndecidableInstances #-}
--   import Data.Singletons
--   import Data.Proxy
--   
--   data IIndex (f :: TyFun Nat Type) :: Type
--   type instance Apply IIndex l = Index ((2^l)+1)
--   
--   populationCount' :: (KnownNat k, KnownNat (2^k))
--                    => BitVector (2^k) -> Index ((2^k)+1)
--   populationCount' bv = dtfold (Proxy @IIndex)
--                                fromIntegral
--                                (\_ x y -> add x y)
--                                (bv2v bv)
--   
-- -- And we can test that it works: -- --
--   >>> :t populationCount' (7 :: BitVector 16)
--   populationCount' (7 :: BitVector 16) :: Index 17
--   
--   >>> populationCount' (7 :: BitVector 16)
--   3
--   
-- -- Some final remarks: -- -- -- -- NB: The depth, or delay, of the structure produced by -- "dtfold m f g xs" is O(log_2(length -- xs)). dtfold :: forall p k a. KnownNat k => Proxy (p :: TyFun Nat Type -> Type) -> (a -> p @@ 0) -> (forall l. SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1)) -> Vec (2 ^ k) a -> p @@ k -- | Specialised version of dfold that builds a triangular -- computational structure. -- --

doctests setup

-- --
--   >>> let compareSwap a b = if a > b then (a,b) else (b,a)
--   
--   >>> let insert y xs = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   
--   >>> let insertionSort = vfold (const insert)
--   
-- --

Example usage

-- --
--   compareSwap a b = if a > b then (a,b) else (b,a)
--   insert y xs     = let (y',xs') = mapAccumL compareSwap y xs in xs' :< y'
--   insertionSort   = vfold (const insert)
--   
-- -- Builds a triangular structure of compare and swaps to sort a row. -- --
--   >>> insertionSort (7 :> 3 :> 9 :> 1 :> Nil)
--   1 :> 3 :> 7 :> 9 :> Nil
--   
-- -- The circuit layout of insertionSort, build using -- vfold, is: -- vfold :: forall k a b. KnownNat k => (forall l. SNat l -> a -> Vec l b -> Vec (l + 1) b) -> Vec k a -> Vec k b -- | The largest element of a non-empty vector maximum :: Ord a => Vec (n + 1) a -> a -- | The least element of a non-empty vector minimum :: Ord a => Vec (n + 1) a -> a -- | Apply a function to every element of a vector and the element's -- position (as an SNat value) in the vector. -- --
--   >>> let rotateMatrix = smap (flip rotateRightS)
--   
--   >>> let xss = (1:>2:>3:>Nil):>(1:>2:>3:>Nil):>(1:>2:>3:>Nil):>Nil
--   
--   >>> xss
--   (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> (1 :> 2 :> 3 :> Nil) :> Nil
--   
--   >>> rotateMatrix xss
--   (1 :> 2 :> 3 :> Nil) :> (3 :> 1 :> 2 :> Nil) :> (2 :> 3 :> 1 :> Nil) :> Nil
--   
smap :: forall k a b. KnownNat k => (forall l. SNat l -> a -> b) -> Vec k a -> Vec k b concatBitVector# :: forall n m. (KnownNat n, KnownNat m) => Vec n (BitVector m) -> BitVector (n * m) unconcatBitVector# :: forall n m. (KnownNat n, KnownNat m) => BitVector (n * m) -> Vec n (BitVector m) -- | Convert a Vec of Bits to a BitVector. -- --
--   >>> let x = (0:>0:>0:>1:>0:>0:>1:>0:>Nil) :: Vec 8 Bit
--   
--   >>> x
--   0 :> 0 :> 0 :> 1 :> 0 :> 0 :> 1 :> 0 :> Nil
--   
--   >>> v2bv x
--   0b0001_0010
--   
v2bv :: KnownNat n => Vec n Bit -> BitVector n -- | Evaluate all elements of a vector to WHNF, returning the second -- argument seqV :: KnownNat n => Vec n a -> b -> b infixr 0 `seqV` -- | Evaluate all elements of a vector to WHNF forceV :: KnownNat n => Vec n a -> Vec n a -- | Evaluate all elements of a vector to WHNF, returning the second -- argument. Does not propagate XExceptions. seqVX :: KnownNat n => Vec n a -> b -> b infixr 0 `seqVX` -- | Evaluate all elements of a vector to WHNF. Does not propagate -- XExceptions. forceVX :: KnownNat n => Vec n a -> Vec n a -- | Representable types of kind *. This class is derivable in GHC -- with the DeriveGeneric flag on. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class Generic a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) -- | A Lift instance can have any of its values turned into a -- Template Haskell expression. This is needed when a value used within a -- Template Haskell quotation is bound outside the Oxford brackets -- ([| ... |] or [|| ... ||]) but not at the top level. -- As an example: -- --
--   add1 :: Int -> Q (TExp Int)
--   add1 x = [|| x + 1 ||]
--   
-- -- Template Haskell has no way of knowing what value x will take -- on at splice-time, so it requires the type of x to be an -- instance of Lift. -- -- A Lift instance must satisfy $(lift x) ≡ x and -- $$(liftTyped x) ≡ x for all x, where $(...) -- and $$(...) are Template Haskell splices. It is additionally -- expected that lift x ≡ unTypeQ (liftTyped -- x). -- -- Lift instances can be derived automatically by use of the -- -XDeriveLift GHC language extension: -- --
--   {-# LANGUAGE DeriveLift #-}
--   module Foo where
--   
--   import Language.Haskell.TH.Syntax
--   
--   data Bar a = Bar1 a (Bar a) | Bar2 String
--     deriving Lift
--   
-- -- Levity-polymorphic since template-haskell-2.16.0.0. class Lift (t :: TYPE r) -- | Turn a value into a Template Haskell expression, suitable for use in a -- splice. lift :: Lift t => t -> Q Exp -- | Turn a value into a Template Haskell typed expression, suitable for -- use in a typed splice. liftTyped :: Lift t => t -> Q (TExp t) -- | autoReg is a "smart" version of register. It does two -- things: -- --
    --
  1. It splits product types over their fields. For example, given a -- 3-tuple, the corresponding HDL will end up with three instances of a -- register (or more if the three fields can be split up similarly).
  2. --
  3. Given a data type where a constructor indicates (parts) of the -- data will (not) be updated a given cycle, it will split the data in -- two parts. The first part will contain the "always interesting" parts -- (the constructor bits). The second holds the "potentially -- uninteresting" data (the rest). Both parts will be stored in separate -- registers. The register holding the "potentially uninteresting" part -- will only be enabled if the constructor bits indicate they're -- interesting.
  4. --
-- -- The most important example of this is Maybe. Consider Maybe -- (Signed 16); when viewed as bits, a Nothing would look -- like: -- --
--   >>> pack @(Maybe (Signed 16)) Nothing
--   0b0_...._...._...._....
--   
-- -- and Just -- --
--   >>> pack @(Maybe (Signed 16)) (Just 3)
--   0b1_0000_0000_0000_0011
--   
-- -- In the first case, Nothing, we don't particularly care about updating -- the register holding the Signed 16 field, as they'll be -- unknown anyway. We can therefore deassert its enable line. -- -- Making Clash lay it out like this increases the chances of synthesis -- tools clock gating the registers, saving energy. -- -- This version of autoReg will split the given data type up -- recursively. For example, given a :: Maybe (Maybe Int, Maybe -- Int), a total of five registers will be rendered. Both the -- "interesting" and "uninteresting" enable lines of the inner Maybe -- types will be controlled by the outer one, in addition to the inner -- parts controlling their "uninteresting" parts as described in (2). -- -- The default implementation is just register. If you don't need -- or want the special features of AutoReg, you can use that by -- writing an empty instance. -- --
--   data MyDataType = ...
--   instance AutoReg MyDataType
--   
-- -- If you have a product type you can use deriveAutoReg to derive -- an instance. class NFDataX a => AutoReg a -- | Implicit version of autoReg autoReg :: (HasCallStack, HiddenClockResetEnable dom, AutoReg a) => a -> Signal dom a -> Signal dom a -- | Automatically derives an AutoReg instance for a product type -- -- Usage: -- --
--   data Pair a b = MkPair { getA :: a, getB :: b } deriving (Generic, NFDataX)
--   data Tup3 a b c = MkTup3 { getAB :: Pair a b, getC :: c } deriving (Generic, NFDataX)
--   deriveAutoReg ''Pair
--   deriveAutoReg ''Tup3
--   
-- -- NB: Because of the way template haskell works the order here -- matters, if you try to deriveAutoReg ''Tup3 before -- Pair it will complain about missing an instance AutoReg -- (Pair a b). deriveAutoReg :: Name -> DecsQ -- | The kind of types with lifted values. For example Int :: -- Type. type Type = Type -- | The kind of constraints, like Show a data Constraint module Clash.Tutorial module Clash.Examples.Internal decoderCase :: Bool -> BitVector 4 -> BitVector 16 decoderShift :: Bool -> BitVector 4 -> BitVector 16 encoderCase :: Bool -> BitVector 16 -> BitVector 4 upCounter :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom (Unsigned 8) upCounterLdT :: Num a => a -> (Bool, Bool, a) -> (a, a) upCounterLd :: HiddenClockResetEnable dom => Signal dom (Bool, Bool, Unsigned 8) -> Signal dom (Unsigned 8) upDownCounter :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom (Unsigned 8) lfsrF' :: BitVector 16 -> BitVector 16 lfsrF :: HiddenClockResetEnable dom => BitVector 16 -> Signal dom Bit lfsrGP :: (KnownNat (n + 1), Bits a) => Vec (n + 1) Bool -> Vec (n + 1) a -> Vec (n + 1) a lfsrG :: HiddenClockResetEnable dom => BitVector 16 -> Signal dom Bit grayCounter :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom (BitVector 8) oneHotCounter :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom (BitVector 8) crcT :: (Bits a, BitPack a) => a -> Bit -> a crc :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Bool -> Signal dom Bit -> Signal dom (BitVector 16) data RxReg RxReg :: BitVector 8 -> BitVector 8 -> Unsigned 4 -> Unsigned 4 -> Bool -> Bool -> Bool -> Bit -> Bit -> Bool -> RxReg [_rx_reg] :: RxReg -> BitVector 8 [_rx_data] :: RxReg -> BitVector 8 [_rx_sample_cnt] :: RxReg -> Unsigned 4 [_rx_cnt] :: RxReg -> Unsigned 4 [_rx_frame_err] :: RxReg -> Bool [_rx_over_run] :: RxReg -> Bool [_rx_empty] :: RxReg -> Bool [_rx_d1] :: RxReg -> Bit [_rx_d2] :: RxReg -> Bit [_rx_busy] :: RxReg -> Bool rx_sample_cnt :: Lens' RxReg (Unsigned 4) rx_reg :: Lens' RxReg (BitVector 8) rx_over_run :: Lens' RxReg Bool rx_frame_err :: Lens' RxReg Bool rx_empty :: Lens' RxReg Bool rx_data :: Lens' RxReg (BitVector 8) rx_d2 :: Lens' RxReg Bit rx_d1 :: Lens' RxReg Bit rx_cnt :: Lens' RxReg (Unsigned 4) rx_busy :: Lens' RxReg Bool data TxReg TxReg :: BitVector 8 -> Bool -> Bool -> Bit -> Unsigned 4 -> TxReg [_tx_reg] :: TxReg -> BitVector 8 [_tx_empty] :: TxReg -> Bool [_tx_over_run] :: TxReg -> Bool [_tx_out] :: TxReg -> Bit [_tx_cnt] :: TxReg -> Unsigned 4 tx_reg :: Lens' TxReg (BitVector 8) tx_over_run :: Lens' TxReg Bool tx_out :: Lens' TxReg Bit tx_empty :: Lens' TxReg Bool tx_cnt :: Lens' TxReg (Unsigned 4) uartTX :: TxReg -> Bool -> BitVector 8 -> Bool -> TxReg uartRX :: RxReg -> Bit -> Bool -> Bool -> RxReg uart :: forall (dom1 :: Symbol) (dom2 :: Symbol). (KnownDomain dom1, KnownDomain dom2, IP (AppendSymbol dom1 "_clk") (Clock dom1), IP (AppendSymbol dom1 "_rst") (Reset dom1), IP (AppendSymbol dom1 "_en") (Enable dom1), IP (AppendSymbol dom2 "_clk") (Clock dom2), IP (AppendSymbol dom2 "_rst") (Reset dom2), IP (AppendSymbol dom2 "_en") (Enable dom2)) => Signal dom1 Bool -> Signal dom1 (BitVector 8) -> Signal dom1 Bool -> Signal dom2 Bit -> Signal dom2 Bool -> Signal dom2 Bool -> (Signal dom1 Bit, Signal dom1 Bool, Signal dom2 (BitVector 8), Signal dom2 Bool) instance Clash.XException.NFDataX Clash.Examples.Internal.TxReg instance GHC.Generics.Generic Clash.Examples.Internal.TxReg instance Clash.XException.NFDataX Clash.Examples.Internal.RxReg instance GHC.Generics.Generic Clash.Examples.Internal.RxReg module Clash.Examples -- | We simulate DDR signal by using Signals which have exactly half -- the period (or double the speed) of our normal Signals. -- -- The primitives in this module can be used to produce or consume DDR -- signals. -- -- DDR signals are not meant to be used internally in a design, but only -- to communicate with the outside world. -- -- In some cases hardware specific DDR IN registers can be inferred by -- synthesis tools from these generic primitives. But to be sure your -- design will synthesize to dedicated hardware resources use the -- functions from Clash.Intel.DDR or Clash.Xilinx.DDR. module Clash.Explicit.DDR -- | DDR input primitive -- -- Consumes a DDR input signal and produces a regular signal containing a -- pair of values. -- --
--   >>> printX $ sampleN 5 $ ddrIn systemClockGen systemResetGen enableGen (-1,-2,-3) (fromList [0..10] :: Signal "Fast" Int)
--   [(-1,-2),(-1,-2),(-3,2),(3,4),(5,6)]
--   
ddrIn :: (HasCallStack, NFDataX a, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity)) => Clock slow -> Reset slow -> Enable slow -> (a, a, a) -> Signal fast a -> Signal slow (a, a) -- | DDR output primitive -- -- Produces a DDR output signal from a normal signal of pairs of input. -- --
--   >>> sampleN 7 (ddrOut systemClockGen systemResetGen enableGen (-1) (fromList [(0,1),(2,3),(4,5)]) :: Signal "Fast" Int)
--   [-1,-1,-1,2,3,4,5]
--   
ddrOut :: (HasCallStack, NFDataX a, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity)) => Clock slow -> Reset slow -> Enable slow -> a -> Signal slow (a, a) -> Signal fast a ddrIn# :: forall a slow fast fPeriod polarity edge reset init. (HasCallStack, NFDataX a, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity)) => Clock slow -> Reset slow -> Enable slow -> a -> a -> a -> Signal fast a -> Signal slow (a, a) ddrOut# :: (HasCallStack, NFDataX a, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity)) => Clock slow -> Reset slow -> Enable slow -> a -> Signal slow a -> Signal slow a -> Signal fast a -- | DDR primitives for Xilinx FPGAs -- -- For general information about DDR primitives see -- Clash.Explicit.DDR. -- -- For more information about the Xilinx DDR primitives see: -- -- module Clash.Xilinx.DDR -- | Xilinx specific variant of ddrIn implemented using the Xilinx -- IDDR primitive in SAME_EDGE mode. -- -- Reset values are 0 iddr :: (HasCallStack, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity), KnownNat m) => Clock slow -> Reset slow -> Enable slow -> Signal fast (BitVector m) -> Signal slow (BitVector m, BitVector m) -- | Xilinx specific variant of ddrOut implemented using the Xilinx -- ODDR primitive in SAME_EDGE mode. -- -- Reset value is 0 oddr :: (KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity), KnownNat m) => Clock slow -> Reset slow -> Enable slow -> Signal slow (BitVector m, BitVector m) -> Signal fast (BitVector m) -- | DDR primitives for Intel FPGAs using ALTDDIO primitives. -- -- For general information about DDR primitives see -- Clash.Explicit.DDR. -- -- Note that a reset is only available on certain devices, see ALTDDIO -- userguide for the specifics: -- https://www.altera.com/content/dam/altera-www/global/en_US/pdfs/literature/ug/ug_altddio.pdf module Clash.Intel.DDR -- | Intel specific variant of ddrIn implemented using the -- ALTDDIO_IN IP core. -- -- Reset values are 0 altddioIn :: (HasCallStack, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity), KnownNat m) => SSymbol deviceFamily -> Clock slow -> Reset slow -> Enable slow -> Signal fast (BitVector m) -> Signal slow (BitVector m, BitVector m) -- | Intel specific variant of ddrOut implemented using the -- ALTDDIO_OUT IP core. -- -- Reset value is 0 altddioOut :: (HasCallStack, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity), KnownConfiguration slow ('DomainConfiguration slow (2 * fPeriod) edge reset init polarity), KnownNat m) => SSymbol deviceFamily -> Clock slow -> Reset slow -> Enable slow -> Signal slow (BitVector m, BitVector m) -> Signal fast (BitVector m)