Language extension proposal: aspects

On 06/05/17 14:14, MarLinn wrote:
Here is a more complete example without my ramblings to disturb you. Imagine the code being distributed across three files.
--- aspect Data.Aspect.Bool.All where
instance Monoid Bool where mempty = True mappend False _ = False mappend True b = b
--- aspect Data.Aspect.Bool.Any where
instance Monoid Bool where mempty = False mappend True _ = True mappend False b = b
how would this interact with superclasses class Monoid m => Newclass m As I understand the proposal, you got default instances. But how do you extend with the alternative instance? by you examples with foldMap you would need to extend the data type with the aspect you mean to do it, well that is exactly what newtypes are! thus far I don't see any benefits of making it less explicit. -- -- Ruben

Thanks for the feedback!
aspect Data.Aspect.Bool.Any where
instance Monoid Bool where mempty = False mappend True _ = True mappend False b = b how would this interact with superclasses
class Monoid m => Newclass m
Aspects wouldn't care about superclasses directly. That's still the role of the instance declaration. But aspects – like normal modules – would be able to choose under which aspects to import their own dependencies. So in this way they would be able to "choose" their line of heritage. Of course if you import an aspect, you would also get all that heritage.
As I understand the proposal, you got default instances.
Mostly as a convenience and for backwards compatibility, but yes, in the form of the Default aspect. In fact every single instance we have now would initially be a "default instance" in the new model, by implicitly being in that aspect. It would probably be a good idea to move at least some of them to dedicated aspects though. The class system itself would be unchanged, including the defaulting and inheritance rules. But you would be able to drop the default instances by dropping the default aspect. You just would have to be aware that you'd be dropping all the default instances for the whole hierarchy of this constructor.
But how do you extend with the alternative instance? by you examples with foldMap you would need to extend the data type with the aspect you mean to do it, well that is exactly what newtypes are! thus far I don't see any benefits of making it less explicit.
I would have to implement the second instance in a second aspect, just without all the wrapping we do now. So yes, on first sight my proposed solution really offers little functionality that newtypes don't. But I claim the results already look much cleaner and should lead to more readable code. I also expect there might be bigger benefits to come from the separation of concerns and when you're able to just inherit big chunks of theory. Imagine that instead of injecting lots of Sum and getSum deep into a structure you could just add one type signature via proxy. Imagine extending the Sum aspect to elaborate on what the concept of "summation" really means instead of being stuck in the Num hierarchy. Why have All/Any and Sum/Product separately when they really describe the same basic concept? Why have Data.Ord.Down and Control.Applicative.Backwards when the underlying idea is exactly the same? Also, it's such a simple idea but how many would even think to look for these newtypes here? And do you know if there is a similar newtype for Foldable? Where would you look? If there is one aspect, just look into this aspect, done. That's what I really want aspects to describe: mathematical concepts that we use over and over, independently from the concrete types. Hope I was able to answer some questions? Cheers, MarLinn

