Skip to content

Commit

Permalink
Initial refactoring, introduction of platform-specific handlers.
Browse files Browse the repository at this point in the history
Refactoring:
- Reorganize src directory
- Rename Program -> Machine, RiscvProgram -> RiscvMachine.

RiscvMachine has new function: getPlatform returns a Platform, which contains
functions for deciding things not specified in the spec. Included an example
usage for deciding whether to set dirty/access bits in hardware or software.
  • Loading branch information
ijc8 committed Jan 17, 2019
1 parent e4f35fb commit 25f096a
Show file tree
Hide file tree
Showing 55 changed files with 337 additions and 292 deletions.
File renamed without changes.
File renamed without changes.
2 changes: 1 addition & 1 deletion make-circuit.sh
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
#!/bin/bash
cd src
stack exec -- clash --verilog Clash.hs
stack exec -- clash --verilog Platform/Clash.hs


2 changes: 1 addition & 1 deletion riscv-compliance.py
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@

# ================================================================

simulator = "stack exec -- riscv-semantics-rv32im-compliance src/device_tree.bin"
simulator = "stack exec -- riscv-semantics-rv32im-compliance device_tree.bin"

num_executed = 0
num_passed = 0
Expand Down
12 changes: 6 additions & 6 deletions riscv-semantics.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -16,18 +16,18 @@ extra-source-files: ChangeLog.md, README.md
cabal-version: >=1.10

executable riscv-semantics
main-is: MainRun.hs
main-is: Platform/MainRun.hs
ghc-options: -threaded
other-modules: Run, Run32, CSR, CSRField, CSRFile, CSRSpec, Decode, Elf, Execute, ExecuteCSR, ExecuteI, ExecuteI64, ExecuteM, ExecuteM64, Minimal64, Minimal32, ExecuteA, ExecuteA64, ExecuteF, ExecuteF64, MMIO, MapMemory, Memory, Program, Utility, VirtualMemory, Spec, TLBExperiment, BufferMMIO
other-modules: Platform.Run, Platform.Run32, Spec.CSR, Spec.CSRField, Spec.CSRFile, Spec.CSRSpec, Spec.Decode, Utility.Elf, Spec.Execute, Spec.ExecuteCSR, Spec.ExecuteI, Spec.ExecuteI64, Spec.ExecuteM, Spec.ExecuteM64, Platform.Minimal64, Platform.Minimal32, Spec.ExecuteA, Spec.ExecuteA64, Spec.ExecuteF, Spec.ExecuteF64, Platform.MMIO, Utility.MapMemory, Spec.Memory, Spec.Machine, Utility.Utility, Spec.VirtualMemory, Spec.Spec, Platform.TLBExperiment, Platform.BufferMMIO
other-extensions: MultiParamTypeClasses, FlexibleInstances, MultiWayIf, FunctionalDependencies, ScopedTypeVariables, NamedFieldPuns
build-depends: base >=4.9 && <4.11, mtl >=2.2 && <2.3, transformers >=0.5 && <0.6, containers >=0.5 && <0.6, bytestring >=0.10 && <0.11, text >=1.2 && <1.3, elf >=0.28, nondeterminism >=1.4, ilist >=0.3, softfloat-hs ==0.1.0
hs-source-dirs: src
default-language: Haskell2010

