Laatste wijzigingen
authorChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 31 Aug 2009 11:22:17 +0000 (13:22 +0200)
committerChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 31 Aug 2009 11:22:17 +0000 (13:22 +0200)
PolyAlu.hs
PolyAlu.lhs
clash-haskell09.pdf
reducer.lhs
reducerschematic.png [new file with mode: 0644]

index 21f6eff03f2516e9b834e154ec6fb28656e5d3fc..8752f955c2aa9044c734fa1d66866dca039d89c1 100644 (file)
@@ -3,32 +3,32 @@
 module Main where
 
 import qualified Prelude as P
-{-# LINE 29 "PolyAlu.lhs" #-}
+{-# LINE 34 "PolyAlu.lhs" #-}
 import CLasH.HardwareTypes
-{-# LINE 36 "PolyAlu.lhs" #-}
+{-# LINE 41 "PolyAlu.lhs" #-}
 import CLasH.Translator.Annotations
-{-# LINE 48 "PolyAlu.lhs" #-}
+{-# LINE 56 "PolyAlu.lhs" #-}
 type Op s a         =   a -> Vector s a -> a
 type Opcode         =   Bit
-{-# LINE 56 "PolyAlu.lhs" #-}
+{-# LINE 64 "PolyAlu.lhs" #-}
 type RegBank s a    =   Vector (s :+: D1) a
 type RegState s a   =   State (RegBank s a)
-{-# LINE 64 "PolyAlu.lhs" #-}
+{-# LINE 72 "PolyAlu.lhs" #-}
 type Word           =   SizedInt D12
-{-# LINE 76 "PolyAlu.lhs" #-}
+{-# LINE 89 "PolyAlu.lhs" #-}
 primOp :: (a -> a -> a) -> Op s a
 primOp f a b = a `f` a
-{-# LINE 84 "PolyAlu.lhs" #-}
+{-# LINE 97 "PolyAlu.lhs" #-}
 vectOp :: (a -> a -> a) -> Op s a
 vectOp f a b = foldl f a b
-{-# LINE 99 "PolyAlu.lhs" #-}
+{-# LINE 116 "PolyAlu.lhs" #-}
 alu :: 
   Op s a -> 
   Op s a -> 
   Opcode -> a -> Vector s a -> a
 alu op1 op2 Low    a b = op1 a b
 alu op1 op2 High   a b = op2 a b
-{-# LINE 118 "PolyAlu.lhs" #-}
+{-# LINE 139 "PolyAlu.lhs" #-}
 registerBank :: 
   ((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => (RegState s a) -> a -> RangedWord s ->
   RangedWord s -> Bit -> ((RegState s a), a )
@@ -39,7 +39,7 @@ registerBank (State mem) data_in rdaddr wraddr wrenable =
     data_out  =   mem!rdaddr
     mem'  | wrenable == Low    = mem
           | otherwise          = replace mem wraddr data_in
-{-# LINE 141 "PolyAlu.lhs" #-}
+{-# LINE 167 "PolyAlu.lhs" #-}
 {-# ANN actual_cpu TopEntity#-}
 actual_cpu :: 
   (Opcode, Word, Vector D4 Word, RangedWord D9, 
@@ -50,7 +50,7 @@ actual_cpu (opc, a ,b, rdaddr, wraddr, wren) ram = (ram', alu_out)
   where
     alu_out = alu (primOp (+)) (vectOp (+)) opc ram_out b
     (ram',ram_out)  = registerBank ram a rdaddr wraddr wren
-{-# LINE 160 "PolyAlu.lhs" #-}
+{-# LINE 191 "PolyAlu.lhs" #-}
 {-# ANN initstate InitState#-}
 initstate :: RegState D9 Word
 initstate = State (copy (0 :: Word))  
@@ -58,9 +58,9 @@ initstate = State (copy (0 :: Word))
 {-# ANN program TestInput#-}
 program :: [(Opcode, Word, Vector D4 Word, RangedWord D9, RangedWord D9, Bit)]
 program =
-  [ (Low, 4, copy (0::Word), 0, 0, High) --  Write 4 to Reg0, out = 0
-  , (Low, 3, copy (0::Word), 0, 1, High) --  Write 3 to Reg1, out = Reg0 + Reg0 = 8
-  , (High,0, copy (3::Word), 1, 0, Low)  --  No Write       , out = 15
+  [ (Low, 4, copy (0), 0, 0, High) --  Write 4 to Reg0, out = 0
+  , (Low, 3, copy (0), 0, 1, High) --  Write 3 to Reg1, out = 8
+  , (High,0, copy (3), 1, 0, Low)  --  No Write       , out = 15
   ]
 
 run func state [] = []
@@ -74,5 +74,5 @@ main = do
   let input = program
   let istate = initstate
   let output = run actual_cpu istate input
-  mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output
+  mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output
   return ()
index 842da238e628477a6ea9face795323e11022e38e..5ff0a60e38c6e29aa109192429d1af9b2b67d626 100644 (file)
@@ -122,7 +122,7 @@ alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-}   a b = op2 a b
 \end{code}
 \end{beamercolorbox}
 \begin{itemize}
-\uncover<2->{\item We support Patter Matching}
+\uncover<2->{\item We support Pattern Matching}
 \end{itemize}
 }\note[itemize]{
 \item Alu is both higher-order, and polymorphic
@@ -195,9 +195,9 @@ initstate = State (copy (0 :: Word))
 ANN(program TestInput)
 program :: [(Opcode, Word, Vector D4 Word, RangedWord D9, RangedWord D9, Bit)]
 program =
-  [ (Low, 4, copy (0::Word), 0, 0, High) -- Write 4 to Reg0, out = 0
-  , (Low, 3, copy (0::Word), 0, 1, High) -- Write 3 to Reg1, out = Reg0 + Reg0 = 8
-  , (High,0, copy (3::Word), 1, 0, Low)  -- No Write       , out = 15
+  [ (Low, 4, copy (0), 0, 0, High) -- Write 4 to Reg0, out = 0
+  , (Low, 3, copy (0), 0, 1, High) -- Write 3 to Reg1, out = 8
+  , (High,0, copy (3), 1, 0, Low)  -- No Write       , out = 15
   ]
 
 run func state [] = []
index 46bdb66dcac327b27fc4984674712789cb6e22f6..56da49ee87a1d7bd1e40466004fee6d6352e9a25 100644 (file)
Binary files a/clash-haskell09.pdf and b/clash-haskell09.pdf differ
index f71d1f62a270dfd15bdf702ae43175bbddc5e120..cc6d89fb62cc924c201edc33ef78114cfe1ed4e8 100644 (file)
@@ -3,14 +3,26 @@
 \frametitle{More than just toys}
 \pause
 \begin{itemize}
-  \item We designed a matrix reduction circuit\pause
+  \item We designed a reduction circuit in \clash{}\pause
   \item Simulation results in Haskell match VHDL simulation results\pause
   \item Synthesis completes without errors or warnings\pause
-  \item It runs at half the speed of a hand-coded VHDL design
+  \item For the same Virtex-4 FPGA: \pause
+    \begin{itemize}
+      \item Hand coded VHDL design runs at 200 MHz\pause
+      \item \clash{} design runs at around 85* MHz
+    \end{itemize}
 \end{itemize}
+\vspace{6em}
+\uncover<7->{\scriptsize{*Guestimate: design synthesized at 105 MHz, but with an Integer datapath instead of a floating point datapath.}}
 }\note[itemize]{
 \item Toys like the poly cpu one are good to give a quick demo
 \item But we used \clash{} to design 'real' hardware
 \item Reduction circuit sums the numbers in a row of a (sparse) matrix
-\item Half speed is nice, considering we don't optimize for speed
-}
\ No newline at end of file
+\item Nice speed considering we don't optimize for it
+}
+
+\begin{frame}[plain] 
+   \begin{centering} 
+      \includegraphics[height=\paperheight]{reducerschematic.png} 
+      \end{centering} 
+\end{frame} 
\ No newline at end of file
diff --git a/reducerschematic.png b/reducerschematic.png
new file mode 100644 (file)
index 0000000..0d5f0a2
Binary files /dev/null and b/reducerschematic.png differ