Skip to content

Commit

Permalink
Use CLASH_OPAQUE through libraries
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Jul 3, 2023
1 parent 5af775f commit 4a322a1
Show file tree
Hide file tree
Showing 291 changed files with 1,952 additions and 773 deletions.
25 changes: 17 additions & 8 deletions benchmark/tests/ManyEntitiesEqual.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}

module ManyEntitiesEqual where
Expand Down Expand Up @@ -34,42 +35,50 @@ type Top n =
=> Signal System (Unsigned n)
-> Signal System (Unsigned n)

{-# NOINLINE top0 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top0 #-}
{-# ANN top0 (defSyn "top_0") #-}
top0 :: Top 64
top0 = entity (SNat @64)

{-# NOINLINE top1 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top1 #-}
{-# ANN top1 (defSyn "top_1") #-}
top1 :: Top 64
top1 = entity (SNat @64)

{-# NOINLINE top2 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top2 #-}
{-# ANN top2 (defSyn "top_2") #-}
top2 :: Top 64
top2 = entity (SNat @64)

{-# NOINLINE top3 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top3 #-}
{-# ANN top3 (defSyn "top_3") #-}
top3 :: Top 64
top3 = entity (SNat @64)

{-# NOINLINE top4 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top4 #-}
{-# ANN top4 (defSyn "top_4") #-}
top4 :: Top 64
top4 = entity (SNat @64)

{-# NOINLINE top5 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top5 #-}
{-# ANN top5 (defSyn "top_5") #-}
top5 :: Top 64
top5 = entity (SNat @64)

{-# NOINLINE top6 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top6 #-}
{-# ANN top6 (defSyn "top_6") #-}
top6 :: Top 64
top6 = entity (SNat @64)

{-# NOINLINE top7 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top7 #-}
{-# ANN top7 (defSyn "top_7") #-}
top7 :: Top 64
top7 = entity (SNat @64)
16 changes: 11 additions & 5 deletions benchmark/tests/ManyEntitiesVaried.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}

module ManyEntitiesVaried where
Expand Down Expand Up @@ -34,27 +35,32 @@ type Top n =
=> Signal System (Unsigned n)
-> Signal System (Unsigned n)

{-# NOINLINE top0 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top0 #-}
{-# ANN top0 (defSyn "top_0") #-}
top0 :: Top 24
top0 = entity (SNat @24)

{-# NOINLINE top1 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top1 #-}
{-# ANN top1 (defSyn "top_1") #-}
top1 :: Top 32
top1 = entity (SNat @32)

{-# NOINLINE top2 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top2 #-}
{-# ANN top2 (defSyn "top_2") #-}
top2 :: Top 48
top2 = entity (SNat @48)

{-# NOINLINE top3 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top3 #-}
{-# ANN top3 (defSyn "top_3") #-}
top3 :: Top 64
top3 = entity (SNat @64)

{-# NOINLINE top4 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE top4 #-}
{-# ANN top4 (defSyn "top_4") #-}
top4 :: Top 96
top4 = entity (SNat @96)
Expand Down
6 changes: 4 additions & 2 deletions clash-cores/src/Clash/Cores/LatticeSemi/ECP5/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,9 @@
LATTICE ECP5 IO primitives. Implementations are documented in the
<http://www.latticesemi.com/-/media/LatticeSemi/Documents/ApplicationNotes/EH/FPGA-TN-02032-1-2-ECP5-ECP5G-sysIO-Usage-Guide.ashx?document_id=50464>.
-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}

{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE GADTs #-}
Expand Down Expand Up @@ -74,7 +75,8 @@ bbECP5 _intrinsicName pkgPinIn output notOutputEnable
toMaybe :: Bool -> a -> Maybe a
toMaybe True a = Just a
toMaybe False _ = Nothing
{-# NOINLINE bbECP5 #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE bbECP5 #-}
{-# ANN bbECP5 hasBlackBox #-}
{-# ANN bbECP5 (InlineYamlPrimitive [VHDL,Verilog,SystemVerilog] [__i|
BlackBox:
Expand Down
6 changes: 4 additions & 2 deletions clash-cores/src/Clash/Cores/LatticeSemi/ICE40/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,12 @@
<http://www.latticesemi.com/~/media/LatticeSemi/Documents/TechnicalBriefs/SBTICETechnologyLibrary201504.pdf LATTICE ICE Technology Library>,
referred to as LITL.
-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}

module Clash.Cores.LatticeSemi.ICE40.IO
( sbio
Expand Down Expand Up @@ -230,7 +231,8 @@ sbio pinConf pkgPinIn latchInput dOut_0 _dOut_1 outputEnable0 =
writeToBiSignal
pkgPinIn
(toMaybe <$> outputEnable1 <*> pkgPinWriteInput)
{-# NOINLINE sbio #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE sbio #-}
{-# ANN sbio hasBlackBox #-}
{-# ANN sbio (InlineYamlPrimitive [VHDL,Verilog,SystemVerilog] [__i|
BlackBox:
Expand Down
5 changes: 4 additions & 1 deletion clash-cores/src/Clash/Cores/Xilinx/BlockRam.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@
Xilinx block RAM primitives
-}

{-# LANGUAGE CPP #-}

-- See [Note: eta port names for tdpbram]
{-# OPTIONS_GHC -fno-do-lambda-eta-expansion #-}

Expand Down Expand Up @@ -76,4 +78,5 @@ tdpbram clkA enA addrA byteEnaA datA clkB enB addrB byteEnaB datB =
clashCompileError "tdpbram: domain A needs a rising active edge"
(_, SFalling) ->
clashCompileError "tdpbram: domain B needs a rising active edge"
{-# NOINLINE tdpbram #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE tdpbram #-}
4 changes: 3 additions & 1 deletion clash-cores/src/Clash/Cores/Xilinx/BlockRam/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
Expand Down Expand Up @@ -157,7 +158,8 @@ updateRam addr (IsDefined byteEna) dat mem
isDefinedMaxBound _ = False

{-# ANN tdpbram# hasBlackBox #-}
{-# NOINLINE tdpbram# #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE tdpbram# #-}
{-# ANN tdpbram# (
let
primName = 'tdpbram#
Expand Down
4 changes: 3 additions & 1 deletion clash-cores/src/Clash/Cores/Xilinx/DcFifo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ acknowledge, valid, or programmable full\/empty flags)
Vivado 2022.1.)
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
Expand Down Expand Up @@ -253,7 +254,8 @@ dcFifo DcConfig{..} wClk wRst rClk rRst writeData rEnable =
Seq.EmptyR -> (q, deepErrorX "FIFO empty", True :- preUnder)
qData Seq.:> qDatum -> (qData, qDatum, False :- preUnder)
else (q, deepErrorX "Enable off", False :- preUnder)
{-# NOINLINE dcFifo #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE dcFifo #-}
{-# ANN dcFifo (
let primName = 'dcFifo
tfName = 'dcFifoBBF
Expand Down
22 changes: 15 additions & 7 deletions clash-cores/src/Clash/Cores/Xilinx/Floating/Explicit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@ type variable for delay annotation in circuits.
-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_HADDOCK hide #-}
Expand Down Expand Up @@ -107,7 +108,8 @@ addWith !_ clk en (conditionFloatF -> x) (conditionFloatF -> y) =
delayI und en clk . conditionFloatF $ x + y
where
und = withFrozenCallStack $ deepErrorX "Initial values of add undefined"
{-# NOINLINE addWith #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE addWith #-}
{-# ANN addWith (vhdlBinaryPrim 'addWith 'addTclTF "add") #-}
{-# ANN addWith (veriBinaryPrim 'addWith 'addTclTF "add") #-}

Expand Down Expand Up @@ -145,7 +147,8 @@ subWith !_ clk en (conditionFloatF -> x) (conditionFloatF -> y) =
delayI und en clk . conditionFloatF $ x - y
where
und = withFrozenCallStack $ deepErrorX "Initial values of sub undefined"
{-# NOINLINE subWith #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE subWith #-}
{-# ANN subWith (vhdlBinaryPrim 'subWith 'subTclTF "sub") #-}
{-# ANN subWith (veriBinaryPrim 'subWith 'subTclTF "sub") #-}

Expand Down Expand Up @@ -184,7 +187,8 @@ mulWith !_ clk en (conditionFloatF -> x) (conditionFloatF -> y) =
delayI und en clk . conditionFloatF $ x * y
where
und = withFrozenCallStack $ deepErrorX "Initial values of mul undefined"
{-# NOINLINE mulWith #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE mulWith #-}
{-# ANN mulWith (vhdlBinaryPrim 'mulWith 'mulTclTF "mul") #-}
{-# ANN mulWith (veriBinaryPrim 'mulWith 'mulTclTF "mul") #-}

Expand Down Expand Up @@ -223,7 +227,8 @@ divWith !_ clk en (conditionFloatF -> x) (conditionFloatF -> y) =
delayI und en clk . conditionFloatF $ x / y
where
und = withFrozenCallStack $ deepErrorX "Initial values of div undefined"
{-# NOINLINE divWith #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE divWith #-}
{-# ANN divWith (vhdlBinaryPrim 'divWith 'divTclTF "div") #-}
{-# ANN divWith (veriBinaryPrim 'divWith 'divTclTF "div") #-}

Expand Down Expand Up @@ -261,7 +266,8 @@ fromU32With
fromU32With clk en = delayI und en clk . fmap fromIntegral
where
und = withFrozenCallStack $ errorX "Initial values of fromU32 undefined"
{-# NOINLINE fromU32With #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE fromU32With #-}
{-# ANN fromU32With (vhdlFromUPrim 'fromU32With "fromU32") #-}
{-# ANN fromU32With (veriFromUPrim 'fromU32With "fromU32") #-}

Expand Down Expand Up @@ -298,7 +304,8 @@ fromS32With
fromS32With clk en = delayI und en clk . fmap fromIntegral
where
und = withFrozenCallStack $ errorX "Initial values of fromS32 undefined"
{-# NOINLINE fromS32With #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE fromS32With #-}
{-# ANN fromS32With (vhdlFromSPrim 'fromS32With "fromS32") #-}
{-# ANN fromS32With (veriFromSPrim 'fromS32With "fromS32") #-}

Expand Down Expand Up @@ -339,7 +346,8 @@ compareWith
compareWith clk ena a b = delayI und ena clk (xilinxCompare <$> a <*> b)
where
und = withFrozenCallStack $ errorX "Initial values of compare undefined"
{-# NOINLINE compareWith #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE compareWith #-}
{-# ANN compareWith (vhdlComparePrim 'compareWith 'compareTclTF "compare") #-}
{-# ANN compareWith (veriComparePrim 'compareWith 'compareTclTF "compare") #-}

Expand Down
8 changes: 5 additions & 3 deletions clash-cores/src/Clash/Cores/Xilinx/VIO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,11 +28,12 @@ JTAG clock speed:
-}

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE UndecidableInstances #-}

module Clash.Cores.Xilinx.VIO
Expand Down Expand Up @@ -104,7 +105,8 @@ vioProbe ::
Clock dom ->
a
vioProbe !_inputNames !_outputNames !_initialOutputProbeValues !_clk = vioX @dom @a @o
{-# NOINLINE vioProbe #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE vioProbe #-}
{-# ANN vioProbe (
let primName = 'vioProbe
tfName = 'vioProbeBBF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <[email protected]>
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}
Expand Down Expand Up @@ -127,7 +128,8 @@ xpmCdcArraySingleTF# bbCtx

xpmCdcArraySingleTF# bbCtx = error (ppShow bbCtx)

{-# NOINLINE xpmCdcArraySingle# #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE xpmCdcArraySingle# #-}
{-# ANN xpmCdcArraySingle# hasBlackBox #-}
{-# ANN xpmCdcArraySingle#
let
Expand Down
4 changes: 3 additions & 1 deletion clash-cores/src/Clash/Cores/Xilinx/Xpm/Cdc/Gray/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <[email protected]>
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
Expand Down Expand Up @@ -126,7 +127,8 @@ xpmCdcGrayTF# bbCtx

xpmCdcGrayTF# bbCtx = error (ppShow bbCtx)

{-# NOINLINE xpmCdcGray# #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE xpmCdcGray# #-}
{-# ANN xpmCdcGray# hasBlackBox #-}
{-# ANN xpmCdcGray#
let
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <[email protected]>
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}
Expand Down Expand Up @@ -120,7 +121,8 @@ xpmCdcSingleTF# bbCtx

xpmCdcSingleTF# bbCtx = error (ppShow bbCtx)

{-# NOINLINE xpmCdcSingle# #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE xpmCdcSingle# #-}
{-# ANN xpmCdcSingle# hasBlackBox #-}
{-# ANN xpmCdcSingle#
let
Expand Down
5 changes: 5 additions & 0 deletions clash-cosim/src/Clash/CoSim/CodeGeneration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,8 +79,13 @@ coSimGen' clks args = do
-- Function declaration and body
let coSim = FunD coSimName [Clause [] (NormalB $ VarE $ mkName "coSimN") []]

#if __GLASGOW_HASKELL__ >= 904
-- OPAQUE pragma
let inline = PragmaD $ OpaqueP coSimName
#else
-- NOINLINE pragma
let inline = PragmaD $ InlineP coSimName NoInline FunLike AllPhases
#endif

-- Clash blackbox pragma
primDir <- runIO $ getDataFileName "src/prims/verilog"
Expand Down
2 changes: 1 addition & 1 deletion clash-ghc/src-ghc/Clash/GHC/GenerateBindings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ setNoInlineTopEntities bm tes =
go b@Binding{bindingId}
| bindingId `elemVarSet` ids
#if MIN_VERSION_ghc(9,4,0)
= b { bindingSpec = GHC.NoInline GHC.NoSourceText }
= b { bindingSpec = GHC.Opaque GHC.NoSourceText }
#else
= b { bindingSpec = GHC.NoInline }
#endif
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -924,7 +924,8 @@ buildPack dataRepr@(DataReprAnn _name _size constrs) = do
-- This is used in the generated pack/unpack to not do anything in HDL.
dontApplyInHDL :: (a -> b) -> a -> b
dontApplyInHDL f a = f a
{-# NOINLINE dontApplyInHDL #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE dontApplyInHDL #-}
{-# ANN dontApplyInHDL hasBlackBox #-}

buildUnpackField
Expand Down
Loading

0 comments on commit 4a322a1

Please sign in to comment.