executable riscv-semantics-rv32im-compliance
main-is: MainCompliance.hs
main-is: Platform/MainCompliance.hs
ghc-options: -threaded
other-modules: Run, Run32, CSR, CSRField, CSRFile, CSRSpec, Decode, Elf, Execute, ExecuteCSR, ExecuteI, ExecuteI64, ExecuteM, ExecuteM64, Minimal64, Minimal32, ExecuteA, ExecuteA64, ExecuteF, ExecuteF64, MMIO, MapMemory, Memory, Program, Utility, VirtualMemory, Spec, TLBExperiment, BufferMMIO
other-modules: Platform.Run, Platform.Run32, Spec.CSR, Spec.CSRField, Spec.CSRFile, Spec.CSRSpec, Spec.Decode, Utility.Elf, Spec.Execute, Spec.ExecuteCSR, Spec.ExecuteI, Spec.ExecuteI64, Spec.ExecuteM, Spec.ExecuteM64, Platform.Minimal64, Platform.Minimal32, Spec.ExecuteA, Spec.ExecuteA64, Spec.ExecuteF, Spec.ExecuteF64, Platform.MMIO, Utility.MapMemory, Spec.Memory, Spec.Machine, Utility.Utility, Spec.VirtualMemory, Spec.Spec, Platform.TLBExperiment, Platform.BufferMMIO
other-extensions: MultiParamTypeClasses, FlexibleInstances, MultiWayIf, FunctionalDependencies, ScopedTypeVariables, NamedFieldPuns
build-depends: base >=4.9 && <4.11, mtl >=2.2 && <2.3, transformers >=0.5 && <0.6, containers >=0.5 && <0.6, bytestring >=0.10 && <0.11, text >=1.2 && <1.3, elf >=0.28, nondeterminism >=1.4, ilist >=0.3, softfloat-hs ==0.1.0
hs-source-dirs: src
Expand All @@ -36,9 +36,9 @@ executable riscv-semantics-rv32im-compliance


executable riscv-semantics-tests
main-is: MainTest.hs
main-is: Platform/MainTest.hs
ghc-options: -threaded
other-modules: Run, Test, BufferMMIO, CSR, CSRField, CSRFile, CSRSpec, Decode, Elf, Execute, ExecuteCSR, ExecuteI, ExecuteI64, ExecuteM, ExecuteM64, ExecuteA, ExecuteA64, ExecuteF, ExecuteF64, Minimal64, MMIO, MapMemory, Memory, Program, Utility, VirtualMemory, Spec, TLBExperiment
other-modules: Platform.Run, Platform.Test, Platform.BufferMMIO, Spec.CSR, Spec.CSRField, Spec.CSRFile, Spec.CSRSpec, Spec.Decode, Utility.Elf, Spec.Execute, Spec.ExecuteCSR, Spec.ExecuteI, Spec.ExecuteI64, Spec.ExecuteM, Spec.ExecuteM64, Spec.ExecuteA, Spec.ExecuteA64, Spec.ExecuteF, Spec.ExecuteF64, Platform.Minimal64, Platform.MMIO, Utility.MapMemory, Spec.Memory, Spec.Machine, Utility.Utility, Spec.VirtualMemory, Spec.Spec, Platform.TLBExperiment
other-extensions: MultiParamTypeClasses, FlexibleInstances, MultiWayIf, FunctionalDependencies, ScopedTypeVariables, NamedFieldPuns
build-depends: base >=4.9 && <4.11, mtl >=2.2 && <2.3, transformers >=0.5 && <0.6, containers >=0.5 && <0.6, bytestring >=0.10 && <0.11, text >=1.2 && <1.3, elf >=0.28, directory >=1.3 && <1.4, filepath >=1.4 && <1.5, nondeterminism >=1.4, ilist >=0.3, softfloat-hs ==0.1.0
hs-source-dirs: src
Expand Down
3 changes: 0 additions & 3 deletions src/MainCompliance.hs

This file was deleted.

3 changes: 0 additions & 3 deletions src/MainRun.hs

This file was deleted.

4 changes: 0 additions & 4 deletions src/MainTest.hs

This file was deleted.

9 changes: 5 additions & 4 deletions src/BufferMMIO.hs → src/Platform/BufferMMIO.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, MultiWayIf, UndecidableInstances #-}
module BufferMMIO where
module Platform.BufferMMIO where
import Data.Bits
import Data.Int
import Data.Char
Expand All @@ -8,8 +8,8 @@ import Control.Monad.State
import Control.Monad.Writer
import qualified Data.Map as S

import Program
import Utility
import Spec.Machine
import Utility.Utility

