{-# LANGUAGE OverloadedStrings #-}
module Clash.Backend where
import Control.Lens (Lens')
import qualified Control.Lens as Lens
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.HashSet (HashSet)
import Data.Maybe (fromMaybe)
import Data.Semigroup.Monad (Mon (..))
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Text.Lazy as LT
import Control.Monad.State (State)
import Data.Text.Prettyprint.Doc.Extra (Doc)
import SrcLoc (SrcSpan)
import Clash.Netlist.Id
import {-# SOURCE #-} Clash.Netlist.Types
import Clash.Netlist.BlackBox.Types
import Clash.Annotations.Primitive (HDL)
type ModName = Identifier
data Usage
= Internal
| External Text
class Backend state where
initBackend :: Int -> HdlSyn -> Bool -> Maybe (Maybe Int) -> state
hdlKind :: state -> HDL
primDirs :: state -> IO [FilePath]
name :: state -> String
extension :: state -> String
:: state -> HashSet HWType
genHDL :: Identifier -> SrcSpan -> HashMap Identifier Word -> Component -> Mon (State state) ((String, Doc),[(String,Doc)])
mkTyPackage :: Identifier -> [HWType] -> Mon (State state) [(String, Doc)]
hdlType :: Usage -> HWType -> Mon (State state) Doc
hdlTypeErrValue :: HWType -> Mon (State state) Doc
hdlTypeMark :: HWType -> Mon (State state) Doc
hdlRecSel :: HWType -> Int -> Mon (State state) Doc
hdlSig :: LT.Text -> HWType -> Mon (State state) Doc
genStmt :: Bool -> State state Doc
inst :: Declaration -> Mon (State state) (Maybe Doc)
expr :: Bool
-> Expr
-> Mon (State state) Doc
iwWidth :: State state Int
toBV :: HWType -> LT.Text -> Mon (State state) Doc
fromBV :: HWType -> LT.Text -> Mon (State state) Doc
hdlSyn :: State state HdlSyn
mkIdentifier :: State state (IdType -> Identifier -> Identifier)
extendIdentifier :: State state (IdType -> Identifier -> Identifier -> Identifier)
setModName :: ModName -> state -> state
setSrcSpan :: SrcSpan -> State state ()
getSrcSpan :: State state SrcSpan
blockDecl :: Text -> [Declaration] -> Mon (State state) Doc
unextend :: State state (Identifier -> Identifier)
addIncludes :: [(String, Doc)] -> State state ()
addLibraries :: [LT.Text] -> State state ()
addImports :: [LT.Text] -> State state ()
addAndSetData :: FilePath -> State state String
getDataFiles :: State state [(String,FilePath)]
addMemoryDataFile :: (String,String) -> State state ()
getMemoryDataFiles :: State state [(String,String)]
seenIdentifiers :: Lens' state (HashMap Identifier Word)
ifThenElseExpr :: state -> Bool
escapeTemplate :: Identifier -> Identifier
escapeTemplate :: Identifier -> Identifier
escapeTemplate "~RESULT" = "~ERESULT"
escapeTemplate t :: Identifier
t = Identifier -> Maybe Identifier -> Identifier
forall a. a -> Maybe a -> a
fromMaybe Identifier
t (Maybe Identifier -> Identifier) -> Maybe Identifier -> Identifier
forall a b. (a -> b) -> a -> b
$ do
Identifier
t1 <- Identifier -> Identifier -> Maybe Identifier
T.stripPrefix "~ARG[" Identifier
t
Identifier
n <- Identifier -> Identifier -> Maybe Identifier
T.stripSuffix "]" Identifier
t1
Identifier -> Maybe Identifier
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Identifier] -> Identifier
T.concat ["~EARG[",Identifier
n,"]"])
mkUniqueIdentifier
:: Backend s
=> IdType
-> Identifier
-> State s Identifier
mkUniqueIdentifier :: IdType -> Identifier -> State s Identifier
mkUniqueIdentifier typ :: IdType
typ nm :: Identifier
nm = do
IdType -> Identifier -> Identifier
mkId <- State s (IdType -> Identifier -> Identifier)
forall state.
Backend state =>
State state (IdType -> Identifier -> Identifier)
mkIdentifier
IdType -> Identifier -> Identifier -> Identifier
extendId <- State s (IdType -> Identifier -> Identifier -> Identifier)
forall state.
Backend state =>
State state (IdType -> Identifier -> Identifier -> Identifier)
extendIdentifier
HashMap Identifier Word
seen <- Getting (HashMap Identifier Word) s (HashMap Identifier Word)
-> StateT s Identity (HashMap Identifier Word)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
Lens.use Getting (HashMap Identifier Word) s (HashMap Identifier Word)
forall state.
Backend state =>
Lens' state (HashMap Identifier Word)
seenIdentifiers
let i :: Identifier
i = IdType -> Identifier -> Identifier
mkId IdType
typ Identifier
nm
case Identifier -> HashMap Identifier Word -> Maybe Word
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Identifier
i HashMap Identifier Word
seen of
Just n :: Word
n -> (IdType -> Identifier -> Identifier -> Identifier)
-> Word
-> HashMap Identifier Word
-> Identifier
-> State s Identifier
forall (m :: * -> *) s t v.
(MonadState s m, Backend s) =>
(IdType -> t -> Identifier -> Identifier)
-> Word -> HashMap Identifier v -> t -> m Identifier
go IdType -> Identifier -> Identifier -> Identifier
extendId Word
n HashMap Identifier Word
seen Identifier
i
Nothing -> do
(HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s
forall state.
Backend state =>
Lens' state (HashMap Identifier Word)
seenIdentifiers ((HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s)
-> (HashMap Identifier Word -> HashMap Identifier Word)
-> StateT s Identity ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
Lens.%= (Identifier
-> Word -> HashMap Identifier Word -> HashMap Identifier Word
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Identifier
i 0)
Identifier -> State s Identifier
forall (m :: * -> *) a. Monad m => a -> m a
return Identifier
i
where
go :: (IdType -> t -> Identifier -> Identifier)
-> Word -> HashMap Identifier v -> t -> m Identifier
go extendId :: IdType -> t -> Identifier -> Identifier
extendId n :: Word
n seen :: HashMap Identifier v
seen i :: t
i = do
let i' :: Identifier
i' = IdType -> t -> Identifier -> Identifier
extendId IdType
typ t
i (String -> Identifier
T.pack ('_'Char -> String -> String
forall a. a -> [a] -> [a]
:Word -> String
forall a. Show a => a -> String
show Word
n))
case Identifier -> HashMap Identifier v -> Maybe v
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Identifier
i' HashMap Identifier v
seen of
Just _ -> (IdType -> t -> Identifier -> Identifier)
-> Word -> HashMap Identifier v -> t -> m Identifier
go IdType -> t -> Identifier -> Identifier
extendId (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
+1) HashMap Identifier v
seen t
i
Nothing -> do
(HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s
forall state.
Backend state =>
Lens' state (HashMap Identifier Word)
seenIdentifiers ((HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s)
-> (HashMap Identifier Word -> HashMap Identifier Word) -> m ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
Lens.%= (Identifier
-> Word -> HashMap Identifier Word -> HashMap Identifier Word
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Identifier
i' (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
+1))
Identifier -> m Identifier
forall (m :: * -> *) a. Monad m => a -> m a
return Identifier
i'
preserveSeen
:: Backend s
=> Mon (State s) a
-> Mon (State s) a
preserveSeen :: Mon (State s) a -> Mon (State s) a
preserveSeen m :: Mon (State s) a
m = do
HashMap Identifier Word
s <- State s (HashMap Identifier Word)
-> Mon (State s) (HashMap Identifier Word)
forall (f :: * -> *) m. f m -> Mon f m
Mon (Getting (HashMap Identifier Word) s (HashMap Identifier Word)
-> State s (HashMap Identifier Word)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
Lens.use Getting (HashMap Identifier Word) s (HashMap Identifier Word)
forall state.
Backend state =>
Lens' state (HashMap Identifier Word)
seenIdentifiers)
a
a <- Mon (State s) a
m
State s () -> Mon (State s) ()
forall (f :: * -> *) m. f m -> Mon f m
Mon ((HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s
forall state.
Backend state =>
Lens' state (HashMap Identifier Word)
seenIdentifiers ((HashMap Identifier Word -> Identity (HashMap Identifier Word))
-> s -> Identity s)
-> HashMap Identifier Word -> State s ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
Lens..= HashMap Identifier Word
s)
a -> Mon (State s) a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a