{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Clash.Primitives.Sized.Vector where
import           Control.Monad.State                (State, zipWithM)
import qualified Control.Lens                       as Lens
import           Data.Either                        (rights)
import qualified Data.IntMap                        as IntMap
import           Data.List.Extra                    (iterateNM)
import           Data.Maybe                         (fromMaybe)
import           Data.Semigroup.Monad               (getMon)
import qualified Data.Text                          as Text
import qualified Data.Text.Lazy                     as LText
import           Data.Text.Lazy                     (pack)
import           Data.Text.Prettyprint.Doc.Extra
  (Doc, string, renderLazy, layoutPretty, LayoutOptions(..),
   PageWidth(AvailablePerLine))
import           Text.Trifecta.Result               (Result(Success))
import qualified Data.String.Interpolate            as I
import qualified Data.String.Interpolate.Util       as I
import           Clash.Backend
  (Backend, hdlTypeErrValue, expr, mkUniqueIdentifier, blockDecl)
import           Clash.Core.Type
  (Type(LitTy), LitTy(NumTy), coreView)
import           Clash.Netlist.BlackBox             (isLiteral)
import           Clash.Netlist.BlackBox.Util        (renderElem)
import           Clash.Netlist.BlackBox.Parser      (runParse)
import           Clash.Netlist.BlackBox.Types
  (BlackBoxFunction, BlackBoxMeta(..), TemplateKind(TExpr, TDecl),
   Element(Component, Typ, TypElem, Text), Decl(Decl), emptyBlackBoxMeta)
import           Clash.Netlist.Types
  (Identifier, TemplateFunction, BlackBoxContext, HWType(Vector),
   Declaration(..), Expr(BlackBoxE, Literal, Identifier), Literal(NumLit),
   BlackBox(BBTemplate, BBFunction), TemplateFunction(..), WireOrReg(Wire),
   Modifier(Indexed, Nested), bbInputs, bbResult, emptyBBContext, tcCache,
   bbFunctions)
import           Clash.Netlist.Id                   (IdType(Basic))
import           Clash.Netlist.Util                 (typeSize)
import qualified Clash.Primitives.DSL               as Prim
import           Clash.Primitives.DSL
  (declarationReturn, instHO, tInputs, tExprToInteger)
import           Clash.Util                         (HasCallStack, curLoc)
iterateBBF :: HasCallStack => BlackBoxFunction
iterateBBF :: BlackBoxFunction
iterateBBF Bool
_isD Text
_primName [Either Term Type]
args Type
_resTy = do
  TyConMap
tcm <- Getting TyConMap NetlistState TyConMap -> NetlistMonad TyConMap
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
Lens.use Getting TyConMap NetlistState TyConMap
Lens' NetlistState TyConMap
tcCache
  Either String (BlackBoxMeta, BlackBox)
-> NetlistMonad (Either String (BlackBoxMeta, BlackBox))
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ((BlackBoxMeta, BlackBox) -> Either String (BlackBoxMeta, BlackBox)
forall a b. b -> Either a b
Right (TyConMap -> BlackBoxMeta
meta TyConMap
tcm, BlackBox
bb))
 where
  bb :: BlackBox
bb = String -> BBHash -> TemplateFunction -> BlackBox
BBFunction String
"Clash.Primitives.Sized.Vector.iterateBBF" BBHash
0 TemplateFunction
iterateTF
  vecLength :: TyConMap -> p
vecLength TyConMap
tcm =
    case TyConMap -> Type -> Type
coreView TyConMap
tcm ([Type] -> Type
forall a. [a] -> a
head ([Either Term Type] -> [Type]
forall a b. [Either a b] -> [b]
rights [Either Term Type]
args)) of
      (LitTy (NumTy Integer
0)) -> String -> p
forall a. HasCallStack => String -> a
error String
"Unexpected empty vector in 'iterateBBF'"
      (LitTy (NumTy Integer
n)) -> Integer -> p
forall a. Num a => Integer -> a
fromInteger (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1)
      Type
vl -> String -> p
forall a. HasCallStack => String -> a
error (String -> p) -> String -> p
forall a b. (a -> b) -> a -> b
$ String
"Unexpected vector length: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Type -> String
forall a. Show a => a -> String
show Type
vl
  meta :: TyConMap -> BlackBoxMeta
meta TyConMap
tcm = BlackBoxMeta
emptyBlackBoxMeta {
      bbKind :: TemplateKind
bbKind=TemplateKind
TDecl
    , bbFunctionPlurality :: [(BBHash, BBHash)]
bbFunctionPlurality=[(BBHash
1, TyConMap -> BBHash
forall p. Num p => TyConMap -> p
vecLength TyConMap
tcm)]
    }
iterateTF :: TemplateFunction
iterateTF :: TemplateFunction
iterateTF = [BBHash]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [] (Bool -> BlackBoxContext -> Bool
forall a b. a -> b -> a
const Bool
True) forall s.
(HasCallStack, Backend s) =>
BlackBoxContext -> State s Doc
forall s. Backend s => BlackBoxContext -> State s Doc
iterateTF'
iterateTF'
  :: forall s
   . (HasCallStack, Backend s)
  => BlackBoxContext
  -> State s Doc
iterateTF' :: BlackBoxContext -> State s Doc
iterateTF' BlackBoxContext
bbCtx
  | [ (Integer -> Maybe Integer -> Integer
forall a. a -> Maybe a -> a
fromMaybe (String -> Integer
forall a. HasCallStack => String -> a
error String
"n") (Maybe Integer -> Integer)
-> (TExpr -> Maybe Integer) -> TExpr -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpr -> Maybe Integer
tExprToInteger -> Integer
n, HWType
_)
    , (TExpr, HWType)
_hoFunction
    , (TExpr
a, HWType
aType)
    ] <- BlackBoxContext -> [(TExpr, HWType)]
tInputs BlackBoxContext
bbCtx
  , let aTemplateType :: [Element]
aTemplateType = [Element -> Element
TypElem (Maybe BBHash -> Element
Typ (BBHash -> Maybe BBHash
forall a. a -> Maybe a
Just BBHash
2))]
  , let inst :: TExpr -> State (BlockState backend) TExpr
inst TExpr
arg = BlackBoxContext
-> BBHash
-> (HWType, [Element])
-> [(TExpr, [Element])]
-> State (BlockState backend) TExpr
forall backend.
Backend backend =>
BlackBoxContext
-> BBHash
-> (HWType, [Element])
-> [(TExpr, [Element])]
-> State (BlockState backend) TExpr
instHO BlackBoxContext
bbCtx BBHash
1 (HWType
aType, [Element]
aTemplateType) [(TExpr
arg, [Element]
aTemplateType)]
  = BlackBoxContext
-> Text -> State (BlockState s) TExpr -> State s Doc
forall backend.
Backend backend =>
BlackBoxContext
-> Text -> State (BlockState backend) TExpr -> State backend Doc
declarationReturn BlackBoxContext
bbCtx Text
"iterateI" ([TExpr] -> State (BlockState s) TExpr
forall backend.
(HasCallStack, Backend backend) =>
[TExpr] -> State (BlockState backend) TExpr
Prim.vec ([TExpr] -> State (BlockState s) TExpr)
-> StateT (BlockState s) Identity [TExpr]
-> State (BlockState s) TExpr
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Word
-> (TExpr -> State (BlockState s) TExpr)
-> TExpr
-> StateT (BlockState s) Identity [TExpr]
forall (m :: Type -> Type) a.
Monad m =>
Word -> (a -> m a) -> a -> m [a]
iterateNM (Integer -> Word
forall a. Num a => Integer -> a
fromInteger Integer
n) TExpr -> State (BlockState s) TExpr
forall backend.
Backend backend =>
TExpr -> State (BlockState backend) TExpr
inst TExpr
a)
  | Bool
otherwise
  =  String -> State s Doc
forall a. HasCallStack => String -> a
error (String -> State s Doc) -> String -> State s Doc
forall a b. (a -> b) -> a -> b
$ String
"Unexpected number of arguments: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ BBHash -> String
forall a. Show a => a -> String
show ([(Expr, HWType, Bool)] -> BBHash
forall (t :: Type -> Type) a. Foldable t => t a -> BBHash
length (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx))
data FCall =
  FCall
    Identifier 
    Identifier 
    Identifier 
foldFunctionPlurality :: HasCallStack => Int -> Int
foldFunctionPlurality :: BBHash -> BBHash
foldFunctionPlurality BBHash
1 = BBHash
0
foldFunctionPlurality BBHash
2 = BBHash
1
foldFunctionPlurality BBHash
n
  | BBHash
n BBHash -> BBHash -> Bool
forall a. Ord a => a -> a -> Bool
<= BBHash
0 = String -> BBHash
forall a. HasCallStack => String -> a
error (String -> BBHash) -> String -> BBHash
forall a b. (a -> b) -> a -> b
$ String
"functionPlurality: unexpected n: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ BBHash -> String
forall a. Show a => a -> String
show BBHash
n
  | Bool
otherwise =
      let (BBHash
d, BBHash
r) = BBHash
n BBHash -> BBHash -> (BBHash, BBHash)
forall a. Integral a => a -> a -> (a, a)
`divMod` BBHash
2 in
      BBHash
1 BBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
+ HasCallStack => BBHash -> BBHash
BBHash -> BBHash
foldFunctionPlurality BBHash
d BBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
+ HasCallStack => BBHash -> BBHash
BBHash -> BBHash
foldFunctionPlurality (BBHash
dBBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
+BBHash
r)
foldBBF :: HasCallStack => BlackBoxFunction
foldBBF :: BlackBoxFunction
foldBBF Bool
_isD Text
_primName [Either Term Type]
args Type
_resTy = do
  TyConMap
tcm <- Getting TyConMap NetlistState TyConMap -> NetlistMonad TyConMap
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
Lens.use Getting TyConMap NetlistState TyConMap
Lens' NetlistState TyConMap
tcCache
  Either String (BlackBoxMeta, BlackBox)
-> NetlistMonad (Either String (BlackBoxMeta, BlackBox))
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ((BlackBoxMeta, BlackBox) -> Either String (BlackBoxMeta, BlackBox)
forall a b. b -> Either a b
Right (TyConMap -> BlackBoxMeta
meta TyConMap
tcm, BlackBox
bb))
 where
  bb :: BlackBox
bb = String -> BBHash -> TemplateFunction -> BlackBox
BBFunction String
"Clash.Primitives.Sized.Vector.foldTF" BBHash
0 TemplateFunction
foldTF
  [Type
_, Type
vecLengthMinusOne] = [Either Term Type] -> [Type]
forall a b. [Either a b] -> [b]
rights [Either Term Type]
args
  vecLength :: TyConMap -> Integer
vecLength TyConMap
tcm =
    case TyConMap -> Type -> Type
coreView TyConMap
tcm Type
vecLengthMinusOne of
      (LitTy (NumTy Integer
n)) -> Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
      Type
vl -> String -> Integer
forall a. HasCallStack => String -> a
error (String -> Integer) -> String -> Integer
forall a b. (a -> b) -> a -> b
$ String
"Unexpected vector length: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Type -> String
forall a. Show a => a -> String
show Type
vl
  funcPlural :: TyConMap -> BBHash
funcPlural TyConMap
tcm = HasCallStack => BBHash -> BBHash
BBHash -> BBHash
foldFunctionPlurality (Integer -> BBHash
forall a. Num a => Integer -> a
fromInteger (TyConMap -> Integer
vecLength TyConMap
tcm))
  meta :: TyConMap -> BlackBoxMeta
meta TyConMap
tcm = BlackBoxMeta
emptyBlackBoxMeta {bbKind :: TemplateKind
bbKind=TemplateKind
TDecl, bbFunctionPlurality :: [(BBHash, BBHash)]
bbFunctionPlurality=[(BBHash
0, TyConMap -> BBHash
funcPlural TyConMap
tcm)]}
foldTF :: TemplateFunction
foldTF :: TemplateFunction
foldTF = [BBHash]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [] (Bool -> BlackBoxContext -> Bool
forall a b. a -> b -> a
const Bool
True) forall s.
(HasCallStack, Backend s) =>
BlackBoxContext -> State s Doc
forall s. Backend s => BlackBoxContext -> State s Doc
foldTF'
foldTF' :: forall s . (HasCallStack, Backend s) => BlackBoxContext -> State s Doc
foldTF' :: BlackBoxContext -> State s Doc
foldTF' bbCtx :: BlackBoxContext
bbCtx@(BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs -> [(Expr, HWType, Bool)
_f, (Expr
vec, vecType :: HWType
vecType@(Vector BBHash
n HWType
aTy), Bool
_isLiteral)]) = do
  
  [Text]
vecIds <- (BBHash -> StateT s Identity Text)
-> [BBHash] -> StateT s Identity [Text]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\BBHash
i -> String -> StateT s Identity Text
mkId (String
"acc_0_" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> BBHash -> String
forall a. Show a => a -> String
show BBHash
i)) [BBHash
0..BBHash
nBBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
-BBHash
1]
  Text
