lion-0.4.0.0: RISC-V Core
Copyright(c) David Cox 2024
LicenseBSD-3-Clause
Maintainerstandardsemiconductor@gmail.com
Safe HaskellNone
LanguageHaskell2010

Lion.Core

Description

The Lion core is a 32-bit RISC-V processor written in Haskell using Clash. Note, all peripherals and memory must have single cycle latency. See lion-soc for an example of using the Lion core in a system.

Synopsis

Documentation

core Source #

Arguments

:: 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

Instances details
Eq CoreConfig Source # 
Instance details

Defined in Lion.Core

Show CoreConfig Source # 
Instance details

Defined in Lion.Core

Generic CoreConfig Source # 
Instance details

Defined in Lion.Core

Associated Types

type Rep CoreConfig :: Type -> Type Source #

type Rep CoreConfig Source # 
Instance details

Defined in Lion.Core

type Rep CoreConfig = D1 ('MetaData "CoreConfig" "Lion.Core" "lion-0.4.0.0-inplace" 'False) (C1 ('MetaCons "CoreConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "aluConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AluConfig) :*: S1 ('MetaSel ('Just "pipeConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PipeConfig)))

data AluConfig Source #

ALU configuration

Constructors

Hard

use hard adder and subtractor from iCE40 SB_MAC16

Soft

use generic adder and subtractor: (+) and (-)

Instances

Instances details
Eq AluConfig Source # 
Instance details

Defined in Lion.Alu

Show AluConfig Source # 
Instance details

Defined in Lion.Alu

Generic AluConfig Source # 
Instance details

Defined in Lion.Alu

Associated Types

type Rep AluConfig :: Type -> Type Source #

type Rep AluConfig Source # 
Instance details

Defined in Lion.Alu

type Rep AluConfig = D1 ('MetaData "AluConfig" "Lion.Alu" "lion-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Hard" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Soft" 'PrefixI 'False) (U1 :: Type -> Type))

newtype PipeConfig Source #

Pipeline configuration

Constructors

PipeConfig 

Fields

Instances

Instances details
Eq PipeConfig Source # 
Instance details

Defined in Lion.Pipe

Show PipeConfig Source # 
Instance details

Defined in Lion.Pipe

Generic PipeConfig Source # 
Instance details

Defined in Lion.Pipe

Associated Types

type Rep PipeConfig :: Type -> Type Source #

type Rep PipeConfig Source # 
Instance details

Defined in Lion.Pipe

type Rep PipeConfig = D1 ('MetaData "PipeConfig" "Lion.Pipe" "lion-0.4.0.0-inplace" 'True) (C1 ('MetaCons "PipeConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "startPC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BitVector 32))))

data FromCore dom Source #

Core outputs

Constructors

FromCore 

Fields

data ToMem Source #

Memory bus

Constructors

ToMem 

Fields

Instances

Instances details
Eq ToMem Source # 
Instance details

Defined in Lion.Pipe

Methods

(==) :: ToMem -> ToMem -> Bool Source #

(/=) :: ToMem -> ToMem -> Bool Source #

Show ToMem Source # 
Instance details

Defined in Lion.Pipe

Generic ToMem Source # 
Instance details

Defined in Lion.Pipe

Associated Types

type Rep ToMem :: Type -> Type Source #

Methods

from :: ToMem -> Rep ToMem x Source #

to :: Rep ToMem x -> ToMem Source #

NFDataX ToMem Source # 
Instance details

Defined in Lion.Pipe

type Rep ToMem Source # 
Instance details

Defined in Lion.Pipe

data MemoryAccess Source #

Memory access - Lion has a shared instruction/memory bus

Constructors

InstrMem

instruction access

DataMem

data access

Instances

Instances details
Eq MemoryAccess Source # 
Instance details

Defined in Lion.Pipe

Show MemoryAccess Source # 
Instance details

Defined in Lion.Pipe

Generic MemoryAccess Source # 
Instance details

Defined in Lion.Pipe

Associated Types

type Rep MemoryAccess :: Type -> Type Source #

NFDataX MemoryAccess Source # 
Instance details

Defined in Lion.Pipe

type Rep MemoryAccess Source # 
Instance details

Defined in Lion.Pipe

type Rep MemoryAccess = D1 ('MetaData "MemoryAccess" "Lion.Pipe" "lion-0.4.0.0-inplace" 'False) (C1 ('MetaCons "InstrMem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMem" 'PrefixI 'False) (U1 :: Type -> Type))