How does compiler can infer a type for "allEven = foldMap even" ?
Something like
allEven :: (Monoid (aspect Bool), Integral a) => [a] -> Bool ?
Should all Bool's in function body have the same aspects?
2017-05-06 19:42 GMT+03:00 MarLinn
Hi people,
in the last couple days this list has once again seen examples of how our class system is not perfect yet. Here are some of the problems we face:
- Useful, but confusing instances like Foldable ((,) a) - Alternative possible instances like Alternative [] - Orphan instances - Reliance on the order of arguments makes some instances impossible, for example Traversable (,a)
How we usually resolve some of such issues is with newtype. Among the drawbacks are
- This clutters code with artificial wrappers and unwrappers that have nothing to do with the task at hand - It implies two levels of hierarchy by marking the one instance without a newtype as special - Every type needs its own wrapper. E.g. a Foldable (,a) (if possible) would need a different wrapper from a Foldable (a,,c) - Definitions are scattered at unexpected places, like All and Any, partly to avoid orphan instances.
After some thought I therefore propose a language extension I call "aspects". Keep in mind that this is a very rough draft just to gauge your reaction.
The core change would be the introduction of a keyword "aspect" that would work in a comparable way to the keyword "module". In other words you could say
aspect Data.Aspect.ChooseNonEmpty where
import qualified Data.Set as Set
instance Alternative [] where empty = [] a <|> b = if null a then b else a
instance Alternative Set.Set where … empty = Set.empty a <|> b = if null a then b else a
Changes compared to a normal module would be:
- An aspect can only contain instances - An aspect can import anything, but exports only instances - An aspect will never produce orphan instance warnings (duh.) - An aspect can be a file level definition, but it can also be contained in a module (we'll see why that is useful)
You also wouldn't import an aspect like a normal module, but with a second syntax extension:
import Data.List under (Data.Aspect.ChooseNonEmpty) import qualified Data.Set as Set hiding (Set) import qualified Data.Set under (Default, Data.Aspect.ChooseNonEmpty) as CNE (Set)
So you could also import the same structure twice with different aspects under different names:
import Data.Bool import qualified Data.Bool under (Data.Aspect.All) as All (Bool) import qualified Data.Bool under (Data.Aspect.Any) as Any (Bool)
Now, because of the first import, you could use the boolean functions normally, and even use the normal Bool type in signatures. And because of the qualified imports if you want to use one of the Monoid instances, all you would have to do is change Bool in the type signature to Any.Bool or All.Bool respectively, like so:
allEven :: (Integral a) => [a] -> Bool allEven = foldMap even -- error: Could not deduce (Monoid Bool)…
-- old way allEven :: (Integral a) => [a] -> Bool allEven = getAll . foldMap (All . even)
-- new way allEven :: (Integral a) => [a] -> All.Bool -- qualified name adds the monoidal aspect (and possibly others) allEven = foldMap even -- works
In other words, aspects would only be used for instance lookups. That is also why you could state several aspects at once when importing. Conflicts would be solved as usual: All is well until you try to use class functions that create an ambiguity.
I imagine a few special rules to make backwards compatibility easier. Most importantly, you could define default aspects in several ways:
- aspect Default where … -- reserved aspect name - default aspect ChooseNonEmpty where … -- re-used reserved keyword, but also gives a name to the aspect - default aspect where … -- short form for default aspect Default where … - An instance defined in a module outside of an aspect would automatically be in the Default aspect. In other words the definition can be seen as a short form of a local extension to the aspect. That's also why aspects would be allowed to be part of a module.
If you don't specify an aspect while importing, it would be imported under the Default aspect. To hide the Default aspect, just don't add it to the aspect list when importing.
Other random thoughts about this:
- An aspect doesn't need to be complete. E.g. I imagine an aspect that only defines Alternative.empty, with several other aspects relying on that by importing this incomplete aspect. OO programmers might call them abstract aspects. This might possibly help resolve some disputes about the "perfect" hierarchy. - If aspects can be part of a module, can aspects also be part of an aspect? Maybe, but I haven't made a cost-benefit analysis yet. - Aspects seem to form a level of container between definitions and modules. Maybe there should also be a new container type (or several) for the other parts of code? Say, a container that can contain everything *but* instances. - There could be an extension to the export syntax to choose which aspects to export. I just don't see the usefulness right now. - There could also be special syntax like import * under (Default,SpecialAspect) as a short form to add some aspects to every imported module. - The Default aspect is obviously extensible. I consider that a universally useful, if not essential feature. On the other hand in this proposal aspects use the module name space – which means such extensions would only be possible on a package level or by using several code folder roots. I'm not sure I'm happy with that. - The proposal doesn't solve the issue that instances rely the order of arguments. But an introduction of such new syntax might be a good time to introduce two extensions at once. I imagine something like instance Foldable (,) _ a where…
The biggest drawbacks from this idea that I can see right now are:
- The language extension might be infectious: once one library in a project uses it, many parts of the project might need it. This is different from most extensions that stay rather local. - Such a change might necessitate huge amounts of cpp. - Because aspects would be extensible and would have a global name space, care would have to be taken to not create a mess.
So… feel free to bikeshed and more importantly criticize! What am I overlooking? Would you consider such an idea worthwhile? Happy to hear your thoughts.
Cheers, MarLinn
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

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

Namespace notation might not be optimal, because it's not clear at a glance
that this is an aspect and not a regular qualified import of a type (an
important distinction if you have multiple versions of the same type
imported, e.g. Bytestring). Why not make it look like type application
instead? Modifying your example:
allEven :: (Integral a) => [a] -> Bool@A_All_
And for that matter, I'd rather not be forced to write a signature (what if
I want to use this in a where clause?) So... does this break anything?
allEven = foldMap@A_All_ even
Which means, for this invocation of foldMap, instances within A_All_
are in effect for all of its constraints. You could chain multiple @'s
together so long as they don't produce any relevant overlapping
instances.
To avoid surprises, they shouldn't propagate -- when foldMap invokes
even, it sees the default Monoid instance for Bool (i.e. none). If it
were also a function that needs a Monoid, you'd need another @.
There's potential for boilerplate here. Falling back to doing it in
the type signature could force propagation? I'm not sure it's ever a
safe idea, though.
On Sat, May 6, 2017 at 1:55 PM, MarLinn
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
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Mon, May 8, 2017 at 1:16 PM, MarLinn
On 2017-05-07 05:19, Theodore Lief Gannon wrote:
To avoid surprises, they shouldn't propagate -- when foldMap invokes even, it sees the default Monoid instance for Bool (i.e. none).
That sounds like a gateway to inconsistency. I think the solution is that adding an aspect to, say, an Int would not apply that aspects to all Int's, but only to the ones unifying with the annotated one.
Hmm... this might work? As long as you can handle the situation where a higher-order function depends on one instance, but a function passed to it depends on another. (Consider Maybe, which has at least four legal Monoid instances, one of which is default!)