-- Simple State monad to simulate IO. The first string represents input, the
-- second represents output.
Expand Down Expand Up @@ -50,7 +50,7 @@ rvNull val = return ()
mmioTable :: S.Map MachineInt (LoadFunc s, StoreFunc s)
mmioTable = S.fromList [(0xfff0, (rvZero, rvPutChar)), (0xfff4, (rvGetChar, rvNull))]

instance (RiscvProgram (State s) t, MachineWidth t) => RiscvProgram (BufferState s) t where
instance (RiscvMachine (State s) t, MachineWidth t) => RiscvMachine (BufferState s) t where
getRegister r = liftState (getRegister r)
setRegister r v = liftState (setRegister r v)
getFPRegister r = liftState (getFPRegister r)
Expand Down Expand Up @@ -83,3 +83,4 @@ instance (RiscvProgram (State s) t, MachineWidth t) => RiscvProgram (BufferState
inTLB a b = liftState (inTLB a b) -- noTLB
addTLB a b c = liftState (addTLB a b c)
flushTLB = liftState flushTLB
getPlatform = liftState getPlatform
14 changes: 7 additions & 7 deletions src/Clash.hs → src/Platform/Clash.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, MultiWayIf #-}
module Clash where
module Platform.Clash where
--import qualified Prelude as P
import Program
import Utility
import CSR
import Spec.Machine
import Utility.Utility
import Spec.CSR
import Data.Int
import Data.Word
import Data.Bits
Expand All @@ -17,8 +17,8 @@ import Control.Monad.Trans
import Control.Monad.Trans.Maybe
import System.IO.Error
import qualified Data.Map as S
import ExecuteClash
import qualified Decode as D
import Platform.ExecuteClash
import qualified Spec.Decode as D
import Clash.Prelude


Expand Down Expand Up @@ -47,7 +47,7 @@ embed byteen store -- quot get rid of the bits on the right fromIntegral, those
|(\(x,y,z,t)-> y) byteen == True = fromIntegral (store * 65536)
|(\(x,y,z,t)-> x) byteen == True = fromIntegral (store * 16777216)

instance RiscvProgram MState Int32 where
instance RiscvMachine MState Int32 where
getRegister reg = state $ \comp -> (if reg == 0 then 0 else (registers comp) !! (fromIntegral reg-1), comp)
setRegister reg val = state $ \comp -> ((), if reg == 0 then comp else comp { registers = replace (fromIntegral reg-1) (fromIntegral val) (registers comp) })
loadByte ina = state $ \comp -> let a = ina .&. (complement 3)
Expand Down
14 changes: 7 additions & 7 deletions src/ClashAccelerator.hs → src/Platform/ClashAccelerator.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, MultiWayIf #-}
module Clash where
module Platform.Clash where
--import qualified Prelude as P
import Program
import Utility
import CSR
import Spec.Machine
import Utility.Utility
import Spec.CSR
import Data.Int
import Data.Word
import Data.Bits
Expand All @@ -16,11 +16,11 @@ import Control.Monad.State
import Control.Monad.Trans
import Control.Monad.Trans.Maybe
import qualified Data.Map as S
import ExecuteClash
import Spec.ExecuteClash
import qualified Decode as D
import Clash.Prelude
import qualified Memory as M
import MapMemory()
import qualified Spec.Memory as M
import Utility.MapMemory()
import GcdExpr

data MMIOClash = MMIOClash { registers :: Vec 31 Int32, pc :: Int32, nextPC :: Int32 , store:: Maybe (Int32,Int32,(Bool,Bool,Bool,Bool)), gcdI1 :: Int32, gcdI2 :: Int32 , exception :: Bool }
Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.
18 changes: 9 additions & 9 deletions src/ExecuteClash.hs → src/Platform/ExecuteClash.hs
Original file line number Diff line number Diff line change
@@ -1,15 +1,15 @@
module ExecuteClash where
import Decode
import Program
import qualified CSRField as Field
import ExecuteI as I
import ExecuteM as M
import ExecuteCSR as CSR
module Platform.ExecuteClash where
import Spec.Decode
import Spec.Machine
import qualified Spec.CSRField as Field
import Spec.ExecuteI as I
import Spec.ExecuteM as M
import Spec.ExecuteCSR as CSR
import Control.Monad
import Control.Monad.Trans.Maybe
import Prelude
import Prelude

execute :: (RiscvProgram p t) => Instruction -> p ()
execute :: (RiscvMachine p t) => Instruction -> p ()
execute inst = do
case inst of
IInstruction i -> I.execute i
Expand Down
File renamed without changes.
6 changes: 3 additions & 3 deletions src/MMGFX32.hs → src/Platform/MMGFX32.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, MultiWayIf #-}
module MMGFX32 where
import Prelude
import Program
import Utility
import CSR
import Spec.Machine
import Utility.Utility
import Spec.CSR
import Data.Int
import Data.Word
import Data.Bits
Expand Down
8 changes: 4 additions & 4 deletions src/MMIO.hs → src/Platform/MMIO.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, MultiWayIf, UndecidableInstances, ScopedTypeVariables, InstanceSigs #-}
module MMIO where
module Platform.MMIO where
import Data.Bits
import Data.Int
import Data.Char
Expand All @@ -8,8 +8,8 @@ import Control.Monad.State
import System.IO.Error
import qualified Data.Map as S

import Program
import Utility
import Spec.Machine
import Utility.Utility

type IOState s = StateT s IO

Expand Down Expand Up @@ -38,7 +38,7 @@ rvNull val = return ()
mmioTable :: S.Map MachineInt (LoadFunc s, StoreFunc s)
mmioTable = S.fromList [(0xfff0, (rvZero, rvPutChar)), (0xfff4, (rvGetChar, rvNull))]

instance (RiscvProgram (State s) t, MachineWidth t) => RiscvProgram (IOState s) t where
instance (RiscvMachine (State s) t, MachineWidth t) => RiscvMachine (IOState s) t where
getRegister r = liftState (getRegister r)
setRegister r v = liftState (setRegister r v)
getFPRegister r = liftState (getFPRegister r)
Expand Down
3 changes: 3 additions & 0 deletions src/Platform/MainCompliance.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
import qualified Platform.RunCompliance as Run

main = Run.main
3 changes: 3 additions & 0 deletions src/Platform/MainRun.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
import qualified Platform.Run as Run

main = Run.main
4 changes: 4 additions & 0 deletions src/Platform/MainTest.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
import qualified Platform.Test as Test


main = Test.main
18 changes: 9 additions & 9 deletions src/Minimal32.hs → src/Platform/Minimal32.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables, InstanceSigs #-}
module Minimal32 where
import Program
import Decode
import Utility
import CSRFile
import qualified CSRField as Field
import qualified Memory as M
import MapMemory
module Platform.Minimal32 where
import Spec.Machine
import Spec.Decode
import Utility.Utility
import Spec.CSRFile
import qualified Spec.CSRField as Field
import qualified Spec.Memory as M
import Utility.MapMemory
import Data.Bits
import Data.Int
import Data.Word
Expand Down Expand Up @@ -44,7 +44,7 @@ wrapLoad loadFunc addr = state $ \comp -> ((fromIntegral:: r -> r') $ loadFunc (
wrapStore :: forall a' v v' m. (Integral a', Integral v, Integral v') => (MapMemory Int -> Int -> v -> MapMemory Int) -> (a' -> v' -> MState ())
wrapStore storeFunc addr val = state $ \comp -> ((), comp { mem = storeFunc (mem comp) ((fromIntegral:: Word32 -> Int) ((fromIntegral:: a' -> Word32) addr)) ((fromIntegral:: v' -> v) val) })

instance RiscvProgram MState Int32 where
instance RiscvMachine MState Int32 where
getRegister reg = state $ \comp -> (if reg == 0 then 0 else (registers comp) !! ((fromIntegral:: Register -> Int) reg-1), comp)
setRegister :: forall s. (Integral s) => Register -> s -> MState ()
setRegister reg val = state $ \comp -> ((), if reg == 0 then comp else comp { registers = setIndex ((fromIntegral:: Register -> Int) reg-1) ((fromIntegral:: s -> Int32) val) (registers comp) })
Expand Down
20 changes: 11 additions & 9 deletions src/Minimal64.hs → src/Platform/Minimal64.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables, InstanceSigs, AllowAmbiguousTypes #-}
module Minimal64 where
import Program
import Decode
import Utility
import CSRFile
import qualified CSRField as Field
import qualified Memory as M
import MapMemory
module Platform.Minimal64 where
import Spec.Machine
import Spec.Decode
import Utility.Utility
import Spec.CSRFile
import qualified Spec.CSRField as Field
import qualified Spec.Memory as M
import Utility.MapMemory
import Data.Bits
import Data.Int
import Data.Word
Expand Down Expand Up @@ -53,7 +53,7 @@ wrapLoad loadFunc addr = state $ \comp -> ((fromIntegral:: r -> r') $ loadFunc (
wrapStore :: forall a' v v' m. (Integral a', Integral v, Integral v') => (MapMemory Int -> Int -> v -> MapMemory Int) -> (a' -> v' -> MState ())
wrapStore storeFunc addr val = state $ \comp -> ((), comp { mem = storeFunc (mem comp) ((fromIntegral:: Word64 -> Int) ((fromIntegral:: a' -> Word64) addr)) ((fromIntegral:: v' -> v) val) })

instance RiscvProgram MState Int64 where
instance RiscvMachine MState Int64 where
getRegister reg = state $ \comp -> (if reg == 0 then 0 else fromMaybe 0 (S.lookup reg (registers comp)), comp)
setRegister :: forall s. (Integral s) => Register -> s -> MState ()
setRegister reg val = state $ \comp -> ((), if reg == 0 then comp else comp { registers = S.insert reg (fromIntegral val) (registers comp) })
Expand Down Expand Up @@ -121,3 +121,5 @@ instance RiscvProgram MState Int64 where
inTLB a b = return Nothing -- noTLB
addTLB a b c= return ()
flushTLB = return ()

getPlatform = return (Platform (return False))
28 changes: 14 additions & 14 deletions src/Run.hs → src/Platform/Run.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,22 @@
module Run where
module Platform.Run where
import System.IO
import System.Environment
import System.Exit
import Data.Int
import Data.List
import Data.Word
import Utility
import Program
import Minimal64
import MMIO
import Elf
import qualified CSRField as Field
import CSRFile
import Decode
import Execute
import VirtualMemory
import Spec
import MapMemory
import Utility.Utility
import Spec.Machine
import Platform.Minimal64
import Platform.MMIO
import Utility.Elf
import qualified Spec.CSRField as Field
import Spec.CSRFile
import Spec.Decode
import Spec.Execute
import Spec.VirtualMemory
import Spec.Spec
import Utility.MapMemory
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.Maybe
Expand Down Expand Up @@ -73,7 +73,7 @@ readProgram f = do

runFile :: String -> IO Int64
runFile f = do
deviceTree <- B.readFile "src/device_tree.bin"
deviceTree <- B.readFile "device_tree.bin"
(maybeToHostAddress, program) <- readProgram f
let mem = S.union (S.fromList (zip [0..] (B.unpack deviceTree))) (S.fromList program)
let c = Minimal64 { registers = S.empty,
Expand Down
22 changes: 11 additions & 11 deletions src/Run32.hs → src/Platform/Run32.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,20 @@
module Run32 where
module Platform.Run32 where
import System.IO
import System.Environment
import System.Exit
import Data.Int
import Data.List
import Data.Word
import Utility
import Program
import Minimal32
import MMIO
import Elf
import qualified CSRField as Field
import CSRFile
import Decode
import Execute
import MapMemory
import Utility.Utility
import Spec.Machine
import Platform.Minimal32
import Platform.MMIO
import Utility.Elf
import qualified Spec.CSRField as Field
import Spec.CSRFile
import Spec.Decode
import Spec.Execute
import Utility.MapMemory
import Control.Monad.Trans
import Control.Monad.Trans.State
import qualified Data.Map as S
Expand Down
Loading

0 comments on commit 25f096a

Please sign in to comment.