Copyright | (c) Aleksandr Penskoi 2019 |
---|---|
License | BSD3 |
Maintainer | aleksandr.penskoi@gmail.com |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype I v = I v
- newtype O v = O (Set v)
- newtype X x = X x
- data F v x where
- data FView = FView {}
- packF :: (Function f v, Patch f (v, v), Locks f v, Show f, Label f, FunctionSimulation f v x, Typeable f, Eq f) => f -> F v x
- castF :: (Typeable f, Typeable v, Typeable x) => F v x -> Maybe (f v x)
- functionType :: F v x -> TypeRep
- class Function f v | f -> v where
- data Lock v = Lock {}
- class Var v => Locks x v | x -> v where
- inputsLockOutputs :: Function f v => f -> [Lock v]
- class WithFunctions a f | a -> f where
- functions :: a -> [f]
- class Label a where
- class FunctionSimulation f v x | f -> v x where
- newtype CycleCntx v x = CycleCntx {}
- data Cntx v x = Cntx {
- cntxProcess :: [CycleCntx v x]
- cntxReceived :: Map v [x]
- cntxCycleNumber :: Int
- log2md :: ToString a => [HashMap a String] -> String
- log2json :: ToString a => [HashMap a String] -> ByteString
- log2csv :: ToString a => [HashMap a String] -> ByteString
- cntxReceivedBySlice :: Ord v => Cntx v x -> [Map v x]
- getCntx :: (Hashable a, ToString a) => CycleCntx a v -> a -> v
- updateCntx :: (Hashable v, ToString v) => CycleCntx v x -> [(v, x)] -> Either String (CycleCntx v x)
- class Patch f diff where
- patch :: diff -> f -> f
- data Changeset v = Changeset {}
- reverseDiff :: Ord t => Changeset t -> Changeset t
- module NITTA.Intermediate.Value
- module NITTA.Intermediate.Variable
Function interface
Input variable.
I v |
Output variable set.
Value of variable (constant or initial value).
X x |
Function description
Box forall functions.
Instances
Helper for JSON serialization
Instances
ToJSON FView Source # | |
Defined in NITTA.Intermediate.Types | |
Generic FView Source # | |
Show FView Source # | |
Viewable (F v x) FView Source # | |
type Rep FView Source # | |
Defined in NITTA.Intermediate.Types type Rep FView = D1 ('MetaData "FView" "NITTA.Intermediate.Types" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "FView" 'PrefixI 'True) (S1 ('MetaSel ('Just "fvFun") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "fvHistory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) |
packF :: (Function f v, Patch f (v, v), Locks f v, Show f, Label f, FunctionSimulation f v x, Typeable f, Eq f) => f -> F v x Source #
castF :: (Typeable f, Typeable v, Typeable x) => F v x -> Maybe (f v x) Source #
Helper for extraction function from existential container F
.
functionType :: F v x -> TypeRep Source #
class Function f v | f -> v where Source #
Type class for application algorithm functions.
Nothing
Get all input variables.
outputs :: f -> Set v Source #
Get all output variables.
isInternalLockPossible :: f -> Bool Source #
Sometimes, one function can cause internal process unit lock for another function.
Instances
Var v => Function (Add v x) v Source # | |
Var v => Function (BrokenBuffer v x) v Source # | |
Defined in NITTA.Intermediate.Functions inputs :: BrokenBuffer v x -> Set v Source # outputs :: BrokenBuffer v x -> Set v Source # isInternalLockPossible :: BrokenBuffer v x -> Bool Source # | |
Var v => Function (Buffer v x) v Source # | |
(Show x, Eq x, Typeable x) => Function (Constant v x) v Source # | |
Var v => Function (Division v x) v Source # | |
Function (Loop v x) v Source # | |
Var v => Function (LoopBegin v x) v Source # | |
Var v => Function (LoopEnd v x) v Source # | |
Var v => Function (Multiply v x) v Source # | |
Ord v => Function (Neg v x) v Source # | |
Var v => Function (Receive v x) v Source # | |
Var v => Function (Send v x) v Source # | |
Var v => Function (ShiftLR v x) v Source # | |
Var v => Function (Sub v x) v Source # | |
Ord v => Function (Acc v x) v Source # | |
Function (F v x) v Source # | |
Variable casuality.
Instances
ToJSON v => ToJSON (Lock v) Source # | |
Defined in NITTA.Intermediate.Types | |
Generic (Lock v) Source # | |
ToString v => Show (Lock v) Source # | |
Eq v => Eq (Lock v) Source # | |
Ord v => Ord (Lock v) Source # | |
UnitTag tag => ToSample (Lock tag) Source # | |
UnitTag tag => ToSample [(Text, [Lock tag])] Source # | |
type Rep (Lock v) Source # | |
Defined in NITTA.Intermediate.Types type Rep (Lock v) = D1 ('MetaData "Lock" "NITTA.Intermediate.Types" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "Lock" 'PrefixI 'True) (S1 ('MetaSel ('Just "locked") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Just "lockBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v))) |
class Var v => Locks x v | x -> v where Source #
Casuality of variable processing sequence in term of locks.
For example: +function in progress, if it is.
Defined in NITTA.Model.ProcessorUnits.Multiplier
functions :: Multiplier v x t -> [F v x] Source #
Defined in NITTA.Model.Networks.Bus
functions :: BusNetwork tag v x t -> [F v x] Source #
Defined in NITTA.Model.TargetSystem
functions :: TargetSystem u tag v x t -> [F v x] Source #
Helper for JSON serialization
Instances
ToJSON FView Source # | |
Defined in NITTA.Intermediate.Types toEncoding :: FView -> Encoding # toJSONList :: [FView] -> Value # toEncodingList :: [FView] -> Encoding # | |
Generic FView Source # | |
Show FView Source # | |
Viewable (F v x) FView Source # | |
type Rep FView Source # | |
Defined in NITTA.Intermediate.Types type Rep FView = D1 ('MetaData "FView" "NITTA.Intermediate.Types" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "FView" 'PrefixI 'True) (S1 ('MetaSel ('Just "fvFun") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "fvHistory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) |
packF :: (Function f v, Patch f (v, v), Locks f v, Show f, Label f, FunctionSimulation f v x, Typeable f, Eq f) => f -> F v x Source #
castF :: (Typeable f, Typeable v, Typeable x) => F v x -> Maybe (f v x) Source #
Helper for extraction function from existential container F
.
functionType :: F v x -> TypeRep Source #
class Function f v | f -> v where Source #
Type class for application algorithm functions.
Nothing
Get all input variables.
outputs :: f -> Set v Source #
Get all output variables.
isInternalLockPossible :: f -> Bool Source #
Sometimes, one function can cause internal process unit lock for another function.
Instances
Var v => Function (Add v x) v Source # | |
Var v => Function (BrokenBuffer v x) v Source # | |
Defined in NITTA.Intermediate.Functions inputs :: BrokenBuffer v x -> Set v Source # outputs :: BrokenBuffer v x -> Set v Source # isInternalLockPossible :: BrokenBuffer v x -> Bool Source # | |
Var v => Function (Buffer v x) v Source # | |
(Show x, Eq x, Typeable x) => Function (Constant v x) v Source # | |
Var v => Function (Division v x) v Source # | |
Function (Loop v x) v Source # | |
Var v => Function (LoopBegin v x) v Source # | |
Var v => Function (LoopEnd v x) v Source # | |
Var v => Function (Multiply v x) v Source # | |
Ord v => Function (Neg v x) v Source # | |
Var v => Function (Receive v x) v Source # | |
Var v => Function (Send v x) v Source # | |
Var v => Function (ShiftLR v x) v Source # | |
Var v => Function (Sub v x) v Source # | |
Ord v => Function (Acc v x) v Source # | |
Function (F v x) v Source # | |
Variable casuality.
Instances
ToJSON v => ToJSON (Lock v) Source # | |
Defined in NITTA.Intermediate.Types toEncoding :: Lock v -> Encoding # toJSONList :: [Lock v] -> Value # toEncodingList :: [Lock v] -> Encoding # | |
Generic (Lock v) Source # | |
ToString v => Show (Lock v) Source # | |
Eq v => Eq (Lock v) Source # | |
Ord v => Ord (Lock v) Source # | |
UnitTag tag => ToSample (Lock tag) Source # | |
UnitTag tag => ToSample [(Text, [Lock tag])] Source # | |
type Rep (Lock v) Source # | |
Defined in NITTA.Intermediate.Types type Rep (Lock v) = D1 ('MetaData "Lock" "NITTA.Intermediate.Types" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "Lock" 'PrefixI 'True) (S1 ('MetaSel ('Just "locked") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Just "lockBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v))) |
class Var v => Locks x v | x -> v where Source #
Casuality of variable processing sequence in term of locks.
For example: > c := a + b > [ Lock{ locked=c, lockBy=a }, Lock{ locked=c, lockBy=b } ]
Instances
Var v => Locks (Add v x) v Source # | |
Var v => Locks (BrokenBuffer v x) v Source # | |
Defined in NITTA.Intermediate.Functions locks :: BrokenBuffer v x -> [Lock v] Source # | |
Var v => Locks (Buffer v x) v Source # | |
Var v => Locks (Constant v x) v Source # | |
Var v => Locks (Division v x) v Source # | |
Var v => Locks (Loop v x) v Source # | |
Var v => Locks (LoopBegin v x) v Source # | |
Var v => Locks (LoopEnd v x) v Source # | |
Var v => Locks (Multiply v x) v Source # | |
Var v => Locks (Neg v x) v Source # | |
Var v => Locks (Receive v x) v Source # | |
Var v => Locks (Send v x) v Source # | |
Var v => Locks (ShiftLR v x) v Source # | |
Var v => Locks (Sub v x) v Source # | |
Var v => Locks (Acc v x) v Source # | |
Var v => Locks (F v x) v Source # | |
Var v => Locks (PU v x t) v Source # | |
Var v => Locks (Accum v x t) v Source # | |
Var v => Locks (Broken v x t) v Source # | |
(Var v, Time t) => Locks (Divider v x t) v Source # | |
Var v => Locks (Fram v x t) v Source # | |
Var v => Locks (Multiplier v x t) v Source # | Tracking internal dependencies on the processed variables. It includes:
|
Defined in NITTA.Model.ProcessorUnits.Multiplier locks :: Multiplier v x t -> [Lock v] Source # | |
Var v => Locks (Shift v x t) v Source # | |
Var v => Locks (SimpleIO i v x t) v Source # | |
inputsLockOutputs :: Function f v => f -> [Lock v] Source #
All input variables locks all output variables.
class WithFunctions a f | a -> f where Source #
Type class of something, which is related to functions.
Instances
Instances
ToJSON Relation Source # | |
Defined in NITTA.Model.ProcessorUnits.Types toEncoding :: Relation -> Encoding # toJSONList :: [Relation] -> Value # toEncodingList :: [Relation] -> Encoding # | |
Generic Relation Source # | |
Show Relation Source # | |
Eq Relation Source # | |
Ord Relation Source # | |
Defined in NITTA.Model.ProcessorUnits.Types | |
type Rep Relation Source # | |
Defined in NITTA.Model.ProcessorUnits.Types type Rep Relation = D1 ('MetaData "Relation" "NITTA.Model.ProcessorUnits.Types" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "Vertical" 'PrefixI 'True) (S1 ('MetaSel ('Just "vUp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessStepID) :*: S1 ('MetaSel ('Just "vDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessStepID)) :+: C1 ('MetaCons "Horizontal" 'PrefixI 'True) (S1 ('MetaSel ('Just "hPrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessStepID) :*: S1 ('MetaSel ('Just "hNext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessStepID))) |
extractInstructionAt :: (ProcessorUnit u v x t, Typeable u) => u -> t -> [Instruction u] Source #
withShift :: (Eq a, Num a) => a -> a -> a Source #
Shift nextTick
value if it is not zero on a specific offset. Use case: The
processor unit has buffered output, so we should provide oe
signal for one
tick before data actually send to the bus. That raises the following cases:
First usage. We can receive value immediately on nextTick
tick | Endpoint | Instruction | 0 | Target "c" | WR | <- nextTick diff --git a/haddock/nitta/NITTA-Model-Time.html b/haddock/nitta/NITTA-Model-Time.html index 2a3c6c515..eae23a63d 100644 --- a/haddock/nitta/NITTA-Model-Time.html +++ b/haddock/nitta/NITTA-Model-Time.html @@ -1 +1 @@ -
NITTA.Model.Time \ No newline at end of file +Copyright (c) Aleksandr Penskoi 2019 License BSD3 Maintainer aleksandr.penskoi@gmail.com Stability experimental Safe Haskell Safe-Inferred Language Haskell2010 Synopsis
- type VarValTime v x t = (Var v, Val x, Time t)
- type VarValTimeJSON v x t = (VarValTime v x t, ToJSONKey v, ToJSON v, ToJSON x, ToJSON t)
- type Time t = (Default t, Num t, Bounded t, Ord t, Show t, Typeable t, Enum t, Integral t)
- data TimeConstraint t = TimeConstraint {
- tcAvailable :: Interval t
- tcDuration :: Interval t
- data TaggedTime tag t = TaggedTime {}
Documentation
type VarValTime v x t = (Var v, Val x, Time t) Source #
Shortcut for variable (
v
), value (x
) and time (t
) type constrains.type VarValTimeJSON v x t = (VarValTime v x t, ToJSONKey v, ToJSON v, ToJSON x, ToJSON t) Source #
type Time t = (Default t, Num t, Bounded t, Ord t, Show t, Typeable t, Enum t, Integral t) Source #
Shortcut for time type constrain.
data TimeConstraint t Source #
Time constrain for processor activity.
TimeConstraint - tcAvailable :: Interval t
Inclusive interval, when value available to transfer.
- tcDuration :: Interval t
Inclusive interval, possible for value transfers.
Instances
ToJSON tp => ToJSON (TimeConstraint tp) Source # Defined in NITTA.Model.Time
toJSON :: TimeConstraint tp -> Value #
toEncoding :: TimeConstraint tp -> Encoding #
toJSONList :: [TimeConstraint tp] -> Value #
toEncodingList :: [TimeConstraint tp] -> Encoding #
Generic (TimeConstraint t) Source # Defined in NITTA.Model.Time
type Rep (TimeConstraint t) :: Type -> Type #
from :: TimeConstraint t -> Rep (TimeConstraint t) x #
to :: Rep (TimeConstraint t) x -> TimeConstraint t #
(Show t, Eq t, Bounded t) => Show (TimeConstraint t) Source # Defined in NITTA.Model.Time
showsPrec :: Int -> TimeConstraint t -> ShowS #
show :: TimeConstraint t -> String #
showList :: [TimeConstraint t] -> ShowS #
Eq t => Eq (TimeConstraint t) Source # Defined in NITTA.Model.Time
(==) :: TimeConstraint t -> TimeConstraint t -> Bool #
(/=) :: TimeConstraint t -> TimeConstraint t -> Bool #
(ToString v, Time t) => Show (EndpointSt v (TimeConstraint t)) Source # Defined in NITTA.Model.Problems.Endpoint
showsPrec :: Int -> EndpointSt v (TimeConstraint t) -> ShowS #
show :: EndpointSt v (TimeConstraint t) -> String #
showList :: [EndpointSt v (TimeConstraint t)] -> ShowS #
ToSample (EndpointSt String (TimeConstraint Int)) Source # Defined in NITTA.UIBackend.REST
toSamples :: Proxy (EndpointSt String (TimeConstraint Int)) -> [(Text, EndpointSt String (TimeConstraint Int))] #
(UnitTag tag, VarValTime v x t) => SynthesisDecisionCls (SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t) (TargetSystem (BusNetwork tag v x t) tag v x t) (DataflowSt tag v (TimeConstraint t)) (DataflowSt tag v (Interval t)) DataflowMetrics Source # Defined in NITTA.Synthesis.Steps.Dataflow
decisions :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> [(DataflowSt tag v (Interval t), TargetSystem (BusNetwork tag v x t) tag v x t)] Source #
parameters :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> DataflowSt tag v (Interval t) -> DataflowMetrics Source #
estimate :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> DataflowSt tag v (Interval t) -> DataflowMetrics -> Float Source #
type Rep (TimeConstraint t) Source # Defined in NITTA.Model.Time
type Rep (TimeConstraint t) = D1 ('MetaData "TimeConstraint" "NITTA.Model.Time" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "TimeConstraint" 'PrefixI 'True) (S1 ('MetaSel ('Just "tcAvailable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval t)) :*: S1 ('MetaSel ('Just "tcDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval t))))data TaggedTime tag t Source #
Forgoten implementation of tagged time for speculative if statement. Current - dead code.
Instances
Num t => Bounded (TaggedTime tag t) Source # Defined in NITTA.Model.Time
minBound :: TaggedTime tag t #
maxBound :: TaggedTime tag t #
Enum t => Enum (TaggedTime tag t) Source # Defined in NITTA.Model.Time
succ :: TaggedTime tag t -> TaggedTime tag t #
pred :: TaggedTime tag t -> TaggedTime tag t #
toEnum :: Int -> TaggedTime tag t #
fromEnum :: TaggedTime tag t -> Int #
enumFrom :: TaggedTime tag t -> [TaggedTime tag t] #
enumFromThen :: TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
enumFromTo :: TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
enumFromThenTo :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
Generic (TaggedTime tag t) Source # Defined in NITTA.Model.Time
type Rep (TaggedTime tag t) :: Type -> Type #
from :: TaggedTime tag t -> Rep (TaggedTime tag t) x #
to :: Rep (TaggedTime tag t) x -> TaggedTime tag t #
(Num t, Show tag, Eq tag) => Num (TaggedTime tag t) Source # Defined in NITTA.Model.Time
(+) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
(-) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
(*) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
negate :: TaggedTime tag t -> TaggedTime tag t #
abs :: TaggedTime tag t -> TaggedTime tag t #
signum :: TaggedTime tag t -> TaggedTime tag t #
fromInteger :: Integer -> TaggedTime tag t #
Time t => Show (TaggedTime String t) Source # Defined in NITTA.Model.Time
(Time t, Show tag) => Show (TaggedTime tag t) Source # Defined in NITTA.Model.Time
showsPrec :: Int -> TaggedTime tag t -> ShowS #
show :: TaggedTime tag t -> String #
showList :: [TaggedTime tag t] -> ShowS #
Default t => Default (TaggedTime tag t) Source # Defined in NITTA.Model.Time
def :: TaggedTime tag t #
Eq t => Eq (TaggedTime tag t) Source # Defined in NITTA.Model.Time
(==) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(/=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
Ord t => Ord (TaggedTime tag t) Source # Defined in NITTA.Model.Time
compare :: TaggedTime tag t -> TaggedTime tag t -> Ordering #
(<) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(<=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(>) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(>=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
max :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
min :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
type Rep (TaggedTime tag t) Source # Defined in NITTA.Model.Time
type Rep (TaggedTime tag t) = D1 ('MetaData "TaggedTime" "NITTA.Model.Time" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "TaggedTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "tTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe tag)) :*: S1 ('MetaSel ('Just "tClock") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t)))Orphan instances
NITTA.Model.Time \ No newline at end of file diff --git a/haddock/nitta/NITTA-Project-TestBench.html b/haddock/nitta/NITTA-Project-TestBench.html index 9738e14a9..b5ccdaea7 100644 --- a/haddock/nitta/NITTA-Project-TestBench.html +++ b/haddock/nitta/NITTA-Project-TestBench.html @@ -3,4 +3,4 @@ process. You can see tests inCopyright (c) Aleksandr Penskoi 2019 License BSD3 Maintainer aleksandr.penskoi@gmail.com Stability experimental Safe Haskell Safe-Inferred Language Haskell2010 Synopsis
- type VarValTime v x t = (Var v, Val x, Time t)
- type VarValTimeJSON v x t = (VarValTime v x t, ToJSONKey v, ToJSON v, ToJSON x, ToJSON t)
- type Time t = (Default t, Num t, Bounded t, Ord t, Show t, Typeable t, Enum t, Integral t)
- data TimeConstraint t = TimeConstraint {
- tcAvailable :: Interval t
- tcDuration :: Interval t
- data TaggedTime tag t = TaggedTime {}
Documentation
type VarValTime v x t = (Var v, Val x, Time t) Source #
Shortcut for variable (
v
), value (x
) and time (t
) type constrains.type VarValTimeJSON v x t = (VarValTime v x t, ToJSONKey v, ToJSON v, ToJSON x, ToJSON t) Source #
type Time t = (Default t, Num t, Bounded t, Ord t, Show t, Typeable t, Enum t, Integral t) Source #
Shortcut for time type constrain.
data TimeConstraint t Source #
Time constrain for processor activity.
TimeConstraint - tcAvailable :: Interval t
Inclusive interval, when value available to transfer.
- tcDuration :: Interval t
Inclusive interval, possible for value transfers.
Instances
ToJSON tp => ToJSON (TimeConstraint tp) Source # Defined in NITTA.Model.Time
toJSON :: TimeConstraint tp -> Value #
toEncoding :: TimeConstraint tp -> Encoding #
toJSONList :: [TimeConstraint tp] -> Value #
toEncodingList :: [TimeConstraint tp] -> Encoding #
Generic (TimeConstraint t) Source # Defined in NITTA.Model.Time
type Rep (TimeConstraint t) :: Type -> Type #
from :: TimeConstraint t -> Rep (TimeConstraint t) x #
to :: Rep (TimeConstraint t) x -> TimeConstraint t #
(Show t, Eq t, Bounded t) => Show (TimeConstraint t) Source # Defined in NITTA.Model.Time
showsPrec :: Int -> TimeConstraint t -> ShowS #
show :: TimeConstraint t -> String #
showList :: [TimeConstraint t] -> ShowS #
Eq t => Eq (TimeConstraint t) Source # Defined in NITTA.Model.Time
(==) :: TimeConstraint t -> TimeConstraint t -> Bool #
(/=) :: TimeConstraint t -> TimeConstraint t -> Bool #
(ToString v, Time t) => Show (EndpointSt v (TimeConstraint t)) Source # Defined in NITTA.Model.Problems.Endpoint
showsPrec :: Int -> EndpointSt v (TimeConstraint t) -> ShowS #
show :: EndpointSt v (TimeConstraint t) -> String #
showList :: [EndpointSt v (TimeConstraint t)] -> ShowS #
ToSample (EndpointSt String (TimeConstraint Int)) Source # Defined in NITTA.UIBackend.REST
toSamples :: Proxy (EndpointSt String (TimeConstraint Int)) -> [(Text, EndpointSt String (TimeConstraint Int))] #
(UnitTag tag, VarValTime v x t) => SynthesisDecisionCls (SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t) (TargetSystem (BusNetwork tag v x t) tag v x t) (DataflowSt tag v (TimeConstraint t)) (DataflowSt tag v (Interval t)) DataflowMetrics Source # Defined in NITTA.Synthesis.Steps.Dataflow
decisions :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> [(DataflowSt tag v (Interval t), TargetSystem (BusNetwork tag v x t) tag v x t)] Source #
parameters :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> DataflowSt tag v (Interval t) -> DataflowMetrics Source #
estimate :: SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t -> DataflowSt tag v (TimeConstraint t) -> DataflowSt tag v (Interval t) -> DataflowMetrics -> Float Source #
type Rep (TimeConstraint t) Source # Defined in NITTA.Model.Time
type Rep (TimeConstraint t) = D1 ('MetaData "TimeConstraint" "NITTA.Model.Time" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "TimeConstraint" 'PrefixI 'True) (S1 ('MetaSel ('Just "tcAvailable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval t)) :*: S1 ('MetaSel ('Just "tcDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval t))))data TaggedTime tag t Source #
Forgoten implementation of tagged time for speculative if statement. Current - dead code.
Instances
Num t => Bounded (TaggedTime tag t) Source # Defined in NITTA.Model.Time
minBound :: TaggedTime tag t #
maxBound :: TaggedTime tag t #
Enum t => Enum (TaggedTime tag t) Source # Defined in NITTA.Model.Time
succ :: TaggedTime tag t -> TaggedTime tag t #
pred :: TaggedTime tag t -> TaggedTime tag t #
toEnum :: Int -> TaggedTime tag t #
fromEnum :: TaggedTime tag t -> Int #
enumFrom :: TaggedTime tag t -> [TaggedTime tag t] #
enumFromThen :: TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
enumFromTo :: TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
enumFromThenTo :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t -> [TaggedTime tag t] #
Generic (TaggedTime tag t) Source # Defined in NITTA.Model.Time
type Rep (TaggedTime tag t) :: Type -> Type #
from :: TaggedTime tag t -> Rep (TaggedTime tag t) x #
to :: Rep (TaggedTime tag t) x -> TaggedTime tag t #
(Num t, Show tag, Eq tag) => Num (TaggedTime tag t) Source # Defined in NITTA.Model.Time
(+) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
(-) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
(*) :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
negate :: TaggedTime tag t -> TaggedTime tag t #
abs :: TaggedTime tag t -> TaggedTime tag t #
signum :: TaggedTime tag t -> TaggedTime tag t #
fromInteger :: Integer -> TaggedTime tag t #
Time t => Show (TaggedTime String t) Source # Defined in NITTA.Model.Time
(Time t, Show tag) => Show (TaggedTime tag t) Source # Defined in NITTA.Model.Time
showsPrec :: Int -> TaggedTime tag t -> ShowS #
show :: TaggedTime tag t -> String #
showList :: [TaggedTime tag t] -> ShowS #
Default t => Default (TaggedTime tag t) Source # Defined in NITTA.Model.Time
def :: TaggedTime tag t #
Eq t => Eq (TaggedTime tag t) Source # Defined in NITTA.Model.Time
(==) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(/=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
Ord t => Ord (TaggedTime tag t) Source # Defined in NITTA.Model.Time
compare :: TaggedTime tag t -> TaggedTime tag t -> Ordering #
(<) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(<=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(>) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
(>=) :: TaggedTime tag t -> TaggedTime tag t -> Bool #
max :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
min :: TaggedTime tag t -> TaggedTime tag t -> TaggedTime tag t #
type Rep (TaggedTime tag t) Source # Defined in NITTA.Model.Time
type Rep (TaggedTime tag t) = D1 ('MetaData "TaggedTime" "NITTA.Model.Time" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "TaggedTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "tTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe tag)) :*: S1 ('MetaSel ('Just "tClock") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t)))Orphan instances
test/Spec.hs
. Testbench contains:- The sequence of control signals that implement the already scheduled process.
- The sequence of bus state checks in which we compare actual values with the results of the functional simulation.
Defined in NITTA.Model.ProcessorUnits.Multiplier
testBenchImplementation :: Project (Multiplier v x t) v x -> Implementation Source #
(UnitTag tag, VarValTime v x t) => Testable (BusNetwork tag v x t) v x Source # Defined in NITTA.Model.Networks.Bus
testBenchImplementation :: Project (BusNetwork tag v x t) v x -> Implementation Source #
class IOTestBench pu v x | pu -> v x where Source #
Processor units with input/output ports should be tested by generation external input ports signals and checking output port signals.
Nothing
testEnvironmentInitFlag :: Text -> pu -> Maybe Text Source #
testEnvironment :: Text -> pu -> UnitEnv pu -> TestEnvironment v x -> Maybe Verilog Source #
Instances
IOTestBench (PU v x t) v x Source # | |
Defined in NITTA.Model.Networks.Types | |
IOTestBench (Accum v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.Accum | |
IOTestBench (Broken v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.Broken | |
IOTestBench (Divider v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.Divider | |
IOTestBench (Fram v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.Fram | |
VarValTime v x t => IOTestBench (SPI v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.IO.SPI | |
IOTestBench (Multiplier v x t) v x Source # | Empty implementation of |
Defined in NITTA.Model.ProcessorUnits.Multiplier testEnvironmentInitFlag :: Text -> Multiplier v x t -> Maybe Text Source # testEnvironment :: Text -> Multiplier v x t -> UnitEnv (Multiplier v x t) -> TestEnvironment v x -> Maybe Verilog Source # | |
IOTestBench (Shift v x t) v x Source # | |
Defined in NITTA.Model.ProcessorUnits.Shift |
data TestEnvironment v x Source #
Information required for testbench generation.
TestEnvironment | |
|
data TestbenchReport v x Source #
TestbenchReport | |
|
Instances
(ToJSONKey v, ToJSON v, ToJSON x) => ToJSON (TestbenchReport v x) Source # | |
Defined in NITTA.UIBackend.ViewHelper toJSON :: TestbenchReport v x -> Value # toEncoding :: TestbenchReport v x -> Encoding # toJSONList :: [TestbenchReport v x] -> Value # toEncodingList :: [TestbenchReport v x] -> Encoding # | |
Generic (TestbenchReport v x) Source # | |
Defined in NITTA.Project.TestBench type Rep (TestbenchReport v x) :: Type -> Type # from :: TestbenchReport v x -> Rep (TestbenchReport v x) x0 # to :: Rep (TestbenchReport v x) x0 -> TestbenchReport v x # | |
(ToString v, Show x) => Show (TestbenchReport v x) Source # | |
Defined in NITTA.Project.TestBench showsPrec :: Int -> TestbenchReport v x -> ShowS # show :: TestbenchReport v x -> String # showList :: [TestbenchReport v x] -> ShowS # | |
ToSample (TestbenchReport String Int) Source # | |
Defined in NITTA.UIBackend.ViewHelper toSamples :: Proxy (TestbenchReport String Int) -> [(Text, TestbenchReport String Int)] # | |
type Rep (TestbenchReport v x) Source # | |
Defined in NITTA.Project.TestBench type Rep (TestbenchReport v x) = D1 ('MetaData "TestbenchReport" "NITTA.Project.TestBench" "nitta-0.0.0.1-Bv1VcjPxpSzB9i0NGusGVn" 'False) (C1 ('MetaCons "TestbenchReport" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tbStatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "tbPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :*: (S1 ('MetaSel ('Just "tbFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "tbFunctions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) :*: ((S1 ('MetaSel ('Just "tbSynthesisSteps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "tbCompilerDump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tbSimulationDump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "tbFunctionalSimulationLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HashMap v x]) :*: S1 ('MetaSel ('Just "tbLogicalSimulationLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HashMap v x])))))) |
testBenchTopModuleName :: (TargetSystemComponent m, Testable m v x) => Project m v x -> FilePath Source #
Get name of testbench top module.
verilogProjectFiles :: (TargetSystemComponent m, Testable m v x) => Project m v x -> [FilePath] Source #
Generate list of project verilog files (including testbench).
data SnippetTestBenchConf m Source #
Data Type for SnippetTestBench function
SnippetTestBenchConf | |
|
snippetTestBench :: forall m v x t. (WithFunctions m (F v x), ProcessorUnit m v x t, TargetSystemComponent m, UnambiguouslyDecode m, Typeable m, Show (Instruction m), Default (Microcode m)) => Project m v x -> SnippetTestBenchConf m -> Text Source #
Function for testBench PU test