vecId <- String -> StateT s Identity Text
mkId String
"vec"
  let vecDecl :: Declaration
vecDecl = HWType -> WireOrReg -> Text -> Declaration
sigDecl HWType
vecType WireOrReg
Wire Text
vecId
      vecAssign :: Declaration
vecAssign = Text -> Expr -> Declaration
Assignment Text
vecId Expr
vec
      elemAssigns :: [Declaration]
elemAssigns = (Text -> Expr -> Declaration) -> [Text] -> [Expr] -> [Declaration]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Text -> Expr -> Declaration
Assignment [Text]
vecIds ((BBHash -> Expr) -> [BBHash] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> BBHash -> Expr
iIndex Text
vecId) [BBHash
0..])
      resultId :: Text
resultId =
        case BlackBoxContext -> (Expr, HWType)
bbResult BlackBoxContext
bbCtx of
          (Identifier Text
t Maybe Modifier
_, HWType
_) -> Text
t
          (Expr, HWType)
_ -> String -> Text
forall a. HasCallStack => String -> a
error String
"Unexpected result identifier"
  
  
  ([[FCall]] -> [FCall]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat -> [FCall]
fCalls, Text
result) <- BBHash -> [Text] -> State s ([[FCall]], Text)
mkTree BBHash
1 [Text]
vecIds
  let intermediateResultIds :: [Text]
