lion-0.3.0.0: RISC-V Core
Copyright(c) David Cox 2021
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

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

Default core configuration

ALU configuration = Soft

pipeConfig = defaultPipeConfig

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

Instances details
Eq (CoreConfig startPC a) Source # 
Instance details

Defined in Lion.Core

Methods

(==) :: CoreConfig startPC a -> CoreConfig startPC a -> Bool #

(/=) :: CoreConfig startPC a -> CoreConfig startPC a -> Bool #

Show (CoreConfig startPC a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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

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 #

type Rep AluConfig Source # 
Instance details

Defined in Lion.Alu

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

data PipeConfig (startPC :: Nat) Source #

Pipeline configuration

Constructors

PipeConfig 

Instances

Instances details
Eq (PipeConfig startPC) Source # 
Instance details

Defined in Lion.Pipe

Methods

(==) :: PipeConfig startPC -> PipeConfig startPC -> Bool #

(/=) :: PipeConfig startPC -> PipeConfig startPC -> Bool #

Show (PipeConfig startPC) Source # 
Instance details

Defined in Lion.Pipe

Methods

showsPrec :: Int -> PipeConfig startPC -> ShowS #

show :: PipeConfig startPC -> String #

showList :: [PipeConfig startPC] -> ShowS #

Generic (PipeConfig startPC) Source # 
Instance details

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 # 
Instance details

Defined in Lion.Pipe

type Rep (PipeConfig startPC) = D1 ('MetaData "PipeConfig" "Lion.Pipe" "lion-0.3.0.0-5TeZzf2f4nX8XqM2dA3bRI" 'False) (C1 ('MetaCons "PipeConfig" 'PrefixI 'False) (U1 :: Type -> Type))

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 #

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

Show ToMem Source # 
Instance details

Defined in Lion.Pipe

Methods

showsPrec :: Int -> ToMem -> ShowS #

show :: ToMem -> String #

showList :: [ToMem] -> ShowS #

Generic ToMem Source # 
Instance details

Defined in Lion.Pipe

Associated Types

type Rep ToMem :: Type -> Type #

Methods

from :: ToMem -> Rep ToMem x #

to :: Rep ToMem x -> ToMem #

NFDataX ToMem Source # 
Instance details

Defined in Lion.Pipe

type Rep ToMem Source # 
Instance details

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

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 #

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.3.0.0-5TeZzf2f4nX8XqM2dA3bRI" 'False) (C1 ('MetaCons "InstrMem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMem" 'PrefixI 'False) (U1 :: Type -> Type))

class Alu (config :: AluConfig) Source #

Minimal complete definition

alu

Instances

Instances details
Alu 'Hard Source # 
Instance details

Defined in Lion.Alu

Methods

alu :: forall (dom :: Domain). HiddenClockResetEnable dom => Proxy 'Hard -> Signal dom Op -> Signal dom (BitVector 32) -> Signal dom (BitVector 32) -> Signal dom (BitVector 32)

Alu 'Soft Source # 
Instance details

Defined in Lion.Alu

Methods

alu :: forall (dom :: Domain). HiddenClockResetEnable dom => Proxy 'Soft -> Signal dom Op -> Signal dom (BitVector 32) -> Signal dom (BitVector 32) -> Signal dom (BitVector 32)