[Haskell-cafe] arr considered harmful

Ryan Ingram ryani.spam at gmail.com
Tue Nov 1 22:52:13 CET 2011


On Tue, Nov 1, 2011 at 3:36 AM, Serguey Zefirov <sergueyz at gmail.com> wrote:

> 2011/11/1 Ryan Ingram <ryani.spam at 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.
>

When I did some circuit generation for the ICFP contest last year, I also
went with monadic netlists.  But I had problems coming up with
compile-time-enforcable guarantees like 'this wire is only used once'

And really, this description is for more than circuit generation; it
applies to any sort of computation that you might want to create with
arrows.  I was looking at arrowized FRP earlier this year and was
frustrated by how impossible it was to optimize the resulting dataflow
networks.  I was continually plagued by the appearance of 'arr' in my
networks, in situations where I didn't think it belonged, and with no good
way to see what that 'arr' was actually doing.

  -- ryan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111101/ade94299/attachment.htm>


More information about the Haskell-Cafe mailing list