Skip to content

Commit

Permalink
Add 'KnownDomain' constraint
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan authored and omelkonian committed Jul 1, 2019
1 parent 9c4d092 commit 4bf8888
Show file tree
Hide file tree
Showing 6 changed files with 17 additions and 14 deletions.
4 changes: 2 additions & 2 deletions clash-cosim/.travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ install:
echo 'source-repository-package' >> cabal.project
echo ' type: git' >> cabal.project
echo ' location: https://github.com/clash-lang/clash-compiler' >> cabal.project
echo ' tag: 3c7f92ad2357a577467ec84df61fffa36843cb50' >> cabal.project
echo ' tag: 1111111111111111111111111111111111111111' >> cabal.project
echo ' subdir: clash-prelude' >> cabal.project
echo '' >> cabal.project
echo 'source-repository-package' >> cabal.project
Expand Down Expand Up @@ -138,7 +138,7 @@ script:
echo 'source-repository-package' >> cabal.project
echo ' type: git' >> cabal.project
echo ' location: https://github.com/clash-lang/clash-compiler' >> cabal.project
echo ' tag: 3c7f92ad2357a577467ec84df61fffa36843cb50' >> cabal.project
echo ' tag: 1111111111111111111111111111111111111111' >> cabal.project
echo ' subdir: clash-prelude' >> cabal.project
echo '' >> cabal.project
echo 'source-repository-package' >> cabal.project
Expand Down
3 changes: 2 additions & 1 deletion clash-cosim/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,8 @@ blackboxJson'
blackboxJson' clks args = blackboxObject bbname "" templateD
where
-- Offset where 'real' arguments start, instead of constraints
argsOffset = 1 -- result constraint
argsOffset = 1 -- result constraint
+ 1 -- knowndomain constraint
+ args -- argument constraints

-- Offset where signal arguments start
Expand Down
2 changes: 1 addition & 1 deletion clash-cosim/cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ repository head.hackage
source-repository-package
type: git
location: https://github.com/clash-lang/clash-compiler
tag: 3c7f92ad2357a577467ec84df61fffa36843cb50
tag: 1111111111111111111111111111111111111111
subdir: clash-prelude

-- | We need: a <=? Max a b ~ True
Expand Down
1 change: 1 addition & 0 deletions clash-cosim/src/Clash/CoSim/CoSimInstances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,3 +49,4 @@ qCoSim clks args = do
$e
|]


15 changes: 8 additions & 7 deletions clash-cosim/src/Clash/CoSim/CodeGeneration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ import Clash.CoSim.Paths_clash_cosim

import Clash.Annotations.Primitive (Primitive(..), HDL(..))
import Clash.CoSim.Types
import Clash.Prelude (Clock, ClockKind (..), Signal)
import Clash.Prelude (Clock, Signal, KnownDomain)
import System.Environment (getEnv)
import Language.Haskell.TH
import Control.Monad (replicateM)
Expand Down Expand Up @@ -111,20 +111,21 @@ coSimTypeGen clks args = do
let domName = mkName "dom"
let dom = return $ VarT domName

let confName = mkName "conf"
let conf = return (VarT confName)

-- Generate contraints:
argConstraints <- sequence $ map (\name -> [t| ClashType $name |]) argTypeNames
resConstraint <- [t| ClashType $result |]
let constraints = resConstraint : argConstraints
kdConstraint <- [t| KnownDomain $dom $conf |]
let constraints = kdConstraint : resConstraint : argConstraints

-- Generate type:
fixedArgs <- sequence [[t| String |], [t| String |], [t| CoSimSettings |]]
clkSignalTypes <- sequence (replicate clks [t|Clock $dom 'Source|])
clkSignalTypes <- sequence (replicate clks [t|Clock $dom |])
argSignalTypes <- sequence $ map (\name -> [t| Signal $dom $name |]) argTypeNames
resSignalType <- [t| Signal $dom $result |]

let ctx = (fixedArgs ++ clkSignalTypes ++ argSignalTypes) `arrowsR` resSignalType
let varNames = resultName : domName : argNames
let varNames = resultName : domName : confName : argNames
return $ ForallT (map PlainTV varNames) constraints ctx



6 changes: 3 additions & 3 deletions clash-cosim/src/Clash/CoSim/Simulator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -361,7 +361,7 @@ parseInput doDup streams t = dup (toSignalStream t) : streams

parseClock
:: [SignalStream]
-> CS.Clock dom gated
-> CS.Clock dom
-> [SignalStream]
parseClock streams _clk = (cycle [[0],[1]]) : streams

Expand Down Expand Up @@ -408,7 +408,7 @@ class CoSim r where
instance {-# OVERLAPPABLE #-} CoSimType r => CoSim r where
coSim b s = parseOutput b (coSimStart s)

instance {-# OVERLAPPING #-} (CoSim r) => CoSim (CS.Clock dom 'CS.Source -> r) where
instance {-# OVERLAPPING #-} (CoSim r) => CoSim (CS.Clock dom -> r) where
coSim _ s streams = coSim True s . parseClock streams

instance {-# OVERLAPPING #-} (CoSimType t, CoSim r) => CoSim (t -> r) where
Expand All @@ -418,6 +418,6 @@ class CoSimType t where
toSignalStream :: t -> SignalStream
fromSignalStream :: SignalStream -> t

instance (ClashType a, CP.Undefined a) => CoSimType (CP.Signal clk a) where
instance (ClashType a, CS.KnownDomain clk dom) => CoSimType (CP.Signal clk a) where
toSignalStream = map (wordPack . CP.pack) . CP.sample
fromSignalStream = CP.fromList . map (CP.unpack . wordUnpack)

0 comments on commit 4bf8888

Please sign in to comment.