{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
module Clash.Examples.Internal where
import Clash.Prelude hiding (feedback)
import Control.Lens
import Control.Monad
import Control.Monad.Trans.State
decoderCase :: Bool -> BitVector 4 -> BitVector 16
decoderCase :: Bool -> BitVector 4 -> BitVector 16
decoderCase Bool
enable BitVector 4
binaryIn | Bool
enable =
case BitVector 4
binaryIn of
BitVector 4
0x0 -> BitVector 16
0x0001
BitVector 4
0x1 -> BitVector 16
0x0002
BitVector 4
0x2 -> BitVector 16
0x0004
BitVector 4
0x3 -> BitVector 16
0x0008
BitVector 4
0x4 -> BitVector 16
0x0010
BitVector 4
0x5 -> BitVector 16
0x0020
BitVector 4
0x6 -> BitVector 16
0x0040
BitVector 4
0x7 -> BitVector 16
0x0080
BitVector 4
0x8 -> BitVector 16
0x0100
BitVector 4
0x9 -> BitVector 16
0x0200
BitVector 4
0xA -> BitVector 16
0x0400
BitVector 4
0xB -> BitVector 16
0x0800
BitVector 4
0xC -> BitVector 16
0x1000
BitVector 4
0xD -> BitVector 16
0x2000
BitVector 4
0xE -> BitVector 16
0x4000
BitVector 4
0xF -> BitVector 16
0x8000
decoderCase Bool
_ BitVector 4
_ = BitVector 16
0
decoderShift :: Bool -> BitVector 4 -> BitVector 16
decoderShift :: Bool -> BitVector 4 -> BitVector 16
decoderShift Bool
enable BitVector 4
binaryIn =
if Bool
enable
then BitVector 16
1 BitVector 16 -> Int -> BitVector 16
forall a. Bits a => a -> Int -> a
`shiftL` (BitVector 4 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral BitVector 4
binaryIn)
else BitVector 16
0
encoderCase :: Bool -> BitVector 16 -> BitVector 4
encoderCase :: Bool -> BitVector 16 -> BitVector 4
encoderCase Bool
enable BitVector 16
binaryIn | Bool
enable =
case BitVector 16
binaryIn of
BitVector 16
0x0001 -> BitVector 4
0x0
BitVector 16
0x0002 -> BitVector 4
0x1
BitVector 16
0x0004 -> BitVector 4
0x2
BitVector 16
0x0008 -> BitVector 4
0x3
BitVector 16
0x0010 -> BitVector 4
0x4
BitVector 16
0x0020 -> BitVector 4
0x5
BitVector 16
0x0040 -> BitVector 4
0x6
BitVector 16
0x0080 -> BitVector 4
0x7
BitVector 16
0x0100 -> BitVector 4
0x8
BitVector 16
0x0200 -> BitVector 4
0x9
BitVector 16
0x0400 -> BitVector 4
0xA
BitVector 16
0x0800 -> BitVector 4
0xB
BitVector 16
0x1000 -> BitVector 4
0xC
BitVector 16
0x2000 -> BitVector 4
0xD
BitVector 16
0x4000 -> BitVector 4
0xE
BitVector 16
0x8000 -> BitVector 4
0xF
encoderCase Bool
_ BitVector 16
_ = BitVector 4
0
upCounter
:: HiddenClockResetEnable dom
=> Signal dom Bool
-> Signal dom (Unsigned 8)
upCounter :: Signal dom Bool -> Signal dom (Unsigned 8)
upCounter Signal dom Bool
enable = Signal dom (Unsigned 8)
s
where
s :: Signal dom (Unsigned 8)
s = Unsigned 8 -> Signal dom (Unsigned 8) -> Signal dom (Unsigned 8)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register Unsigned 8
0 (Signal dom Bool
-> Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8)
forall (f :: Type -> Type) a.
Applicative f =>
f Bool -> f a -> f a -> f a
mux Signal dom Bool
enable (Signal dom (Unsigned 8)
s Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8) -> Signal dom (Unsigned 8)
forall a. Num a => a -> a -> a
+ Signal dom (Unsigned 8)
1) Signal dom (Unsigned 8)
s)
upCounterLdT
:: Num a => a -> (Bool, Bool, a) -> (a,a)
upCounterLdT :: a -> (Bool, Bool, a) -> (a, a)
upCounterLdT a
s (Bool
ld,Bool
en,a
dIn) = (a
s',a
s)
where
s' :: a
s' | Bool
ld = a
dIn
| Bool
en = a
s a -> a -> a
forall a. Num a => a -> a -> a
+ a
1
| Bool
otherwise = a
s
upCounterLd
:: HiddenClockResetEnable dom
=> Signal dom (Bool, Bool, Unsigned 8)
-> Signal dom (Unsigned 8)
upCounterLd :: Signal dom (Bool, Bool, Unsigned 8) -> Signal dom (Unsigned 8)
upCounterLd = (Unsigned 8
-> (Bool, Bool, Unsigned 8) -> (Unsigned 8, Unsigned 8))
-> Unsigned 8
-> Signal dom (Bool, Bool, Unsigned 8)
-> Signal dom (Unsigned 8)
forall (dom :: Symbol) s i o.
(HiddenClockResetEnable dom, NFDataX s) =>
(s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o
mealy Unsigned 8 -> (Bool, Bool, Unsigned 8) -> (Unsigned 8, Unsigned 8)
forall a. Num a => a -> (Bool, Bool, a) -> (a, a)
upCounterLdT Unsigned 8
0
upDownCounter
:: HiddenClockResetEnable dom
=> Signal dom Bool
-> Signal dom (Unsigned 8)
upDownCounter :: Signal dom Bool -> Signal dom (Unsigned 8)
upDownCounter Signal dom Bool
upDown = Signal dom (Unsigned 8)
s
where
s :: Signal dom (Unsigned 8)
s = Unsigned 8 -> Signal dom (Unsigned 8) -> Signal dom (Unsigned 8)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register Unsigned 8
0 (Signal dom Bool
-> Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8)
forall (f :: Type -> Type) a.
Applicative f =>
f Bool -> f a -> f a -> f a
mux Signal dom Bool
upDown (Signal dom (Unsigned 8)
s Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8) -> Signal dom (Unsigned 8)
forall a. Num a => a -> a -> a
+ Signal dom (Unsigned 8)
1) (Signal dom (Unsigned 8)
s Signal dom (Unsigned 8)
-> Signal dom (Unsigned 8) -> Signal dom (Unsigned 8)
forall a. Num a => a -> a -> a
- Signal dom (Unsigned 8)
1))
lfsrF' :: BitVector 16 -> BitVector 16
lfsrF' :: BitVector 16 -> BitVector 16
lfsrF' BitVector 16
s = Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack Bit
feedback BitVector 1 -> BitVector 15 -> BitVector (1 + 15)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# SNat 15 -> SNat 1 -> BitVector 16 -> BitVector ((15 + 1) - 1)
forall a (m :: Nat) (i :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ ((m + 1) + i)) =>
SNat m -> SNat n -> a -> BitVector ((m + 1) - n)
slice (KnownNat 15 => SNat 15
forall (n :: Nat). KnownNat n => SNat n
SNat @15) SNat 1
d1 BitVector 16
s
where
feedback :: Bit
feedback = BitVector 16
sBitVector 16 -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
5 Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` BitVector 16
sBitVector 16 -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
3 Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` BitVector 16
sBitVector 16 -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
2 Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` BitVector 16
sBitVector 16 -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
0
lfsrF
:: HiddenClockResetEnable dom
=> BitVector 16 -> Signal dom Bit
lfsrF :: BitVector 16 -> Signal dom Bit
lfsrF BitVector 16
seed = BitVector 16 -> Bit
forall a. BitPack a => a -> Bit
msb (BitVector 16 -> Bit)
-> Signal dom (BitVector 16) -> Signal dom Bit
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom (BitVector 16)
r
where r :: Signal dom (BitVector 16)
r = BitVector 16
-> Signal dom (BitVector 16) -> Signal dom (BitVector 16)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register BitVector 16
seed (BitVector 16 -> BitVector 16
lfsrF' (BitVector 16 -> BitVector 16)
-> Signal dom (BitVector 16) -> Signal dom (BitVector 16)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom (BitVector 16)
r)
lfsrGP
:: (KnownNat (n + 1), Bits a)
=> Vec (n + 1) Bool
-> Vec (n + 1) a
-> Vec (n + 1) a
lfsrGP :: Vec (n + 1) Bool -> Vec (n + 1) a -> Vec (n + 1) a
lfsrGP Vec (n + 1) Bool
taps Vec (n + 1) a
regs = (Bool -> a -> a)
-> Vec (n + 1) Bool -> Vec (n + 1) a -> Vec (n + 1) a
forall a b c (n :: Nat).
(a -> b -> c) -> Vec n a -> Vec n b -> Vec n c
zipWith Bool -> a -> a
xorM Vec (n + 1) Bool
taps (a
fb a -> Vec (n + 1) a -> Vec (n + 1) a
forall (n :: Nat) a. KnownNat n => a -> Vec n a -> Vec n a
+>> Vec (n + 1) a
regs)
where
fb :: a
fb = Vec (n + 1) a -> a
forall (n :: Nat) a. Vec (n + 1) a -> a
last Vec (n + 1) a
regs
xorM :: Bool -> a -> a
xorM Bool
i a
x | Bool
i = a
x a -> a -> a
forall a. Bits a => a -> a -> a
`xor` a
fb
| Bool
otherwise = a
x
lfsrG
:: HiddenClockResetEnable dom
=> BitVector 16
-> Signal dom Bit
lfsrG :: BitVector 16 -> Signal dom Bit
lfsrG BitVector 16
seed = Vec (15 + 1) (Signal dom Bit) -> Signal dom Bit
forall (n :: Nat) a. Vec (n + 1) a -> a
last (Signal dom (Vec 16 Bit) -> Unbundled dom (Vec 16 Bit)
forall a (dom :: Symbol).
Bundle a =>
Signal dom a -> Unbundled dom a
unbundle Signal dom (Vec 16 Bit)
r)
where r :: Signal dom (Vec 16 Bit)
r = Vec 16 Bit -> Signal dom (Vec 16 Bit) -> Signal dom (Vec 16 Bit)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register (BitVector (BitSize (Vec 16 Bit)) -> Vec 16 Bit
forall a. BitPack a => BitVector (BitSize a) -> a
unpack BitVector 16
BitVector (BitSize (Vec 16 Bit))
seed) (Vec (15 + 1) Bool -> Vec (15 + 1) Bit -> Vec (15 + 1) Bit
forall (n :: Nat) a.
(KnownNat (n + 1), Bits a) =>
Vec (n + 1) Bool -> Vec (n + 1) a -> Vec (n + 1) a
lfsrGP (BitVector (BitSize (Vec 16 Bool)) -> Vec 16 Bool
forall a. BitPack a => BitVector (BitSize a) -> a
unpack BitVector (BitSize (Vec 16 Bool))
0b0011010000000000) (Vec 16 Bit -> Vec 16 Bit)
-> Signal dom (Vec 16 Bit) -> Signal dom (Vec 16 Bit)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom (Vec 16 Bit)
r)
grayCounter
:: HiddenClockResetEnable dom
=> Signal dom Bool
-> Signal dom (BitVector 8)
grayCounter :: Signal dom Bool -> Signal dom (BitVector 8)
grayCounter Signal dom Bool
en = Unsigned 8 -> BitVector 8
forall a (i :: Nat) (i :: Nat).
(BitPack a, BitSize a ~ (8 + i), BitSize a ~ (7 + i)) =>
a -> BitVector 8
gray (Unsigned 8 -> BitVector 8)
-> Signal dom (Unsigned 8) -> Signal dom (BitVector 8)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Bool -> Signal dom (Unsigned 8)
forall (dom :: Symbol).
HiddenClockResetEnable dom =>
Signal dom Bool -> Signal dom (Unsigned 8)
upCounter Signal dom Bool
en
where gray :: a -> BitVector (1 + 7)
gray a
xs = Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (a -> Bit
forall a. BitPack a => a -> Bit
msb a
xs) BitVector 1 -> BitVector 7 -> BitVector (1 + 7)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector 7 -> BitVector 7 -> BitVector 7
forall a. Bits a => a -> a -> a
xor (SNat 7 -> SNat 1 -> a -> BitVector ((7 + 1) - 1)
forall a (m :: Nat) (i :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ ((m + 1) + i)) =>
SNat m -> SNat n -> a -> BitVector ((m + 1) - n)
slice SNat 7
d7 SNat 1
d1 a
xs) (SNat 6 -> SNat 0 -> a -> BitVector ((6 + 1) - 0)
forall a (m :: Nat) (i :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ ((m + 1) + i)) =>
SNat m -> SNat n -> a -> BitVector ((m + 1) - n)
slice SNat 6
d6 SNat 0
d0 a
xs)
oneHotCounter
:: HiddenClockResetEnable dom
=> Signal dom Bool
-> Signal dom (BitVector 8)
oneHotCounter :: Signal dom Bool -> Signal dom (BitVector 8)
oneHotCounter Signal dom Bool
enable = Signal dom (BitVector 8)
s
where
s :: Signal dom (BitVector 8)
s = BitVector 8 -> Signal dom (BitVector 8) -> Signal dom (BitVector 8)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register BitVector 8
1 (Signal dom Bool
-> Signal dom (BitVector 8)
-> Signal dom (BitVector 8)
-> Signal dom (BitVector 8)
forall (f :: Type -> Type) a.
Applicative f =>
f Bool -> f a -> f a -> f a
mux Signal dom Bool
enable (BitVector 8 -> Int -> BitVector 8
forall a. Bits a => a -> Int -> a
rotateL (BitVector 8 -> Int -> BitVector 8)
-> Signal dom (BitVector 8) -> Signal dom (Int -> BitVector 8)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom (BitVector 8)
s Signal dom (Int -> BitVector 8)
-> Signal dom Int -> Signal dom (BitVector 8)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Int
1) Signal dom (BitVector 8)
s)
crcT
:: (Bits a, BitPack a)
=> a
-> Bit
-> a
crcT :: a -> Bit -> a
crcT a
bv Bit
dIn = Integer -> Bit -> a -> a
forall a i. (BitPack a, Enum i) => i -> Bit -> a -> a
replaceBit Integer
0 Bit
dInXor
(a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ Integer -> Bit -> a -> a
forall a i. (BitPack a, Enum i) => i -> Bit -> a -> a
replaceBit Integer
5 (a
bva -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
4 Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` Bit
dInXor)
(a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ Integer -> Bit -> a -> a
forall a i. (BitPack a, Enum i) => i -> Bit -> a -> a
replaceBit Integer
12 (a
bva -> Integer -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
!Integer
11 Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` Bit
dInXor)
a
rotated
where
dInXor :: Bit
dInXor = Bit
dIn Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
`xor` Bit
fb
rotated :: a
rotated = a -> Int -> a
forall a. Bits a => a -> Int -> a
rotateL a
bv Int
1
fb :: Bit
fb = a -> Bit
forall a. BitPack a => a -> Bit
msb a
bv
crc
:: HiddenClockResetEnable dom
=> Signal dom Bool
-> Signal dom Bool
-> Signal dom Bit
-> Signal dom (BitVector 16)
crc :: Signal dom Bool
-> Signal dom Bool -> Signal dom Bit -> Signal dom (BitVector 16)
crc Signal dom Bool
enable Signal dom Bool
ld Signal dom Bit
dIn = Signal dom (BitVector 16)
s
where
s :: Signal dom (BitVector 16)
s = BitVector 16
-> Signal dom (BitVector 16) -> Signal dom (BitVector 16)
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register BitVector 16
0xFFFF (Signal dom Bool
-> Signal dom (BitVector 16)
-> Signal dom (BitVector 16)
-> Signal dom (BitVector 16)
forall (f :: Type -> Type) a.
Applicative f =>
f Bool -> f a -> f a -> f a
mux Signal dom Bool
enable (Signal dom Bool
-> Signal dom (BitVector 16)
-> Signal dom (BitVector 16)
-> Signal dom (BitVector 16)
forall (f :: Type -> Type) a.
Applicative f =>
f Bool -> f a -> f a -> f a
mux Signal dom Bool
ld Signal dom (BitVector 16)
0xFFFF (BitVector 16 -> Bit -> BitVector 16
forall a. (Bits a, BitPack a) => a -> Bit -> a
crcT (BitVector 16 -> Bit -> BitVector 16)
-> Signal dom (BitVector 16) -> Signal dom (Bit -> BitVector 16)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom (BitVector 16)
s Signal dom (Bit -> BitVector 16)
-> Signal dom Bit -> Signal dom (BitVector 16)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bit
dIn)) Signal dom (BitVector 16)
s)
data RxReg
= RxReg
{ RxReg -> BitVector 8
_rx_reg :: BitVector 8
, RxReg -> BitVector 8
_rx_data :: BitVector 8
, RxReg -> Unsigned 4
_rx_sample_cnt :: Unsigned 4
, RxReg -> Unsigned 4
_rx_cnt :: Unsigned 4
, RxReg -> Bool
_rx_frame_err :: Bool
, RxReg -> Bool
_rx_over_run :: Bool
, RxReg -> Bool
_rx_empty :: Bool
, RxReg -> Bit
_rx_d1 :: Bit
, RxReg -> Bit
_rx_d2 :: Bit
, RxReg -> Bool
_rx_busy :: Bool
} deriving ((forall x. RxReg -> Rep RxReg x)
-> (forall x. Rep RxReg x -> RxReg) -> Generic RxReg
forall x. Rep RxReg x -> RxReg
forall x. RxReg -> Rep RxReg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RxReg x -> RxReg
$cfrom :: forall x. RxReg -> Rep RxReg x
Generic, HasCallStack => String -> RxReg
RxReg -> Bool
RxReg -> ()
RxReg -> RxReg
(HasCallStack => String -> RxReg)
-> (RxReg -> Bool)
-> (RxReg -> RxReg)
-> (RxReg -> ())
-> NFDataX RxReg
forall a.
(HasCallStack => String -> a)
-> (a -> Bool) -> (a -> a) -> (a -> ()) -> NFDataX a
rnfX :: RxReg -> ()
$crnfX :: RxReg -> ()
ensureSpine :: RxReg -> RxReg
$censureSpine :: RxReg -> RxReg
hasUndefined :: RxReg -> Bool
$chasUndefined :: RxReg -> Bool
deepErrorX :: String -> RxReg
$cdeepErrorX :: HasCallStack => String -> RxReg
NFDataX)
makeLenses ''RxReg
data TxReg
= TxReg
{ TxReg -> BitVector 8
_tx_reg :: BitVector 8
, TxReg -> Bool
_tx_empty :: Bool
, TxReg -> Bool
_tx_over_run :: Bool
, TxReg -> Bit
_tx_out :: Bit
, TxReg -> Unsigned 4
_tx_cnt :: Unsigned 4
}
deriving ((forall x. TxReg -> Rep TxReg x)
-> (forall x. Rep TxReg x -> TxReg) -> Generic TxReg
forall x. Rep TxReg x -> TxReg
forall x. TxReg -> Rep TxReg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxReg x -> TxReg
$cfrom :: forall x. TxReg -> Rep TxReg x
Generic, HasCallStack => String -> TxReg
TxReg -> Bool
TxReg -> ()
TxReg -> TxReg
(HasCallStack => String -> TxReg)
-> (TxReg -> Bool)
-> (TxReg -> TxReg)
-> (TxReg -> ())
-> NFDataX TxReg
forall a.
(HasCallStack => String -> a)
-> (a -> Bool) -> (a -> a) -> (a -> ()) -> NFDataX a
rnfX :: TxReg -> ()
$crnfX :: TxReg -> ()
ensureSpine :: TxReg -> TxReg
$censureSpine :: TxReg -> TxReg
hasUndefined :: TxReg -> Bool
$chasUndefined :: TxReg -> Bool
deepErrorX :: String -> TxReg
$cdeepErrorX :: HasCallStack => String -> TxReg
NFDataX)
makeLenses ''TxReg
uartTX :: TxReg -> Bool -> BitVector 8 -> Bool -> TxReg
uartTX t :: TxReg
t@(TxReg {Bool
Bit
BitVector 8
Unsigned 4
_tx_cnt :: Unsigned 4
_tx_out :: Bit
_tx_over_run :: Bool
_tx_empty :: Bool
_tx_reg :: BitVector 8
_tx_cnt :: TxReg -> Unsigned 4
_tx_out :: TxReg -> Bit
_tx_over_run :: TxReg -> Bool
_tx_empty :: TxReg -> Bool
_tx_reg :: TxReg -> BitVector 8
..}) Bool
ld_tx_data BitVector 8
tx_data Bool
tx_enable = (State TxReg () -> TxReg -> TxReg)
-> TxReg -> State TxReg () -> TxReg
forall a b c. (a -> b -> c) -> b -> a -> c
flip State TxReg () -> TxReg -> TxReg
forall s a. State s a -> s -> s
execState TxReg
t (State TxReg () -> TxReg) -> State TxReg () -> TxReg
forall a b. (a -> b) -> a -> b
$ do
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when Bool
ld_tx_data (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$ do
if Bool -> Bool
not Bool
_tx_empty then
(Bool -> Identity Bool) -> TxReg -> Identity TxReg
Lens' TxReg Bool
tx_over_run ((Bool -> Identity Bool) -> TxReg -> Identity TxReg)
-> Bool -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
else do
(BitVector 8 -> Identity (BitVector 8)) -> TxReg -> Identity TxReg
Lens' TxReg (BitVector 8)
tx_reg ((BitVector 8 -> Identity (BitVector 8))
-> TxReg -> Identity TxReg)
-> BitVector 8 -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= BitVector 8
tx_data
(Bool -> Identity Bool) -> TxReg -> Identity TxReg
Lens' TxReg Bool
tx_empty ((Bool -> Identity Bool) -> TxReg -> Identity TxReg)
-> Bool -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Bool
tx_enable Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
_tx_empty) (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$ do
(Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg
Lens' TxReg (Unsigned 4)
tx_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg)
-> Unsigned 4 -> State TxReg ()
forall s (m :: Type -> Type) a.
(MonadState s m, Num a) =>
ASetter' s a -> a -> m ()
+= Unsigned 4
1
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_tx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned 4
0) (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$
(Bit -> Identity Bit) -> TxReg -> Identity TxReg
Lens' TxReg Bit
tx_out ((Bit -> Identity Bit) -> TxReg -> Identity TxReg)
-> Bit -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bit
0
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_tx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Ord a => a -> a -> Bool
> Unsigned 4
0 Bool -> Bool -> Bool
&& Unsigned 4
_tx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Ord a => a -> a -> Bool
< Unsigned 4
9) (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$
(Bit -> Identity Bit) -> TxReg -> Identity TxReg
Lens' TxReg Bit
tx_out ((Bit -> Identity Bit) -> TxReg -> Identity TxReg)
-> Bit -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= BitVector 8
_tx_reg BitVector 8 -> Unsigned 4 -> Bit
forall a i. (BitPack a, Enum i) => a -> i -> Bit
! (Unsigned 4
_tx_cnt Unsigned 4 -> Unsigned 4 -> Unsigned 4
forall a. Num a => a -> a -> a
- Unsigned 4
1)
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_tx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned 4
9) (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$ do
(Bit -> Identity Bit) -> TxReg -> Identity TxReg
Lens' TxReg Bit
tx_out ((Bit -> Identity Bit) -> TxReg -> Identity TxReg)
-> Bit -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bit
1
(Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg
Lens' TxReg (Unsigned 4)
tx_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg)
-> Unsigned 4 -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Unsigned 4
0
(Bool -> Identity Bool) -> TxReg -> Identity TxReg
Lens' TxReg Bool
tx_empty ((Bool -> Identity Bool) -> TxReg -> Identity TxReg)
-> Bool -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
Bool -> State TxReg () -> State TxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless Bool
tx_enable (State TxReg () -> State TxReg ())
-> State TxReg () -> State TxReg ()
forall a b. (a -> b) -> a -> b
$
(Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg
Lens' TxReg (Unsigned 4)
tx_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> TxReg -> Identity TxReg)
-> Unsigned 4 -> State TxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Unsigned 4
0
uartRX :: RxReg -> Bit -> Bool -> Bool -> RxReg
uartRX r :: RxReg
r@(RxReg {Bool
Bit
BitVector 8
Unsigned 4
_rx_busy :: Bool
_rx_d2 :: Bit
_rx_d1 :: Bit
_rx_empty :: Bool
_rx_over_run :: Bool
_rx_frame_err :: Bool
_rx_cnt :: Unsigned 4
_rx_sample_cnt :: Unsigned 4
_rx_data :: BitVector 8
_rx_reg :: BitVector 8
_rx_busy :: RxReg -> Bool
_rx_d2 :: RxReg -> Bit
_rx_d1 :: RxReg -> Bit
_rx_empty :: RxReg -> Bool
_rx_over_run :: RxReg -> Bool
_rx_frame_err :: RxReg -> Bool
_rx_cnt :: RxReg -> Unsigned 4
_rx_sample_cnt :: RxReg -> Unsigned 4
_rx_data :: RxReg -> BitVector 8
_rx_reg :: RxReg -> BitVector 8
..}) Bit
rx_in Bool
uld_rx_data Bool
rx_enable = (State RxReg () -> RxReg -> RxReg)
-> RxReg -> State RxReg () -> RxReg
forall a b c. (a -> b -> c) -> b -> a -> c
flip State RxReg () -> RxReg -> RxReg
forall s a. State s a -> s -> s
execState RxReg
r (State RxReg () -> RxReg) -> State RxReg () -> RxReg
forall a b. (a -> b) -> a -> b
$ do
(Bit -> Identity Bit) -> RxReg -> Identity RxReg
Lens' RxReg Bit
rx_d1 ((Bit -> Identity Bit) -> RxReg -> Identity RxReg)
-> Bit -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bit
rx_in
(Bit -> Identity Bit) -> RxReg -> Identity RxReg
Lens' RxReg Bit
rx_d2 ((Bit -> Identity Bit) -> RxReg -> Identity RxReg)
-> Bit -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bit
_rx_d1
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when Bool
uld_rx_data (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
(BitVector 8 -> Identity (BitVector 8)) -> RxReg -> Identity RxReg
Lens' RxReg (BitVector 8)
rx_data ((BitVector 8 -> Identity (BitVector 8))
-> RxReg -> Identity RxReg)
-> BitVector 8 -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= BitVector 8
_rx_reg
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_empty ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
if Bool
rx_enable then do
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
_rx_busy Bool -> Bool -> Bool
&& Bit
_rx_d2 Bit -> Bit -> Bool
forall a. Eq a => a -> a -> Bool
== Bit
0) (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_busy ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
(Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg
Lens' RxReg (Unsigned 4)
rx_sample_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg)
-> Unsigned 4 -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Unsigned 4
1
(Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg
Lens' RxReg (Unsigned 4)
rx_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg)
-> Unsigned 4 -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Unsigned 4
0
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when Bool
_rx_busy (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
(Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg
Lens' RxReg (Unsigned 4)
rx_sample_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg)
-> Unsigned 4 -> State RxReg ()
forall s (m :: Type -> Type) a.
(MonadState s m, Num a) =>
ASetter' s a -> a -> m ()
+= Unsigned 4
1
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_rx_sample_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned 4
7) (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
if Bit
_rx_d1 Bit -> Bit -> Bool
forall a. Eq a => a -> a -> Bool
== Bit
1 Bool -> Bool -> Bool
&& Unsigned 4
_rx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned 4
0 then
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_busy ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
else do
(Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg
Lens' RxReg (Unsigned 4)
rx_cnt ((Unsigned 4 -> Identity (Unsigned 4)) -> RxReg -> Identity RxReg)
-> Unsigned 4 -> State RxReg ()
forall s (m :: Type -> Type) a.
(MonadState s m, Num a) =>
ASetter' s a -> a -> m ()
+= Unsigned 4
1
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_rx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Ord a => a -> a -> Bool
> Unsigned 4
0 Bool -> Bool -> Bool
&& Unsigned 4
_rx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Ord a => a -> a -> Bool
< Unsigned 4
9) (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
(BitVector 8 -> Identity (BitVector 8)) -> RxReg -> Identity RxReg
Lens' RxReg (BitVector 8)
rx_reg ((BitVector 8 -> Identity (BitVector 8))
-> RxReg -> Identity RxReg)
-> (BitVector 8 -> BitVector 8) -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Unsigned 4 -> Bit -> BitVector 8 -> BitVector 8
forall a i. (BitPack a, Enum i) => i -> Bit -> a -> a
replaceBit (Unsigned 4
_rx_cnt Unsigned 4 -> Unsigned 4 -> Unsigned 4
forall a. Num a => a -> a -> a
- Unsigned 4
1) Bit
_rx_d2
Bool -> State RxReg () -> State RxReg ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (Unsigned 4
_rx_cnt Unsigned 4 -> Unsigned 4 -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned 4
9) (State RxReg () -> State RxReg ())
-> State RxReg () -> State RxReg ()
forall a b. (a -> b) -> a -> b
$ do
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_busy ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
if Bit
_rx_d2 Bit -> Bit -> Bool
forall a. Eq a => a -> a -> Bool
== Bit
0 then
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_frame_err ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
else do
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_empty ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_frame_err ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_over_run ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool -> Bool
not Bool
_rx_empty
else do
(Bool -> Identity Bool) -> RxReg -> Identity RxReg
Lens' RxReg Bool
rx_busy ((Bool -> Identity Bool) -> RxReg -> Identity RxReg)
-> Bool -> State RxReg ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
uart :: Signal dom Bool
-> Signal dom (BitVector 8)
-> Signal dom Bool
-> Signal dom Bit
-> Signal dom Bool
-> Signal dom Bool
-> (Signal dom Bit, Signal dom Bool, Signal dom (BitVector 8),
Signal dom Bool)
uart Signal dom Bool
ld_tx_data Signal dom (BitVector 8)
tx_data Signal dom Bool
tx_enable Signal dom Bit
rx_in Signal dom Bool
uld_rx_data Signal dom Bool
rx_enable =
( TxReg -> Bit
_tx_out (TxReg -> Bit) -> Signal dom TxReg -> Signal dom Bit
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom TxReg
txReg
, TxReg -> Bool
_tx_empty (TxReg -> Bool) -> Signal dom TxReg -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom TxReg
txReg
, RxReg -> BitVector 8
_rx_data (RxReg -> BitVector 8)
-> Signal dom RxReg -> Signal dom (BitVector 8)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom RxReg
rxReg
, RxReg -> Bool
_rx_empty (RxReg -> Bool) -> Signal dom RxReg -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom RxReg
rxReg
)
where
rxReg :: Signal dom RxReg
rxReg = RxReg -> Signal dom RxReg -> Signal dom RxReg
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register RxReg
rxRegInit (RxReg -> Bit -> Bool -> Bool -> RxReg
uartRX (RxReg -> Bit -> Bool -> Bool -> RxReg)
-> Signal dom RxReg -> Signal dom (Bit -> Bool -> Bool -> RxReg)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom RxReg
rxReg Signal dom (Bit -> Bool -> Bool -> RxReg)
-> Signal dom Bit -> Signal dom (Bool -> Bool -> RxReg)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bit
rx_in Signal dom (Bool -> Bool -> RxReg)
-> Signal dom Bool -> Signal dom (Bool -> RxReg)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bool
uld_rx_data
Signal dom (Bool -> RxReg) -> Signal dom Bool -> Signal dom RxReg
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bool
rx_enable)
rxRegInit :: RxReg
rxRegInit = RxReg :: BitVector 8
-> BitVector 8
-> Unsigned 4
-> Unsigned 4
-> Bool
-> Bool
-> Bool
-> Bit
-> Bit
-> Bool
-> RxReg
RxReg { _rx_reg :: BitVector 8
_rx_reg = BitVector 8
0
, _rx_data :: BitVector 8
_rx_data = BitVector 8
0
, _rx_sample_cnt :: Unsigned 4
_rx_sample_cnt = Unsigned 4
0
, _rx_cnt :: Unsigned 4
_rx_cnt = Unsigned 4
0
, _rx_frame_err :: Bool
_rx_frame_err = Bool
False
, _rx_over_run :: Bool
_rx_over_run = Bool
False
, _rx_empty :: Bool
_rx_empty = Bool
True
, _rx_d1 :: Bit
_rx_d1 = Bit
1
, _rx_d2 :: Bit
_rx_d2 = Bit
1
, _rx_busy :: Bool
_rx_busy = Bool
False
}
txReg :: Signal dom TxReg
txReg = TxReg -> Signal dom TxReg -> Signal dom TxReg
forall (dom :: Symbol) a.
(HiddenClockResetEnable dom, NFDataX a) =>
a -> Signal dom a -> Signal dom a
register TxReg
txRegInit (TxReg -> Bool -> BitVector 8 -> Bool -> TxReg
uartTX (TxReg -> Bool -> BitVector 8 -> Bool -> TxReg)
-> Signal dom TxReg
-> Signal dom (Bool -> BitVector 8 -> Bool -> TxReg)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom TxReg
txReg Signal dom (Bool -> BitVector 8 -> Bool -> TxReg)
-> Signal dom Bool -> Signal dom (BitVector 8 -> Bool -> TxReg)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bool
ld_tx_data Signal dom (BitVector 8 -> Bool -> TxReg)
-> Signal dom (BitVector 8) -> Signal dom (Bool -> TxReg)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom (BitVector 8)
tx_data
Signal dom (Bool -> TxReg) -> Signal dom Bool -> Signal dom TxReg
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Signal dom Bool
tx_enable)
txRegInit :: TxReg
txRegInit = TxReg :: BitVector 8 -> Bool -> Bool -> Bit -> Unsigned 4 -> TxReg
TxReg { _tx_reg :: BitVector 8
_tx_reg = BitVector 8
0
, _tx_empty :: Bool
_tx_empty = Bool
True
, _tx_over_run :: Bool
_tx_over_run = Bool
False
, _tx_out :: Bit
_tx_out = Bit
1
, _tx_cnt :: Unsigned 4
_tx_cnt = Unsigned 4
0
}