Skip to content

Commit

Permalink
Rename Undefined to NFDataX
Browse files Browse the repository at this point in the history
We didn't like the name `Undefined` because:

1. We were creating unknown values, not undefined values
2. Also, not the entire value is unkown, just the leafs
3. It also traverses data-structures, without touching
   unknown values (which throw XExceptions)

We went through multiple alternatives: `Unknown`, `Spine`,
`SpineX`, `LeafX`, `ClashData`, etc. all somewhat horrible.

Ultimately we decided to call it `NFDataX`, because it has some
`NFData`-like functionality.
  • Loading branch information
christiaanb committed Sep 3, 2019
1 parent 9e2e423 commit d1f325e
Show file tree
Hide file tree
Showing 53 changed files with 295 additions and 295 deletions.
4 changes: 2 additions & 2 deletions clash-cosim/src/Clash/CoSim/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Clash.CoSim.Types where
import Data.Data (Data, Typeable)

import Clash.Prelude (BitPack, BitSize, KnownNat)
import Clash.XException (Undefined)
import Clash.XException (NFDataX)

-- | Settings passed to the simulator. Does not affect synthetization.
data CoSimSettings = CoSimSettings
Expand Down Expand Up @@ -45,7 +45,7 @@ defaultSettings = CoSimSettings
-- can be simultated.
type ClashType a = ( BitPack a
, KnownNat (BitSize a)
, Undefined a
, NFDataX a
)

-- | Supported simulators
Expand Down
2 changes: 1 addition & 1 deletion clash-cosim/tests/test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ tests = testGroup "Inline verilog"
-- "normal" Haskell types.
bin
:: forall t a
. (t ~ Signal System a, Undefined a)
. (t ~ Signal System a, NFDataX a)
=> (t -> t -> t)
-> a
-> a
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/clash-prelude.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -323,7 +323,7 @@ test-suite unittests
Clash.Tests.DerivingDataRepr
Clash.Tests.DerivingDataReprTypes
Clash.Tests.Signal
Clash.Tests.Undefined
Clash.Tests.NFDataX


benchmark benchmark-clash-prelude
Expand Down
4 changes: 2 additions & 2 deletions clash-prelude/src/Clash/Examples.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,7 @@ data RxReg
, _rx_d1 :: Bit
, _rx_d2 :: Bit
, _rx_busy :: Bool
} deriving (Generic, Undefined)
} deriving (Generic, NFDataX)

makeLenses ''RxReg

Expand All @@ -207,7 +207,7 @@ data TxReg
, _tx_out :: Bit
, _tx_cnt :: Unsigned 4
}
deriving (Generic, Undefined)
deriving (Generic, NFDataX)

makeLenses ''TxReg

Expand Down
20 changes: 10 additions & 10 deletions clash-prelude/src/Clash/Explicit/BlockRam.hs
Original file line number Diff line number Diff line change
Expand Up @@ -424,7 +424,7 @@ import Clash.Sized.Index (Index)
import Clash.Sized.Vector (Vec, replicate, toList, iterateI)
import qualified Clash.Sized.Vector as CV
import Clash.XException
(maybeIsX, seqX, Undefined, deepErrorX, defaultSeqX, errorX)
(maybeIsX, seqX, NFDataX, deepErrorX, defaultSeqX, errorX)

