[Haskell-cafe] sharing

Tom Schouten tom at zwizwa.be
Wed Feb 5 16:02:30 UTC 2020


(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 <tom at zwizwa.be 
>> <mailto:tom at 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)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20200205/dbcf7fc6/attachment.html>


More information about the Haskell-Cafe mailing list