
I know it's a bit of an 'intentionally provocative' title, but with the recent discussions on Arrows I thought it timely to bring this up. Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and prevents describing some very useful objects as arrows. For example, I would love to be able to use the arrow syntax to define objects of this type: data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc. Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc. However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate. The arrow syntax translation uses arr to do plumbing of variables. I think a promising project would be to figure out exactly what plumbing is needed, and add those functions to a sort of 'PrimitiveArrow' class. All of these plumbing functions are trivially implemented in terms of 'arr', when it exists, but if it doesn't, it should be possible to use the arrow syntax regardless. -- ryan

Have you seen Adam Megacz's work on generalized arrows? I think he proposes
to kill arr and has done a decent amount of work on it.
On Mon, Oct 31, 2011 at 8:33 PM, Ryan Ingram
I know it's a bit of an 'intentionally provocative' title, but with the recent discussions on Arrows I thought it timely to bring this up.
Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
The arrow syntax translation uses arr to do plumbing of variables. I think a promising project would be to figure out exactly what plumbing is needed, and add those functions to a sort of 'PrimitiveArrow' class. All of these plumbing functions are trivially implemented in terms of 'arr', when it exists, but if it doesn't, it should be possible to use the arrow syntax regardless.
-- ryan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Oct 31, 2011 at 10:33 PM, Ryan Ingram
The arrow syntax translation uses arr to do plumbing of variables. I think a promising project would be to figure out exactly what plumbing is needed, and add those functions to a sort of 'PrimitiveArrow' class. All of these plumbing functions are trivially implemented in terms of 'arr', when it exists, but if it doesn't, it should be possible to use the arrow syntax regardless.
There are already generalized arrows [1]. Is that what you are looking for? Cheers, [1] http://www.cs.berkeley.edu/~megacz/garrows/ -- Felipe.

This seems basically what I'm talking about, except even more hardcore. I think mostly what I'm suggesting is that the GHC arrow preprocessor to compile to something like generalized arrows, by default, with current Arrows as a special case. -- ryan On Mon, Oct 31, 2011 at 5:48 PM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
The arrow syntax translation uses arr to do plumbing of variables. I
a promising project would be to figure out exactly what plumbing is needed, and add those functions to a sort of 'PrimitiveArrow' class. All of
On Mon, Oct 31, 2011 at 10:33 PM, Ryan Ingram
wrote: think these plumbing functions are trivially implemented in terms of 'arr', when it exists, but if it doesn't, it should be possible to use the arrow syntax regardless.
There are already generalized arrows [1]. Is that what you are looking for?
Cheers,
[1] http://www.cs.berkeley.edu/~megacz/garrows/
-- Felipe.

Ryan Ingram writes:
Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides (http://www.soi.city.ac.uk/~ross/papers/fop.html).

On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html).
That's a neat trick, Ross! It seems really similar to using parametricity to recover the insides of lambdas in PHOAS metaprogramming: -- HOAS expression language data Expr (v :: * -> *) a where Ap :: Expr v (a -> b) -> Expr v a -> Expr v b Var :: v a -> Expr v a Lam :: (v a -> Expr v b) -> Expr v (a -> b) -- some expressions that are paremetric in the variable type ex_id :: Expr v (a -> a) ex_id = Lam $ \x -> Var x ex_const :: Expr v (a -> b -> a) ex_const = Lam $ \x -> Lam $ \y -> Var x -- a print function that relies on parametricity to expose the insides of the functions inside "Lam" printExpr :: (forall v. Expr v a) -> String printExpr e = pe_helper vars 0 e "" where vars = map (:[]) ['a' .. 'z'] ++ map (\n -> "t" ++ show n) [1..] prec_lam = 1 prec_ap = 2 newtype VarName a = VarName String pe_helper :: [String] -> Expr VarName a -> Int -> ShowS pe_helper fv prec (Var (VarName s)) = showString s pe_helper fv prec (Ap x y) = showParen (prec > prec_ap) (pe_helper fv prec_ap x . showString " " . pe_helper fv (prec_ap+1) y) pe_helper (v:fv) prec (Lam k) = showParen (prec > prec_lam) (showString "\" . showString v . showString " -> " . pe_helper fv prec_lam e) where e = k (VarName v) -- some test cases test1 = printExpr ex_const -- "\a -> \b -> a" test2 = printExpr (ex_id `Ap` ex_const) -- "(\a -> a) (\a -> \b -> a)"

