{-# LANGUAGE CPP #-}
{-# 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)
#ifdef CABAL
import qualified Paths_clash_lib
import qualified Data.Version
#else
import qualified System.FilePath
#endif
primsRoot :: IO FilePath
#ifdef CABAL
primsRoot = Paths_clash_lib.getDataFileName "prims"
#else
primsRoot = return ("clash-lib" System.FilePath.</> "prims")
#endif
clashVer :: String
#ifdef CABAL
clashVer = Data.Version.showVersion Paths_clash_lib.version
#else
clashVer = "development"
#endif
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
extractTypes :: 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 "~RESULT" = "~ERESULT"
escapeTemplate t = fromMaybe t $ do
t1 <- T.stripPrefix "~ARG[" t
n <- T.stripSuffix "]" t1
pure (T.concat ["~EARG[",n,"]"])
mkUniqueIdentifier
:: Backend s
=> IdType
-> Identifier
-> State s Identifier
mkUniqueIdentifier typ nm = do
mkId <- mkIdentifier
extendId <- extendIdentifier
seen <- Lens.use seenIdentifiers
let i = mkId typ nm
case HashMap.lookup i seen of
Just n -> go extendId n seen i
Nothing -> do
seenIdentifiers Lens.%= (HashMap.insert i 0)
return i
where
go extendId n seen i = do
let i' = extendId typ i (T.pack ('_':show n))
case HashMap.lookup i' seen of
Just _ -> go extendId (n+1) seen i
Nothing -> do
seenIdentifiers Lens.%= (HashMap.insert i' (n+1))
return i'
preserveSeen
:: Backend s
=> Mon (State s) a
-> Mon (State s) a
preserveSeen m = do
s <- Mon (Lens.use seenIdentifiers)
a <- m
Mon (seenIdentifiers Lens..= s)
return a