{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeFamilies #-}
module Clash.Backend.VHDL (VHDLState) where
import Control.Arrow (second)
import Control.Applicative (liftA2)
import Control.Lens hiding (Indexed, Empty)
import Control.Monad (forM,join,zipWithM)
import Control.Monad.State (State, StateT)
import Data.Bifunctor (first)
import Data.Bits (testBit, Bits)
import qualified Data.ByteString.Char8 as B8
import Data.Coerce (coerce)
import Data.Function (on)
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap
import qualified Data.HashMap.Strict as HashMapS
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.List
(mapAccumL, nub, nubBy, intersperse, group, sort)
import Data.List.Extra ((<:>), equalLength, zipEqual)
import Data.Maybe (catMaybes,mapMaybe)
import Data.Monoid (Ap(Ap))
import Data.Monoid.Extra ()
import qualified Data.Text.Lazy as T
import qualified Data.Text as TextS
import Data.Text.Extra
#if MIN_VERSION_prettyprinter(1,7,0)
import qualified Prettyprinter as PP
#else
import qualified Data.Text.Prettyprint.Doc as PP
#endif
import Data.Text.Prettyprint.Doc.Extra
import GHC.Stack (HasCallStack)
import qualified System.FilePath
import Text.Printf
import Clash.Annotations.Primitive (HDL (..))
import Clash.Annotations.BitRepresentation.Internal
(ConstrRepr'(..), DataRepr'(..))
import Clash.Annotations.BitRepresentation.ClashLib
(bitsToBits)
import Clash.Annotations.BitRepresentation.Util
(BitOrigin(Lit, Field), bitOrigins, bitRanges)
import Clash.Backend
import Clash.Core.Var (Attr'(..),attrName)
import Clash.Debug (traceIf)
import Clash.Driver.Types (ClashOpts(..))
import Clash.Explicit.BlockRam.Internal (unpackNats)
import Clash.Netlist.BlackBox.Types (HdlSyn (..))
import Clash.Netlist.BlackBox.Util
(extractLiterals, renderBlackBox, renderFilePath)
import qualified Clash.Netlist.Id as Id
import Clash.Netlist.Types hiding (intWidth)
import Clash.Netlist.Util
import Clash.Util
(SrcSpan, noSrcSpan, clogBase, curLoc, makeCached, indexNote)
import qualified Clash.Util.Interpolate as I
import Clash.Util.Graph (reverseTopSort)
import Clash.Backend.Verilog (Range (..), continueWithRange)
import Debug.Trace (traceM)
data VHDLState =
VHDLState
{ VHDLState -> HashSet HWType
_tyCache :: HashSet HWType
, VHDLState -> HashMap (HWType, Bool) Text
_nameCache :: (HashMap (HWType, Bool) TextS.Text)
, VHDLState -> Text
_modNm :: ModName
, VHDLState -> Identifier
_topNm :: Identifier
, VHDLState -> SrcSpan
_srcSpan :: SrcSpan
, VHDLState -> [Text]
_libraries :: [T.Text]
, VHDLState -> [Text]
_packages :: [T.Text]
, VHDLState -> [(String, Doc)]
_includes :: [(String,Doc)]
, VHDLState -> [(String, String)]
_dataFiles :: [(String,FilePath)]
, VHDLState -> [(String, String)]
_memoryDataFiles:: [(String,String)]
, VHDLState -> IdentifierSet
_idSeen :: IdentifierSet
, VHDLState -> Bool
_tyPkgCtx :: Bool
, VHDLState -> Int
_intWidth :: Int
, VHDLState -> HdlSyn
_hdlsyn :: HdlSyn
, VHDLState -> Maybe (Maybe Int)
_undefValue :: Maybe (Maybe Int)
, VHDLState -> HashMap (Maybe [Text], [HWType]) [Text]
_productFieldNameCache :: HashMap (Maybe [TextS.Text], [HWType]) [TextS.Text]
, VHDLState -> HashMap HWType [Text]
_enumNameCache :: HashMap HWType [TextS.Text]
, VHDLState -> AggressiveXOptBB
_aggressiveXOptBB_ :: AggressiveXOptBB
, VHDLState -> RenderEnums
_renderEnums_ :: RenderEnums
, VHDLState -> DomainMap
_domainConfigurations_ :: DomainMap
}
makeLenses ''VHDLState
instance HasIdentifierSet VHDLState where
identifierSet :: (IdentifierSet -> f IdentifierSet) -> VHDLState -> f VHDLState
identifierSet = (IdentifierSet -> f IdentifierSet) -> VHDLState -> f VHDLState
Lens' VHDLState IdentifierSet
idSeen
instance Backend VHDLState where
initBackend :: ClashOpts -> VHDLState
initBackend ClashOpts
opts = VHDLState :: HashSet HWType
-> HashMap (HWType, Bool) Text
-> Text
-> Identifier
-> SrcSpan
-> [Text]
-> [Text]
-> [(String, Doc)]
-> [(String, String)]
-> [(String, String)]
-> IdentifierSet
-> Bool
-> Int
-> HdlSyn
-> Maybe (Maybe Int)
-> HashMap (Maybe [Text], [HWType]) [Text]
-> HashMap HWType [Text]
-> AggressiveXOptBB
-> RenderEnums
-> DomainMap
-> VHDLState
VHDLState
{ _tyCache :: HashSet HWType
_tyCache=HashSet HWType
forall a. Monoid a => a
mempty
, _nameCache :: HashMap (HWType, Bool) Text
_nameCache=HashMap (HWType, Bool) Text
forall a. Monoid a => a
mempty
, _modNm :: Text
_modNm=Text
""
, _topNm :: Identifier
_topNm=HasCallStack => Text -> Identifier
Text -> Identifier
Id.unsafeMake Text
""
, _srcSpan :: SrcSpan
_srcSpan=SrcSpan
noSrcSpan
, _libraries :: [Text]
_libraries=[]
, _packages :: [Text]
_packages=[]
, _includes :: [(String, Doc)]
_includes=[]
, _dataFiles :: [(String, String)]
_dataFiles=[]
, _memoryDataFiles :: [(String, String)]
_memoryDataFiles=[]
, _idSeen :: IdentifierSet
_idSeen=Bool -> PreserveCase -> HDL -> IdentifierSet
Id.emptyIdentifierSet (ClashOpts -> Bool
opt_escapedIds ClashOpts
opts) (ClashOpts -> PreserveCase
opt_lowerCaseBasicIds ClashOpts
opts) HDL
VHDL
, _tyPkgCtx :: Bool
_tyPkgCtx=Bool
False
, _intWidth :: Int
_intWidth=ClashOpts -> Int
opt_intWidth ClashOpts
opts
, _hdlsyn :: HdlSyn
_hdlsyn=ClashOpts -> HdlSyn
opt_hdlSyn ClashOpts
opts
, _undefValue :: Maybe (Maybe Int)
_undefValue=ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined ClashOpts
opts
, _productFieldNameCache :: HashMap (Maybe [Text], [HWType]) [Text]
_productFieldNameCache=HashMap (Maybe [Text], [HWType]) [Text]
forall a. Monoid a => a
mempty
, _enumNameCache :: HashMap HWType [Text]
_enumNameCache=HashMap HWType [Text]
forall a. Monoid a => a
mempty
, _aggressiveXOptBB_ :: AggressiveXOptBB
_aggressiveXOptBB_=Bool -> AggressiveXOptBB
coerce (ClashOpts -> Bool
opt_aggressiveXOptBB ClashOpts
opts)
, _renderEnums_ :: RenderEnums
_renderEnums_=Bool -> RenderEnums
coerce (ClashOpts -> Bool
opt_renderEnums ClashOpts
opts)
, _domainConfigurations_ :: DomainMap
_domainConfigurations_=DomainMap
emptyDomainMap
}
hdlKind :: VHDLState -> HDL
hdlKind = HDL -> VHDLState -> HDL
forall a b. a -> b -> a
const HDL
VHDL
primDirs :: VHDLState -> IO [String]
primDirs = IO [String] -> VHDLState -> IO [String]
forall a b. a -> b -> a
const (IO [String] -> VHDLState -> IO [String])
-> IO [String] -> VHDLState -> IO [String]
forall a b. (a -> b) -> a -> b
$ do String
root <- IO String
primsRoot
[String] -> IO [String]
forall (m :: Type -> Type) a. Monad m => a -> m a
return [ String
root String -> String -> String
System.FilePath.</> String
"common"
, String
root String -> String -> String
System.FilePath.</> String
"vhdl"
]
extractTypes :: VHDLState -> HashSet HWType
extractTypes = VHDLState -> HashSet HWType
_tyCache
name :: VHDLState -> String
name = String -> VHDLState -> String
forall a b. a -> b -> a
const String
"vhdl"
extension :: VHDLState -> String
extension = String -> VHDLState -> String
forall a b. a -> b -> a
const String
".vhdl"
genHDL :: Text
-> SrcSpan
-> IdentifierSet
-> Component
-> Ap (State VHDLState) ((String, Doc), [(String, Doc)])
genHDL = Text
-> SrcSpan
-> IdentifierSet
-> Component
-> Ap (State VHDLState) ((String, Doc), [(String, Doc)])
genVHDL
mkTyPackage :: Text -> [HWType] -> Ap (State VHDLState) [(String, Doc)]
mkTyPackage = Text -> [HWType] -> Ap (State VHDLState) [(String, Doc)]
mkTyPackage_
hdlHWTypeKind :: HWType -> State VHDLState HWKind
hdlHWTypeKind = \case
Vector {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
UserType
RTree {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
UserType
Product {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
UserType
MemBlob {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
UserType
Sum {} -> do
RenderEnums Bool
enums <- State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
if Bool
enums then HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
UserType else HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
Clock {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
Reset {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
Enable {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
Index {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
CustomSP {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
SP {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
CustomSum {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
CustomProduct {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
SynonymType
BitVector Int
_ -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
HWType
Bool -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
HWType
Bit -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
Unsigned {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
Signed {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
HWType
String -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
HWType
Integer -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
HWType
FileType -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
BiDirectional PortDirection
_ HWType
ty -> HWType -> State VHDLState HWKind
forall state. Backend state => HWType -> State state HWKind
hdlHWTypeKind HWType
ty
Annotated [Attr']
_ HWType
ty -> HWType -> State VHDLState HWKind
forall state. Backend state => HWType -> State state HWKind
hdlHWTypeKind HWType
ty
Void {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
KnownDomain {} -> HWKind -> State VHDLState HWKind
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure HWKind
PrimitiveType
hdlType :: Usage -> HWType -> Ap (State VHDLState) Doc
hdlType Usage
Internal (HWType -> HWType
filterTransparent -> HWType
ty) = HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
ty
hdlType (External Text
nm) (HWType -> HWType
filterTransparent -> HWType
ty) =
let sized :: Ap (State VHDLState) Doc
sized = HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
ty in
case HWType
ty of
HWType
Bit -> Ap (State VHDLState) Doc
sized
HWType
Bool -> Ap (State VHDLState) Doc
sized
Signed Int
_ -> Ap (State VHDLState) Doc
sized
Unsigned Int
_ -> Ap (State VHDLState) Doc
sized
BitVector Int
_ -> Ap (State VHDLState) Doc
sized
HWType
_ -> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
nm Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
dot Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
sized
hdlTypeErrValue :: HWType -> Ap (State VHDLState) Doc
hdlTypeErrValue = HWType -> Ap (State VHDLState) Doc
sizedQualTyNameErrValue
hdlTypeMark :: HWType -> Ap (State VHDLState) Doc
hdlTypeMark = HWType -> Ap (State VHDLState) Doc
qualTyName
hdlRecSel :: HWType -> Int -> Ap (State VHDLState) Doc
hdlRecSel = HWType -> Int -> Ap (State VHDLState) Doc
vhdlRecSel
hdlSig :: Text -> HWType -> Ap (State VHDLState) Doc
hdlSig Text
t HWType
ty = Ap (State VHDLState) Doc -> HWType -> Ap (State VHDLState) Doc
sigDecl (Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
t) HWType
ty
genStmt :: Bool -> State VHDLState Doc
genStmt = State VHDLState Doc -> Bool -> State VHDLState Doc
forall a b. a -> b -> a
const State VHDLState Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
inst :: Declaration -> Ap (State VHDLState) (Maybe Doc)
inst = Declaration -> Ap (State VHDLState) (Maybe Doc)
inst_
expr :: Bool -> Expr -> Ap (State VHDLState) Doc
expr = HasCallStack => Bool -> Expr -> Ap (State VHDLState) Doc
Bool -> Expr -> Ap (State VHDLState) Doc
expr_
iwWidth :: State VHDLState Int
iwWidth = Getting Int VHDLState Int -> State VHDLState Int
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Int VHDLState Int
Lens' VHDLState Int
intWidth
toBV :: HWType -> Text -> Ap (State VHDLState) Doc
toBV HWType
t Text
id_ = do
RenderEnums
enums <- State VHDLState RenderEnums -> Ap (State VHDLState) RenderEnums
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
if RenderEnums -> HWType -> Bool
isBV RenderEnums
enums HWType
t then Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
id_ else do
Text
nm <- State VHDLState Text -> Ap (State VHDLState) Text
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState Text -> Ap (State VHDLState) Text)
-> State VHDLState Text -> Ap (State VHDLState) Text
forall a b. (a -> b) -> a -> b
$ Getting Text VHDLState Text -> State VHDLState Text
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Text VHDLState Text
Lens' VHDLState Text
modNm
let e :: Ap (State VHDLState) Doc
e = HWType -> Ap (State VHDLState) Doc
forall state. Backend state => HWType -> Ap (State state) Doc
hdlTypeMark HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
squote Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
id_)
Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
nm Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"_types.toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
e
fromBV :: HWType -> Text -> Ap (State VHDLState) Doc
fromBV HWType
t Text
id_ = do
RenderEnums
enums <- State VHDLState RenderEnums -> Ap (State VHDLState) RenderEnums
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
if RenderEnums -> HWType -> Bool
isBV RenderEnums
enums HWType
t then Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
id_ else do
Text
nm <- State VHDLState Text -> Ap (State VHDLState) Text
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState Text -> Ap (State VHDLState) Text)
-> State VHDLState Text -> Ap (State VHDLState) Text
forall a b. (a -> b) -> a -> b
$ Getting Text VHDLState Text -> State VHDLState Text
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Text VHDLState Text
Lens' VHDLState Text
modNm
HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
nm Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"_types.fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
id_))
hdlSyn :: State VHDLState HdlSyn
hdlSyn = Getting HdlSyn VHDLState HdlSyn -> State VHDLState HdlSyn
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting HdlSyn VHDLState HdlSyn
Lens' VHDLState HdlSyn
hdlsyn
setModName :: Text -> VHDLState -> VHDLState
setModName Text
nm VHDLState
s = VHDLState
s {_modNm :: Text
_modNm = Text
nm}
setTopName :: Identifier -> VHDLState -> VHDLState
setTopName Identifier
nm VHDLState
s = VHDLState
s {_topNm :: Identifier
_topNm = Identifier
nm}
getTopName :: State VHDLState Identifier
getTopName = Getting Identifier VHDLState Identifier
-> State VHDLState Identifier
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Identifier VHDLState Identifier
Lens' VHDLState Identifier
topNm
setSrcSpan :: SrcSpan -> State VHDLState ()
setSrcSpan = ((SrcSpan -> Identity SrcSpan) -> VHDLState -> Identity VHDLState
Lens' VHDLState SrcSpan
srcSpan ((SrcSpan -> Identity SrcSpan) -> VHDLState -> Identity VHDLState)
-> SrcSpan -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.=)
getSrcSpan :: State VHDLState SrcSpan
getSrcSpan = Getting SrcSpan VHDLState SrcSpan -> State VHDLState SrcSpan
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting SrcSpan VHDLState SrcSpan
Lens' VHDLState SrcSpan
srcSpan
blockDecl :: Identifier -> [Declaration] -> Ap (State VHDLState) Doc
blockDecl Identifier
nm [Declaration]
ds = do
Doc
decs <- [Declaration] -> Ap (State VHDLState) Doc
decls [Declaration]
ds
let attrs :: [(Identifier, Attr')]
attrs = [ (Identifier
id_, Attr'
attr)
| NetDecl' Maybe Text
_ WireOrReg
_ Identifier
id_ (Right HWType
hwtype) Maybe Expr
_ <- [Declaration]
ds
, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
if Doc -> Bool
isEmpty Doc
decs
then [Declaration] -> Ap (State VHDLState) Doc
insts [Declaration]
ds
else Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
nest Int
2
(Identifier -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Identifier
nm Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"block" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
decs Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
if [(Identifier, Attr')] -> Bool
forall (t :: Type -> Type) a. Foldable t => t a -> Bool
null [(Identifier, Attr')]
attrs
then Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
else Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Text -> [(Identifier, Attr')] -> Ap (State VHDLState) Doc
renderAttrs (String -> Text
TextS.pack String
"signal") [(Identifier, Attr')]
attrs) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
nest Int
2
(Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
[Declaration] -> Ap (State VHDLState) Doc
insts [Declaration]
ds) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end block" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
addIncludes :: [(String, Doc)] -> State VHDLState ()
addIncludes [(String, Doc)]
inc = ([(String, Doc)] -> Identity [(String, Doc)])
-> VHDLState -> Identity VHDLState
Lens' VHDLState [(String, Doc)]
includes (([(String, Doc)] -> Identity [(String, Doc)])
-> VHDLState -> Identity VHDLState)
-> ([(String, Doc)] -> [(String, Doc)]) -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= ([(String, Doc)]
inc[(String, Doc)] -> [(String, Doc)] -> [(String, Doc)]
forall a. [a] -> [a] -> [a]
++)
addLibraries :: [Text] -> State VHDLState ()
addLibraries [Text]
libs = ([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState
Lens' VHDLState [Text]
libraries (([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState)
-> ([Text] -> [Text]) -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= ([Text]
libs [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++)
addImports :: [Text] -> State VHDLState ()
addImports [Text]
imps = ([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState
Lens' VHDLState [Text]
packages (([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState)
-> ([Text] -> [Text]) -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= ([Text]
imps [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++)
addAndSetData :: String -> State VHDLState String
addAndSetData String
f = do
[(String, String)]
fs <- Getting [(String, String)] VHDLState [(String, String)]
-> State VHDLState [(String, String)]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [(String, String)] VHDLState [(String, String)]
Lens' VHDLState [(String, String)]
dataFiles
let ([(String, String)]
fs',String
f') = [(String, String)] -> String -> ([(String, String)], String)
renderFilePath [(String, String)]
fs String
f
([(String, String)] -> Identity [(String, String)])
-> VHDLState -> Identity VHDLState
Lens' VHDLState [(String, String)]
dataFiles (([(String, String)] -> Identity [(String, String)])
-> VHDLState -> Identity VHDLState)
-> [(String, String)] -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [(String, String)]
fs'
String -> State VHDLState String
forall (m :: Type -> Type) a. Monad m => a -> m a
return String
f'
getDataFiles :: State VHDLState [(String, String)]
getDataFiles = Getting [(String, String)] VHDLState [(String, String)]
-> State VHDLState [(String, String)]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [(String, String)] VHDLState [(String, String)]
Lens' VHDLState [(String, String)]
dataFiles
addMemoryDataFile :: (String, String) -> State VHDLState ()
addMemoryDataFile (String, String)
f = ([(String, String)] -> Identity [(String, String)])
-> VHDLState -> Identity VHDLState
Lens' VHDLState [(String, String)]
memoryDataFiles (([(String, String)] -> Identity [(String, String)])
-> VHDLState -> Identity VHDLState)
-> ([(String, String)] -> [(String, String)]) -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= ((String, String)
f(String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
:)
getMemoryDataFiles :: State VHDLState [(String, String)]
getMemoryDataFiles = Getting [(String, String)] VHDLState [(String, String)]
-> State VHDLState [(String, String)]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [(String, String)] VHDLState [(String, String)]
Lens' VHDLState [(String, String)]
memoryDataFiles
ifThenElseExpr :: VHDLState -> Bool
ifThenElseExpr VHDLState
_ = Bool
False
aggressiveXOptBB :: State VHDLState AggressiveXOptBB
aggressiveXOptBB = Getting AggressiveXOptBB VHDLState AggressiveXOptBB
-> State VHDLState AggressiveXOptBB
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting AggressiveXOptBB VHDLState AggressiveXOptBB
Lens' VHDLState AggressiveXOptBB
aggressiveXOptBB_
renderEnums :: State VHDLState RenderEnums
renderEnums = Getting RenderEnums VHDLState RenderEnums
-> State VHDLState RenderEnums
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting RenderEnums VHDLState RenderEnums
Lens' VHDLState RenderEnums
renderEnums_
domainConfigurations :: State VHDLState DomainMap
domainConfigurations = Getting DomainMap VHDLState DomainMap -> State VHDLState DomainMap
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting DomainMap VHDLState DomainMap
Lens' VHDLState DomainMap
domainConfigurations_
setDomainConfigurations :: DomainMap -> VHDLState -> VHDLState
setDomainConfigurations DomainMap
confs VHDLState
s = VHDLState
s {_domainConfigurations_ :: DomainMap
_domainConfigurations_ = DomainMap
confs}
type VHDLM a = Ap (State VHDLState) a
isBV :: RenderEnums -> HWType -> Bool
isBV :: RenderEnums -> HWType -> Bool
isBV RenderEnums
e (RenderEnums -> HWType -> HWType
normaliseType RenderEnums
e -> BitVector Int
_) = Bool
True
isBV RenderEnums
_ HWType
_ = Bool
False
productFieldNames
:: HasCallStack
=> Maybe [IdentifierText]
-> [HWType]
-> VHDLM [IdentifierText]
productFieldNames :: Maybe [Text] -> [HWType] -> VHDLM [Text]
productFieldNames Maybe [Text]
labels0 [HWType]
fields = do
let labels1 :: [Maybe Text]
labels1 = Maybe [Text] -> [Maybe Text]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence Maybe [Text]
labels0 [Maybe Text] -> [Maybe Text] -> [Maybe Text]
forall a. [a] -> [a] -> [a]
++ Maybe Text -> [Maybe Text]
forall a. a -> [a]
repeat Maybe Text
forall a. Maybe a
Nothing
[Text]
hFields <- (Maybe Text -> HWType -> Ap (State VHDLState) Text)
-> [Maybe Text] -> [HWType] -> VHDLM [Text]
forall (m :: Type -> Type) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Maybe Text -> HWType -> Ap (State VHDLState) Text
hName [Maybe Text]
labels1 [HWType]
fields
let grouped :: [[Text]]
grouped = [Text] -> [[Text]]
forall a. Eq a => [a] -> [[a]]
group ([Text] -> [[Text]]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Ord a => [a] -> [a]
sort ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text]
hFields
counted :: HashMap Text Int
counted = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMapS.fromList (([Text] -> (Text, Int)) -> [[Text]] -> [(Text, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
g:[Text]
gs) -> (Text
g, Int -> Int
forall a. Enum a => a -> a
succ ([Text] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [Text]
gs))) [[Text]]
grouped)
names :: [Text]
names = (HashMap Text Int, [Text]) -> [Text]
forall a b. (a, b) -> b
snd ((HashMap Text Int, [Text]) -> [Text])
-> (HashMap Text Int, [Text]) -> [Text]
forall a b. (a -> b) -> a -> b
$ (HashMap Text Int -> Text -> (HashMap Text Int, Text))
-> HashMap Text Int -> [Text] -> (HashMap Text Int, [Text])
forall (t :: Type -> Type) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL (HashMap Text Int
-> HashMap Text Int -> Text -> (HashMap Text Int, Text)
name' HashMap Text Int
counted) HashMap Text Int
forall k v. HashMap k v
HashMapS.empty [Text]
hFields
[Text] -> VHDLM [Text]
forall (m :: Type -> Type) a. Monad m => a -> m a
return [Text]
names
where
hName
:: Maybe IdentifierText
-> HWType
-> VHDLM IdentifierText
hName :: Maybe Text -> HWType -> Ap (State VHDLState) Text
hName Maybe Text
Nothing HWType
field = HasCallStack => Bool -> HWType -> Ap (State VHDLState) Text
Bool -> HWType -> Ap (State VHDLState) Text
tyName' Bool
False HWType
field
hName (Just Text
label) HWType
_field = Identifier -> Text
Id.toText (Identifier -> Text)
-> Ap (State VHDLState) Identifier -> Ap (State VHDLState) Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Ap (State VHDLState) Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic Text
label
name'
:: HashMap IdentifierText Int
-> HashMap IdentifierText Int
-> IdentifierText
-> (HashMap IdentifierText Int, IdentifierText)
name' :: HashMap Text Int
-> HashMap Text Int -> Text -> (HashMap Text Int, Text)
name' HashMap Text Int
counted HashMap Text Int
countMap Text
fieldName
| HashMap Text Int
counted HashMap Text Int -> Text -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMapS.! Text
fieldName Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 =
let succ' :: Maybe Int -> Maybe Int
succ' Maybe Int
n = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int
0 :: Int) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Maybe Int
n) in
let countMap' :: HashMap Text Int
countMap' = (Maybe Int -> Maybe Int)
-> Text -> HashMap Text Int -> HashMap Text Int
forall k v.
(Eq k, Hashable k) =>
(Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v
HashMapS.alter Maybe Int -> Maybe Int
succ' Text
fieldName HashMap Text Int
countMap in
let count :: Int
count = HashMap Text Int
countMap' HashMap Text Int -> Text -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMapS.! Text
fieldName in
(HashMap Text Int
countMap', [Text] -> Text
TextS.concat [Text
fieldName, Text
"_", Int -> Text
forall a. Show a => a -> Text
showt Int
count])
| Bool
otherwise =
(HashMap Text Int
countMap, Text
fieldName)
productFieldName
:: HasCallStack
=> Maybe [IdentifierText]
-> [HWType]
-> Int
-> VHDLM Doc
productFieldName :: Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
productFieldName Maybe [Text]
labels [HWType]
fields Int
fieldIndex = do
[Text]
names <-
(Maybe [Text], [HWType])
-> Lens' VHDLState (HashMap (Maybe [Text], [HWType]) [Text])
-> VHDLM [Text]
-> VHDLM [Text]
forall s (m :: Type -> Type) k v.
(MonadState s m, Hashable k, Eq k) =>
k -> Lens' s (HashMap k v) -> m v -> m v
makeCached
(Maybe [Text]
labels, [HWType]
fields)
Lens' VHDLState (HashMap (Maybe [Text], [HWType]) [Text])
productFieldNameCache
(HasCallStack => Maybe [Text] -> [HWType] -> VHDLM [Text]
Maybe [Text] -> [HWType] -> VHDLM [Text]
productFieldNames Maybe [Text]
labels [HWType]
fields)
Doc -> Ap (State VHDLState) Doc
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Text -> Doc
forall a ann. Pretty a => a -> Doc ann
PP.pretty ([Text]
names [Text] -> Int -> Text
forall a. [a] -> Int -> a
!! Int
fieldIndex))
selectProductField
:: HasCallStack
=> Maybe [IdentifierText]
-> [HWType]
-> Int
-> VHDLM Doc
selectProductField :: Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
selectProductField Maybe [Text]
fieldLabels [HWType]
fieldTypes Int
fieldIndex =
Ap (State VHDLState) Doc
"_sel" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
fieldIndex Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"_" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HasCallStack =>
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
productFieldName Maybe [Text]
fieldLabels [HWType]
fieldTypes Int
fieldIndex
enumVariantName
:: HasCallStack
=> HWType
-> Int
-> VHDLM Doc
enumVariantName :: HWType -> Int -> Ap (State VHDLState) Doc
enumVariantName ty :: HWType
ty@(Sum Text
_ [Text]
vs) Int
i = do
[Text]
names <- HWType
-> Lens' VHDLState (HashMap HWType [Text])
-> VHDLM [Text]
-> VHDLM [Text]
forall s (m :: Type -> Type) k v.
(MonadState s m, Hashable k, Eq k) =>
k -> Lens' s (HashMap k v) -> m v -> m v
makeCached HWType
ty Lens' VHDLState (HashMap HWType [Text])
enumNameCache ((Text -> Ap (State VHDLState) Text) -> [Text] -> VHDLM [Text]
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Ap (State VHDLState) Text
variantName [Text]
vs)
Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text -> Doc
forall a ann. Pretty a => a -> Doc ann
PP.pretty ([Text]
names [Text] -> Int -> Text
forall a. [a] -> Int -> a
!! Int
i))
where
variantName :: Text -> Ap (State VHDLState) Text
variantName = (Identifier -> Text)
-> Ap (State VHDLState) Identifier -> Ap (State VHDLState) Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Identifier -> Text
Id.toText (Ap (State VHDLState) Identifier -> Ap (State VHDLState) Text)
-> (Text -> Ap (State VHDLState) Identifier)
-> Text
-> Ap (State VHDLState) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Ap (State VHDLState) Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic (Text -> Ap (State VHDLState) Identifier)
-> (Text -> Text) -> Text -> Ap (State VHDLState) Identifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Text, Text) -> Text) -> (Text -> (Text, Text)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> (Text, Text)
TextS.breakOnEnd Text
"."
enumVariantName HWType
_ Int
_ =
String -> Ap (State VHDLState) Doc
forall a. HasCallStack => String -> a
error (String -> Ap (State VHDLState) Doc)
-> String -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ $(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"enumVariantName called on non-enum type"
genVHDL
:: ModName
-> SrcSpan
-> IdentifierSet
-> Component
-> VHDLM ((String, Doc), [(String, Doc)])
genVHDL :: Text
-> SrcSpan
-> IdentifierSet
-> Component
-> Ap (State VHDLState) ((String, Doc), [(String, Doc)])
genVHDL Text
nm SrcSpan
sp IdentifierSet
seen Component
c = do
State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState () -> Ap (State VHDLState) ())
-> State VHDLState () -> Ap (State VHDLState) ()
forall a b. (a -> b) -> a -> b
$ (IdentifierSet -> Identity IdentifierSet)
-> VHDLState -> Identity VHDLState
Lens' VHDLState IdentifierSet
idSeen ((IdentifierSet -> Identity IdentifierSet)
-> VHDLState -> Identity VHDLState)
-> (IdentifierSet -> IdentifierSet) -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= HasCallStack => IdentifierSet -> IdentifierSet -> IdentifierSet
IdentifierSet -> IdentifierSet -> IdentifierSet
Id.union IdentifierSet
seen
State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState () -> Ap (State VHDLState) ())
-> State VHDLState () -> Ap (State VHDLState) ()
forall a b. (a -> b) -> a -> b
$ SrcSpan -> State VHDLState ()
forall state. Backend state => SrcSpan -> State state ()
setSrcSpan SrcSpan
sp
Doc
v <- Ap (State VHDLState) Doc
vhdl
[(String, Doc)]
i <- State VHDLState [(String, Doc)]
-> Ap (State VHDLState) [(String, Doc)]
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState [(String, Doc)]
-> Ap (State VHDLState) [(String, Doc)])
-> State VHDLState [(String, Doc)]
-> Ap (State VHDLState) [(String, Doc)]
forall a b. (a -> b) -> a -> b
$ Getting [(String, Doc)] VHDLState [(String, Doc)]
-> State VHDLState [(String, Doc)]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [(String, Doc)] VHDLState [(String, Doc)]
Lens' VHDLState [(String, Doc)]
includes
State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState () -> Ap (State VHDLState) ())
-> State VHDLState () -> Ap (State VHDLState) ()
forall a b. (a -> b) -> a -> b
$ ([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState
Lens' VHDLState [Text]
libraries (([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState)
-> [Text] -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= []
State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState () -> Ap (State VHDLState) ())
-> State VHDLState () -> Ap (State VHDLState) ()
forall a b. (a -> b) -> a -> b
$ ([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState
Lens' VHDLState [Text]
packages (([Text] -> Identity [Text]) -> VHDLState -> Identity VHDLState)
-> [Text] -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= []
((String, Doc), [(String, Doc)])
-> Ap (State VHDLState) ((String, Doc), [(String, Doc)])
forall (m :: Type -> Type) a. Monad m => a -> m a
return ((Text -> String
TextS.unpack (Identifier -> Text
Id.toText Identifier
cName), Doc
v), [(String, Doc)]
i)
where
cName :: Identifier
cName = Component -> Identifier
componentName Component
c
vhdl :: Ap (State VHDLState) Doc
vhdl = do
Doc
ent <- Component -> Ap (State VHDLState) Doc
entity Component
c
Doc
arch <- Component -> Ap (State VHDLState) Doc
architecture Component
c
Doc
imps <- Text -> Ap (State VHDLState) Doc
tyImports Text
nm
(Ap (State VHDLState) Doc
"-- Automatically generated VHDL-93" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
imps Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
ent Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
arch)
mkTyPackage_ :: ModName -> [HWType] -> VHDLM [(String,Doc)]
mkTyPackage_ :: Text -> [HWType] -> Ap (State VHDLState) [(String, Doc)]
mkTyPackage_ Text
modName ((HWType -> HWType) -> [HWType] -> [HWType]
forall a b. (a -> b) -> [a] -> [b]
map HWType -> HWType
filterTransparent -> [HWType]
hwtys) = do
{ State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap ((Bool -> Identity Bool) -> VHDLState -> Identity VHDLState
Lens' VHDLState Bool
tyPkgCtx ((Bool -> Identity Bool) -> VHDLState -> Identity VHDLState)
-> Bool -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True)
; HdlSyn
syn <- State VHDLState HdlSyn -> Ap (State VHDLState) HdlSyn
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState HdlSyn
forall state. Backend state => State state HdlSyn
hdlSyn
; RenderEnums
enums <- State VHDLState RenderEnums -> Ap (State VHDLState) RenderEnums
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
; let usedTys :: [HWType]
usedTys = (HWType -> [HWType]) -> [HWType] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [HWType]
mkUsedTys [HWType]
hwtys
; let normTys0 :: [HWType]
normTys0 = [HWType] -> [HWType]
forall a. Eq a => [a] -> [a]
nub ((HWType -> HWType) -> [HWType] -> [HWType]
forall a b. (a -> b) -> [a] -> [b]
map HWType -> HWType
mkVecZ ([HWType]
hwtys [HWType] -> [HWType] -> [HWType]
forall a. [a] -> [a] -> [a]
++ [HWType]
usedTys))
; let sortedTys0 :: [HWType]
sortedTys0 = [HWType] -> [HWType]
topSortHWTys [HWType]
normTys0
packageDec :: Ap (State VHDLState) Doc
packageDec = Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ (HWType -> Ap (State VHDLState) Doc)
-> [HWType] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
tyDec ((HWType -> HWType -> Bool) -> [HWType] -> [HWType]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy HWType -> HWType -> Bool
eqTypM [HWType]
sortedTys0)
([Ap (State VHDLState) Doc]
funDecs,[Ap (State VHDLState) Doc]
funBodies) = [(Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)]
-> ([Ap (State VHDLState) Doc], [Ap (State VHDLState) Doc])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)]
-> ([Ap (State VHDLState) Doc], [Ap (State VHDLState) Doc]))
-> ([HWType]
-> [(Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)])
-> [HWType]
-> ([Ap (State VHDLState) Doc], [Ap (State VHDLState) Doc])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HWType
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc))
-> [HWType]
-> [(Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (RenderEnums
-> HdlSyn
-> HWType
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
funDec RenderEnums
enums HdlSyn
syn) ([HWType]
-> ([Ap (State VHDLState) Doc], [Ap (State VHDLState) Doc]))
-> [HWType]
-> ([Ap (State VHDLState) Doc], [Ap (State VHDLState) Doc])
forall a b. (a -> b) -> a -> b
$ (HWType -> HWType -> Bool) -> [HWType] -> [HWType]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy HWType -> HWType -> Bool
eqTypM (RenderEnums -> HWType -> HWType
normaliseType RenderEnums
enums (HWType -> HWType) -> [HWType] -> [HWType]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> [HWType]
sortedTys0)
; [(String, Doc)]
pkg <- ((String, Doc) -> [(String, Doc)] -> [(String, Doc)]
forall a. a -> [a] -> [a]
:[]) ((String, Doc) -> [(String, Doc)])
-> (Doc -> (String, Doc)) -> Doc -> [(String, Doc)]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> String
TextS.unpack (Text
modName Text -> Text -> Text
`TextS.append` Text
"_types"),) (Doc -> [(String, Doc)])
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) [(String, Doc)]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>
Ap (State VHDLState) Doc
"library IEEE;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"use IEEE.STD_LOGIC_1164.ALL;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"use IEEE.NUMERIC_STD.ALL;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"package" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty (Text
modName Text -> Text -> Text
`TextS.append` Text
"_types") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 ( Ap (State VHDLState) Doc
packageDec Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat ([Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc]
funDecs)
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> [Ap (State VHDLState) Doc] -> Ap (State VHDLState) Doc
packageBodyDec [Ap (State VHDLState) Doc]
funBodies
; State VHDLState () -> Ap (State VHDLState) ()
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap ((Bool -> Identity Bool) -> VHDLState -> Identity VHDLState
Lens' VHDLState Bool
tyPkgCtx ((Bool -> Identity Bool) -> VHDLState -> Identity VHDLState)
-> Bool -> State VHDLState ()
forall s (m :: Type -> Type) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False)
; [(String, Doc)] -> Ap (State VHDLState) [(String, Doc)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return [(String, Doc)]
pkg
}
where
packageBodyDec :: [VHDLM Doc] -> VHDLM Doc
packageBodyDec :: [Ap (State VHDLState) Doc] -> Ap (State VHDLState) Doc
packageBodyDec [Ap (State VHDLState) Doc]
funBodies = case [Ap (State VHDLState) Doc]
funBodies of
[] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
[Ap (State VHDLState) Doc]
_ -> do
{ Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"package" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"body" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty (Text
modName Text -> Text -> Text
`TextS.append` Text
"_types") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat ([Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc]
funBodies)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
}
eqTypM :: HWType -> HWType -> Bool
eqTypM :: HWType -> HWType -> Bool
eqTypM (Signed Int
_) (Signed Int
_) = Bool
True
eqTypM (Unsigned Int
_) (Unsigned Int
_) = Bool
True
eqTypM (BitVector Int
_) (BitVector Int
_) = Bool
True
eqTypM HWType
ty1 HWType
ty2 = HWType
ty1 HWType -> HWType -> Bool
forall a. Eq a => a -> a -> Bool
== HWType
ty2
mkUsedTys :: HWType -> [HWType]
mkUsedTys :: HWType -> [HWType]
mkUsedTys HWType
hwty = HWType
hwty HWType -> [HWType] -> [HWType]
forall a. a -> [a] -> [a]
: case HWType
hwty of
Vector Int
_ HWType
elTy -> HWType -> [HWType]
mkUsedTys HWType
elTy
RTree Int
_ HWType
elTy -> HWType -> [HWType]
mkUsedTys HWType
elTy
Product Text
_ Maybe [Text]
_ [HWType]
elTys -> (HWType -> [HWType]) -> [HWType] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [HWType]
mkUsedTys [HWType]
elTys
SP Text
_ [(Text, [HWType])]
elTys -> (HWType -> [HWType]) -> [HWType] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [HWType]
mkUsedTys (((Text, [HWType]) -> [HWType]) -> [(Text, [HWType])] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap (Text, [HWType]) -> [HWType]
forall a b. (a, b) -> b
snd [(Text, [HWType])]
elTys)
BiDirectional PortDirection
_ HWType
elTy -> HWType -> [HWType]
mkUsedTys HWType
elTy
Annotated [Attr']
_ HWType
elTy -> HWType -> [HWType]
mkUsedTys HWType
elTy
CustomProduct Text
_ DataRepr'
_ Int
_ Maybe [Text]
_ [(FieldAnn, HWType)]
tys0 ->
(HWType -> [HWType]) -> [HWType] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [HWType]
mkUsedTys (((FieldAnn, HWType) -> HWType) -> [(FieldAnn, HWType)] -> [HWType]
forall a b. (a -> b) -> [a] -> [b]
map (FieldAnn, HWType) -> HWType
forall a b. (a, b) -> b
snd [(FieldAnn, HWType)]
tys0)
CustomSP Text
_ DataRepr'
_ Int
_ [(ConstrRepr', Text, [HWType])]
tys0 ->
let tys1 :: [HWType]
tys1 = [[HWType]] -> [HWType]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[HWType]
tys | (ConstrRepr'
_repr, Text
_id, [HWType]
tys) <- [(ConstrRepr', Text, [HWType])]
tys0] in
(HWType -> [HWType]) -> [HWType] -> [HWType]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [HWType]
mkUsedTys [HWType]
tys1
HWType
_ ->
[]
topSortHWTys
:: [HWType]
-> [HWType]
topSortHWTys :: [HWType] -> [HWType]
topSortHWTys [HWType]
hwtys = [HWType]
sorted
where
nodes :: [(Int, HWType)]
nodes = [Int] -> [HWType] -> [(Int, HWType)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [HWType]
hwtys
nodesI :: HashMap HWType Int
nodesI = [(HWType, Int)] -> HashMap HWType Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([HWType] -> [Int] -> [(HWType, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [HWType]
hwtys [Int
0..])
edges :: [(Int, Int)]
edges = (HWType -> [(Int, Int)]) -> [HWType] -> [(Int, Int)]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap HWType -> [(Int, Int)]
edge [HWType]
hwtys
sorted :: [HWType]
sorted =
case [(Int, HWType)] -> [(Int, Int)] -> Either String [HWType]
forall a. [(Int, a)] -> [(Int, Int)] -> Either String [a]
reverseTopSort [(Int, HWType)]
nodes [(Int, Int)]
edges of
Left String
err -> String -> [HWType]
forall a. HasCallStack => String -> a
error (String -> [HWType]) -> String -> [HWType]
forall a b. (a -> b) -> a -> b
$ $(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"[BUG IN CLASH] topSortHWTys: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
err
Right [HWType]
ns -> [HWType]
ns
edge :: HWType -> [(Int, Int)]
edge t :: HWType
t@(Vector Int
_ HWType
elTy) =
case HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (HWType -> HWType
mkVecZ HWType
elTy) HashMap HWType Int
nodesI of
Just Int
node ->
[(HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t, Int
node)]
Maybe Int
Nothing ->
[]
edge t :: HWType
t@(RTree Int
_ HWType
elTy) =
let vecZ :: HWType
vecZ = HWType -> HWType
mkVecZ HWType
elTy in
case HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup HWType
vecZ HashMap HWType Int
nodesI of
Just Int
node ->
[(HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t, Int
node)] [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ HWType -> [(Int, Int)]
edge HWType
elTy
Maybe Int
Nothing ->
[]
edge t :: HWType
t@(Product Text
_ Maybe [Text]
_ [HWType]
tys0) =
let tys1 :: [Maybe Int]
tys1 = [HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (HWType -> HWType
mkVecZ HWType
ty) HashMap HWType Int
nodesI | HWType
ty <- [HWType]
tys0] in
(Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t,) ([Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
tys1)
edge t :: HWType
t@(SP Text
_ [(Text, [HWType])]
tys0) =
let tys1 :: [HWType]
tys1 = [[HWType]] -> [HWType]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat (((Text, [HWType]) -> [HWType]) -> [(Text, [HWType])] -> [[HWType]]
forall a b. (a -> b) -> [a] -> [b]
map (Text, [HWType]) -> [HWType]
forall a b. (a, b) -> b
snd [(Text, [HWType])]
tys0) in
let tys2 :: [Maybe Int]
tys2 = [HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (HWType -> HWType
mkVecZ HWType
ty) HashMap HWType Int
nodesI | HWType
ty <- [HWType]
tys1] in
(Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t,) ([Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
tys2)
edge t :: HWType
t@(CustomSP Text
_ DataRepr'
_ Int
_ [(ConstrRepr', Text, [HWType])]
tys0) =
let tys1 :: [HWType]
tys1 = [[HWType]] -> [HWType]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[HWType]
tys | (ConstrRepr'
_repr, Text
_id, [HWType]
tys) <- [(ConstrRepr', Text, [HWType])]
tys0] in
let tys2 :: [Maybe Int]
tys2 = [HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (HWType -> HWType
mkVecZ HWType
ty) HashMap HWType Int
nodesI | HWType
ty <- [HWType]
tys1] in
(Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t,) ([Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
tys2)
edge t :: HWType
t@(CustomProduct Text
_ DataRepr'
_ Int
_ Maybe [Text]
_ (((FieldAnn, HWType) -> HWType) -> [(FieldAnn, HWType)] -> [HWType]
forall a b. (a -> b) -> [a] -> [b]
map (FieldAnn, HWType) -> HWType
forall a b. (a, b) -> b
snd -> [HWType]
tys0)) =
let tys1 :: [Maybe Int]
tys1 = [HWType -> HashMap HWType Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (HWType -> HWType
mkVecZ HWType
ty) HashMap HWType Int
nodesI | HWType
ty <- [HWType]
tys0] in
(Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (HashMap HWType Int
nodesI HashMap HWType Int -> HWType -> Int
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! HWType
t,) ([Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
tys1)
edge HWType
_ = []
mkVecZ :: HWType -> HWType
mkVecZ :: HWType -> HWType
mkVecZ (Vector Int
_ HWType
elTy) = Int -> HWType -> HWType
Vector Int
0 HWType
elTy
mkVecZ (RTree Int
_ HWType
elTy) = Int -> HWType -> HWType
RTree Int
0 HWType
elTy
mkVecZ HWType
t = HWType
t
typAliasDec :: HasCallStack => HWType -> VHDLM Doc
typAliasDec :: HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty = do
RenderEnums
enums <- State VHDLState RenderEnums -> Ap (State VHDLState) RenderEnums
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
Ap (State VHDLState) Doc
"subtype" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedTyName (RenderEnums -> HWType -> HWType
normaliseType RenderEnums
enums HWType
hwty)
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
tyDec :: HasCallStack => HWType -> VHDLM Doc
tyDec :: HWType -> Ap (State VHDLState) Doc
tyDec HWType
hwty = do
HdlSyn
syn <- State VHDLState HdlSyn -> Ap (State VHDLState) HdlSyn
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState HdlSyn
forall state. Backend state => State state HdlSyn
hdlSyn
RenderEnums Bool
enums <- State VHDLState RenderEnums -> Ap (State VHDLState) RenderEnums
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState RenderEnums
forall state. Backend state => State state RenderEnums
renderEnums
case HWType
hwty of
Vector Int
_ HWType
elTy ->
case HdlSyn
syn of
HdlSyn
Vivado ->
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is array (integer range <>) of std_logic_vector"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"downto 0")
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
HdlSyn
_ ->
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is array (integer range <>) of"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
elTy
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
RTree Int
_ HWType
elTy ->
case HdlSyn
syn of
HdlSyn
Vivado ->
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is array (integer range <>) of"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"downto 0")
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
HdlSyn
_ ->
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is array (integer range <>) of"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
elTy
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
Product Text
_ Maybe [Text]
labels tys :: [HWType]
tys@(HWType
_:HWType
_:[HWType]
_) ->
let selNames :: [Ap (State VHDLState) Doc]
selNames = (Int -> Ap (State VHDLState) Doc)
-> [Int] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
i -> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HasCallStack =>
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
selectProductField Maybe [Text]
labels [HWType]
tys Int
i) [Int
0..] in
let selTys :: [Ap (State VHDLState) Doc]
selTys = (HWType -> Ap (State VHDLState) Doc)
-> [HWType] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map HWType -> Ap (State VHDLState) Doc
sizedQualTyName [HWType]
tys in
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is record" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ (Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc)
-> [Ap (State VHDLState) Doc]
-> [Ap (State VHDLState) Doc]
-> Ap (State VHDLState) [Doc]
forall (m :: Type -> Type) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (\Ap (State VHDLState) Doc
x Ap (State VHDLState) Doc
y -> Ap (State VHDLState) Doc
x Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
y Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) [Ap (State VHDLState) Doc]
selNames [Ap (State VHDLState) Doc]
selTys) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end record" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
Sum Text
_ [Text]
vs | Bool
enums ->
let variantNames :: Ap (State VHDLState) [Doc]
variantNames = (Int -> Ap (State VHDLState) Doc)
-> [Int] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (HasCallStack => HWType -> Int -> Ap (State VHDLState) Doc
HWType -> Int -> Ap (State VHDLState) Doc
enumVariantName HWType
hwty) [Int
0..[Text] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [Text]
vs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] in
Ap (State VHDLState) Doc
"type" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
hwty
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
hsep (Ap (State VHDLState) Doc
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) [Doc]
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f [Doc] -> f [Doc]
punctuate Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
comma Ap (State VHDLState) [Doc]
variantNames))
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
MemBlob Int
n Int
m -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
tyDec (Int -> HWType -> HWType
Vector Int
n (Int -> HWType
BitVector Int
m))
Clock Text
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
Reset Text
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
Enable Text
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
Index FieldAnn
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
CustomSP Text
_ DataRepr'
_ Int
_ [(ConstrRepr', Text, [HWType])]
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
Sum Text
_ [Text]
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
SP Text
_ [(Text, [HWType])]
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
CustomSum Text
_ DataRepr'
_ Int
_ [(ConstrRepr', Text)]
_ -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
CustomProduct {} -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
typAliasDec HWType
hwty
BitVector Int
_ -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
HWType
Bool -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
HWType
Bit -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
Unsigned Int
_ -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
Signed Int
_ -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
HWType
String -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
HWType
Integer -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
HWType
FileType -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
BiDirectional PortDirection
_ HWType
ty -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
tyDec HWType
ty
Annotated [Attr']
_ HWType
ty -> HasCallStack => HWType -> Ap (State VHDLState) Doc
HWType -> Ap (State VHDLState) Doc
tyDec HWType
ty
Void {} -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
KnownDomain {} -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
Product Text
_ Maybe [Text]
_ [HWType]
_ -> String -> Ap (State VHDLState) Doc
forall a. HasCallStack => String -> a
error (String -> Ap (State VHDLState) Doc)
-> String -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ $(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ [I.i|
Unexpected Product with fewer than 2 fields: #{hwty}
|]
funDec :: RenderEnums -> HdlSyn -> HWType -> Maybe (VHDLM Doc,VHDLM Doc)
funDec :: RenderEnums
-> HdlSyn
-> HWType
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
funDec RenderEnums
_ HdlSyn
_ HWType
Bool = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"sl" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"tagToEnum" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"s" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"dataToTag" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"then"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
dquotes (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"else"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
dquotes (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
0) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
]) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"sl" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"sl" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
dquotes (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"then"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"true" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"else"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"false" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
]) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"tagToEnum" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"s" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"s" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to_signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
0 Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
comma Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> (State VHDLState Int -> Ap (State VHDLState) Int
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (Getting Int VHDLState Int -> State VHDLState Int
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Int VHDLState Int
Lens' VHDLState Int
intWidth) Ap (State VHDLState) Int
-> (Int -> Ap (State VHDLState) Doc) -> Ap (State VHDLState) Doc
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"then"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"false" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"else"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"true" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
]) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"dataToTag" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"boolean") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"b" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"then"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to_signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
1 Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
comma Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> (State VHDLState Int -> Ap (State VHDLState) Int
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (Getting Int VHDLState Int -> State VHDLState Int
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Int VHDLState Int
Lens' VHDLState Int
intWidth) Ap (State VHDLState) Int
-> (Int -> Ap (State VHDLState) Doc) -> Ap (State VHDLState) Doc
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"else"
, Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to_signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
0 Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
comma Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> (State VHDLState Int -> Ap (State VHDLState) Int
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (Getting Int VHDLState Int -> State VHDLState Int
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting Int VHDLState Int
Lens' VHDLState Int
intWidth) Ap (State VHDLState) Int
-> (Int -> Ap (State VHDLState) Doc) -> Ap (State VHDLState) Doc
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
,Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
]) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
funDec RenderEnums
_ HdlSyn
_ bit :: HWType
bit@HWType
Bit = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"sl" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
bit) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
bit Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"sl" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
bit) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector'" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
0 Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
rarrow Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"sl") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
tyName HWType
bit Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"alias islv : std_logic_vector (0 to slv'length - 1) is slv;"
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"islv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
0) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
funDec RenderEnums
_ HdlSyn
_ (Signed Int
_) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"s" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"s" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"s") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"alias islv : std_logic_vector(0 to slv'length - 1) is slv;") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"signed" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"islv") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
funDec RenderEnums
_ HdlSyn
_ (Unsigned Int
_) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"u" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"unsigned") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"unsigned" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"u" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"unsigned") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"u") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"unsigned" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 Ap (State VHDLState) Doc
"alias islv : std_logic_vector(0 to slv'length - 1) is slv;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"unsigned" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"islv") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
funDec RenderEnums
_ HdlSyn
_ t :: HWType
t@(Product Text
_ Maybe [Text]
labels [HWType]
elTys) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"p :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"p :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
hcat (Ap (State VHDLState) Doc
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) [Doc]
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f [Doc] -> f [Doc]
punctuate Ap (State VHDLState) Doc
" & " Ap (State VHDLState) [Doc]
elTyToSLV)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"alias islv : std_logic_vector(0 to slv'length - 1) is slv;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
hcat (Ap (State VHDLState) Doc
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) [Doc]
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f [Doc] -> f [Doc]
punctuate Ap (State VHDLState) Doc
"," Ap (State VHDLState) [Doc]
elTyFromSLV)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
where
elTyToSLV :: Ap (State VHDLState) [Doc]
elTyToSLV = [Int]
-> (Int -> Ap (State VHDLState) Doc) -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0..([HWType] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [HWType]
elTys Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)]
(\Int
i -> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"p." Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HWType -> Ap (State VHDLState) Doc
tyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HasCallStack =>
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
Maybe [Text] -> [HWType] -> Int -> Ap (State VHDLState) Doc
selectProductField Maybe [Text]
labels [HWType]
elTys Int
i))
argLengths :: [Int]
argLengths = (HWType -> Int) -> [HWType] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map HWType -> Int
typeSize [HWType]
elTys
starts :: [Int]
starts = Int
0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: (Int, [Int]) -> [Int]
forall a b. (a, b) -> b
snd ((Int -> Int -> (Int, Int)) -> Int -> [Int] -> (Int, [Int])
forall (t :: Type -> Type) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL (((Int -> Int -> (Int, Int)) -> Int -> (Int, Int)
forall (m :: Type -> Type) a. Monad m => m (m a) -> m a
join (,) (Int -> (Int, Int)) -> (Int -> Int) -> Int -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Int -> Int) -> Int -> (Int, Int))
-> (Int -> Int -> Int) -> Int -> Int -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)) Int
0 [Int]
argLengths)
ends :: [Int]
ends = (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
1) ([Int] -> [Int]
forall a. [a] -> [a]
tail [Int]
starts)
elTyFromSLV :: Ap (State VHDLState) [Doc]
elTyFromSLV = [(Int, Int)]
-> ((Int, Int) -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ([Int] -> [Int] -> [(Int, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int]
starts [Int]
ends)
(\(Int
s,Int
e) -> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"islv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
s Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int Int
e)))
funDec (RenderEnums Bool
enums) HdlSyn
_ t :: HWType
t@(Sum Text
_ [Text]
_) | Bool
enums = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens(Ap (State VHDLState) Doc
"value" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"value" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"to_unsigned" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'pos(value)" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
comma Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
t))
)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
(
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
(Semigroup (f Doc), IsString (f Doc), Applicative f) =>
f Doc -> f Doc
translate_off (
Ap (State VHDLState) Doc
"if unsigned(slv) <= " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'pos("Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'high) then"
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'val" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"to_integer" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"unsigned" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
"slv"))) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
(Semigroup (f Doc), IsString (f Doc), Applicative f) =>
f Doc -> f Doc
translate_off (
Ap (State VHDLState) Doc
"else" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"'val(0)") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end if" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
where
translate_off :: f Doc -> f Doc
translate_off f Doc
body = f Doc
"-- pragma translate_off" f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> f Doc
forall (f :: Type -> Type). Applicative f => f Doc
line f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> f Doc
body f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> f Doc
forall (f :: Type -> Type). Applicative f => f Doc
line f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> f Doc
"-- pragma translate_on"
funDec RenderEnums
_ HdlSyn
syn t :: HWType
t@(Vector Int
_ HWType
elTy) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"value : " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"value : " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"alias ivalue :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"(1 to value'length) is value;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"variable result :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"1 to value'length * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
(Ap (State VHDLState) Doc
"for i in ivalue'range loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"(i - 1) * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"+ 1" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>
Ap (State VHDLState) Doc
"to i*" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>
Ap (State VHDLState) Doc
":=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> (case HdlSyn
syn of
HdlSyn
Vivado -> Ap (State VHDLState) Doc
"ivalue" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i")
HdlSyn
_ -> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"ivalue" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i"))) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"alias islv :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"(0 to slv'length - 1) is slv;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"variable result :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"0 to slv'length / " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"- 1") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
(Ap (State VHDLState) Doc
"for i in result'range loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
"i" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
":=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> case HdlSyn
syn of
HdlSyn
Vivado -> Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
HdlSyn
_ | BitVector Int
_ <- HWType
elTy -> Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
| Bool
otherwise -> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
where
eSz :: Ap (State VHDLState) Doc
eSz = Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)
getElem :: Ap (State VHDLState) Doc
getElem = Ap (State VHDLState) Doc
"islv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to (i+1) * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"- 1")
funDec RenderEnums
_ HdlSyn
_ (BitVector Int
_) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 (Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
funDec RenderEnums
_ HdlSyn
syn t :: HWType
t@(RTree Int
_ HWType
elTy) = (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
-> Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. a -> Maybe a
Just
( Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"value : " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
, Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"value : " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"alias ivalue :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"(1 to value'length) is value;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"variable result :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"1 to value'length * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
(Ap (State VHDLState) Doc
"for i in ivalue'range loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"(i - 1) * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"+ 1" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>
Ap (State VHDLState) Doc
"to i*" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>
Ap (State VHDLState) Doc
":=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> (case HdlSyn
syn of
HdlSyn
Vivado -> Ap (State VHDLState) Doc
"ivalue" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i")
HdlSyn
_ -> Ap (State VHDLState) Doc
"toSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"ivalue" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i"))) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"function" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"slv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"in" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"alias islv :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"std_logic_vector" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"(0 to slv'length - 1) is slv;" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"variable result :" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
qualTyName HWType
t Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"0 to slv'length / " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"- 1") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
(Ap (State VHDLState) Doc
"for i in result'range loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2
( Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
"i" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
":=" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> case HdlSyn
syn of
HdlSyn
Vivado -> Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
HdlSyn
_ | BitVector Int
_ <- HWType
elTy -> Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
| Bool
otherwise -> Ap (State VHDLState) Doc
"fromSLV" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens Ap (State VHDLState) Doc
getElem Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"loop" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"return" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"result" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
where
eSz :: Ap (State VHDLState) Doc
eSz = Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (HWType -> Int
typeSize HWType
elTy)
getElem :: Ap (State VHDLState) Doc
getElem = Ap (State VHDLState) Doc
"islv" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"i * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"to (i+1) * " Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
eSz Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"- 1")
funDec RenderEnums
_ HdlSyn
_ HWType
_ = Maybe (Ap (State VHDLState) Doc, Ap (State VHDLState) Doc)
forall a. Maybe a
Nothing
tyImports :: ModName -> VHDLM Doc
tyImports :: Text -> Ap (State VHDLState) Doc
tyImports Text
nm = do
[Text]
libs <- State VHDLState [Text] -> Ap (State VHDLState) [Text]
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState [Text] -> Ap (State VHDLState) [Text])
-> State VHDLState [Text] -> Ap (State VHDLState) [Text]
forall a b. (a -> b) -> a -> b
$ Getting [Text] VHDLState [Text] -> State VHDLState [Text]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [Text] VHDLState [Text]
Lens' VHDLState [Text]
libraries
[Text]
packs <- State VHDLState [Text] -> Ap (State VHDLState) [Text]
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap (State VHDLState [Text] -> Ap (State VHDLState) [Text])
-> State VHDLState [Text] -> Ap (State VHDLState) [Text]
forall a b. (a -> b) -> a -> b
$ Getting [Text] VHDLState [Text] -> State VHDLState [Text]
forall s (m :: Type -> Type) a.
MonadState s m =>
Getting a s a -> m a
use Getting [Text] VHDLState [Text]
Lens' VHDLState [Text]
packages
Ap (State VHDLState) Doc
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (m :: Type -> Type).
Monad m =>
Ap m Doc -> Ap m [Doc] -> Ap m Doc
punctuate' Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([ Ap (State VHDLState) Doc
"library IEEE"
, Ap (State VHDLState) Doc
"use IEEE.STD_LOGIC_1164.ALL"
, Ap (State VHDLState) Doc
"use IEEE.NUMERIC_STD.ALL"
, Ap (State VHDLState) Doc
"use IEEE.MATH_REAL.ALL"
, Ap (State VHDLState) Doc
"use std.textio.all"
, Ap (State VHDLState) Doc
"use work.all"
, Ap (State VHDLState) Doc
"use work." Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty (Text
nm Text -> Text -> Text
`TextS.append` Text
"_types") Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
".all"
] [Ap (State VHDLState) Doc]
-> [Ap (State VHDLState) Doc] -> [Ap (State VHDLState) Doc]
forall a. [a] -> [a] -> [a]
++ ((Text -> Ap (State VHDLState) Doc)
-> [Text] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map ((Ap (State VHDLState) Doc
"library" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>) (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc)
-> (Text -> Ap (State VHDLState) Doc)
-> Text
-> Ap (State VHDLState) Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty) ([Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub [Text]
libs))
[Ap (State VHDLState) Doc]
-> [Ap (State VHDLState) Doc] -> [Ap (State VHDLState) Doc]
forall a. [a] -> [a] -> [a]
++ ((Text -> Ap (State VHDLState) Doc)
-> [Text] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map ((Ap (State VHDLState) Doc
"use" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+>) (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc)
-> (Text -> Ap (State VHDLState) Doc)
-> Text
-> Ap (State VHDLState) Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty) ([Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub [Text]
packs)))
port :: Num t
=> Identifier
-> HWType
-> VHDLM Doc
-> Int
-> Maybe Expr
-> VHDLM (Doc, t)
port :: Identifier
-> HWType
-> Ap (State VHDLState) Doc
-> Int
-> Maybe Expr
-> VHDLM (Doc, t)
port (Identifier -> Text
Id.toText -> Text
elName) HWType
hwType Ap (State VHDLState) Doc
portDirection Int
fillToN Maybe Expr
iEM =
(,Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> t) -> Int -> t
forall a b. (a -> b) -> a -> b
$ Text -> Int
TextS.length Text
elName) (Doc -> (Doc, t)) -> Ap (State VHDLState) Doc -> VHDLM (Doc, t)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>
(HWType -> Ap (State VHDLState) Doc
encodingNote HWType
hwType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc -> f Doc
fill Int
fillToN (Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty Text
elName) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
direction
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
hwType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
iE)
where
direction :: Ap (State VHDLState) Doc
direction | HWType -> Bool
isBiSignalIn HWType
hwType = Ap (State VHDLState) Doc
"inout"
| Bool
otherwise = Ap (State VHDLState) Doc
portDirection
iE :: Ap (State VHDLState) Doc
iE = Ap (State VHDLState) Doc
-> (Expr -> Ap (State VHDLState) Doc)
-> Maybe Expr
-> Ap (State VHDLState) Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
noEmptyInit (Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc)
-> (Expr -> Ap (State VHDLState) Doc)
-> Expr
-> Ap (State VHDLState) Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Bool -> Expr -> Ap (State VHDLState) Doc
Bool -> Expr -> Ap (State VHDLState) Doc
expr_ Bool
False) Maybe Expr
iEM
entity :: Component -> VHDLM Doc
entity :: Component -> Ap (State VHDLState) Doc
entity Component
c = do
HdlSyn
syn <- State VHDLState HdlSyn -> Ap (State VHDLState) HdlSyn
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState HdlSyn
forall state. Backend state => State state HdlSyn
hdlSyn
rec ([Doc]
p,[Int]
ls) <- ([(Doc, Int)] -> ([Doc], [Int]))
-> Ap (State VHDLState) [(Doc, Int)]
-> Ap (State VHDLState) ([Doc], [Int])
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap [(Doc, Int)] -> ([Doc], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip (Int -> Ap (State VHDLState) [(Doc, Int)]
ports ([Int] -> Int
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
ls))
Ap (State VHDLState) Doc
"entity" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Identifier -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty (Component -> Identifier
componentName Component
c) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
(case [Doc]
p of
[] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc
[Doc]
_ -> case HdlSyn
syn of
HdlSyn
Other -> Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 ([Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
(Semigroup (f Doc), IsString (f Doc), Applicative f) =>
[Doc] -> f Doc
rports [Doc]
p Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> if [(Identifier, Attr')] -> Bool
forall (t :: Type -> Type) a. Foldable t => t a -> Bool
null [(Identifier, Attr')]
attrs then Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc else
Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
rattrs) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
HdlSyn
_ -> Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
indent Int
2 ([Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
(Semigroup (f Doc), IsString (f Doc), Applicative f) =>
[Doc] -> f Doc
rports [Doc]
p) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
)
where
ports :: Int -> Ap (State VHDLState) [(Doc, Int)]
ports Int
l = [Ap (State VHDLState) (Doc, Int)]
-> Ap (State VHDLState) [(Doc, Int)]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([Ap (State VHDLState) (Doc, Int)]
-> Ap (State VHDLState) [(Doc, Int)])
-> [Ap (State VHDLState) (Doc, Int)]
-> Ap (State VHDLState) [(Doc, Int)]
forall a b. (a -> b) -> a -> b
$ [Identifier
-> HWType
-> Ap (State VHDLState) Doc
-> Int
-> Maybe Expr
-> Ap (State VHDLState) (Doc, Int)
forall t.
Num t =>
Identifier
-> HWType
-> Ap (State VHDLState) Doc
-> Int
-> Maybe Expr
-> VHDLM (Doc, t)
port Identifier
iName HWType
hwType Ap (State VHDLState) Doc
"in" Int
l Maybe Expr
forall a. Maybe a
Nothing | (Identifier
iName, HWType
hwType) <- Component -> [(Identifier, HWType)]
inputs Component
c]
[Ap (State VHDLState) (Doc, Int)]
-> [Ap (State VHDLState) (Doc, Int)]
-> [Ap (State VHDLState) (Doc, Int)]
forall a. [a] -> [a] -> [a]
++ [Identifier
-> HWType
-> Ap (State VHDLState) Doc
-> Int
-> Maybe Expr
-> Ap (State VHDLState) (Doc, Int)
forall t.
Num t =>
Identifier
-> HWType
-> Ap (State VHDLState) Doc
-> Int
-> Maybe Expr
-> VHDLM (Doc, t)
port Identifier
oName HWType
hwType Ap (State VHDLState) Doc
"out" Int
l Maybe Expr
iEM | (WireOrReg
_, (Identifier
oName, HWType
hwType), Maybe Expr
iEM) <- Component -> [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outputs Component
c]
rports :: [Doc] -> f Doc
rports [Doc]
p = f Doc
"port" f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> (f Doc -> f Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (f Doc -> f Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
align (f [Doc] -> f Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (f Doc -> f [Doc] -> f [Doc]
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f [Doc] -> f [Doc]
punctuate f Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi ([Doc] -> f [Doc]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure [Doc]
p))))) f Doc -> f Doc -> f Doc
forall a. Semigroup a => a -> a -> a
<> f Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
rattrs :: Ap (State VHDLState) Doc
rattrs = Text -> [(Identifier, Attr')] -> Ap (State VHDLState) Doc
renderAttrs (String -> Text
TextS.pack String
"signal") [(Identifier, Attr')]
attrs
attrs :: [(Identifier, Attr')]
attrs = [(Identifier, Attr')]
inputAttrs [(Identifier, Attr')]
-> [(Identifier, Attr')] -> [(Identifier, Attr')]
forall a. [a] -> [a] -> [a]
++ [(Identifier, Attr')]
outputAttrs
inputAttrs :: [(Identifier, Attr')]
inputAttrs = [(Identifier
id_, Attr'
attr) | (Identifier
id_, HWType
hwtype) <- Component -> [(Identifier, HWType)]
inputs Component
c, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
outputAttrs :: [(Identifier, Attr')]
outputAttrs = [(Identifier
id_, Attr'
attr) | (WireOrReg
_wireOrReg, (Identifier
id_, HWType
hwtype), Maybe Expr
_) <- Component -> [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outputs Component
c, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
architecture :: Component -> VHDLM Doc
architecture :: Component -> Ap (State VHDLState) Doc
architecture Component
c = do {
; HdlSyn
syn <- State VHDLState HdlSyn -> Ap (State VHDLState) HdlSyn
forall k (f :: k -> Type) (a :: k). f a -> Ap f a
Ap State VHDLState HdlSyn
forall state. Backend state => State state HdlSyn
hdlSyn
; let attrs :: [(Identifier, Attr')]
attrs = case HdlSyn
syn of
HdlSyn
Other -> [(Identifier, Attr')]
declAttrs
HdlSyn
_ -> [(Identifier, Attr')]
inputAttrs [(Identifier, Attr')]
-> [(Identifier, Attr')] -> [(Identifier, Attr')]
forall a. [a] -> [a] -> [a]
++ [(Identifier, Attr')]
outputAttrs [(Identifier, Attr')]
-> [(Identifier, Attr')] -> [(Identifier, Attr')]
forall a. [a] -> [a] -> [a]
++ [(Identifier, Attr')]
declAttrs
; Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
nest Int
2
((Ap (State VHDLState) Doc
"architecture structural of" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Identifier -> Ap (State VHDLState) Doc
forall (f :: Type -> Type) a.
(Applicative f, Pretty a) =>
a -> f Doc
pretty (Component -> Identifier
componentName Component
c) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
[Declaration] -> Ap (State VHDLState) Doc
decls (Component -> [Declaration]
declarations Component
c)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
if [(Identifier, Attr')] -> Bool
forall (t :: Type -> Type) a. Foldable t => t a -> Bool
null [(Identifier, Attr')]
attrs then Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
emptyDoc else Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Text -> [(Identifier, Attr')] -> Ap (State VHDLState) Doc
renderAttrs (String -> Text
TextS.pack String
"signal") [(Identifier, Attr')]
attrs) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Int -> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => Int -> f Doc -> f Doc
nest Int
2
(Ap (State VHDLState) Doc
"begin" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
[Declaration] -> Ap (State VHDLState) Doc
insts (Component -> [Declaration]
declarations Component
c)) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
Ap (State VHDLState) Doc
"end" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
}
where
netdecls :: [Declaration]
netdecls = (Declaration -> Bool) -> [Declaration] -> [Declaration]
forall a. (a -> Bool) -> [a] -> [a]
filter Declaration -> Bool
isNetDecl (Component -> [Declaration]
declarations Component
c)
declAttrs :: [(Identifier, Attr')]
declAttrs = [(Identifier
id_, Attr'
attr) | NetDecl' Maybe Text
_ WireOrReg
_ Identifier
id_ (Right HWType
hwtype) Maybe Expr
_ <- [Declaration]
netdecls, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
inputAttrs :: [(Identifier, Attr')]
inputAttrs = [(Identifier
id_, Attr'
attr) | (Identifier
id_, HWType
hwtype) <- Component -> [(Identifier, HWType)]
inputs Component
c, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
outputAttrs :: [(Identifier, Attr')]
outputAttrs = [(Identifier
id_, Attr'
attr) | (WireOrReg
_wireOrReg, (Identifier
id_, HWType
hwtype), Maybe Expr
_) <- Component -> [(WireOrReg, (Identifier, HWType), Maybe Expr)]
outputs Component
c, Attr'
attr <- HWType -> [Attr']
hwTypeAttrs HWType
hwtype]
isNetDecl :: Declaration -> Bool
isNetDecl :: Declaration -> Bool
isNetDecl (NetDecl' Maybe Text
_ WireOrReg
_ Identifier
_ (Right HWType
_) Maybe Expr
_) = Bool
True
isNetDecl Declaration
_ = Bool
False
attrType
:: t ~ HashMap T.Text T.Text
=> t
-> Attr'
-> t
attrType :: t -> Attr' -> t
attrType t
types Attr'
attr =
case Text -> HashMap Text Text -> Maybe Text
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
name' t
HashMap Text Text
types of
Maybe Text
Nothing -> Text -> Text -> HashMap Text Text -> HashMap Text Text
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Text
name' Text
type' t
HashMap Text Text
types
Just Text
type'' | Text
type'' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
type' -> t
types
| Bool
otherwise -> String -> t
forall a. HasCallStack => String -> a
error (String -> t) -> String -> t
forall a b. (a -> b) -> a -> b
$
$(String
curLoc) String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [ Text -> String
T.unpack Text
name', String
"already assigned"
, Text -> String
T.unpack Text
type'', String
"while we tried to"
, String
"add", Text -> String
T.unpack Text
type' ]
where
name' :: Text
name' = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Attr' -> String
attrName Attr'
attr
type' :: Text
type' = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ case Attr'
attr of
BoolAttr' String
_ Bool
_ -> String
"boolean"
IntegerAttr' String
_ FieldAnn
_ -> String
"integer"
StringAttr' String
_ String
_ -> String
"string"
Attr' String
_ -> String
"bool"
attrTypes :: [Attr'] -> HashMap T.Text T.Text
attrTypes :: [Attr'] -> HashMap Text Text
attrTypes = (HashMap Text Text -> Attr' -> HashMap Text Text)
-> HashMap Text Text -> [Attr'] -> HashMap Text Text
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl HashMap Text Text -> Attr' -> HashMap Text Text
forall t. (t ~ HashMap Text Text) => t -> Attr' -> t
attrType HashMap Text Text
forall k v. HashMap k v
HashMap.empty
attrMap
:: forall t
. t ~ HashMap T.Text (T.Text, [(TextS.Text, T.Text)])
=> [(Identifier, Attr')]
-> t
attrMap :: [(Identifier, Attr')] -> t
attrMap [(Identifier, Attr')]
attrs0 = (t -> (Text, Attr') -> t) -> t -> [(Text, Attr')] -> t
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl t -> (Text, Attr') -> t
go t
HashMap Text (Text, [(Text, Text)])
empty' [(Text, Attr')]
attrs1
where
attrs1 :: [(Text, Attr')]
attrs1 = ((Identifier, Attr') -> (Text, Attr'))
-> [(Identifier, Attr')] -> [(Text, Attr')]
forall a b. (a -> b) -> [a] -> [b]
map ((Identifier -> Text) -> (Identifier, Attr') -> (Text, Attr')
forall (p :: Type -> Type -> Type) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Identifier -> Text
Id.toText) [(Identifier, Attr')]
attrs0
empty' :: HashMap Text (Text, [(Text, Text)])
empty' = [(Text, (Text, [(Text, Text)]))]
-> HashMap Text (Text, [(Text, Text)])
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[(Text
k, (HashMap Text Text
types HashMap Text Text -> Text -> Text
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
HashMap.! Text
k, [])) | Text
k <- HashMap Text Text -> [Text]
forall k v. HashMap k v -> [k]
HashMap.keys HashMap Text Text
types]
types :: HashMap Text Text
types = [Attr'] -> HashMap Text Text
attrTypes (((Text, Attr') -> Attr') -> [(Text, Attr')] -> [Attr']
forall a b. (a -> b) -> [a] -> [b]
map (Text, Attr') -> Attr'
forall a b. (a, b) -> b
snd [(Text, Attr')]
attrs1)
go :: t -> (TextS.Text, Attr') -> t
go :: t -> (Text, Attr') -> t
go t
map' (Text, Attr')
attr = ((Text, [(Text, Text)]) -> (Text, [(Text, Text)]))
-> Text
-> HashMap Text (Text, [(Text, Text)])
-> HashMap Text (Text, [(Text, Text)])
forall k v.
(Eq k, Hashable k) =>
(v -> v) -> k -> HashMap k v -> HashMap k v
HashMap.adjust
((Text, Attr') -> (Text, [(Text, Text)]) -> (Text, [(Text, Text)])
go' (Text, Attr')
attr)
(String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Attr' -> String
attrName (Attr' -> String) -> Attr' -> String
forall a b. (a -> b) -> a -> b
$ (Text, Attr') -> Attr'
forall a b. (a, b) -> b
snd (Text, Attr')
attr)
t
HashMap Text (Text, [(Text, Text)])
map'
go'
:: (TextS.Text, Attr')
-> (T.Text, [(TextS.Text, T.Text)])
-> (T.Text, [(TextS.Text, T.Text)])
go' :: (Text, Attr') -> (Text, [(Text, Text)]) -> (Text, [(Text, Text)])
go' (Text
signalName, Attr'
attr) (Text
typ, [(Text, Text)]
elems) =
(Text
typ, (Text
signalName, Attr' -> Text
renderAttr Attr'
attr) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
elems)
renderAttrs
:: TextS.Text
-> [(Identifier, Attr')]
-> VHDLM Doc
renderAttrs :: Text -> [(Identifier, Attr')] -> Ap (State VHDLState) Doc
renderAttrs Text
what ([(Identifier, Attr')] -> HashMap Text (Text, [(Text, Text)])
forall t.
(t ~ HashMap Text (Text, [(Text, Text)])) =>
[(Identifier, Attr')] -> t
attrMap -> HashMap Text (Text, [(Text, Text)])
attrs) =
Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc])
-> [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall a b. (a -> b) -> a -> b
$ Ap (State VHDLState) Doc
-> [Ap (State VHDLState) Doc] -> [Ap (State VHDLState) Doc]
forall a. a -> [a] -> [a]
intersperse Ap (State VHDLState) Doc
" " ([Ap (State VHDLState) Doc] -> [Ap (State VHDLState) Doc])
-> [Ap (State VHDLState) Doc] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> a -> b
$ ((Text, (Text, [(Text, Text)])) -> Ap (State VHDLState) Doc)
-> [(Text, (Text, [(Text, Text)]))] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Text, (Text, [(Text, Text)])) -> Ap (State VHDLState) Doc
renderAttrGroup (HashMap Text (Text, [(Text, Text)])
-> [(Text, (Text, [(Text, Text)]))]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap Text (Text, [(Text, Text)])
attrs)
where
renderAttrGroup
:: (T.Text, (T.Text, [(TextS.Text, T.Text)]))
-> VHDLM Doc
renderAttrGroup :: (Text, (Text, [(Text, Text)])) -> Ap (State VHDLState) Doc
renderAttrGroup (Text
attrname, (Text
typ, [(Text, Text)]
elems)) =
(Ap (State VHDLState) Doc
"attribute" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
string Text
attrname Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
string Text
typ Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi)
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
line Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<>
(Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f [Doc] -> f Doc
vcat (Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc)
-> Ap (State VHDLState) [Doc] -> Ap (State VHDLState) Doc
forall a b. (a -> b) -> a -> b
$ [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc])
-> [Ap (State VHDLState) Doc] -> Ap (State VHDLState) [Doc]
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Ap (State VHDLState) Doc)
-> [(Text, Text)] -> [Ap (State VHDLState) Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> (Text, Text) -> Ap (State VHDLState) Doc
renderAttrDecl Text
attrname) [(Text, Text)]
elems)
renderAttrDecl
:: T.Text
-> (TextS.Text, T.Text)
-> VHDLM Doc
renderAttrDecl :: Text -> (Text, Text) -> Ap (State VHDLState) Doc
renderAttrDecl Text
attrname (Text
signalName, Text
value) =
Ap (State VHDLState) Doc
"attribute"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
string Text
attrname
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"of"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
stringS Text
signalName
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
stringS Text
what Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"is"
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Text -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Text -> f Doc
string Text
value
Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
semi
renderAttr :: Attr' -> T.Text
renderAttr :: Attr' -> Text
renderAttr (StringAttr' String
_key String
value) = Text -> Text -> Text -> Text
T.replace Text
"\\\"" Text
"\"\"" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. Show a => a -> String
show String
value
renderAttr (IntegerAttr' String
_key FieldAnn
value) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ FieldAnn -> String
forall a. Show a => a -> String
show FieldAnn
value
renderAttr (BoolAttr' String
_key Bool
True ) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"true"
renderAttr (BoolAttr' String
_key Bool
False) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"false"
renderAttr (Attr' String
_key ) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"true"
sigDecl :: VHDLM Doc -> HWType -> VHDLM Doc
sigDecl :: Ap (State VHDLState) Doc -> HWType -> Ap (State VHDLState) Doc
sigDecl Ap (State VHDLState) Doc
d HWType
t = Ap (State VHDLState) Doc
d Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => f Doc
colon Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> HWType -> Ap (State VHDLState) Doc
sizedQualTyName HWType
t
appendSize :: VHDLM Doc -> HWType -> VHDLM Doc
appendSize :: Ap (State VHDLState) Doc -> HWType -> Ap (State VHDLState) Doc
appendSize Ap (State VHDLState) Doc
baseType HWType
sizedType = case HWType
sizedType of
BitVector Int
n -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"downto 0")
Signed Int
n -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"downto 0")
Unsigned Int
n -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Ap (State VHDLState) Doc
"downto 0")
Vector Int
n HWType
_ -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"0 to" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
RTree Int
d HWType
_ -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"0 to" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int ((Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Int
d)Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
MemBlob Int
n Int
_ -> Ap (State VHDLState) Doc
baseType Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall a. Semigroup a => a -> a -> a
<> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Functor f => f Doc -> f Doc
parens (Ap (State VHDLState) Doc
"0 to" Ap (State VHDLState) Doc
-> Ap (State VHDLState) Doc -> Ap (State VHDLState) Doc
forall (f :: Type -> Type).
Applicative f =>
f Doc -> f Doc -> f Doc
<+> Int -> Ap (State VHDLState) Doc
forall (f :: Type -> Type). Applicative f => Int -> f Doc
int (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
Annotated [Attr']
_ HWType
elTy -> Ap (State VHDLState) Doc -> HWType -> Ap (State VHDLState) Doc
appendSize Ap (State VHDLState) Doc
baseType HWType
elTy
HWType
_ -> Ap (State VHDLState) Doc
baseType
sizedQualTyName :: HWType -> VHDLM Doc
sizedQualTyName :: HWType -> Ap (State VHDLState) Doc
sizedQualTyName (HWType -> HWType
filterTransparent -> HWType
hwty) =