[Haskell-cafe] Language extension proposal: aspects

MarLinn monkleyon at gmail.com
Sat May 6 20:55:21 UTC 2017


On 2017-05-06 21:37, Dmitry Olshansky wrote:
> How does compiler can infer a type for "allEven = foldMap even" ?
>
> Something like
> allEven :: (Monoid (aspect Bool), Integral a) => [a] -> Bool ?

I hadn't thought about inference actually. But even if the compiler 
inferred a type, it would still fail with a missing constraint. So I 
don't strongly care what the implied constraint is, as long as the error 
message is comprehensible. Maybe it could mention aspects in the future, 
but that's not even necessary. So basically the inferred type would just be

	allEven :: (Monoid Bool, Integral a) => [a] -> Bool

The compiler would just know "I need a Monoid instance for Bool!" as it 
does right now. And just as now, it knows where to look – the only 
difference is that with my proposal that place to look has a different 
name.

> Should all Bool's in function body have the same aspects?

Yes, if the aspect comes from a type signature. If the type signature is 
local, it would be local to its region of application. For example:

---
module Test where

     import qualified Data.Bool under (Default, Data.Aspect.Bool.All) as A_All_ (Bool)
     import qualified Data.Bool under (Default, Data.Aspect.Bool.Any) as A_Any_ (Bool)

     test2 :: (Integral a) => [a] -> Bool
     test2 xs = (foldMap even xs :: A_All_.Bool) == not (foldMap odd xs :: A_Any_.Bool)

The type is imported twice with different names and under different 
aspects. The local type signatures use these names to define which are 
the right instances.

An alternative would be something like

     test2 :: (Integral a) => [a] -> Bool
     test2 xs = (foldMap even xs :: (Bool under A_All_)) == not (foldMap odd xs :: (Bool under A_Any_))

which would make the aspect-nature clearer. But I didn't want to 
introduce even more syntax, especially as the naming scheme is already 
enough.

Was that clarifying?

I have to say, your questions did make me ponder how much of my proposal 
would already be possible by exploiting type families. I'm not sure yet, 
but I'll think about it. So thanks!

Cheers,
MarLinn



More information about the Haskell-Cafe mailing list