{- $setup
>>> import Clash.Explicit.Prelude as C
Expand All @@ -442,7 +442,7 @@ data Reg
| RegC
| RegD
| RegE
deriving (Eq,Show,Enum,C.Generic,Undefined)
deriving (Eq,Show,Enum,C.Generic,NFDataX)
:}
>>> :{
Expand Down Expand Up @@ -719,7 +719,7 @@ fromJustX (Just x) = x
blockRam
:: ( KnownDomain dom
, HasCallStack
, Undefined a
, NFDataX a
, Enum addr )
=> Clock dom
-- ^ 'Clock' to synchronize to
Expand Down Expand Up @@ -765,7 +765,7 @@ blockRam = \clk gen content rd wrM ->
blockRamPow2
:: ( KnownDomain dom
, HasCallStack
, Undefined a
, NFDataX a
, KnownNat n )
=> Clock dom
-- ^ 'Clock' to synchronize to
Expand Down Expand Up @@ -798,7 +798,7 @@ blockRamU
:: forall n dom a r addr
. ( KnownDomain dom
, HasCallStack
, Undefined a
, NFDataX a
, Enum addr
, 1 <= n )
=> Clock dom
Expand Down Expand Up @@ -855,7 +855,7 @@ blockRamU#
:: forall n dom a
. ( KnownDomain dom
, HasCallStack
, Undefined a )
, NFDataX a )
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand Down Expand Up @@ -889,7 +889,7 @@ blockRam1
:: forall n dom a r addr
. ( KnownDomain dom
, HasCallStack
, Undefined a
, NFDataX a
, Enum addr
, 1 <= n )
=> Clock dom
Expand Down Expand Up @@ -946,7 +946,7 @@ blockRam1#
:: forall n dom a
. ( KnownDomain dom
, HasCallStack
, Undefined a )
, NFDataX a )
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand Down Expand Up @@ -975,7 +975,7 @@ blockRam1# clk en n a =
blockRam#
:: ( KnownDomain dom
, HasCallStack
, Undefined a )
, NFDataX a )
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand Down Expand Up @@ -1022,7 +1022,7 @@ blockRam# (Clock _) gen content rd wen =
-- | Create read-after-write blockRAM from a read-before-write one
readNew
:: ( KnownDomain dom
, Undefined a
, NFDataX a
, Eq addr )
=> Clock dom
-> Reset dom
Expand Down
8 changes: 4 additions & 4 deletions clash-prelude/src/Clash/Explicit/DDR.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ import Clash.Signal.Internal
-- [(X,X),((-1),(-2)),((-3),2),(3,4),(5,6)]
ddrIn
:: ( HasCallStack
, Undefined a
, NFDataX a
, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity) )
=> Clock slow
Expand All @@ -79,7 +79,7 @@ ddrIn clk rst en (i0,i1,i2) =
ddrIn#
:: forall a slow fast fPeriod polarity edge reset init
. ( HasCallStack
, Undefined a
, NFDataX a
, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity) )
=> Clock slow
Expand Down Expand Up @@ -142,7 +142,7 @@ ddrIn# (Clock _) (unsafeToHighPolarity -> hRst) (fromEnable -> ena) i0 i1 i2 =
-- [-1,-1,-1,2,3,4,5]
ddrOut
:: ( HasCallStack
, Undefined a
, NFDataX a
, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity) )
=> Clock slow
Expand All @@ -160,7 +160,7 @@ ddrOut clk rst en i0 =

ddrOut#
:: ( HasCallStack
, Undefined a
, NFDataX a
, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity) )
=> Clock slow
Expand Down
6 changes: 3 additions & 3 deletions clash-prelude/src/Clash/Explicit/Mealy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ where

import Clash.Explicit.Signal
(KnownDomain, Bundle (..), Clock, Reset, Signal, Enable, register)
import Clash.XException (Undefined)
import Clash.XException (NFDataX)