intermediateResultIds = (FCall -> [Text]) -> [FCall] -> [Text]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap (\(FCall Text
l Text
r Text
_) -> [Text
l, Text
r]) [FCall]
fCalls
      wr :: WireOrReg
wr = case BBHash
-> IntMap
     [(Either BlackBox (Text, [Declaration]), WireOrReg, [[Element]],
       [[Element]], [((Text, Text), BlackBox)], BlackBoxContext)]
-> Maybe
     [(Either BlackBox (Text, [Declaration]), WireOrReg, [[Element]],
       [[Element]], [((Text, Text), BlackBox)], BlackBoxContext)]
forall a. BBHash -> IntMap a -> Maybe a
IntMap.lookup BBHash
0 (BlackBoxContext
-> IntMap
     [(Either BlackBox (Text, [Declaration]), WireOrReg, [[Element]],
       [[Element]], [((Text, Text), BlackBox)], BlackBoxContext)]
bbFunctions BlackBoxContext
bbCtx) of
             Just ((Either BlackBox (Text, [Declaration])
_,WireOrReg
rw,[[Element]]
_,[[Element]]
_,[((Text, Text), BlackBox)]
_,BlackBoxContext
_):[(Either BlackBox (Text, [Declaration]), WireOrReg, [[Element]],
  [[Element]], [((Text, Text), BlackBox)], BlackBoxContext)]
_) -> WireOrReg
rw
             Maybe
  [(Either BlackBox (Text, [Declaration]), WireOrReg, [[Element]],
    [[Element]], [((Text, Text), BlackBox)], BlackBoxContext)]
