Copyright | (c) David Cox 2024 |
---|---|
License | BSD-3-Clause |
Maintainer | standardsemiconductor@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Lion.Core
Description
Synopsis
- core :: forall (dom :: Domain). HiddenClockResetEnable dom => CoreConfig -> Signal dom (BitVector 32) -> FromCore dom
- defaultCoreConfig :: CoreConfig
- defaultPipeConfig :: PipeConfig
- data CoreConfig = CoreConfig {}
- data AluConfig
- newtype PipeConfig = PipeConfig {}
- data FromCore (dom :: Domain) = FromCore {}
- data ToMem = ToMem {
- memAccess :: MemoryAccess
- memAddress :: BitVector 32
- memByteMask :: BitVector 4
- memWrite :: Maybe (BitVector 32)
- data MemoryAccess
Documentation
Arguments
:: forall (dom :: Domain). HiddenClockResetEnable dom | |
=> CoreConfig | core configuration |
-> Signal dom (BitVector 32) | core input, from memory/peripherals |
-> FromCore dom | core output |
RISC-V Core: RV32I
defaultPipeConfig :: PipeConfig Source #
Default pipeline configuration
startPC
= 0
data CoreConfig Source #
Core configuration
Constructors
CoreConfig | |
Fields
|
Instances
ALU configuration
Constructors
Hard | use hard adder and subtractor from iCE40 SB_MAC16 |
Soft | use generic adder and subtractor: (+) and (-) |
newtype PipeConfig Source #
Pipeline configuration
Constructors
PipeConfig | |
Instances
Generic PipeConfig Source # | |||||
Defined in Lion.Pipe Associated Types
| |||||
Show PipeConfig Source # | |||||
Defined in Lion.Pipe Methods showsPrec :: Int -> PipeConfig -> ShowS # show :: PipeConfig -> String # showList :: [PipeConfig] -> ShowS # | |||||
Eq PipeConfig Source # | |||||
Defined in Lion.Pipe | |||||
type Rep PipeConfig Source # | |||||
Defined in Lion.Pipe type Rep PipeConfig = D1 ('MetaData "PipeConfig" "Lion.Pipe" "lion-0.4.0.1-inplace" 'True) (C1 ('MetaCons "PipeConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "startPC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BitVector 32)))) |
Memory bus
Constructors
ToMem | |
Fields
|
Instances
Generic ToMem Source # | |||||
Defined in Lion.Pipe Associated Types
| |||||
Show ToMem Source # | |||||
NFDataX ToMem Source # | |||||
Eq ToMem Source # | |||||
type Rep ToMem Source # | |||||
Defined in Lion.Pipe type Rep ToMem = D1 ('MetaData "ToMem" "Lion.Pipe" "lion-0.4.0.1-inplace" 'False) (C1 ('MetaCons "ToMem" 'PrefixI 'True) ((S1 ('MetaSel ('Just "memAccess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MemoryAccess) :*: S1 ('MetaSel ('Just "memAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BitVector 32))) :*: (S1 ('MetaSel ('Just "memByteMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BitVector 4)) :*: S1 ('MetaSel ('Just "memWrite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (BitVector 32)))))) |
data MemoryAccess Source #
Memory access - Lion has a shared instruction/memory bus
Instances
Generic MemoryAccess Source # | |||||
Defined in Lion.Pipe Associated Types
| |||||
Show MemoryAccess Source # | |||||
Defined in Lion.Pipe Methods showsPrec :: Int -> MemoryAccess -> ShowS # show :: MemoryAccess -> String # showList :: [MemoryAccess] -> ShowS # | |||||
NFDataX MemoryAccess Source # | |||||
Defined in Lion.Pipe Methods deepErrorX :: String -> MemoryAccess # hasUndefined :: MemoryAccess -> Bool # ensureSpine :: MemoryAccess -> MemoryAccess # rnfX :: MemoryAccess -> () # | |||||
Eq MemoryAccess Source # | |||||
Defined in Lion.Pipe | |||||
type Rep MemoryAccess Source # | |||||