If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html).
I'm running into this same issue: I have something (another circuits
formulation) that's almost an arrow but doesn't support arr. I'd like to
use arrow notation, but then I run afoul of my missing arr. I'd like to
understand Ross's suggestion and how to apply it. (I've read the "FoP"
slides.)
Ross: do you mean to say that you were able to implement arr and thus run
your circuit examples via the standard arrow desugarer?
Ryan: did you get a working solution to the problem you described for your
Circuit arrow?
Thanks. -- Conal
On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross
Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and
Ryan Ingram writes: prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, I see Ross's trick. By quantifying over the domain & range types, they
can later be specialized to analysis-time types (like circuit labels) or to
run-time types (like Boolean or Integer).
On Thu, Dec 20, 2012 at 4:55 PM, Conal Elliott
If you require the circuit to be parametric in the value types, you can
limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html).
I'm running into this same issue: I have something (another circuits formulation) that's almost an arrow but doesn't support arr. I'd like to use arrow notation, but then I run afoul of my missing arr. I'd like to understand Ross's suggestion and how to apply it. (I've read the "FoP" slides.)
Ross: do you mean to say that you were able to implement arr and thus run your circuit examples via the standard arrow desugarer?
Ryan: did you get a working solution to the problem you described for your Circuit arrow?
Thanks. -- Conal
On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross
wrote: Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and
Ryan Ingram writes: prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey Conal,
I have something (another circuits formulation) that's almost an arrow but doesn't support arr.
Have you seen Adam Megacz's generalized arrows?
http://www.cs.berkeley.edu/~megacz/garrows/
-- Kim-Ee
On Fri, Dec 21, 2012 at 7:55 AM, Conal Elliott
If you require the circuit to be parametric in the value types, you can
limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html).
I'm running into this same issue: I have something (another circuits formulation) that's almost an arrow but doesn't support arr. I'd like to use arrow notation, but then I run afoul of my missing arr. I'd like to understand Ross's suggestion and how to apply it. (I've read the "FoP" slides.)
Ross: do you mean to say that you were able to implement arr and thus run your circuit examples via the standard arrow desugarer?
Ryan: did you get a working solution to the problem you described for your Circuit arrow?
Thanks. -- Conal
On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross
wrote: Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and
Ryan Ingram writes: prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks, Kim-Ee. Adam M's garrows look very useful for what I'm doing. --
Conal
On Fri, Dec 21, 2012 at 5:14 AM, Kim-Ee Yeoh
Hey Conal,
I have something (another circuits formulation) that's almost an arrow but doesn't support arr.
Have you seen Adam Megacz's generalized arrows?
http://www.cs.berkeley.edu/~megacz/garrows/
-- Kim-Ee
On Fri, Dec 21, 2012 at 7:55 AM, Conal Elliott
wrote: If you require the circuit to be parametric in the value types, you can
limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html).
I'm running into this same issue: I have something (another circuits formulation) that's almost an arrow but doesn't support arr. I'd like to use arrow notation, but then I run afoul of my missing arr. I'd like to understand Ross's suggestion and how to apply it. (I've read the "FoP" slides.)
Ross: do you mean to say that you were able to implement arr and thus run your circuit examples via the standard arrow desugarer?
Ryan: did you get a working solution to the problem you described for your Circuit arrow?
Thanks. -- Conal
On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross
wrote: Ryan Ingram writes:
Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and prevents describing some very useful objects as arrows.
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
If you require the circuit to be parametric in the value types, you can limit the types of function you can pass to arr to simple plumbing. See the netlist example at the end of my "Fun of Programming" slides ( http://www.soi.city.ac.uk/~ross/papers/fop.html). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2011/11/1 Ryan Ingram
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Would you mind give me some examples on how you desribe real circuits with that abstraction and, especially, an Arrow instance (even imaginary one)? 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.

On Tue, Nov 1, 2011 at 3:36 AM, Serguey Zefirov
2011/11/1 Ryan Ingram
: 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

On Mon, Oct 31, 2011 at 5:33 PM, Ryan Ingram
For example, I would love to be able to use the arrow syntax to define objects of this type:
data Circuit a b where Const :: Bool -> Circuit () Bool Wire :: Circuit a a Delay :: Circuit a a And :: Circuit (Bool,Bool) Bool Or :: Circuit (Bool,Bool) Bool Not :: Circuit Bool Bool Then :: Circuit a b -> Circuit b c -> Circuit a c Pair :: Circuit a c -> Circuit b d -> Circuit (a,b) (c,d) First :: Circuit a b -> Circuit (a,c) (b,c) Swap :: Circuit (a,b) (b,a) AssocL :: Circuit ((a,b),c) (a,(b,c)) AssocR :: Circuit (a,(b,c)) ((a,b),c) Loop :: Circuit (a,b) (a,c) -> Circuit b c etc.
Then we can have code that examines this concrete data representation, converts it to VHDL, optimizes it, etc.
As mentioned by others, Adam Megacz's generalized arrow (and its syntax) could accomplish this. But if all you want is VHDL and the like, consider Conal Elliott's work on Vertigo, Pan, Compiling Embedded Languages [1], and the similar work on the Haskell GPipe package. [1] http://conal.net/papers/jfp-saig/ Regards, Dave
However, due to the presence of the opaque 'arr', there's no way to make this type an arrow without adding an 'escape hatch' Arr :: (a -> b) -> Circuit a b which breaks the abstraction: circuit is supposed to represent an actual boolean circuit; (Arr not) is not a valid circuit because we've lost the information about the existence of a 'Not' gate.
The arrow syntax translation uses arr to do plumbing of variables. I think a promising project would be to figure out exactly what plumbing is needed, and add those functions to a sort of 'PrimitiveArrow' class. All of these plumbing functions are trivially implemented in terms of 'arr', when it exists, but if it doesn't, it should be possible to use the arrow syntax regardless.
-- ryan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram
I know it's a bit of an 'intentionally provocative' title, but with the recent discussions on Arrows I thought it timely to bring this up.
Most of the conversion from arrow syntax into arrows uses 'arr' to move components around. However, arr is totally opaque to the arrow itself, and prevents describing some very useful objects as arrows.
I can totally understand your frustration, but on the other hand I have to say that /not/ having 'arr' would break a lot of useful things at least for me and probably for most programmers using AFRP. One possible compromise is to move it into its own type class and also offer specialized versions of it for plumbing in a yet simpler class. class Arrow (>~) => ArrowPair (>~) dup :: a >~ (a, a) swap :: (a, b) >~ (b, a) ... class Arrow (>~) => ArrowArr (>~) where arr :: (a -> b) -> (a >~ b) This would enable some interesting optimization opportunities. Perhaps it also makes sense to turn ArrowArr into a subclass of ArrowPair. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (9)
-
Conal Elliott
-
Daniel Peebles
-
David Barbour
-
Ertugrul Soeylemez
-
Felipe Almeida Lessa
-
Kim-Ee Yeoh
-
Paterson, Ross
-
Ryan Ingram
-
Serguey Zefirov