_ -> String -> WireOrReg
forall a. HasCallStack => String -> a
error String
"internal error"
      sigDecls :: [Declaration]
sigDecls = (WireOrReg -> Text -> Declaration)
-> [WireOrReg] -> [Text] -> [Declaration]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (HWType -> WireOrReg -> Text -> Declaration
sigDecl HWType
aTy) (WireOrReg
wrWireOrReg -> [WireOrReg] -> [WireOrReg]
forall a. a -> [a] -> [a]
:BBHash -> WireOrReg -> [WireOrReg]
forall a. BBHash -> a -> [a]
replicate BBHash
n WireOrReg
Wire [WireOrReg] -> [WireOrReg] -> [WireOrReg]
forall a. [a] -> [a] -> [a]
++ WireOrReg -> [WireOrReg]
forall a. a -> [a]
repeat WireOrReg
wr)
                                       (Text
result Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
intermediateResultIds)
      resultAssign :: Declaration
resultAssign = Text -> Expr -> Declaration
Assignment Text
resultId (Text -> Maybe Modifier -> Expr
Identifier Text
result Maybe Modifier
forall a. Maybe a
Nothing)
  [Declaration]
callDecls <- (BBHash -> FCall -> StateT s Identity Declaration)
-> [BBHash] -> [FCall] -> StateT s Identity [Declaration]
forall (m :: Type -> Type) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM BBHash -> FCall -> StateT s Identity Declaration
callDecl [BBHash
0..] [FCall]
fCalls
  Text
