{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module Clash.Backend where
import Data.HashSet (HashSet)
import Data.Maybe (fromMaybe)
import Data.Semigroup.Monad (Mon)
import qualified Data.Text.Lazy as T
import Data.Text.Lazy (Text)
import Control.Monad.State (State)
import Data.Text.Prettyprint.Doc.Extra (Doc)
import SrcLoc (SrcSpan)
import Clash.Netlist.Id
import Clash.Netlist.Types
import Clash.Netlist.BlackBox.Types
import Clash.Annotations.Primitive (HDL)
type ModName = String
data Usage
= Internal
| External Text
class Backend state where
initBackend :: Int -> HdlSyn -> state
hdlKind :: state -> HDL
primDirs :: state -> IO [FilePath]
name :: state -> String
extension :: state -> String
extractTypes :: state -> HashSet HWType
genHDL :: String -> SrcSpan -> Component -> Mon (State state) ((String, Doc),[(String,Doc)])
mkTyPackage :: String -> [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 :: 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 -> Text -> Mon (State state) Doc
fromBV :: HWType -> 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)
addInclude :: (String, Doc) -> State state ()
addLibraries :: [Text] -> State state ()
addImports :: [Text] -> State state ()
nestM :: Modifier -> Modifier -> Maybe Modifier
nestM (Nested a b) m2
| Just m1 <- nestM a b = maybe (Just (Nested m1 m2)) Just (nestM m1 m2)
| Just m2' <- nestM b m2 = maybe (Just (Nested a m2')) Just (nestM a m2')
nestM (Indexed (Vector n t1,1,1)) (Indexed (Vector _ t2,1,0))
| t1 == t2 = Just (Indexed (Vector n t1,10,1))
nestM (Indexed (Vector n t1,1,1)) (Indexed (Vector _ t2,10,k))
| t1 == t2 = Just (Indexed (Vector n t1,10,k+1))
nestM (Indexed (RTree d1 t1,1,n)) (Indexed (RTree d2 t2,0,0))
| t1 == t2
, d1 >= 0
, d2 >= 0
= Just (Indexed (RTree d1 t1,10,n))
nestM (Indexed (RTree d1 t1,1,n)) (Indexed (RTree d2 t2,1,m))
| t1 == t2
, d1 >= 0
, d2 >= 0
= if | n == 1 && m == 1 -> let r = 2 ^ d1
l = r - (2 ^ (d1-1) `div` 2)
in Just (Indexed (RTree (-1) t1, l, r))
| n == 1 && m == 0 -> let l = 2 ^ (d1-1)
r = l + (l `div` 2)
in Just (Indexed (RTree (-1) t1, l, r))
| n == 0 && m == 1 -> let l = (2 ^ (d1-1)) `div` 2
r = 2 ^ (d1-1)
in Just (Indexed (RTree (-1) t1, l, r))
| n == 0 && m == 0 -> let l = 0
r = (2 ^ (d1-1)) `div` 2
in Just (Indexed (RTree (-1) t1, l, r))
nestM (Indexed (RTree (-1) t1,l,_)) (Indexed (RTree d t2,10,k))
| t1 == t2
, d >= 0
= Just (Indexed (RTree d t1,10,l+k))
nestM _ _ = Nothing
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,"]"])