Skip to content

Commit

Permalink
Synthesis uarch automatically
Browse files Browse the repository at this point in the history
Related #157
  • Loading branch information
BasicEC committed Jun 12, 2022
1 parent 9fa1d31 commit 4c634e8
Show file tree
Hide file tree
Showing 13 changed files with 243 additions and 100 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -171,7 +171,7 @@ $ find src -name '*.hs' -exec grep -l '>>>' {} \; | xargs -t -L 1 -P 4 stack exe
# | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
$ stack exec ghc-pkg unregister interpolate -- --force

# run formolu for all files
# run fourmolu for all files
$ find . -name '*.hs' | xargs fourmolu -m inplace

# show modules dependency
Expand Down
33 changes: 30 additions & 3 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ import Control.Exception
import Control.Monad (when)
import Data.ByteString.Lazy.Char8 qualified as BS
import Data.Default (def)
import Data.Functor
import Data.Maybe
import Data.Proxy
import Data.String.Utils qualified as S
Expand Down Expand Up @@ -57,6 +56,7 @@ import Text.Regex
data Nitta = Nitta
{ filename :: FilePath
, uarch :: Maybe FilePath
, auto_uarch :: Bool
, type_ :: Maybe String
, io_sync :: Maybe IOSynchronization
, port :: Int
Expand Down Expand Up @@ -93,6 +93,11 @@ nittaArgs =
&= explicit
&= name "uarch"
&= groupname "Target system configuration"
, auto_uarch =
False
&= help "Use empty microarchitecture and allocate PUs during synthesis process."
&= name "auto-uarch"
&= groupname "Target system configuration"
, type_ =
Nothing
&= name "t"
Expand Down Expand Up @@ -162,6 +167,7 @@ main = do
( Nitta
filename
uarch
auto_uarch
type_
io_sync
port
Expand All @@ -180,7 +186,7 @@ main = do

toml <- case uarch of
Nothing -> return Nothing
Just path -> T.readFile path <&> (Just . getToml)
Just path -> Just . getToml <$> T.readFile path

let fromConf s = getFromTomlSection s =<< toml
let exactFrontendType = identifyFrontendType filename frontend_language
Expand All @@ -194,7 +200,14 @@ main = do
received = [("u#0", map (\i -> read $ show $ sin ((2 :: Double) * 3.14 * 50 * 0.001 * i)) [0 .. toEnum n])]
ioSync = fromJust $ io_sync <|> fromConf "ioSync" <|> Just Sync
confMa = toml >>= Just . mkMicroarchitecture ioSync
ma = fromJust $ confMa <|> Just (defMicroarch ioSync) :: BusNetwork T.Text T.Text (Attr (FX m b)) Int
ma
| auto_uarch && isJust confMa =
error $
"auto_uarch flag means that an empty uarch with default prototypes will be used. "
<> "Remove uarch flag or specify prototypes list in config file and remove auto_uarch."
| auto_uarch = microarchWithProtos ioSync :: BusNetwork T.Text T.Text (Attr (FX m b)) Int
| isJust confMa = fromJust confMa
| otherwise = defMicroarch ioSync

infoM "NITTA" $ "will trace: " <> S.join ", " (map (show . tvVar) frTrace)

Expand Down Expand Up @@ -300,3 +313,17 @@ defMicroarch ioSync = defineNetwork "net1" ioSync $ do
, slave_sclk = InputPortTag "sclk"
, slave_cs = InputPortTag "cs"
}

microarchWithProtos ioSync = defineNetwork "net1" ioSync $ do
addCustomPrototype "fram{x}" (framWithSize 32) FramIO
addPrototype "shift{x}" ShiftIO
addPrototype "mul{x}" MultiplierIO
addPrototype "accum{x}" AccumIO
addPrototype "div{x}" DividerIO
add "spi" $ -- use addPrototype when https://github.com/ryukzak/nitta/issues/194 will be fixed
SPISlave
{ slave_mosi = InputPortTag "mosi"
, slave_miso = OutputPortTag "miso"
, slave_sclk = InputPortTag "sclk"
, slave_cs = InputPortTag "cs"
}
49 changes: 24 additions & 25 deletions examples/microarch.toml
Original file line number Diff line number Diff line change
Expand Up @@ -4,44 +4,43 @@ ioSync = "Sync"
[[networks]]
name = "net1"

[[networks.pus]]
type = "Fram"
name = "fram1"
size = 16
# Array of PUs

[[networks.pus]]
type = "SPI"
name = "spi"
mosi = "mosi"
miso = "miso"
sclk = "sclk"
cs = "cs"
isSlave = true
bufferSize = 6
bounceFilter = 0

# Array of PU prototypes

[[networks.protos]]
type = "Fram"
name = "fram2"
name = "fram{x}" # If you want a PU can be allocated only once, remove {x} from the PU name.
size = 32

[[networks.pus]]
[[networks.protos]]
type = "Shift"
name = "shift"
name = "shift{x}"
sRight = true

[[networks.pus]]
[[networks.protos]]
type = "Multiplier"
name = "mul"
name = "mul{x}"
mock = true

[[networks.pus]]
[[networks.protos]]
type = "Accum"
name = "accum"
name = "accum{x}"
isInt = true

[[networks.pus]]
[[networks.protos]]
type = "Divider"
name = "div"
name = "div{x}"
mock = true
pipeline = 4

[[networks.pus]]
type = "SPI"
name = "spi"
mosi = "mosi"
miso = "miso"
sclk = "sclk"
cs = "cs"
isSlave = true
bufferSize = 6
bounceFilter = 0
pipeline = 4
96 changes: 61 additions & 35 deletions src/NITTA/Model/Microarchitecture/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,33 @@ module NITTA.Model.Microarchitecture.Config (
mkMicroarchitecture,
) where

import Data.Aeson
import Data.Default
import Control.Monad.State (when)
import Data.Aeson (
FromJSON (parseJSON),
Options (sumEncoding),
SumEncoding (TaggedObject, contentsFieldName, tagFieldName),
ToJSON (toJSON),
defaultOptions,
genericParseJSON,
genericToJSON,
)
import Data.Default (Default (def))
import Data.HashMap.Internal.Strict (HashMap)
import Data.Maybe (fromJust, isJust)
import Data.Text qualified as T
import GHC.Generics
import NITTA.Model.Networks.Bus
import GHC.Generics (Generic)
import NITTA.Intermediate.Value (Val)
import NITTA.Intermediate.Variable (Var)
import NITTA.Model.Networks.Bus (
BusNetwork,
addCustom,
addCustomPrototype,
busNetwork,
modifyNetwork,
)
import NITTA.Model.Networks.Types (IOSynchronization)
import NITTA.Model.ProcessorUnits qualified as PU
import NITTA.Utils
import NITTA.Utils (getFromToml)

data PUConf
= Accum
Expand Down Expand Up @@ -58,34 +78,10 @@ instance ToJSON PUConf where
instance FromJSON PUConf where
parseJSON = genericParseJSON puConfJsonOptions

build NetworkConf{pus} = do mapM_ addPU pus
where
addPU Accum{name} = addCustom name def PU.AccumIO
addPU Divider{name, pipeline, mock} = addCustom name (PU.divider pipeline mock) PU.DividerIO
addPU Multiplier{name, mock} = addCustom name (PU.multiplier mock) PU.MultiplierIO
addPU Fram{name, size} = addCustom name (PU.framWithSize size) PU.FramIO
addPU Shift{name, sRight} = addCustom name (PU.shift $ Just False /= sRight) PU.ShiftIO
addPU SPI{name, mosi, miso, sclk, cs, isSlave, bounceFilter, bufferSize} =
addCustom name (PU.anySPI bounceFilter bufferSize) $
if isSlave
then
PU.SPISlave
{ slave_mosi = PU.InputPortTag mosi
, slave_miso = PU.OutputPortTag miso
, slave_sclk = PU.InputPortTag sclk
, slave_cs = PU.InputPortTag cs
}
else
PU.SPIMaster
{ master_mosi = PU.OutputPortTag mosi
, master_miso = PU.InputPortTag miso
, master_sclk = PU.OutputPortTag sclk
, master_cs = PU.OutputPortTag cs
}

data NetworkConf = NetworkConf
{ name :: T.Text
, pus :: [PUConf]
, pus :: Maybe [PUConf]
, protos :: Maybe [PUConf]
}
deriving (Generic, Show)

Expand All @@ -100,9 +96,39 @@ newtype MicroarchitectureConf = MicroarchitectureConf
instance FromJSON MicroarchitectureConf
instance ToJSON MicroarchitectureConf

mkMicroarchitecture :: (Val v, Var x, ToJSON a, ToJSON x) => IOSynchronization -> HashMap T.Text a -> BusNetwork T.Text x v Int
mkMicroarchitecture ioSync toml =
let ns = networks (getFromToml toml :: MicroarchitectureConf)
mkNetwork net@NetworkConf{name} = defineNetwork name ioSync $ build net
in if length ns > 1
let addPU proto
| proto = addCustomPrototype
| otherwise = addCustom
build NetworkConf{pus, protos} = do
when (isJust pus) $ mapM_ (configure False) $ fromJust pus
when (isJust protos) $ mapM_ (configure True) $ fromJust protos
where
configure proto Accum{name} = addPU proto name def PU.AccumIO
configure proto Divider{name, pipeline, mock} = addPU proto name (PU.divider pipeline mock) PU.DividerIO
configure proto Multiplier{name, mock} = addPU proto name (PU.multiplier mock) PU.MultiplierIO
configure proto Fram{name, size} = addPU proto name (PU.framWithSize size) PU.FramIO
configure proto Shift{name, sRight} = addPU proto name (PU.shift $ Just False /= sRight) PU.ShiftIO
configure proto SPI{name, mosi, miso, sclk, cs, isSlave, bounceFilter, bufferSize} =
addPU proto name (PU.anySPI bounceFilter bufferSize) $
if isSlave
then
PU.SPISlave
{ slave_mosi = PU.InputPortTag mosi
, slave_miso = PU.OutputPortTag miso
, slave_sclk = PU.InputPortTag sclk
, slave_cs = PU.InputPortTag cs
}
else
PU.SPIMaster
{ master_mosi = PU.OutputPortTag mosi
, master_miso = PU.InputPortTag miso
, master_sclk = PU.OutputPortTag sclk
, master_cs = PU.OutputPortTag cs
}
nets = networks (getFromToml toml :: MicroarchitectureConf)
mkNetwork net@NetworkConf{name} = modifyNetwork (busNetwork name ioSync) (build net)
in if length nets > 1
then error "multi-networks are not currently supported"
else mkNetwork (head ns)
else mkNetwork (head nets)
3 changes: 3 additions & 0 deletions src/NITTA/Model/Networks/Bus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -283,6 +283,8 @@ instance (UnitTag tag, VarValTime v x t) => ProcessorUnit (BusNetwork tag v x t)

parallelismType _ = error " not support parallelismType for BusNetwork"

puSize BusNetwork{bnPus} = sum $ map puSize $ M.elems bnPus

instance Controllable (BusNetwork tag v x t) where
data Instruction (BusNetwork tag v x t)
= Transport v tag tag
Expand Down Expand Up @@ -849,6 +851,7 @@ modifyNetwork net@BusNetwork{bnPus, bnPUPrototypes, bnSignalBusWidth, bnEnv} bui

defineNetwork bnName ioSync builder = modifyNetwork (busNetwork bnName ioSync) builder

addCustom :: forall tag v x t m pu. (MonadState (BuilderSt tag v x t) m, PUClasses pu v x t, UnitTag tag) => tag -> pu -> IOPorts pu -> m ()
addCustom tag pu ioPorts = do
st@BuilderSt{signalBusWidth, availSignals, pus} <- get
let ctrlPorts = takePortTags availSignals pu
Expand Down
4 changes: 4 additions & 0 deletions src/NITTA/Model/ProcessorUnits/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,10 @@ class (VarValTime v x t) => ProcessorUnit u v x t | u -> v x t where
parallelismType :: u -> ParallelismType
parallelismType _ = None

-- |Provide the processor unit size. At the moment it's just the number of subprocessors
puSize :: u -> Float
puSize _ = 1

bind f pu = case tryBind f pu of
Right pu' -> pu'
Left err -> error $ "can't bind function: " <> err
Expand Down
1 change: 1 addition & 0 deletions src/NITTA/Model/TargetSystem.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ instance
tryBind f ts@TargetSystem{mUnit} = (\u -> ts{mUnit = u}) <$> tryBind f mUnit
process TargetSystem{mUnit} = process mUnit
parallelismType TargetSystem{mUnit} = parallelismType mUnit
puSize TargetSystem{mUnit} = puSize mUnit

instance (BindProblem u tag v x) => BindProblem (TargetSystem u tag v x t) tag v x where
bindOptions TargetSystem{mUnit} = bindOptions mUnit
Expand Down
3 changes: 2 additions & 1 deletion src/NITTA/Synthesis/Method.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,6 +125,7 @@ allBestThreadIO n tree = do
bestLeaf :: (VarValTime v x t, UnitTag tag) => DefTree tag v x t -> [DefTree tag v x t] -> DefTree tag v x t
bestLeaf tree leafs =
let successLeafs = filter (\node -> isComplete node && isLeaf node) leafs
target = sTarget . sState
in case successLeafs of
_ : _ -> minimumOn (processDuration . sTarget . sState) successLeafs
_ : _ -> minimumOn (\l -> (processDuration $ target l, puSize $ target l)) successLeafs
[] -> headDef tree leafs
7 changes: 6 additions & 1 deletion src/NITTA/Synthesis/Steps/Allocation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,4 +89,9 @@ instance
, mAvgParallels = (fromIntegral (sum fCountByWaves) :: Float) / (fromIntegral numberOfProcessWaves :: Float)
}

estimate _ctx _o _d AllocationMetrics{} = -1
estimate _ctx _o _d AllocationMetrics{mParallelism, mMinPusForRemains, mAvgParallels}
| mMinPusForRemains == 0 = 5000
| mParallelism == Full = -1
| mParallelism == Pipeline && (mAvgParallels / mMinPusForRemains >= 3) = 4900
| mAvgParallels / mMinPusForRemains >= 2 = 4900
| otherwise = -1
Loading

0 comments on commit 4c634e8

Please sign in to comment.