Skip to content

Commit

Permalink
Don't loop on hidden recursive data type
Browse files Browse the repository at this point in the history
The recursive occurance was hiding behind a type family. So we
should always expand type families when checking whether a
data type is recursive.

Fixes #1921
  • Loading branch information
christiaanb committed Sep 13, 2021
1 parent 8894dd6 commit a152f39
Show file tree
Hide file tree
Showing 4 changed files with 85 additions and 4 deletions.
1 change: 1 addition & 0 deletions changelog/2021-09-13T16_31_59+02_00_fix_1921
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
FIXED: Dont' loop on recursive data types hiding behind type families [#1921](https://github.com/clash-lang/clash-compiler/issues/1921)
27 changes: 23 additions & 4 deletions clash-lib/src/Clash/Netlist/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,8 +90,8 @@ import Clash.Core.Term
import Clash.Core.TermInfo
import Clash.Core.TyCon
(TyCon (FunTyCon), TyConName, TyConMap, tyConDataCons)
import Clash.Core.Type (Type (..), TypeView (..),
coreView1, splitTyConAppM, tyView, TyVar)
import Clash.Core.Type
(Type (..), TyVar, TypeView (..), coreView1, normalizeType, splitTyConAppM, tyView)
import Clash.Core.Util
(substArgTys, tyLitShow)
import Clash.Core.Var
Expand Down Expand Up @@ -603,11 +603,30 @@ hasUnconstrainedExistential tcm dc =


-- | Simple check if a TyCon is recursively defined.
--
-- Note [Look through type families in recursivity check]
--
-- Consider:
--
-- @
-- data SList :: [Type] -> Type where
-- SNil :: SList []
-- CSons :: a -> Sing (as :: [k]) -> SList (a:as)
--
-- type family Sing [a] = SList [a]
-- @
--
-- Without looking through type families, we would think that /SList/ is not
-- recursive. This lead to issue #1921
isRecursiveTy :: TyConMap -> TyConName -> Bool
isRecursiveTy m tc = case tyConDataCons (m `lookupUniqMap'` tc) of
[] -> False
dcs -> let argTyss = map dcArgTys dcs
argTycons = (map fst . catMaybes) $ (concatMap . map) splitTyConAppM argTyss
dcs -> let argTyss = map dcArgTys dcs
argTycons = (map fst . catMaybes)
$ (concatMap . map)
-- Note [Look through type families in recursivity check]
(splitTyConAppM . normalizeType m)
argTyss
in tc `elem` argTycons

-- | Determines if a Core type is translatable to a HWType given a function that
Expand Down
1 change: 1 addition & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -532,6 +532,7 @@ runClashTest = defaultMain $ clashTestRoot
, outputTest "T431" def{hdlTargets=[VHDL]}
, clashLibTest "T779" def{hdlTargets=[Verilog]}
, outputTest "T1881" def{hdlSim=False}
, runTest "T1921" def{hdlTargets=[Verilog], hdlSim=False}
] <>
if compiledWith == Cabal then
-- This tests fails without environment files present, which are only
Expand Down
60 changes: 60 additions & 0 deletions tests/shouldwork/Issues/T1921.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
{-# LANGUAGE DerivingVia
, DerivingStrategies
, LambdaCase
, AllowAmbiguousTypes
, ApplicativeDo
, StandaloneDeriving
, StandaloneKindSignatures #-}

module T1921 where

import Clash.Prelude
import Control.Lens
import Data.Default
import Data.Singletons.Prelude
import Data.Singletons.TypeLits as TL

topEntity :: Clock System -> Reset System -> Enable System -> Signal System (Unsigned 8)
topEntity = exposeClockResetEnable fibonacciLFSR8

-- Straightforward newtype
type LFSRState :: Nat -> Type
newtype LFSRState n = LFSRState { runLFSRState :: BitVector n }
deriving (NFDataX, AutoReg) via (BitVector n)
instance KnownNat n => Default (LFSRState n) where
def = LFSRState (fromIntegral 1)

fibonacciLFSR8 :: HiddenClockResetEnable dom => Signal dom (Unsigned 8)
fibonacciLFSR8 = fibonacciLFSRType @('[3,4,5,7]) @8

fibonacciLFSRType
:: forall (taps :: [Nat]) (n :: Nat) dom
. SingI taps
=> KnownNat n
=> HiddenClockResetEnable dom
=> Signal dom (Unsigned n)
fibonacciLFSRType =
let lfsr = autoReg def (LFSRState <$> lfsr')
lfsr' = do lfsrState <- lfsr
-- shift the bit register by one, and then replace
-- the bit on the end by xor of the taps (via go)
return $
shiftL (runLFSRState lfsrState) 1
& ix 0
.~ go lfsrState (sing :: Sing taps)
in unpack <$> lfsr'

where
go :: forall (n :: Nat) (indices :: [Nat])
. SingI indices
=> KnownNat n
=> LFSRState n -> SList indices -> Bit
go b@(LFSRState bs) = \case
-- If there is only one tap left, return that bit
(SCons a SNil) -> withKnownNat a
$ bs ^?! ix (fromIntegral $ TL.natVal a)
-- XOR a tapped bit with the remaining taps
(SCons a as) -> withSingI as $ withKnownNat a
$ xor (bs ^?! ix (fromIntegral $ TL.natVal a)) (go b as)
-- This should never happen (we can't have no taps)
SNil -> error "A no-tap LFSR is ill-defined"

0 comments on commit a152f39

Please sign in to comment.