foldNm <- String -> StateT s Identity Text
mkId String
"fold"
  Mon (State s) Doc -> State s Doc
forall (f :: Type -> Type) m. Mon f m -> f m
getMon (Mon (State s) Doc -> State s Doc)
-> Mon (State s) Doc -> State s Doc
forall a b. (a -> b) -> a -> b
$ Text -> [Declaration] -> Mon (State s) Doc
forall state.
Backend state =>
Text -> [Declaration] -> Mon (State state) Doc
blockDecl Text
foldNm ([Declaration] -> Mon (State s) Doc)
-> [Declaration] -> Mon (State s) Doc
forall a b. (a -> b) -> a -> b
$
    Declaration
resultAssign Declaration -> [Declaration] -> [Declaration]
forall a. a -> [a] -> [a]
:
    Declaration
vecAssign Declaration -> [Declaration] -> [Declaration]
forall a. a -> [a] -> [a]
:
    Declaration
vecDecl Declaration -> [Declaration] -> [Declaration]
forall a. a -> [a] -> [a]
:
    [Declaration]
elemAssigns [Declaration] -> [Declaration] -> [Declaration]
forall a. [a] -> [a] -> [a]
++
    [Declaration]
sigDecls [Declaration] -> [Declaration] -> [Declaration]
forall a. [a] -> [a] -> [a]
++
    [Declaration]
callDecls
 where
  mkId :: String -> State s Identifier
  mkId :: String -> StateT s Identity Text
mkId = IdType -> Text -> StateT s Identity Text
forall s. Backend s => IdType -> Text -> State s Text
mkUniqueIdentifier IdType
Basic (Text -> StateT s Identity Text)
-> (String -> Text) -> String -> StateT s Identity Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
  callDecl :: Int -> FCall -> State s Declaration
  callDecl :: BBHash -> FCall -> StateT s Identity Declaration
callDecl BBHash
fSubPos (FCall Text
a Text
b Text
r) = do
    Doc
rendered0 <- Text -> State s Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
string (Text -> State s Doc) -> StateT s Identity Text -> State s Doc
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< (BlackBoxContext -> Element -> State s (BBHash -> Text)
forall backend.
(HasCallStack, Backend backend) =>
BlackBoxContext -> Element -> State backend (BBHash -> Text)
renderElem BlackBoxContext
bbCtx Element
call State s (BBHash -> Text)
-> StateT s Identity BBHash -> StateT s Identity Text
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> BBHash -> StateT s Identity BBHash
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure BBHash
0)
    let layout :: LayoutOptions
layout = PageWidth -> LayoutOptions
LayoutOptions (BBHash -> Double -> PageWidth
AvailablePerLine BBHash
120 Double
0.4)
        rendered1 :: Text
rendered1 = SimpleDocStream () -> Text
forall ann. SimpleDocStream ann -> Text
renderLazy (LayoutOptions -> Doc -> SimpleDocStream ()
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
layoutPretty LayoutOptions
layout Doc
rendered0)
    Declaration -> StateT s Identity Declaration
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (
      Text
-> [[Element]]
-> [[Element]]
-> [((Text, Text), BlackBox)]
-> BlackBox
-> BlackBoxContext
-> Declaration
BlackBoxD
        Text
"__FOLD_BB_INTERNAL__"
        [] [] []
        ([Element] -> BlackBox
BBTemplate [Text -> Element
Text Text
rendered1])
        (Text -> BlackBoxContext
emptyBBContext Text
"__FOLD_BB_INTERNAL__")
        )
   where
    call :: Element
