2011/11/1 Ryan Ingram <ryani.spam@gmail.com>:
Would you mind give me some examples on how you desribe real circuits
with that abstraction and, especially, an Arrow instance (even
imaginary one)?
Sure, here's a simple SR latch:
nor :: Circuit (Bool,Bool) Bool
nor = Or `Then` Not
rs :: Circuit (Bool,Bool) (Bool,Bool)
rs = proc (r,s) -> do
rec
q <- nor -< (r, q')
q' <- nor -< (s, q)
id -< (q,q')
instance Category Circuit where
id = Wire
(.) = flip Then
instance GArrow Circuit where
ga_first = First -- Circuit a b -> Circuit (a,c) (b,c)
ga_second = Second -- Circuit a b -> Circuit(c,a) (c,b)
ga_cancelr = Cancel -- Circuit (a,()) a
ga_cancell = Swap `Then` Cancel -- Circuit ((),a) a
ga_uncancelr = Uncancel -- Circuit a (a, ())
ga_uncancell = Uncancel `Then` Swap -- Circuit a ((),a)
ga_assoc = AssocL -- Circuit ((a,b),c)) (a,(b,c))
ga_unassoc = AssocR -- Circuit (a,(b,c)) ((a,b),c)
instance GArrowDrop Circuit where
ga_drop = Ground -- Circuit a ()
instance GArrowCopy Circuit where
ga_copy = Split -- Circuit a (a,a)
instance GArrowSwap Circuit where
ga_swap = Swap -- Circuit (a,b) (b,a)
instance GArrowLoop Circuit where
ga_loop = Loop -- Circuit (a,c) (b,c) -> Circuit a b
which would turn into something like
rs =
-- (r,s)
Loop (
-- Input plumbing
-- ((r,s),(q_in,q'_in))
AssocL `Then`
-- (r, (s, (q_in,q'_in))
Second (
-- (s, (q_in,q'_in))
Second swap `Then`
-- (s, (q'_in,q_in))
AssocR `Then` First Swap `Then` AssocL
-- (q'_in, (s,q_in))
) `Then`
-- (r, (q'_in, (s,q_in)))
AssocR `Then`
-- ((r,q'_in), (s,q_in))
-- Computation!
First (Or `Then` Not) `Then` -- from "nor"
-- (q, (s,q_in))
Second (Or `Then` Not) `Then` -- from "nor"
-- (q, q')
-- Output plumbing
Split
-- ((q,q'), (q,q'))
) `Then`
-- (q,q')
Wire -- from "id"
I am interested because I thought about an approach like that and
found it not easy to use one. So I stuck with monadic netlists.