{- $setup
>>> :set -XDataKinds -XTypeApplications
Expand Down Expand Up @@ -85,7 +85,7 @@ let macT s (x,y) = (s',s)
-- @
mealy
:: ( KnownDomain dom
, Undefined s )
, NFDataX s )
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Reset dom
Expand Down Expand Up @@ -132,7 +132,7 @@ mealy clk rst en f iS =
-- @
mealyB
:: ( KnownDomain dom
, Undefined s
, NFDataX s
, Bundle i
, Bundle o )
=> Clock dom
Expand Down
10 changes: 5 additions & 5 deletions clash-prelude/src/Clash/Explicit/Moore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ where

import Clash.Explicit.Signal
(KnownDomain, Bundle (..), Clock, Reset, Signal, Enable, register)
import Clash.XException (Undefined)
import Clash.XException (NFDataX)

{- $setup
>>> :set -XDataKinds -XTypeApplications
Expand Down Expand Up @@ -77,7 +77,7 @@ import Clash.XException (Undefined)
-- @
moore
:: ( KnownDomain dom
, Undefined s )
, NFDataX s )
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Reset dom
Expand All @@ -101,7 +101,7 @@ moore clk rst en ft fo iS =
-- a moore machine without any output logic
medvedev
:: ( KnownDomain dom
, Undefined s )
, NFDataX s )
=> Clock dom
-> Reset dom
-> Enable dom
Expand Down Expand Up @@ -140,7 +140,7 @@ medvedev clk rst en tr st = moore clk rst en tr id st
-- @
mooreB
:: ( KnownDomain dom
, Undefined s
, NFDataX s
, Bundle i
, Bundle o )
=> Clock dom
Expand All @@ -163,7 +163,7 @@ mooreB clk rst en ft fo iS i = unbundle (moore clk rst en ft fo iS (bundle i))
-- | A version of 'medvedev' that does automatic 'Bundle'ing
medvedevB
:: ( KnownDomain dom
, Undefined s
, NFDataX s
, Bundle i
, Bundle s )
=> Clock dom
Expand Down
4 changes: 2 additions & 2 deletions clash-prelude/src/Clash/Explicit/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,7 @@ import Clash.XException
window
:: ( KnownNat n
, KnownDomain dom
, Undefined a
, NFDataX a
, Default a
)
=> Clock dom
Expand Down Expand Up @@ -236,7 +236,7 @@ window clk rst en x = res
-- ...
windowD
:: ( KnownNat n
, Undefined a
, NFDataX a
, Default a
, KnownDomain dom )
=> Clock dom
Expand Down
6 changes: 3 additions & 3 deletions clash-prelude/src/Clash/Explicit/Prelude/Safe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,7 @@ import Clash.XException
-- ...
registerB
:: ( KnownDomain dom
, Undefined a
, NFDataX a
, Bundle a )
=> Clock dom
-> Reset dom
Expand All @@ -180,7 +180,7 @@ registerB clk rst en i =
-- | Give a pulse when the 'Signal' goes from 'minBound' to 'maxBound'
isRising
:: ( KnownDomain dom
, Undefined a
, NFDataX a
, Bounded a
, Eq a )
=> Clock dom
Expand All @@ -198,7 +198,7 @@ isRising clk rst en is s = liftA2 edgeDetect prev s
-- | Give a pulse when the 'Signal' goes from 'maxBound' to 'minBound'
isFalling
:: ( KnownDomain dom
, Undefined a
, NFDataX a
, Bounded a
, Eq a )
=> Clock dom
Expand Down
8 changes: 4 additions & 4 deletions clash-prelude/src/Clash/Explicit/ROM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ import Clash.Signal.Internal
(Clock (..), KnownDomain, Signal (..), Enable, fromEnable)
import Clash.Sized.Unsigned (Unsigned)
import Clash.Sized.Vector (Vec, length, toList)
import Clash.XException (deepErrorX, seqX, Undefined)
import Clash.XException (deepErrorX, seqX, NFDataX)

-- | A ROM with a synchronous read port, with space for 2^@n@ elements
--
Expand All @@ -50,7 +50,7 @@ import Clash.XException (deepErrorX, seqX, Undefined)
-- * See "Clash.Sized.Fixed#creatingdatafiles" and "Clash.Explicit.BlockRam#usingrams"
-- for ideas on how to use ROMs and RAMs
romPow2
:: (KnownDomain dom, KnownNat n, Undefined a)
:: (KnownDomain dom, KnownNat n, NFDataX a)
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand All @@ -76,7 +76,7 @@ romPow2 = rom
-- * See "Clash.Sized.Fixed#creatingdatafiles" and "Clash.Explicit.BlockRam#usingrams"
-- for ideas on how to use ROMs and RAMs
rom
:: (KnownDomain dom, KnownNat n, Undefined a, Enum addr)
:: (KnownDomain dom, KnownNat n, NFDataX a, Enum addr)
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand All @@ -95,7 +95,7 @@ rom = \clk en content rd -> rom# clk en content (fromEnum <$> rd)
-- | ROM primitive
rom#
:: forall dom n a
. (KnownDomain dom, KnownNat n, Undefined a)
. (KnownDomain dom, KnownNat n, NFDataX a)
=> Clock dom
-- ^ 'Clock' to synchronize to
-> Enable dom
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/src/Clash/Explicit/ROM/File.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ import Clash.Promoted.Nat (SNat (..), pow2SNat, snatToNum)
import Clash.Sized.BitVector (BitVector)
import Clash.Explicit.Signal (Clock, Enable, Signal, KnownDomain, delay)
import Clash.Sized.Unsigned (Unsigned)
import Clash.XException (Undefined(deepErrorX))
import Clash.XException (NFDataX(deepErrorX))


-- | A ROM with a synchronous read port, with space for 2^@n@ elements
Expand Down
Loading

0 comments on commit d1f325e

Please sign in to comment.