{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
#if __GLASGOW_HASKELL__ >= 806
#define FIELD ^
#endif
module Clash.Netlist.Types
( Declaration (..,NetDecl)
, module Clash.Netlist.Types
)
where
import Control.DeepSeq
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail (MonadFail)
#endif
import Control.Monad.Reader (ReaderT, MonadReader)
import Control.Monad.State as Lazy (State)
import Control.Monad.State.Strict as Strict
(State,MonadIO, MonadState, StateT)
import Data.Bits (testBit)
import Data.Binary (Binary(..))
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import Data.IntMap (IntMap, empty)
import qualified Data.Set as Set
import Data.Text (Text, pack)
import Data.Typeable (Typeable)
import Data.Text.Prettyprint.Doc.Extra (Doc)
import GHC.Generics (Generic)
import Language.Haskell.TH.Syntax (Lift)
import SrcLoc (SrcSpan)
import Clash.Annotations.BitRepresentation (FieldAnn)
import Clash.Annotations.TopEntity (TopEntity)
import Clash.Backend (Backend)
import Clash.Core.Type (Type)
import Clash.Core.Var (Attr', Id, varType)
import Clash.Core.TyCon (TyConMap)
import Clash.Core.VarEnv (VarEnv)
import Clash.Driver.Types (BindingMap, ClashOpts)
import Clash.Netlist.BlackBox.Types (BlackBoxTemplate)
import Clash.Netlist.Id (IdType)
import Clash.Primitives.Types (CompiledPrimMap)
import Clash.Signal.Internal
(ResetPolarity, ActiveEdge, ResetKind, InitBehavior)
import Clash.Util (HasCallStack, makeLenses)
import Clash.Annotations.BitRepresentation.Internal
(CustomReprs, DataRepr', ConstrRepr')
data TopEntityT = TopEntityT
{ TopEntityT -> Id
topId :: Id
, TopEntityT -> Maybe TopEntity
topAnnotation :: Maybe TopEntity
, TopEntityT -> Maybe Id
associatedTestbench :: Maybe Id
} deriving ((forall x. TopEntityT -> Rep TopEntityT x)
-> (forall x. Rep TopEntityT x -> TopEntityT) -> Generic TopEntityT
forall x. Rep TopEntityT x -> TopEntityT
forall x. TopEntityT -> Rep TopEntityT x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TopEntityT x -> TopEntityT
$cfrom :: forall x. TopEntityT -> Rep TopEntityT x
Generic)
newtype NetlistMonad a =
NetlistMonad { NetlistMonad a -> StateT NetlistState (ReaderT NetlistEnv IO) a
runNetlist :: StateT NetlistState (ReaderT NetlistEnv IO) a }
deriving newtype (a -> NetlistMonad b -> NetlistMonad a
(a -> b) -> NetlistMonad a -> NetlistMonad b
(forall a b. (a -> b) -> NetlistMonad a -> NetlistMonad b)
-> (forall a b. a -> NetlistMonad b -> NetlistMonad a)
-> Functor NetlistMonad
forall a b. a -> NetlistMonad b -> NetlistMonad a
forall a b. (a -> b) -> NetlistMonad a -> NetlistMonad b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> NetlistMonad b -> NetlistMonad a
$c<$ :: forall a b. a -> NetlistMonad b -> NetlistMonad a
fmap :: (a -> b) -> NetlistMonad a -> NetlistMonad b
$cfmap :: forall a b. (a -> b) -> NetlistMonad a -> NetlistMonad b
Functor, Applicative NetlistMonad
a -> NetlistMonad a
Applicative NetlistMonad
-> (forall a b.
NetlistMonad a -> (a -> NetlistMonad b) -> NetlistMonad b)
-> (forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b)
-> (forall a. a -> NetlistMonad a)
-> Monad NetlistMonad
NetlistMonad a -> (a -> NetlistMonad b) -> NetlistMonad b
NetlistMonad a -> NetlistMonad b -> NetlistMonad b
forall a. a -> NetlistMonad a
forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b
forall a b.
NetlistMonad a -> (a -> NetlistMonad b) -> NetlistMonad b
forall (m :: Type -> Type).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> NetlistMonad a
$creturn :: forall a. a -> NetlistMonad a
>> :: NetlistMonad a -> NetlistMonad b -> NetlistMonad b
$c>> :: forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b
>>= :: NetlistMonad a -> (a -> NetlistMonad b) -> NetlistMonad b
$c>>= :: forall a b.
NetlistMonad a -> (a -> NetlistMonad b) -> NetlistMonad b
$cp1Monad :: Applicative NetlistMonad
Monad, Functor NetlistMonad
a -> NetlistMonad a
Functor NetlistMonad
-> (forall a. a -> NetlistMonad a)
-> (forall a b.
NetlistMonad (a -> b) -> NetlistMonad a -> NetlistMonad b)
-> (forall a b c.
(a -> b -> c)
-> NetlistMonad a -> NetlistMonad b -> NetlistMonad c)
-> (forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b)
-> (forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad a)
-> Applicative NetlistMonad
NetlistMonad a -> NetlistMonad b -> NetlistMonad b
NetlistMonad a -> NetlistMonad b -> NetlistMonad a
NetlistMonad (a -> b) -> NetlistMonad a -> NetlistMonad b
(a -> b -> c) -> NetlistMonad a -> NetlistMonad b -> NetlistMonad c
forall a. a -> NetlistMonad a
forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad a
forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b
forall a b.
NetlistMonad (a -> b) -> NetlistMonad a -> NetlistMonad b
forall a b c.
(a -> b -> c) -> NetlistMonad a -> NetlistMonad b -> NetlistMonad c
forall (f :: Type -> Type).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: NetlistMonad a -> NetlistMonad b -> NetlistMonad a
$c<* :: forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad a
*> :: NetlistMonad a -> NetlistMonad b -> NetlistMonad b
$c*> :: forall a b. NetlistMonad a -> NetlistMonad b -> NetlistMonad b
liftA2 :: (a -> b -> c) -> NetlistMonad a -> NetlistMonad b -> NetlistMonad c
$cliftA2 :: forall a b c.
(a -> b -> c) -> NetlistMonad a -> NetlistMonad b -> NetlistMonad c
<*> :: NetlistMonad (a -> b) -> NetlistMonad a -> NetlistMonad b
$c<*> :: forall a b.
NetlistMonad (a -> b) -> NetlistMonad a -> NetlistMonad b
pure :: a -> NetlistMonad a
$cpure :: forall a. a -> NetlistMonad a
$cp1Applicative :: Functor NetlistMonad
Applicative, MonadReader NetlistEnv,
MonadState NetlistState, Monad NetlistMonad
Monad NetlistMonad
-> (forall a. IO a -> NetlistMonad a) -> MonadIO NetlistMonad
IO a -> NetlistMonad a
forall a. IO a -> NetlistMonad a
forall (m :: Type -> Type).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> NetlistMonad a
$cliftIO :: forall a. IO a -> NetlistMonad a
$cp1MonadIO :: Monad NetlistMonad
MonadIO, Monad NetlistMonad
Monad NetlistMonad
-> (forall a. String -> NetlistMonad a) -> MonadFail NetlistMonad
String -> NetlistMonad a
forall a. String -> NetlistMonad a
forall (m :: Type -> Type).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> NetlistMonad a
$cfail :: forall a. String -> NetlistMonad a
$cp1MonadFail :: Monad NetlistMonad
MonadFail)
type HWMap = HashMap Type (Either String FilteredHWType)
data NetlistEnv
= NetlistEnv
{ NetlistEnv -> Identifier
_prefixName :: Identifier
, NetlistEnv -> Identifier
_suffixName :: Identifier
, NetlistEnv -> Maybe Identifier
_setName :: Maybe Identifier
}
data NetlistState
= NetlistState
{ NetlistState -> BindingMap
_bindings :: BindingMap
, NetlistState -> Int
_varCount :: !Int
, NetlistState
-> VarEnv ([Bool], SrcSpan, HashMap Identifier Word, Component)
_components :: VarEnv ([Bool],SrcSpan,HashMap Identifier Word,Component)
, NetlistState -> CompiledPrimMap
_primitives :: CompiledPrimMap
, NetlistState
-> CustomReprs
-> TyConMap
-> Type
-> State HWMap (Maybe (Either String FilteredHWType))
_typeTranslator :: CustomReprs -> TyConMap -> Type
-> Strict.State HWMap (Maybe (Either String FilteredHWType))
, NetlistState -> TyConMap
_tcCache :: TyConMap
, NetlistState -> (Identifier, SrcSpan)
_curCompNm :: !(Identifier,SrcSpan)
, NetlistState -> Int
_intWidth :: Int
, NetlistState -> IdType -> Identifier -> Identifier
_mkIdentifierFn :: IdType -> Identifier -> Identifier
, NetlistState -> IdType -> Identifier -> Identifier -> Identifier
_extendIdentifierFn :: IdType -> Identifier -> Identifier -> Identifier
, NetlistState -> HashMap Identifier Word
_seenIds :: HashMap Identifier Word
, NetlistState -> HashMap Identifier Word
_seenComps :: HashMap Identifier Word
, NetlistState -> Set Identifier
_seenPrimitives :: Set.Set Text
, NetlistState -> VarEnv Identifier
_componentNames :: VarEnv Identifier
, NetlistState -> VarEnv TopEntityT
_topEntityAnns :: VarEnv TopEntityT
, NetlistState -> String
_hdlDir :: FilePath
, NetlistState -> Int
_curBBlvl :: Int
, NetlistState -> ComponentPrefix
_componentPrefix :: ComponentPrefix
, NetlistState -> CustomReprs
_customReprs :: CustomReprs
, NetlistState -> ClashOpts
_clashOpts :: ClashOpts
, NetlistState -> Bool
_isTestBench :: Bool
, NetlistState -> Bool
_backEndITE :: Bool
, NetlistState -> SomeBackend
_backend :: SomeBackend
, NetlistState -> HWMap
_htyCache :: HWMap
}
data ComponentPrefix
= ComponentPrefix
{ ComponentPrefix -> Maybe Identifier
componentPrefixTop :: Maybe Identifier
, ComponentPrefix -> Maybe Identifier
componentPrefixOther :: Maybe Identifier
} deriving Int -> ComponentPrefix -> ShowS
[ComponentPrefix] -> ShowS
ComponentPrefix -> String
(Int -> ComponentPrefix -> ShowS)
-> (ComponentPrefix -> String)
-> ([ComponentPrefix] -> ShowS)
-> Show ComponentPrefix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComponentPrefix] -> ShowS
$cshowList :: [ComponentPrefix] -> ShowS
show :: ComponentPrefix -> String
$cshow :: ComponentPrefix -> String
showsPrec :: Int -> ComponentPrefix -> ShowS
$cshowsPrec :: Int -> ComponentPrefix -> ShowS
Show
data SomeBackend where
SomeBackend :: Backend backend => backend -> SomeBackend
type Identifier = Text
type = Text
data Component
= Component
{ Component -> Identifier
componentName :: !Identifier
, Component -> [(Identifier, HWType)]
inputs :: [(Identifier,HWType)]
, Component -> [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outputs :: [(WireOrReg,(Identifier,HWType),Maybe Expr)]
, Component -> [Declaration]
declarations :: [Declaration]
}
deriving Int -> Component -> ShowS
[Component] -> ShowS
Component -> String
(Int -> Component -> ShowS)
-> (Component -> String)
-> ([Component] -> ShowS)
-> Show Component
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Component] -> ShowS
$cshowList :: [Component] -> ShowS
show :: Component -> String
$cshow :: Component -> String
showsPrec :: Int -> Component -> ShowS
$cshowsPrec :: Int -> Component -> ShowS
Show
instance NFData Component where
rnf :: Component -> ()
rnf Component
c = case Component
c of
Component Identifier
nm [(Identifier, HWType)]
inps [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outps [Declaration]
decls -> Identifier -> ()
forall a. NFData a => a -> ()
rnf Identifier
nm () -> () -> ()
`seq` [(Identifier, HWType)] -> ()
forall a. NFData a => a -> ()
rnf [(Identifier, HWType)]
inps () -> () -> ()
`seq`
[(WireOrReg, (Identifier, HWType), Maybe Expr)] -> ()
forall a. NFData a => a -> ()
rnf [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outps () -> () -> ()
`seq` [Declaration] -> ()
forall a. NFData a => a -> ()
rnf [Declaration]
decls
type Size = Int
type IsVoid = Bool
data FilteredHWType =
FilteredHWType HWType [[(IsVoid, FilteredHWType)]]
deriving (FilteredHWType -> FilteredHWType -> Bool
(FilteredHWType -> FilteredHWType -> Bool)
-> (FilteredHWType -> FilteredHWType -> Bool) -> Eq FilteredHWType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilteredHWType -> FilteredHWType -> Bool
$c/= :: FilteredHWType -> FilteredHWType -> Bool
== :: FilteredHWType -> FilteredHWType -> Bool
$c== :: FilteredHWType -> FilteredHWType -> Bool
Eq, Int -> FilteredHWType -> ShowS
[FilteredHWType] -> ShowS
FilteredHWType -> String
(Int -> FilteredHWType -> ShowS)
-> (FilteredHWType -> String)
-> ([FilteredHWType] -> ShowS)
-> Show FilteredHWType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilteredHWType] -> ShowS
$cshowList :: [FilteredHWType] -> ShowS
show :: FilteredHWType -> String
$cshow :: FilteredHWType -> String
showsPrec :: Int -> FilteredHWType -> ShowS
$cshowsPrec :: Int -> FilteredHWType -> ShowS
Show)
data HWType
= Void (Maybe HWType)
| String
| Integer
| Bool
| Bit
| BitVector !Size
| Index !Integer
| Signed !Size
| Unsigned !Size
| Vector !Size !HWType
| RTree !Size !HWType
| Sum !Identifier [Identifier]
| Product !Identifier (Maybe [Text]) [HWType]
| SP !Identifier [(Identifier,[HWType])]
| Clock !Identifier
| Reset !Identifier
| BiDirectional !PortDirection !HWType
| CustomSP !Identifier !DataRepr' !Size [(ConstrRepr', Identifier, [HWType])]
| CustomSum !Identifier !DataRepr' !Size [(ConstrRepr', Identifier)]
| CustomProduct !Identifier !DataRepr' !Size (Maybe [Text]) [(FieldAnn, HWType)]
| Annotated [Attr'] !HWType
| KnownDomain !Identifier !Integer !ActiveEdge !ResetKind !InitBehavior !ResetPolarity
| FileType
deriving (HWType -> HWType -> Bool
(HWType -> HWType -> Bool)
-> (HWType -> HWType -> Bool) -> Eq HWType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HWType -> HWType -> Bool
$c/= :: HWType -> HWType -> Bool
== :: HWType -> HWType -> Bool
$c== :: HWType -> HWType -> Bool
Eq, Eq HWType
Eq HWType
-> (HWType -> HWType -> Ordering)
-> (HWType -> HWType -> Bool)
-> (HWType -> HWType -> Bool)
-> (HWType -> HWType -> Bool)
-> (HWType -> HWType -> Bool)
-> (HWType -> HWType -> HWType)
-> (HWType -> HWType -> HWType)
-> Ord HWType
HWType -> HWType -> Bool
HWType -> HWType -> Ordering
HWType -> HWType -> HWType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HWType -> HWType -> HWType
$cmin :: HWType -> HWType -> HWType
max :: HWType -> HWType -> HWType
$cmax :: HWType -> HWType -> HWType
>= :: HWType -> HWType -> Bool
$c>= :: HWType -> HWType -> Bool
> :: HWType -> HWType -> Bool
$c> :: HWType -> HWType -> Bool
<= :: HWType -> HWType -> Bool
$c<= :: HWType -> HWType -> Bool
< :: HWType -> HWType -> Bool
$c< :: HWType -> HWType -> Bool
compare :: HWType -> HWType -> Ordering
$ccompare :: HWType -> HWType -> Ordering
$cp1Ord :: Eq HWType
Ord, Int -> HWType -> ShowS
[HWType] -> ShowS
HWType -> String
(Int -> HWType -> ShowS)
-> (HWType -> String) -> ([HWType] -> ShowS) -> Show HWType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HWType] -> ShowS
$cshowList :: [HWType] -> ShowS
show :: HWType -> String
$cshow :: HWType -> String
showsPrec :: Int -> HWType -> ShowS
$cshowsPrec :: Int -> HWType -> ShowS
Show, (forall x. HWType -> Rep HWType x)
-> (forall x. Rep HWType x -> HWType) -> Generic HWType
forall x. Rep HWType x -> HWType
forall x. HWType -> Rep HWType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HWType x -> HWType
$cfrom :: forall x. HWType -> Rep HWType x
Generic, HWType -> ()
(HWType -> ()) -> NFData HWType
forall a. (a -> ()) -> NFData a
rnf :: HWType -> ()
$crnf :: HWType -> ()
NFData, Int -> HWType -> Int
HWType -> Int
(Int -> HWType -> Int) -> (HWType -> Int) -> Hashable HWType
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: HWType -> Int
$chash :: HWType -> Int
hashWithSalt :: Int -> HWType -> Int
$chashWithSalt :: Int -> HWType -> Int
Hashable)
hwTypeAttrs :: HWType -> [Attr']
hwTypeAttrs :: HWType -> [Attr']
hwTypeAttrs (Annotated [Attr']
attrs HWType
_type) = [Attr']
attrs
hwTypeAttrs HWType
_ = []
data Declaration
= Assignment
!Identifier
!Expr
| CondAssignment
!Identifier
!HWType
!Expr
!HWType
[(Maybe Literal,Expr)]
| InstDecl
EntityOrComponent
(Maybe Comment)
!Identifier
!Identifier
[(Expr,HWType,Expr)]
[(Expr,PortDirection,HWType,Expr)]
| BlackBoxD
!Text
[BlackBoxTemplate]
[BlackBoxTemplate]
[((Text,Text),BlackBox)]
!BlackBox
BlackBoxContext
| NetDecl'
(Maybe Comment)
WireOrReg
!Identifier
(Either Identifier HWType)
(Maybe Expr)
| TickDecl Comment
| Seq [Seq]
deriving Int -> Declaration -> ShowS
[Declaration] -> ShowS
Declaration -> String
(Int -> Declaration -> ShowS)
-> (Declaration -> String)
-> ([Declaration] -> ShowS)
-> Show Declaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Declaration] -> ShowS
$cshowList :: [Declaration] -> ShowS
show :: Declaration -> String
$cshow :: Declaration -> String
showsPrec :: Int -> Declaration -> ShowS
$cshowsPrec :: Int -> Declaration -> ShowS
Show
data Seq
= AlwaysClocked
ActiveEdge
Expr
[Seq]
| Initial
[Seq]
| AlwaysComb
[Seq]
| SeqDecl
Declaration
| Branch
!Expr
!HWType
[(Maybe Literal,[Seq])]
deriving Int -> Seq -> ShowS
[Seq] -> ShowS
Seq -> String
(Int -> Seq -> ShowS)
-> (Seq -> String) -> ([Seq] -> ShowS) -> Show Seq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seq] -> ShowS
$cshowList :: [Seq] -> ShowS
show :: Seq -> String
$cshow :: Seq -> String
showsPrec :: Int -> Seq -> ShowS
$cshowsPrec :: Int -> Seq -> ShowS
Show
data EntityOrComponent = Entity | Comp | Empty
deriving Int -> EntityOrComponent -> ShowS
[EntityOrComponent] -> ShowS
EntityOrComponent -> String
(Int -> EntityOrComponent -> ShowS)
-> (EntityOrComponent -> String)
-> ([EntityOrComponent] -> ShowS)
-> Show EntityOrComponent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EntityOrComponent] -> ShowS
$cshowList :: [EntityOrComponent] -> ShowS
show :: EntityOrComponent -> String
$cshow :: EntityOrComponent -> String
showsPrec :: Int -> EntityOrComponent -> ShowS
$cshowsPrec :: Int -> EntityOrComponent -> ShowS
Show
data WireOrReg = Wire | Reg
deriving (Int -> WireOrReg -> ShowS
[WireOrReg] -> ShowS
WireOrReg -> String
(Int -> WireOrReg -> ShowS)
-> (WireOrReg -> String)
-> ([WireOrReg] -> ShowS)
-> Show WireOrReg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WireOrReg] -> ShowS
$cshowList :: [WireOrReg] -> ShowS
show :: WireOrReg -> String
$cshow :: WireOrReg -> String
showsPrec :: Int -> WireOrReg -> ShowS
$cshowsPrec :: Int -> WireOrReg -> ShowS
Show,(forall x. WireOrReg -> Rep WireOrReg x)
-> (forall x. Rep WireOrReg x -> WireOrReg) -> Generic WireOrReg
forall x. Rep WireOrReg x -> WireOrReg
forall x. WireOrReg -> Rep WireOrReg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WireOrReg x -> WireOrReg
$cfrom :: forall x. WireOrReg -> Rep WireOrReg x
Generic)
instance NFData WireOrReg
pattern NetDecl
:: Maybe Comment
-> Identifier
-> HWType
-> Declaration
pattern $bNetDecl :: Maybe Identifier -> Identifier -> HWType -> Declaration
$mNetDecl :: forall r.
Declaration
-> (Maybe Identifier -> Identifier -> HWType -> r)
-> (Void# -> r)
-> r
NetDecl note d ty <- NetDecl' note Wire d (Right ty) _
where
NetDecl Maybe Identifier
note Identifier
d HWType
ty = Maybe Identifier
-> WireOrReg
-> Identifier
-> Either Identifier HWType
-> Maybe Expr
-> Declaration
NetDecl' Maybe Identifier
note WireOrReg
Wire Identifier
d (HWType -> Either Identifier HWType
forall a b. b -> Either a b
Right HWType
ty) Maybe Expr
forall a. Maybe a
Nothing
data PortDirection = In | Out
deriving (PortDirection -> PortDirection -> Bool
(PortDirection -> PortDirection -> Bool)
-> (PortDirection -> PortDirection -> Bool) -> Eq PortDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PortDirection -> PortDirection -> Bool
$c/= :: PortDirection -> PortDirection -> Bool
== :: PortDirection -> PortDirection -> Bool
$c== :: PortDirection -> PortDirection -> Bool
Eq,Eq PortDirection
Eq PortDirection
-> (PortDirection -> PortDirection -> Ordering)
-> (PortDirection -> PortDirection -> Bool)
-> (PortDirection -> PortDirection -> Bool)
-> (PortDirection -> PortDirection -> Bool)
-> (PortDirection -> PortDirection -> Bool)
-> (PortDirection -> PortDirection -> PortDirection)
-> (PortDirection -> PortDirection -> PortDirection)
-> Ord PortDirection
PortDirection -> PortDirection -> Bool
PortDirection -> PortDirection -> Ordering
PortDirection -> PortDirection -> PortDirection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PortDirection -> PortDirection -> PortDirection
$cmin :: PortDirection -> PortDirection -> PortDirection
max :: PortDirection -> PortDirection -> PortDirection
$cmax :: PortDirection -> PortDirection -> PortDirection
>= :: PortDirection -> PortDirection -> Bool
$c>= :: PortDirection -> PortDirection -> Bool
> :: PortDirection -> PortDirection -> Bool
$c> :: PortDirection -> PortDirection -> Bool
<= :: PortDirection -> PortDirection -> Bool
$c<= :: PortDirection -> PortDirection -> Bool
< :: PortDirection -> PortDirection -> Bool
$c< :: PortDirection -> PortDirection -> Bool
compare :: PortDirection -> PortDirection -> Ordering
$ccompare :: PortDirection -> PortDirection -> Ordering
$cp1Ord :: Eq PortDirection
Ord,Int -> PortDirection -> ShowS
[PortDirection] -> ShowS
PortDirection -> String
(Int -> PortDirection -> ShowS)
-> (PortDirection -> String)
-> ([PortDirection] -> ShowS)
-> Show PortDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PortDirection] -> ShowS
$cshowList :: [PortDirection] -> ShowS
show :: PortDirection -> String
$cshow :: PortDirection -> String
showsPrec :: Int -> PortDirection -> ShowS
$cshowsPrec :: Int -> PortDirection -> ShowS
Show,(forall x. PortDirection -> Rep PortDirection x)
-> (forall x. Rep PortDirection x -> PortDirection)
-> Generic PortDirection
forall x. Rep PortDirection x -> PortDirection
forall x. PortDirection -> Rep PortDirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PortDirection x -> PortDirection
$cfrom :: forall x. PortDirection -> Rep PortDirection x
Generic,PortDirection -> ()
(PortDirection -> ()) -> NFData PortDirection
forall a. (a -> ()) -> NFData a
rnf :: PortDirection -> ()
$crnf :: PortDirection -> ()
NFData,Int -> PortDirection -> Int
PortDirection -> Int
(Int -> PortDirection -> Int)
-> (PortDirection -> Int) -> Hashable PortDirection
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PortDirection -> Int
$chash :: PortDirection -> Int
hashWithSalt :: Int -> PortDirection -> Int
$chashWithSalt :: Int -> PortDirection -> Int
Hashable)
instance NFData Declaration where
rnf :: Declaration -> ()
rnf Declaration
a = Declaration
a Declaration -> () -> ()
`seq` ()
data Modifier
= Indexed (HWType,Int,Int)
| DC (HWType,Int)
| VecAppend
| RTreeAppend
| Sliced (HWType,Int,Int)
| Nested Modifier Modifier
deriving Int -> Modifier -> ShowS
[Modifier] -> ShowS
Modifier -> String
(Int -> Modifier -> ShowS)
-> (Modifier -> String) -> ([Modifier] -> ShowS) -> Show Modifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Modifier] -> ShowS
$cshowList :: [Modifier] -> ShowS
show :: Modifier -> String
$cshow :: Modifier -> String
showsPrec :: Int -> Modifier -> ShowS
$cshowsPrec :: Int -> Modifier -> ShowS
Show
data Expr
= Literal !(Maybe (HWType,Size)) !Literal
| DataCon !HWType !Modifier [Expr]
| Identifier !Identifier !(Maybe Modifier)
| DataTag !HWType !(Either Identifier Identifier)
| BlackBoxE
!Text
[BlackBoxTemplate]
[BlackBoxTemplate]
[((Text,Text),BlackBox)]
!BlackBox
!BlackBoxContext
!Bool
| ConvBV (Maybe Identifier) HWType Bool Expr
| IfThenElse Expr Expr Expr
| Noop
deriving Int -> Expr -> ShowS
[Expr] -> ShowS
Expr -> String
(Int -> Expr -> ShowS)
-> (Expr -> String) -> ([Expr] -> ShowS) -> Show Expr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Expr] -> ShowS
$cshowList :: [Expr] -> ShowS
show :: Expr -> String
$cshow :: Expr -> String
showsPrec :: Int -> Expr -> ShowS
$cshowsPrec :: Int -> Expr -> ShowS
Show
instance NFData Expr where
rnf :: Expr -> ()
rnf Expr
x = Expr
x Expr -> () -> ()
`seq` ()
data Literal
= NumLit !Integer
| BitLit !Bit
| BitVecLit !Integer !Integer
| BoolLit !Bool
| VecLit [Literal]
| StringLit !String
deriving (Literal -> Literal -> Bool
(Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool) -> Eq Literal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c== :: Literal -> Literal -> Bool
Eq,Int -> Literal -> ShowS
[Literal] -> ShowS
Literal -> String
(Int -> Literal -> ShowS)
-> (Literal -> String) -> ([Literal] -> ShowS) -> Show Literal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Literal] -> ShowS
$cshowList :: [Literal] -> ShowS
show :: Literal -> String
$cshow :: Literal -> String
showsPrec :: Int -> Literal -> ShowS
$cshowsPrec :: Int -> Literal -> ShowS
Show)
data Bit
= H
| L
| U
| Z
deriving (Bit -> Bit -> Bool
(Bit -> Bit -> Bool) -> (Bit -> Bit -> Bool) -> Eq Bit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bit -> Bit -> Bool
$c/= :: Bit -> Bit -> Bool
== :: Bit -> Bit -> Bool
$c== :: Bit -> Bit -> Bool
Eq,Int -> Bit -> ShowS
[Bit] -> ShowS
Bit -> String
(Int -> Bit -> ShowS)
-> (Bit -> String) -> ([Bit] -> ShowS) -> Show Bit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bit] -> ShowS
$cshowList :: [Bit] -> ShowS
show :: Bit -> String
$cshow :: Bit -> String
showsPrec :: Int -> Bit -> ShowS
$cshowsPrec :: Int -> Bit -> ShowS
Show,Typeable,Bit -> Q Exp
Bit -> Q (TExp Bit)
(Bit -> Q Exp) -> (Bit -> Q (TExp Bit)) -> Lift Bit
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Bit -> Q (TExp Bit)
$cliftTyped :: Bit -> Q (TExp Bit)
lift :: Bit -> Q Exp
$clift :: Bit -> Q Exp
Lift)
toBit :: Integer
-> Integer
-> Bit
toBit :: Integer -> Integer -> Bit
toBit Integer
m Integer
i = if Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Integer
m Int
0
then Bit
U
else if Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Integer
i Int
0 then Bit
H else Bit
L
data BlackBoxContext
= Context
{ BlackBoxContext -> Identifier
bbName :: Text
, BlackBoxContext -> (Expr, HWType)
bbResult :: (Expr,HWType)
, BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs :: [(Expr,HWType,Bool)]
, BlackBoxContext
-> IntMap
[(Either BlackBox (Identifier, [Declaration]), WireOrReg,
[BlackBoxTemplate], [BlackBoxTemplate],
[((Identifier, Identifier), BlackBox)], BlackBoxContext)]
bbFunctions :: IntMap [(Either BlackBox (Identifier,[Declaration])
,WireOrReg
,[BlackBoxTemplate]
,[BlackBoxTemplate]
,[((Text,Text),BlackBox)]
,BlackBoxContext)]
, BlackBoxContext -> [Identifier]
bbQsysIncName :: [Identifier]
, BlackBoxContext -> Int
bbLevel :: Int
, BlackBoxContext -> Identifier
bbCompName :: Identifier
, BlackBoxContext -> Maybe Identifier
bbCtxName :: Maybe Identifier
}
deriving Int -> BlackBoxContext -> ShowS
[BlackBoxContext] -> ShowS
BlackBoxContext -> String
(Int -> BlackBoxContext -> ShowS)
-> (BlackBoxContext -> String)
-> ([BlackBoxContext] -> ShowS)
-> Show BlackBoxContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlackBoxContext] -> ShowS
$cshowList :: [BlackBoxContext] -> ShowS
show :: BlackBoxContext -> String
$cshow :: BlackBoxContext -> String
showsPrec :: Int -> BlackBoxContext -> ShowS
$cshowsPrec :: Int -> BlackBoxContext -> ShowS
Show
type BBName = String
type BBHash = Int
data BlackBox
= BBTemplate BlackBoxTemplate
| BBFunction BBName BBHash TemplateFunction
deriving ((forall x. BlackBox -> Rep BlackBox x)
-> (forall x. Rep BlackBox x -> BlackBox) -> Generic BlackBox
forall x. Rep BlackBox x -> BlackBox
forall x. BlackBox -> Rep BlackBox x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlackBox x -> BlackBox
$cfrom :: forall x. BlackBox -> Rep BlackBox x
Generic, BlackBox -> ()
(BlackBox -> ()) -> NFData BlackBox
forall a. (a -> ()) -> NFData a
rnf :: BlackBox -> ()
$crnf :: BlackBox -> ()
NFData, Get BlackBox
[BlackBox] -> Put
BlackBox -> Put
(BlackBox -> Put)
-> Get BlackBox -> ([BlackBox] -> Put) -> Binary BlackBox
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [BlackBox] -> Put
$cputList :: [BlackBox] -> Put
get :: Get BlackBox
$cget :: Get BlackBox
put :: BlackBox -> Put
$cput :: BlackBox -> Put
Binary)
data TemplateFunction where
TemplateFunction
:: [Int]
-> (BlackBoxContext -> Bool)
-> (forall s . Backend s => BlackBoxContext -> Lazy.State s Doc)
-> TemplateFunction
instance Show BlackBox where
show :: BlackBox -> String
show (BBTemplate BlackBoxTemplate
t) = BlackBoxTemplate -> String
forall a. Show a => a -> String
show BlackBoxTemplate
t
show (BBFunction String
nm Int
hsh TemplateFunction
_) =
String
"<TemplateFunction(nm=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
nm String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", hash=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
hsh String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")>"
instance NFData TemplateFunction where
rnf :: TemplateFunction -> ()
rnf (TemplateFunction [Int]
is BlackBoxContext -> Bool
f forall s. Backend s => BlackBoxContext -> State s Doc
_) = [Int] -> ()
forall a. NFData a => a -> ()
rnf [Int]
is () -> () -> ()
`seq` BlackBoxContext -> Bool
f (BlackBoxContext -> Bool) -> () -> ()
`seq` ()
instance Binary TemplateFunction where
put :: TemplateFunction -> Put
put (TemplateFunction [Int]
is BlackBoxContext -> Bool
_ forall s. Backend s => BlackBoxContext -> State s Doc
_ ) = [Int] -> Put
forall t. Binary t => t -> Put
put [Int]
is
get :: Get TemplateFunction
get = (\[Int]
is -> [Int]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [Int]
is BlackBoxContext -> Bool
forall b a. b -> a
err forall s. Backend s => BlackBoxContext -> State s Doc
forall b a. b -> a
err) ([Int] -> TemplateFunction) -> Get [Int] -> Get TemplateFunction
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Int]
forall t. Binary t => Get t
get
where err :: b -> a
err = a -> b -> a
forall a b. a -> b -> a
const (a -> b -> a) -> a -> b -> a
forall a b. (a -> b) -> a -> b
$ String -> a
forall a. HasCallStack => String -> a
error String
"TemplateFunction functions can't be preserved by serialisation"
data NetlistId
= NetlistId Identifier Type
| CoreId Id
| MultiId [Id]
deriving Int -> NetlistId -> ShowS
[NetlistId] -> ShowS
NetlistId -> String
(Int -> NetlistId -> ShowS)
-> (NetlistId -> String)
-> ([NetlistId] -> ShowS)
-> Show NetlistId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetlistId] -> ShowS
$cshowList :: [NetlistId] -> ShowS
show :: NetlistId -> String
$cshow :: NetlistId -> String
showsPrec :: Int -> NetlistId -> ShowS
$cshowsPrec :: Int -> NetlistId -> ShowS
Show
netlistId
:: (Identifier -> r)
-> (Id -> r)
-> NetlistId
-> [r]
netlistId :: (Identifier -> r) -> (Id -> r) -> NetlistId -> [r]
netlistId Identifier -> r
f Id -> r
g = \case
NetlistId Identifier
i Type
_ -> [Identifier -> r
f Identifier
i]
CoreId Id
i -> [Id -> r
g Id
i]
MultiId [Id]
is -> (Id -> r) -> [Id] -> [r]
forall a b. (a -> b) -> [a] -> [b]
map Id -> r
g [Id]
is
netlistId1
:: HasCallStack
=> (Identifier -> r)
-> (Id -> r)
-> NetlistId
-> r
netlistId1 :: (Identifier -> r) -> (Id -> r) -> NetlistId -> r
netlistId1 Identifier -> r
f Id -> r
g = \case
NetlistId Identifier
i Type
_ -> Identifier -> r
f Identifier
i
CoreId Id
i -> Id -> r
g Id
i
NetlistId
m -> String -> r
forall a. HasCallStack => String -> a
error (String
"netlistId1 MultiId: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ NetlistId -> String
forall a. Show a => a -> String
show NetlistId
m)
netlistTypes
:: NetlistId
-> [Type]
netlistTypes :: NetlistId -> [Type]
netlistTypes = \case
NetlistId Identifier
_ Type
t -> [Type
t]
CoreId Id
i -> [Id -> Type
forall a. Var a -> Type
varType Id
i]
MultiId [Id]
is -> (Id -> Type) -> [Id] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Type
forall a. Var a -> Type
varType [Id]
is
netlistTypes1
:: HasCallStack
=> NetlistId
-> Type
netlistTypes1 :: NetlistId -> Type
netlistTypes1 = \case
NetlistId Identifier
_ Type
t -> Type
t
CoreId Id
i -> Id -> Type
forall a. Var a -> Type
varType Id
i
NetlistId
m -> String -> Type
forall a. HasCallStack => String -> a
error (String
"netlistTypes1 MultiId: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ NetlistId -> String
forall a. Show a => a -> String
show NetlistId
m)
data DeclarationType
= Concurrent
| Sequential
emptyBBContext :: Text -> BlackBoxContext
emptyBBContext :: Identifier -> BlackBoxContext
emptyBBContext Identifier
n
= Context :: Identifier
-> (Expr, HWType)
-> [(Expr, HWType, Bool)]
-> IntMap
[(Either BlackBox (Identifier, [Declaration]), WireOrReg,
[BlackBoxTemplate], [BlackBoxTemplate],
[((Identifier, Identifier), BlackBox)], BlackBoxContext)]
-> [Identifier]
-> Int
-> Identifier
-> Maybe Identifier
-> BlackBoxContext
Context
{ bbName :: Identifier
bbName = Identifier
n
, bbResult :: (Expr, HWType)
bbResult = (Identifier -> Maybe Modifier -> Expr
Identifier (String -> Identifier
pack String
"__EMPTY__") Maybe Modifier
forall a. Maybe a
Nothing, Maybe HWType -> HWType
Void Maybe HWType
forall a. Maybe a
Nothing)
, bbInputs :: [(Expr, HWType, Bool)]
bbInputs = []
, bbFunctions :: IntMap
[(Either BlackBox (Identifier, [Declaration]), WireOrReg,
[BlackBoxTemplate], [BlackBoxTemplate],
[((Identifier, Identifier), BlackBox)], BlackBoxContext)]
bbFunctions = IntMap
[(Either BlackBox (Identifier, [Declaration]), WireOrReg,
[BlackBoxTemplate], [BlackBoxTemplate],
[((Identifier, Identifier), BlackBox)], BlackBoxContext)]
forall a. IntMap a
empty
, bbQsysIncName :: [Identifier]
bbQsysIncName = []
, bbLevel :: Int
bbLevel = (-Int
1)
, bbCompName :: Identifier
bbCompName = String -> Identifier
pack String
"__NOCOMPNAME__"
, bbCtxName :: Maybe Identifier
bbCtxName = Maybe Identifier
forall a. Maybe a
Nothing
}
makeLenses ''NetlistEnv
makeLenses ''NetlistState