{-# LANGUAGE CPP               #-}
{-# LANGUAGE OverloadedStrings #-}
module Clash.Backend where
import Data.HashMap.Strict                  (HashMap, empty)
import Data.HashSet                         (HashSet)
import Data.Monoid                          (Ap)
import Data.Text                            (Text)
import qualified Data.Text.Lazy             as LT
import Control.Monad.State                  (State)
import Data.Text.Prettyprint.Doc.Extra      (Doc)
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.SrcLoc (SrcSpan)
#else
import SrcLoc (SrcSpan)
#endif
import Clash.Driver.Types (ClashOpts)
import {-# SOURCE #-} Clash.Netlist.Types
import Clash.Netlist.BlackBox.Types
import Clash.Signal.Internal                (VDomainConfiguration)
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 :: IO FilePath
primsRoot = FilePath -> IO FilePath
Paths_clash_lib.getDataFileName FilePath
"prims"
#else
primsRoot = return ("clash-lib" System.FilePath.</> "prims")
#endif
clashVer :: String
#ifdef CABAL
clashVer :: FilePath
clashVer = Version -> FilePath
Data.Version.showVersion Version
Paths_clash_lib.version
#else
clashVer = "development"
#endif
type ModName = Text
data Usage
  = Internal
  
  | External Text
  
newtype AggressiveXOptBB = AggressiveXOptBB Bool
newtype RenderEnums = RenderEnums Bool
data HWKind
  = PrimitiveType
  
  | SynonymType
  
  
  
  | UserType
  
  
type DomainMap = HashMap Text VDomainConfiguration
emptyDomainMap :: DomainMap
emptyDomainMap :: DomainMap
emptyDomainMap = DomainMap
forall k v. HashMap k v
empty
class HasIdentifierSet state => Backend state where
  
  initBackend :: ClashOpts -> state
  
  hdlKind :: state -> HDL
  
  primDirs :: state -> IO [FilePath]
  
  
  name :: state -> String
  
  extension :: state -> String
  
       :: state -> HashSet HWType
  
  genHDL           :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State state) ((String, Doc),[(String,Doc)])
  
  mkTyPackage      :: ModName -> [HWType] -> Ap (State state) [(String, Doc)]
  
  hdlType          :: Usage -> HWType -> Ap (State state) Doc
  
  hdlHWTypeKind :: HWType -> State state HWKind
  
  hdlTypeErrValue  :: HWType       -> Ap (State state) Doc
  
  hdlTypeMark      :: HWType       -> Ap (State state) Doc
  
  hdlRecSel        :: HWType -> Int -> Ap (State state) Doc
  
  hdlSig           :: LT.Text -> HWType -> Ap (State state) Doc
  
  genStmt          :: Bool -> State state Doc
  
  inst             :: Declaration  -> Ap (State state) (Maybe Doc)
  
  expr             :: Bool 
                   -> Expr 
                   -> Ap (State state) Doc
  
  iwWidth          :: State state Int
  
  toBV             :: HWType -> LT.Text -> Ap (State state) Doc
  
  fromBV           :: HWType -> LT.Text -> Ap (State state) Doc
  
  hdlSyn           :: State state HdlSyn
  
  setModName       :: ModName -> state -> state
  
  setTopName       :: Identifier -> state -> state
  
  getTopName       :: State state Identifier
  
  setSrcSpan       :: SrcSpan -> State state ()
  
  getSrcSpan       :: State state SrcSpan
  
  blockDecl        :: Identifier -> [Declaration] -> Ap (State state) Doc
  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)]
  ifThenElseExpr :: state -> Bool
  
  aggressiveXOptBB :: State state AggressiveXOptBB
  
  renderEnums :: State state RenderEnums
  
  domainConfigurations :: State state DomainMap
  
  setDomainConfigurations :: DomainMap -> state -> state