Skip to content

Commit

Permalink
document folds-as-circuits
Browse files Browse the repository at this point in the history
  • Loading branch information
vmchale committed Apr 26, 2022
1 parent 9580156 commit ce50cb6
Showing 1 changed file with 12 additions and 2 deletions.
14 changes: 12 additions & 2 deletions clash-prelude/src/Clash/Sized/RTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -545,7 +545,8 @@ lazyT :: KnownNat d
-> RTree d a
lazyT = tzipWith (flip const) (trepeat ())

-- | Low-depth (left) scan, see 'Clash.Sized.Vector.scanl'.
-- | Low-depth (left) scan, see 'Clash.Sized.Vector.scanl1'. The generated
-- circuit will use more gates but can be clocked faster.
--
-- >>> scanlPar (+) (1 :> 2 :> 3 :> 4 :> Nil)
-- 1 :> 3 :> 6 :> 10 :> Nil
Expand All @@ -562,7 +563,8 @@ scanlPar ::
scanlPar op = t2v . tscanl op . v2t
{-# INLINE scanlPar #-}

-- | Low-depth (right) scan, see 'Clash.Sized.Vector.scanr'.
-- | Low-depth (right) scan, see 'Clash.Sized.Vector.scanr1'. The generated
-- circuit will use more gates but can be clocked faster.
--
-- >>> scanrPar (+) (1 :> 2 :> 3 :> 4 :> Nil)
-- 10 :> 9 :> 7 :> 4 :> Nil
Expand Down Expand Up @@ -593,6 +595,10 @@ tlast :: RTree n a -> a
tlast (Leaf x) = x
tlast (Branch _ y) = tlast y

-- | Left scan on an 'RTree'; see 'Clash.Sized.Vector.scanl1'
--
-- >>> tscanl (+) $ BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))
-- <<1,3>,<6,10>>
tscanl ::
forall a n.
KnownNat n =>
Expand All @@ -609,6 +615,10 @@ tscanl op tr =
l = tlast x'
in BR x' (fmap (l `op`) y')

-- | Right scan on an 'RTree'; see 'Clash.Sized.Vector.scanr1'
--
-- >>> tscanr (+) $ BR (BR (LR 1) (LR 2)) (BR (LR 3) (LR 4))
-- <<10,9>,<7,4>>
tscanr ::
forall a n.
KnownNat n =>
Expand Down

0 comments on commit ce50cb6

Please sign in to comment.