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