call  = Decl -> Element
Component (BBHash -> BBHash -> [([Element], [Element])] -> Decl
Decl BBHash
fPos BBHash
fSubPos (([Element], [Element])
resEl([Element], [Element])
-> [([Element], [Element])] -> [([Element], [Element])]
forall a. a -> [a] -> [a]
:([Element], [Element])
aEl([Element], [Element])
-> [([Element], [Element])] -> [([Element], [Element])]
forall a. a -> [a] -> [a]
:[([Element], [Element])
bEl]))
    elTyp :: [Element]
elTyp = [Element -> Element
TypElem (Maybe BBHash -> Element
Typ (BBHash -> Maybe BBHash
forall a. a -> Maybe a
Just BBHash
vecPos))]
    resEl :: ([Element], [Element])
resEl = ([Text -> Element
Text (Text -> Text
LText.fromStrict Text
r)], [Element]
elTyp)
    aEl :: ([Element], [Element])
aEl   = ([Text -> Element
Text (Text -> Text
LText.fromStrict Text
a)], [Element]
elTyp)
    bEl :: ([Element], [Element])
bEl   = ([Text -> Element
Text (Text -> Text
LText.fromStrict Text
b)], [Element]
elTyp)
  
  fPos :: BBHash
fPos = BBHash
0
  
  vecPos :: BBHash
vecPos = BBHash
1
  
  mkTree
    :: Int
    
    -> [Identifier]
    
    -> State s ( [[FCall]]    
               , Identifier 
               )
  mkTree :: BBHash -> [Text] -> State s ([[FCall]], Text)
mkTree BBHash
_lvl []  = String -> State s ([[FCall]], Text)
forall a. HasCallStack => String -> a
error String
"Unreachable?"
  mkTree BBHash
_lvl [Text
res] = ([[FCall]], Text) -> State s ([[FCall]], Text)
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([], Text
res)
  mkTree BBHash
lvl [Text]
results0  = do
    ([FCall]
calls0, [Text]
results1) <- (BBHash, BBHash) -> [Text] -> State s ([FCall], [Text])
mkLevel (BBHash
lvl, BBHash
0) [Text]
results0
    ([[FCall]]
calls1, Text
result) <- BBHash -> [Text] -> State s ([[FCall]], Text)
mkTree (BBHash
lvlBBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
+BBHash
1) [Text]
results1
    ([[FCall]], Text) -> State s ([[FCall]], Text)
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([FCall]
calls0 [FCall] -> [[FCall]] -> [[FCall]]
forall a. a -> [a] -> [a]
: [[FCall]]
calls1, Text
result)
  
  mkLevel
    :: (Int, Int)
    
    -> [Identifier]
    -> State s ([FCall], [Identifier])
  mkLevel :: (BBHash, BBHash) -> [Text] -> State s ([FCall], [Text])
mkLevel (!BBHash
lvl, !BBHash
offset) (Text
a:Text
b:[Text]
rest) = do
    Text
c <- String -> StateT s Identity Text
mkId (String
"acc_" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> BBHash -> String
forall a. Show a => a -> String
show BBHash
lvl String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"_" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> BBHash -> String
forall a. Show a => a -> String
show BBHash
offset)
    ([FCall]
calls, [Text]
results) <- (BBHash, BBHash) -> [Text] -> State s ([FCall], [Text])
mkLevel (BBHash
lvl, BBHash
offsetBBHash -> BBHash -> BBHash
forall a. Num a => a -> a -> a
+BBHash
1) [Text]
rest
    ([FCall], [Text]) -> State s ([FCall], [Text])
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text -> Text -> Text -> FCall
FCall Text
a Text
b Text
cFCall -> [FCall] -> [FCall]
forall a. a -> [a] -> [a]
:[FCall]
calls, Text
cText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
results)
  mkLevel (BBHash, BBHash)
_lvl [Text]
rest =
    ([FCall], [Text]) -> State s ([FCall], [Text])
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([], [Text]
rest)
  
  sigDecl :: HWType -> WireOrReg -> Identifier -> Declaration
  sigDecl :: HWType -> WireOrReg -> Text -> Declaration
