Skip to content

Commit

Permalink
Remove custom implementations of deepErrorX
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Sep 30, 2019
1 parent 6a4f27f commit 1e729e0
Show file tree
Hide file tree
Showing 8 changed files with 6 additions and 31 deletions.
1 change: 0 additions & 1 deletion clash-prelude/src/Clash/Sized/Fixed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -277,7 +277,6 @@ instance ( size ~ (int + frac), KnownNat frac, Integral (rep size)
showsPrecX = showsPrecXWith showsPrec

instance NFDataX (rep (int + frac)) => NFDataX (Fixed rep int frac) where
deepErrorX = Fixed . errorX
rnfX f@(~(Fixed x)) = if isLeft (isX f) then () else rnfX x
hasUndefined f@(~(Fixed x)) = if isLeft (isX f) then True else hasUndefined x
ensureSpine ~(Fixed x) = Fixed x
Expand Down
4 changes: 2 additions & 2 deletions clash-prelude/src/Clash/Sized/Internal/BitVector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -221,9 +221,9 @@ instance ShowX Bit where
showsPrecX = showsPrecXWith showsPrec

instance NFDataX Bit where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined bv = isLeft (isX bv) || unsafeMask# bv /= 0
ensureSpine = id

instance Lift Bit where
lift (Bit m i) = [| fromInteger## m i |]
Expand Down Expand Up @@ -368,9 +368,9 @@ instance KnownNat n => ShowX (BitVector n) where
showsPrecX = showsPrecXWith showsPrec

instance NFDataX (BitVector n) where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined bv = isLeft (isX bv) || unsafeMask bv /= 0
ensureSpine = id

-- | Create a binary literal
--
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/src/Clash/Sized/Internal/Index.hs
Original file line number Diff line number Diff line change
Expand Up @@ -401,8 +401,8 @@ instance ShowX (Index n) where
showsPrecX = showsPrecXWith showsPrec

instance NFDataX (Index n) where
deepErrorX = errorX
rnfX = rwhnfX
ensureSpine = id

-- | None of the 'Read' class' methods are synthesizable.
instance KnownNat n => Read (Index n) where
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/src/Clash/Sized/Internal/Signed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -154,8 +154,8 @@ newtype Signed (n :: Nat) =
deriving (Data, Generic)

instance NFDataX (Signed n) where
deepErrorX = errorX
rnfX = rwhnfX
ensureSpine = id

{-# NOINLINE size# #-}
size# :: KnownNat n => Signed n -> Int
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/src/Clash/Sized/Internal/Unsigned.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,8 +160,8 @@ instance ShowX (Unsigned n) where
showsPrecX = showsPrecXWith showsPrec

instance NFDataX (Unsigned n) where
deepErrorX = errorX
rnfX = rwhnfX
ensureSpine = id

-- | None of the 'Read' class' methods are synthesizable.
instance KnownNat n => Read (Unsigned n) where
Expand Down
2 changes: 0 additions & 2 deletions clash-prelude/src/Clash/Sized/RTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -227,8 +227,6 @@ instance (KnownNat d, CoArbitrary a) => CoArbitrary (RTree d a) where
coarbitrary = coarbitrary . toList

instance (KnownNat d, NFDataX a) => NFDataX (RTree d a) where
deepErrorX x = pure (deepErrorX x)

rnfX t = if isLeft (isX t) then () else go t
where
go :: RTree d a -> ()
Expand Down
2 changes: 0 additions & 2 deletions clash-prelude/src/Clash/Sized/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -350,8 +350,6 @@ instance (Default a, KnownNat n) => Default (Vec n a) where
def = repeat def

instance (NFDataX a, KnownNat n) => NFDataX (Vec n a) where
deepErrorX x = repeat (deepErrorX x)

rnfX v =
-- foldl will fail if the spine of the vector is undefined, so we need to
-- seqX the result of it. We need to use foldl so Clash won't treat it as
Expand Down
22 changes: 1 addition & 21 deletions clash-prelude/src/Clash/XException.hs
Original file line number Diff line number Diff line change
Expand Up @@ -704,13 +704,11 @@ instance (NFDataX a, NFDataX b, NFDataX c, NFDataX d, NFDataX e
=> NFDataX (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o)

instance NFDataX b => NFDataX (a -> b) where
deepErrorX = pure . deepErrorX
rnfX = rwhnfX
hasUndefined = error "hasUndefined on Undefined (a -> b): Not Yet Implemented"
ensureSpine = id

instance NFDataX a => NFDataX (Down a) where
deepErrorX = Down . deepErrorX
rnfX d@(~(Down x)) = if isLeft (isX d) then () else rnfX x
hasUndefined d@(~(Down x))= if isLeft (isX d) then True else hasUndefined x
ensureSpine ~(Down x) = Down (ensureSpine x)
Expand All @@ -721,103 +719,86 @@ instance (NFDataX a, NFDataX b) => NFDataX (Either a b)
instance NFDataX a => NFDataX (Maybe a)

instance NFDataX Char where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Double where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Float where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Int where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Int8 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Int16 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Int32 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Int64 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Integer where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Natural where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Word where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Word8 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Word16 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Word32 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Word64 where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX Half where
deepErrorX = errorX
rnfX = rwhnfX
hasUndefined = isLeft . isX
ensureSpine = id

instance NFDataX a => NFDataX (Seq a) where
deepErrorX = errorX
rnfX s =
if isLeft (isX s) then () else go s
where
Expand All @@ -832,13 +813,12 @@ instance NFDataX a => NFDataX (Seq a) where
go (x :<| xs) = hasUndefined x || hasUndefined xs

instance NFDataX a => NFDataX (Ratio a) where
deepErrorX = errorX
rnfX r = rnfX (numerator r) `seq` rnfX (denominator r)
hasUndefined r = isLeft (isX (numerator r)) || isLeft (isX (denominator r))
ensureSpine = id

instance NFDataX a => NFDataX (Complex a) where
deepErrorX = errorX
ensureSpine = id

instance (NFDataX a, NFDataX b) => NFDataX (SG.Arg a b)
instance NFDataX (SG.All)
Expand Down

0 comments on commit 1e729e0

Please sign in to comment.