If we have
allEven :: (Monoid Bool, Integral a) => [a] -> Bool
then, as usual, we have to define an aspect for Bool on the caller's side.
So there are two possibilities for user:
- fix an aspect in the function, there is no need for aspect on caller side
(What will be if on the caller side we already have an another aspect?!
Probably we can ignore it...)
- aspect-oriented constraint in the function's signature and fix an aspect
for the caller
I think that the second case is more useful. We prefer to write generalized
functions!
But in this case I'm afraid that we end-up with the same noise as for the
newtype. But instead of construct to and deconstruct from newtype we will
have to define aspects on type level for caller and define constraint for
function. Usually type-level syntax is more complicated...
2017-05-06 23:55 GMT+03:00 MarLinn
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
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 2017-05-07 11:21, Dmitry Olshansky wrote:
But in this case I'm afraid that we end-up with the same noise as for the newtype. But instead of construct to and deconstruct from newtype we will have to define aspects on type level for caller and define constraint for function. Usually type-level syntax is more complicated...
On the one hand, I get what you're saying. I'm not sure I'm totally convinced my idea is bad because of it, but I'll ponder that. On the other hand… in a way, we're working with two programming languages, a value level one and a type level one. And you're right that the type level programing language can be quite obtuse, even without my proposed additions. But I don't directly see that as an argument against my proposal. It's more of an argument to straighten out our type level language. I mean what is our type level language? It's basically a logic programming language that guides a constraint solver. We state facts and relationships, and we get an "ok" or errors and as "side effects" we sometimes get dictionaries. Now look at Prolog and how simple it is. Our language is more specialized, so we have more specialized operators. But that alone would only make the language more complex, not necessarily more complicated. In an ideal world I would also just be able to use existing tools of our type level language to implement my additions. Right now I can't, so something is amiss. To be honest I don't have any idea how to fix this. And as long as we don't, your argument against my proposal is indeed valid through this indirection. But I'm not happy that it is… Cheers, MarLinn
participants (4)
-
Dmitry Olshansky
-
MarLinn
-
Ruben Astudillo
-
Theodore Lief Gannon