
(Reply from Sebastiaan Joosten) I've tried something similar before but ran into a lot of cases where verbose intermediate type annotations where necessary to resolve double-wrapping ambiguities because the monad is abstract in my case: xor :: DSL m r => r S -> r S -> m (r S)) Where r is representation wrapper, m is the associated compiler/interpreter, and S is a phantom tag. On 2/5/20 10:05 AM, Sebastiaan Joosten wrote:
Hi Tom,
It wasn't entirely clear to me what you're looking for, so I'm probably way off here
On 5 Feb 2020, at 08:59, Tom Schouten
mailto:tom@zwizwa.be> wrote: asking people to give up expressions while they work just fine in C or Verilog
If all you care about is writing hardware expressions, how about providing a handful of self-lifting operators? Below is an example of what I mean (you'd replace the list applicative with your own applicative). I'm freely combining pureed and unpureed Booleans in the 'test' example, which would presumably be what your EE's write (I've only given them a single self-lifting operator, so they're still stuck writing pretty boring code). Does this help?
Best, Sebastiaan
PS: I'm not replying to haskell-cafe only because my mails bounce there due to a technical issue that's entirely on my side, feel free to add this back onto the haskell-cafe thread
{-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} class Pureable a b where maybePure :: a -> b instance Pureable a [a] where maybePure = pure instance Pureable [a] [a] where maybePure = id (.&&) :: (Pureable a [Bool], Pureable b [Bool]) => a -> b -> [Bool] a .&& b = (&&) <$> maybePure a <*> maybePure b test :: [Bool] -> [Bool] test x = (True .&& x) .&& (False .&& x)

I've tried something similar before but ran into a lot of cases where verbose intermediate type annotations where necessary to resolve double-wrapping ambiguities because the monad is abstract in my case:
xor :: DSL m r => r S -> r S -> m (r S)
Do I understand correctly that the actual content of the streams is not important, so S is isomorphic to ()? Or are the contents abstracted away into a more complex type? If it's the former, I fail to see why the monadic interface is even necessary. More broadly, could you provide a bigger example of what you're going for? I have a rough idea of what the goal is, but a more specific example might help. I also feel like there might be a way to adapt Sebastiaan's idea still. But if there isn't yet, there is also a pry-bar lying around: RebindableSyntax. All of pure, return, (<*>), fmap, and (>>=) can be overwritten, and will be used in (applicative) do notation. Cheers, MarLinn

On 2/5/20 4:29 PM, MarLinn wrote:
I've tried something similar before but ran into a lot of cases where verbose intermediate type annotations where necessary to resolve double-wrapping ambiguities because the monad is abstract in my case:
xor :: DSL m r => r S -> r S -> m (r S)
Do I understand correctly that the actual content of the streams is not important, so S is isomorphic to ()? Or are the contents abstracted away into a more complex type? If it's the former, I fail to see why the monadic interface is even necessary.
Currently S is a fixed type representing the scalar value of the signal type. Not very important, but there will be more than one (think float, int, complex float, matrix, ...). The eventual goal is to create a number of primitives that are fairly independent of substrate (code for CPU or DSP, Parallel logic, bitserial logic, time-sliced programmable datapath, ...), but before all of that I'm trying to get the composition mechanism right first, then later extend with some base types and encode bit size in types etc. This is mostly from the Tagless-Final papers and examples. I like that approach and it makes it straightforward for me to change the language later.
More broadly, could you provide a bigger example of what you're going for? I have a rough idea of what the goal is, but a more specific example might help.
I can point to the code. This needs a lot of work, but here is the main class: https://github.com/zwizwa/asm_tools/blob/master/asm-tools-seq/Language/Seq.h... You can interpret a program written in Seq as a stateful sequential logic circuit where the m hides all the registers, or as an operator on streams. And here are two instances: compiler and interpreter: https://github.com/zwizwa/asm_tools/blob/master/asm-tools-seq/Language/Seq/T... https://github.com/zwizwa/asm_tools/blob/master/asm-tools-seq/Language/Seq/E... Logic library: https://github.com/zwizwa/asm_tools/blob/master/asm-tools-seq/Language/Seq/L... A circuit for a small CPU: https://github.com/zwizwa/asm_tools/blob/master/asm-tools-seq/Language/Seq/C...
I also feel like there might be a way to adapt Sebastiaan's idea still. But if there isn't yet, there is also a pry-bar lying around: RebindableSyntax. All of pure, return, (<*>), fmap, and (>>=) can be overwritten, and will be used in (applicative) do notation.
Thanks I was unaware of that.
participants (2)
-
MarLinn
-
Tom Schouten