sigDecl HWType
typ WireOrReg
rw Text
nm = Maybe Text
-> WireOrReg
-> Text
-> Either Text HWType
-> Maybe Expr
-> Declaration
NetDecl' Maybe Text
forall a. Maybe a
Nothing WireOrReg
rw Text
nm (HWType -> Either Text HWType
forall a b. b -> Either a b
Right HWType
typ) Maybe Expr
forall a. Maybe a
Nothing
  
  
  
  iIndex :: Identifier -> Int -> Expr
  iIndex :: Text -> BBHash -> Expr
iIndex Text
vecId BBHash
i = Text -> Maybe Modifier -> Expr
Identifier Text
vecId (Modifier -> Maybe Modifier
forall a. a -> Maybe a
Just ((HWType, BBHash, BBHash) -> Modifier
Indexed (HWType
vecType, BBHash
10, BBHash
i)))
foldTF' BlackBoxContext
args =
  String -> State s Doc
forall a. HasCallStack => String -> a
error (String -> State s Doc) -> String -> State s Doc
forall a b. (a -> b) -> a -> b
$ String
"Unexpected number of arguments: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ BBHash -> String
forall a. Show a => a -> String
show ([(Expr, HWType, Bool)] -> BBHash
forall (t :: Type -> Type) a. Foldable t => t a -> BBHash
length (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
args))
indexIntVerilog ::  BlackBoxFunction
indexIntVerilog :: BlackBoxFunction
indexIntVerilog Bool
_isD Text
_primName [Either Term Type]
args Type
_ty = Either String (BlackBoxMeta, BlackBox)
-> NetlistMonad (Either String (BlackBoxMeta, BlackBox))
forall (m :: Type -> Type) a. Monad m => a -> m a
return ((BlackBoxMeta
meta,) (BlackBox -> (BlackBoxMeta, BlackBox))
-> Either String BlackBox -> Either String (BlackBoxMeta, BlackBox)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String BlackBox
bb)
 where
  meta :: BlackBoxMeta
meta = BlackBoxMeta
emptyBlackBoxMeta{bbKind :: TemplateKind
bbKind=TemplateKind
bbKi}
  bbKi :: TemplateKind
bbKi = case [Either Term Type]
args of
    [Either Term Type
_nTy,Either Term Type
_aTy,Either Term Type
_kn,Either Term Type
_v,Left Term
ix]
      | Term -> Bool
isLiteral Term
ix -> TemplateKind
TExpr
    [Either Term Type]
_ -> TemplateKind
TDecl
  bb :: Either String BlackBox
bb = case [Either Term Type]
args of
    [Either Term Type
_nTy,Either Term Type
_aTy,Either Term Type
_kn,Either Term Type
_v,Left Term
ix] | Term -> Bool
isLiteral Term
ix ->
      BlackBox -> Either String BlackBox
forall a b. b -> Either a b
Right (String -> BBHash -> TemplateFunction -> BlackBox
BBFunction String
"Clash.Primitives.Sized.Vector" BBHash
0 TemplateFunction
indexIntVerilogTF)
    [Either Term Type]
_ ->
      [Element] -> BlackBox
BBTemplate ([Element] -> BlackBox)
-> Either String [Element] -> Either String BlackBox
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> case Text -> Result [Element]
runParse (String -> Text
pack (String -> String
I.unindent String
bbText)) of
        Success [Element]
t -> [Element] -> Either String [Element]
forall a b. b -> Either a b
Right [Element]
t
        Result [Element]
_         -> String -> Either String [Element]
forall a b. a -> Either a b
Left String
"internal error: parse fail"
  bbText :: String
