{-# LANGUAGE CPP #-}
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE Safe #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Annotations.TopEntity
(
TopEntity (..)
, PortName (..)
, defSyn
)
where
import GHC.Generics
import qualified Language.Haskell.TH as TH
import Language.Haskell.TH.Syntax (Lift(..))
#if MIN_VERSION_template_haskell(2,16,0)
import Language.Haskell.TH.Compat
#endif
import Data.Data
data TopEntity
= Synthesize
{ TopEntity -> String
t_name :: String
, TopEntity -> [PortName]
t_inputs :: [PortName]
, TopEntity -> PortName
t_output :: PortName
}
| TestBench TH.Name
deriving (TopEntity -> TopEntity -> Bool
(TopEntity -> TopEntity -> Bool)
-> (TopEntity -> TopEntity -> Bool) -> Eq TopEntity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TopEntity -> TopEntity -> Bool
== :: TopEntity -> TopEntity -> Bool
$c/= :: TopEntity -> TopEntity -> Bool
/= :: TopEntity -> TopEntity -> Bool
Eq,Typeable TopEntity
Typeable TopEntity =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopEntity -> c TopEntity)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopEntity)
-> (TopEntity -> Constr)
-> (TopEntity -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopEntity))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopEntity))
-> ((forall b. Data b => b -> b) -> TopEntity -> TopEntity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r)
-> (forall u. (forall d. Data d => d -> u) -> TopEntity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TopEntity -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity)
-> Data TopEntity
TopEntity -> Constr
TopEntity -> DataType
(forall b. Data b => b -> b) -> TopEntity -> TopEntity
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TopEntity -> u
forall u. (forall d. Data d => d -> u) -> TopEntity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopEntity
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopEntity -> c TopEntity
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopEntity)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopEntity)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopEntity -> c TopEntity
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopEntity -> c TopEntity
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopEntity
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopEntity
$ctoConstr :: TopEntity -> Constr
toConstr :: TopEntity -> Constr
$cdataTypeOf :: TopEntity -> DataType
dataTypeOf :: TopEntity -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopEntity)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopEntity)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopEntity)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopEntity)
$cgmapT :: (forall b. Data b => b -> b) -> TopEntity -> TopEntity
gmapT :: (forall b. Data b => b -> b) -> TopEntity -> TopEntity
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopEntity -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TopEntity -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TopEntity -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TopEntity -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TopEntity -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopEntity -> m TopEntity
Data,Int -> TopEntity -> ShowS
[TopEntity] -> ShowS
TopEntity -> String
(Int -> TopEntity -> ShowS)
-> (TopEntity -> String)
-> ([TopEntity] -> ShowS)
-> Show TopEntity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TopEntity -> ShowS
showsPrec :: Int -> TopEntity -> ShowS
$cshow :: TopEntity -> String
show :: TopEntity -> String
$cshowList :: [TopEntity] -> ShowS
showList :: [TopEntity] -> ShowS
Show,(forall x. TopEntity -> Rep TopEntity x)
-> (forall x. Rep TopEntity x -> TopEntity) -> Generic TopEntity
forall x. Rep TopEntity x -> TopEntity
forall x. TopEntity -> Rep TopEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TopEntity -> Rep TopEntity x
from :: forall x. TopEntity -> Rep TopEntity x
$cto :: forall x. Rep TopEntity x -> TopEntity
to :: forall x. Rep TopEntity x -> TopEntity
Generic)
instance Lift TopEntity where
lift :: forall (m :: Type -> Type). Quote m => TopEntity -> m Exp
lift (Synthesize String
name [PortName]
inputs PortName
output) =
[m Exp] -> m Exp
forall (m :: Type -> Type). Quote m => [m Exp] -> m Exp
TH.appsE
[ Name -> m Exp
forall (m :: Type -> Type). Quote m => Name -> m Exp
TH.conE 'Synthesize
, String -> m Exp
forall t (m :: Type -> Type). (Lift t, Quote m) => t -> m Exp
forall (m :: Type -> Type). Quote m => String -> m Exp
lift String
name
, [PortName] -> m Exp
forall t (m :: Type -> Type). (Lift t, Quote m) => t -> m Exp
forall (m :: Type -> Type). Quote m => [PortName] -> m Exp
lift [PortName]
inputs
, PortName -> m Exp
forall t (m :: Type -> Type). (Lift t, Quote m) => t -> m Exp
forall (m :: Type -> Type). Quote m => PortName -> m Exp
lift PortName
output
]
lift (TestBench Name
_) = String -> m Exp
forall a. HasCallStack => String -> a
error String
"Cannot lift a TestBench"
#if MIN_VERSION_template_haskell(2,16,0)
liftTyped :: forall (m :: Type -> Type).
Quote m =>
TopEntity -> Code m TopEntity
liftTyped = TopEntity -> Code m TopEntity
forall a (m :: Type -> Type). (Lift a, Quote m) => a -> Code m a
liftTypedFromUntyped
#endif
data PortName
= PortName String
| PortProduct String [PortName]
deriving (PortName -> PortName -> Bool
(PortName -> PortName -> Bool)
-> (PortName -> PortName -> Bool) -> Eq PortName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PortName -> PortName -> Bool
== :: PortName -> PortName -> Bool
$c/= :: PortName -> PortName -> Bool
/= :: PortName -> PortName -> Bool
Eq,Typeable PortName
Typeable PortName =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PortName -> c PortName)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PortName)
-> (PortName -> Constr)
-> (PortName -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PortName))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName))
-> ((forall b. Data b => b -> b) -> PortName -> PortName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r)
-> (forall u. (forall d. Data d => d -> u) -> PortName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> PortName -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName)
-> Data PortName
PortName -> Constr
PortName -> DataType
(forall b. Data b => b -> b) -> PortName -> PortName
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PortName -> u
forall u. (forall d. Data d => d -> u) -> PortName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PortName
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PortName -> c PortName
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PortName)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PortName -> c PortName
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PortName -> c PortName
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PortName
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PortName
$ctoConstr :: PortName -> Constr
toConstr :: PortName -> Constr
$cdataTypeOf :: PortName -> DataType
dataTypeOf :: PortName -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PortName)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PortName)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName)
$cgmapT :: (forall b. Data b => b -> b) -> PortName -> PortName
gmapT :: (forall b. Data b => b -> b) -> PortName -> PortName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PortName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PortName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PortName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PortName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PortName -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PortName -> m PortName
Data,Int -> PortName -> ShowS
[PortName] -> ShowS
PortName -> String
(Int -> PortName -> ShowS)
-> (PortName -> String) -> ([PortName] -> ShowS) -> Show PortName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PortName -> ShowS
showsPrec :: Int -> PortName -> ShowS
$cshow :: PortName -> String
show :: PortName -> String
$cshowList :: [PortName] -> ShowS
showList :: [PortName] -> ShowS
Show,(forall x. PortName -> Rep PortName x)
-> (forall x. Rep PortName x -> PortName) -> Generic PortName
forall x. Rep PortName x -> PortName
forall x. PortName -> Rep PortName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PortName -> Rep PortName x
from :: forall x. PortName -> Rep PortName x
$cto :: forall x. Rep PortName x -> PortName
to :: forall x. Rep PortName x -> PortName
Generic,(forall (m :: Type -> Type). Quote m => PortName -> m Exp)
-> (forall (m :: Type -> Type).
Quote m =>
PortName -> Code m PortName)
-> Lift PortName
forall t.
(forall (m :: Type -> Type). Quote m => t -> m Exp)
-> (forall (m :: Type -> Type). Quote m => t -> Code m t) -> Lift t
forall (m :: Type -> Type). Quote m => PortName -> m Exp
forall (m :: Type -> Type). Quote m => PortName -> Code m PortName
$clift :: forall (m :: Type -> Type). Quote m => PortName -> m Exp
lift :: forall (m :: Type -> Type). Quote m => PortName -> m Exp
$cliftTyped :: forall (m :: Type -> Type). Quote m => PortName -> Code m PortName
liftTyped :: forall (m :: Type -> Type). Quote m => PortName -> Code m PortName
Lift)
defSyn :: String -> TopEntity
defSyn :: String -> TopEntity
defSyn String
name = Synthesize
{ t_name :: String
t_name = String
name
, t_inputs :: [PortName]
t_inputs = []
, t_output :: PortName
t_output = String -> PortName
PortName String
""
}