Skip to content

Commit

Permalink
Fix papercuts in clash-prelude (#1702)
Browse files Browse the repository at this point in the history
Fixes for recent small papercuts in clash-prelude, hopefully in
time for the 1.4 release. Fixes #1692 and #1700.
  • Loading branch information
Alex McKenna authored Mar 11, 2021
1 parent 741507e commit 083fc18
Show file tree
Hide file tree
Showing 3 changed files with 4 additions and 2 deletions.
2 changes: 2 additions & 0 deletions clash-prelude/src/Clash/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -140,6 +140,7 @@ module Clash.Prelude
, module Control.Applicative
, module Data.Bits
, module Data.Default.Class
, module Data.Kind
-- ** Exceptions
, module Clash.XException
-- ** Named types
Expand All @@ -157,6 +158,7 @@ where
import Control.Applicative
import Data.Bits
import Data.Default.Class
import Data.Kind (Type, Constraint)
import GHC.Stack (HasCallStack)
import GHC.TypeLits
import GHC.TypeLits.Extra
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 @@ -179,7 +179,7 @@ instance (KnownNat n, 1 <= n) => BitPack (Index n) where
unpack = unpack#

-- | Safely convert an `SNat` value to an `Index`
fromSNat :: (KnownNat m, n <= m + 1) => SNat n -> Index m
fromSNat :: (KnownNat m, n + 1 <= m) => SNat n -> Index m
fromSNat = snatToNum

{-# NOINLINE pack# #-}
Expand Down
2 changes: 1 addition & 1 deletion testsuite/src/Test/Tasty/Clash/NetlistTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module Test.Tasty.Clash.NetlistTest
) where

import qualified Prelude as P
import Clash.Prelude
import Clash.Prelude hiding (Type)

import Clash.Annotations.Primitive (HDL(..))
import Clash.Annotations.BitRepresentation.Internal
Expand Down

0 comments on commit 083fc18

Please sign in to comment.