bbText = [I.i|
    // index begin
    ~IF~SIZE[~TYP[1]]~THENwire ~TYPO ~GENSYM[vecArray][0] [0:~LIT[0]-1];
    genvar ~GENSYM[i][2];
    ~GENERATE
    for (~SYM[2]=0; ~SYM[2] < ~LIT[0]; ~SYM[2]=~SYM[2]+1) begin : ~GENSYM[mk_array][3]
      assign ~SYM[0][(~LIT[0]-1)-~SYM[2]] = ~VAR[vecFlat][1][~SYM[2]*~SIZE[~TYPO]+:~SIZE[~TYPO]];
    end
    ~ENDGENERATE
    assign ~RESULT = ~SYM[0][~ARG[2]];~ELSEassign ~RESULT = ~ERRORO;~FI
    // index end|]
indexIntVerilogTF :: TemplateFunction
indexIntVerilogTF :: TemplateFunction
indexIntVerilogTF = [BBHash]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [BBHash]
used BlackBoxContext -> Bool
forall b. b -> Bool
valid forall s. Backend s => BlackBoxContext -> State s Doc
indexIntVerilogTemplate
 where
  used :: [BBHash]
used  = [BBHash
1,BBHash
2]
  valid :: b -> Bool
valid = Bool -> b -> Bool
forall a b. a -> b -> a
const Bool
True
indexIntVerilogTemplate
  :: Backend s
  => BlackBoxContext
  -> State s Doc
indexIntVerilogTemplate :: BlackBoxContext -> State s Doc
indexIntVerilogTemplate BlackBoxContext
bbCtx = Mon (State s) Doc -> State s Doc
forall (f :: Type -> Type) m. Mon f m -> f m
getMon (Mon (State s) Doc -> State s Doc)
-> Mon (State s) Doc -> State s Doc
forall a b. (a -> b) -> a -> b
$ case HWType -> BBHash
typeSize HWType
vTy of
  BBHash
0 -> HWType -> Mon (State s) Doc
forall state. Backend state => HWType -> Mon (State state) Doc
hdlTypeErrValue HWType
rTy
  BBHash
_ -> case Expr
vec of
    Identifier Text
i Maybe Modifier
mM -> case Maybe Modifier
mM of
      Just Modifier
m ->
           Bool -> Expr -> Mon (State s) Doc
forall state.
Backend state =>
Bool -> Expr -> Mon (State state) Doc
expr Bool
False (Text -> Maybe Modifier -> Expr
Identifier Text
i (Modifier -> Maybe Modifier
forall a. a -> Maybe a
Just (Modifier -> Modifier -> Modifier
Nested Modifier
m ((HWType, BBHash, BBHash) -> Modifier
Indexed (HWType
vTy,BBHash
10,Expr -> BBHash
ixI Expr
ix)))))
      Maybe Modifier
_ -> Bool -> Expr -> Mon (State s) Doc
forall state.
Backend state =>
Bool -> Expr -> Mon (State state) Doc
expr Bool
False (Text -> Maybe Modifier -> Expr
Identifier Text
i (Modifier -> Maybe Modifier
forall a. a -> Maybe a
Just ((HWType, BBHash, BBHash) -> Modifier
Indexed (HWType
vTy,BBHash
10,Expr -> BBHash
ixI Expr
ix))))
    Expr
_ -> String -> Mon (State s) Doc
forall a. HasCallStack => String -> a
error ($(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Expected Identifier: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
vec)
 where
  [  (Expr, HWType, Bool)
_kn
   , (Expr
vec, HWType
vTy, Bool
_)
   , (Expr
ix, HWType
_, Bool
_)
   ] = BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
  (Expr
_,HWType
rTy) = BlackBoxContext -> (Expr, HWType)
bbResult BlackBoxContext
bbCtx
  ixI :: Expr ->  Int
  ixI :: Expr -> BBHash
ixI Expr
ix0 = case Expr
ix0 of
    Literal Maybe (HWType, BBHash)
_ (NumLit Integer
i) ->
      Integer -> BBHash
forall a. Num a => Integer -> a
fromInteger Integer
i
    BlackBoxE Text
"GHC.Types.I#" [[Element]]
_ [[Element]]
_ [((Text, Text), BlackBox)]
_ BlackBox
_ BlackBoxContext
ixCtx Bool
_ ->
      let (Expr
ix1,HWType
_,Bool
_) = [(Expr, HWType, Bool)] -> (Expr, HWType, Bool)
forall a. [a] -> a
head (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
ixCtx)
      in  Expr -> BBHash
ixI Expr
ix1
    Expr
_ ->
      String -> BBHash
forall a. HasCallStack => String -> a
error ($(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Unexpected literal: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
ix)