Object oriented haskell.

Hi Haskell, I've been wondering if (.) is so cool in other languages why can't we make it even cooler in haskell. And went on to implement such a (.) based on multiparameter type classes and type families. type family Output object action class Action object action where (.) :: object -> action -> Output object action I'm not sure if this has been done before like this but i didn't find anything. I used Map as an example, and here is what I ended up with:
:m -Prelude import Prelude hiding ((.)) import Object import Object.Example import Data.Map hiding (size) let m = empty . [ 'f' := Just 1, 'o' := Just 2, 'o' := Nothing ] m fromList [('f',Just 1),('o',Nothing)] m . 'f' Just 1 m . size 2
I also have a pretty cool (almost) solution to the name collision problem. Visit the project homepage for a more thorough explanation. https://github.com/yokto/object And to those who gonna hate on me because they like the (.) as function composition I have only this to say. type instance Output (b -> c) (a -> b') = (a -> c) instance (b ~ b') => Action (b -> c) (a -> b') where f . g = f Prelude.. g Have fun, Silvio

Recently, on LtU: http://lambda-the-ultimate.org/node/4951
Most relevantly: https://ghc.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields...
–
Kyle Marek-Spartz
On May 15, 2014, 12:38:29 PM, silvio
:m -Prelude import Prelude hiding ((.)) import Object import Object.Example import Data.Map hiding (size) let m = empty . [ 'f' := Just 1, 'o' := Just 2, 'o' := Nothing ] m fromList [('f',Just 1),('o',Nothing)] m . 'f' Just 1 m . size 2
I also have a pretty cool (almost) solution to the name collision problem. Visit the project homepage for a more thorough explanation. https://github.com/yokto/object And to those who gonna hate on me because they like the (.) as function composition I have only this to say. type instance Output (b -> c) (a -> b') = (a -> c) instance (b ~ b') => Action (b -> c) (a -> b') where f . g = f Prelude.. g Have fun, Silvio _______________________________________________ Haskell-Cafe mailing list mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

relevantly: https://ghc.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields...
Ways in which I think my implementation is superior 1) in the proposal the thing behind the dot has to be a function. Therefore, you have to wrap everything in a function before you can use it. Something like this is not possible
[1,2,3] . 0 1
2) I'm not sure this proposal solves the name collision problem but that might just be that i don't understand it. 3) my library doesn't require any additional syntax only a few already existing extensions. And you can use a bit of template haskell to assist the creation of objects. 4) Also the proposal doesn't mention updates but if they have to be a function you cant use the same name as for the function to get a field. And you simply can't beat my syntax, in which you can use the same name for both. object . fieldName := value -- update object . fieldName -- get Silvio

One thing that is likely to be surprising is that (.) is
right-associative, whereas in C it's left-associative.
object . action . action would try to parse as object . (action .
action) - which may or may not typecheck but is probably not what was
intended.
On Thu, May 15, 2014 at 11:11 AM, silvio
relevantly: https://ghc.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields...
Ways in which I think my implementation is superior
1) in the proposal the thing behind the dot has to be a function. Therefore, you have to wrap everything in a function before you can use it. Something like this is not possible
[1,2,3] . 0 1
2) I'm not sure this proposal solves the name collision problem but that might just be that i don't understand it.
3) my library doesn't require any additional syntax only a few already existing extensions. And you can use a bit of template haskell to assist the creation of objects.
4) Also the proposal doesn't mention updates but if they have to be a function you cant use the same name as for the function to get a field. And you simply can't beat my syntax, in which you can use the same name for both. object . fieldName := value -- update object . fieldName -- get
Silvio _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, May 15, 2014 at 2:16 PM, silvio
you can specify the associativity using infix(l/r) expression
Which will break almost all existing code in order to enable something that is dubious at best given how much . is already overloaded. And gains you nothing in the way of "object oriented" as cited in your subject line --- . is the *least* of the issues involved with OO, and is used in the way you want by non-OO languages. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 14-05-15 03:06 PM, Brandon Allbery wrote:
On Thu, May 15, 2014 at 2:16 PM, silvio
mailto:silvio.frischi@gmail.com> wrote: you can specify the associativity using infix(l/r) expression
Which will break almost all existing code in order to enable something that is dubious at best given how much . is already overloaded. And gains you nothing in the way of "object oriented" as cited in your subject line --- . is the *least* of the issues involved with OO, and is used in the way you want by non-OO languages.
What Wadler said. Talking too much syntax, too little semantics.

How would setting/modification work in your scheme? This problem has been solved a couple of times within the Haskell community and you're most likely looking for a lens library. They make data accessors first class and a subset of them compose in a way that reads just like object oriented notation. For example, with `lens` you can do the following: data MyState = MyState { _person :: Person } data Person = Person { _pos :: (Int, Int) } makeLenses [''MyState, ''Person] (person.pos._1 += 1) :: State MyState () Notice that the lenses compose with (.), compose in the order you expect from OO programming (and opposite normal function composition -- though it's actually the same), and allow you to set (as well as view). The `lens` package also provides these lenses for most of base along with many other useful tools for this kind of programming (notice _1 that acts as an accessor into a tuple). On Thu, May 15, 2014 at 1:44 PM, Kyle Marek-Spartz < kyle.marek.spartz@gmail.com> wrote:
Recently, on LtU: http://lambda-the-ultimate.org/node/4951
Most relevantly: https://ghc.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields...
– Kyle Marek-Spartz
On May 15, 2014, 12:38:29 PM, silvio
wrote: ------------------------------ Hi Haskell,
I've been wondering if (.) is so cool in other languages why can't we make it even cooler in haskell. And went on to implement such a (.) based on multiparameter type classes and type families.
type family Output object action class Action object action where (.) :: object -> action -> Output object action
I'm not sure if this has been done before like this but i didn't find anything. I used Map as an example, and here is what I ended up with:
:m -Prelude import Prelude hiding ((.)) import Object import Object.Example import Data.Map hiding (size) let m = empty . [ 'f' := Just 1, 'o' := Just 2, 'o' := Nothing ] m fromList [('f',Just 1),('o',Nothing)] m . 'f' Just 1 m . size 2
I also have a pretty cool (almost) solution to the name collision problem.
Visit the project homepage for a more thorough explanation.
https://github.com/yokto/object
And to those who gonna hate on me because they like the (.) as function composition I have only this to say.
type instance Output (b -> c) (a -> b') = (a -> c) instance (b ~ b') => Action (b -> c) (a -> b') where f . g = f Prelude.. g
Have fun,
Silvio _______________________________________________ Haskell-Cafe mailing list mailto: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

With lens, you can write:
[1,2,3] ^?! ix 0 1
Not that much of a difference, IMO.
2014-05-15 20:30 GMT+02:00 silvio
Yes I know lenses do something similar. But they are restricted to lenses in the same way the other proposal is restricted to functions you couldn't write
[1,2,3] . 0 1
and also I don't think they solve the name collision problem either.
silvio _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 For true object-oriented Haskell, read «Haskell's overlooked object system» by Oleg Kiselyov and Ralf Lämmel. - -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlN1Dw4ACgkQRtClrXBQc7Wc7AD+My9i1FVzCaDuprLilD9zGhRK rNaUaJNffs9FYc1BeMcBAJplpwN/nH9AjGl2SunrS8+lfbahGhsA+AYqJKIf/Qqg =2SWo -----END PGP SIGNATURE-----

2014-05-15 21:01 GMT+02:00, Alexander Berntsen
For true object-oriented Haskell, read «Haskell's overlooked object system» by Oleg Kiselyov and Ralf Lämmel.
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple. In the goal of making Haskell mainstream, it would be definitive to make haskell the best OO language besides the best imperative one. It is a matter of a bit of effort by some people to come up with an elegant notation for the ideas of this paper.
- -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/
iF4EAREIAAYFAlN1Dw4ACgkQRtClrXBQc7Wc7AD+My9i1FVzCaDuprLilD9zGhRK rNaUaJNffs9FYc1BeMcBAJplpwN/nH9AjGl2SunrS8+lfbahGhsA+AYqJKIf/Qqg =2SWo -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

On 16 May 2014, at 00:17, Alberto G. Corona
2014-05-15 21:01 GMT+02:00, Alexander Berntsen
: For true object-oriented Haskell, read «Haskell's overlooked object system» by Oleg Kiselyov and Ralf Lämmel.
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple.
Seems to me that FP people also need some encouragement.
In the goal of making Haskell mainstream, it would be definitive to make haskell the best OO language besides the best imperative one.
It is a matter of a bit of effort by some people to come up with an elegant notation for the ideas of this paper.
- -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/
iF4EAREIAAYFAlN1Dw4ACgkQRtClrXBQc7Wc7AD+My9i1FVzCaDuprLilD9zGhRK rNaUaJNffs9FYc1BeMcBAJplpwN/nH9AjGl2SunrS8+lfbahGhsA+AYqJKIf/Qqg =2SWo -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 15/05/14 22:17, Alberto G. Corona wrote:
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple. I hate the examples in that paper with every fibre of my being. Every single cell in my body screams "THIS IS WRONG".
Yet, I am in awe of them. Recommended read! It's very interesting. - -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlN1IbcACgkQRtClrXBQc7VqCwEAqEgEbQ+eqoZwf4KQxzrvmRtk yhMsaOUwi8YYJiAZa4kA/3YY4tz/tFWI5zpNGTxtbD1K5ifq9V/pO6X+4pKSOO38 =ruyQ -----END PGP SIGNATURE-----

On Thu, May 15, 2014 at 10:17 PM, Alberto G. Corona
2014-05-15 21:01 GMT+02:00, Alexander Berntsen
: For true object-oriented Haskell, read «Haskell's overlooked object system» by Oleg Kiselyov and Ralf Lämmel.
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple.
In the goal of making Haskell mainstream, it would be definitive to make haskell the best OO language besides the best imperative one.
I thought the goal was *not* to make Haskell mainstream? Avoid success at all costs, and all that. Erik

I read over the first few example and it does not collide with my library. In fact, It could benefit from my library. From both (.) as well as the label construction. Actually I didn't get how they make the labels (getX). type instance Output (a .*. b) label = OOOutput (a .*. b) label type family OOOutput where OOOutput (label .=. out .*. rest) label = out OOOutput (noMatch .*. rest) label = OOOutput rest label instance Action (label .=. out .*. rest) label where (_ .=. action .*. _) . _ = action instance Action (noMatch .*. rest) label where (_ .*. rest) . b = rest . b I didn't compile this since i didn't have their code so there are probably some errors. Also I assumed their .*. are typeOperators even though they don't start with a :. But the idea should be clear. silvio

Hi Silvio,
.*. has always been a function.
http://hackage.haskell.org/package/HList-0.3.4.1/docs/Data-HList-HListPrelud...
is the current definition. The operations for lookup/update etc. need
to be rewritten to use closed type families as you did for lookup,
since GHC doesn't allow type families to use type classes. If it did,
then we could do the following:
instance (HasField l (Record r) v,
Output (Record r) (Label l) ~ v)
=> Action (Record r) (Label l)
where (.) = flip hLookupByLabel
type instance Output (Record r) (Label l) = (HasField l (Record r) v)
=> v -- not allowed
Regards,
Adam
On Thu, May 15, 2014 at 5:12 PM, silvio
I read over the first few example and it does not collide with my library. In fact, It could benefit from my library. From both (.) as well as the label construction. Actually I didn't get how they make the labels (getX).
type instance Output (a .*. b) label = OOOutput (a .*. b) label type family OOOutput where OOOutput (label .=. out .*. rest) label = out OOOutput (noMatch .*. rest) label = OOOutput rest label instance Action (label .=. out .*. rest) label where (_ .=. action .*. _) . _ = action instance Action (noMatch .*. rest) label where (_ .*. rest) . b = rest . b
I didn't compile this since i didn't have their code so there are probably some errors. Also I assumed their .*. are typeOperators even though they don't start with a :. But the idea should be clear.
silvio _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 16/05/2014, at 8:17 AM, Alberto G. Corona wrote:
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple.
Do we *want* to attract them? Why?
In the goal of making Haskell mainstream, it would be definitive to make haskell the best OO language besides the best imperative one.
To make Haskell "mainstream", you have to make it just like conventional C-family languages, only maybe 1% different. The whole *POINT* of Haskell is to facilitate a whole different way of thinking about programming. The more you make it resemble "mainstream" languages in order to encourage "the OO peple" to adopt it, the less benefit they will get from doing so. If you just wait a bit, Java 28 will probably have monads and lenses.

http://bartoszmilewski.com/2014/02/26/c17-i-see-a-monad-in-your-future/
On Thu, May 15, 2014 at 6:00 PM, Richard A. O'Keefe
On 16/05/2014, at 8:17 AM, Alberto G. Corona wrote:
Which is an excellent haskell framework for OO programming in haskell but desperately need some kind of syntactic sugar to attract the OO peple.
Do we *want* to attract them? Why?
In the goal of making Haskell mainstream, it would be definitive to make haskell the best OO language besides the best imperative one.
To make Haskell "mainstream", you have to make it just like conventional C-family languages, only maybe 1% different.
The whole *POINT* of Haskell is to facilitate a whole different way of thinking about programming.
The more you make it resemble "mainstream" languages in order to encourage "the OO peple" to adopt it, the less benefit they will get from doing so.
If you just wait a bit, Java 28 will probably have monads and lenses.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think every OO programmer coming to Haskell goes through this phase. They start by attempting to use a haskell typeclass as they would a class in an OO language, find it doesn't work and are a little miffed. Nevertheless they persevere and are writing servicable if not idiomatic haskell and are starting to get comfortable with Haskell's type system and experimenting in it but they still feel the gentle tug of familier design patterns(tm) and find themselves coding in a style trying to replicate them. By this point they are familier enough with the haskell type system that they start to realize they can simulate the behavior they are used to, hey, an OO class is simply a type class combined with an existential type and a default value all rolled into one! (which is more or less, completely true.) So, they start making type classes that look like OO ones, restricting their inherentence trees to be singular, using type class parameters in linear covariant position because that is what they are used to and find things good. they have replicated OO behavior, even got a working syntax down and start programming in their own brand of OO-Haskell. Then something happens. They go back to C++, or Java, or C#, and suddenly, they feel horribly restricted. They start to wonder.. like. why do methods only get to choose an implementation based on their first argument? Why the heck is the class interface and an implementation related at all? why the heck is code re-use tied to inherentence and why is multiple inheritence tricky? why am I no longer happy? They have had their flowers for algernon moment. While attempting to change haskell to an OO language, Haskell has been changing them into a type system hacker. while writing their restricted OO like class, they experimented with other models of combining type classes with concrete data, perhaps by accident and found them useful. They realized a data type they created was an instance of a class and was able to declare that after the fact without cahnging any existing code. They found that the ability for type inference to work in any direction, and represent the relationship between types was useful. They are enlightened, and look back at their OO - Haskell framework as a curiosity from their past. We all have one in our attic. An attempt at a stock pattern shoehorned into something that a single higher order function would solve. It's not a bad thing, It's part of learning Haskell. But there is a reason most of these OO proposals tend to peter out. They just are not really needed beyond a point.

Hi Silvio, Somebody can still hate on your: instance (b ~ b') => Action (b -> c) (a -> b') With standard haskell we can write:
(read . show) (1 :: Int) :: Double 1.0
But with your '.', that's a type error:
Couldn't match expected type ‘Int -> Double’
with actual type ‘Output (String -> a0) (a1 -> String)’
The type variables ‘a0’, ‘a1’ are ambiguous
I can't come up with a type annotation that makes it work out. Type
inference can work out better when you have something like:
class Dot a b c where (.) :: a -> b -> c
instance (f ~ (b -> c), g ~ (a -> b), fg ~ (a -> c)) => Dot f g fg --
"fallback" instance is what Prelude does
But composing functions overloaded like this tends to need type
annotations because ghc does not allow inferring type signatures that
contain ambiguous types.
Also I have a couple suggestions for your code:
Instead of `lookupTypeName "Object.Types.MethodOutput" *> fromMaybe
(error "no MethodOutput in scope")', you probably should just refer to
the actual Name ''MethodOutput. The "no MethodOutput in scope" didn't
prompt me to add an "import Object.Types". I'm not sure you are
expecting people to substitute their own MethodOutput (by import
qualified MyModule as Object.Types (MethodOutput)).
Instead of Object.Letters, you can use promoted strings
(GHC.TypeLits.Symbol)? Those look prettier, and you're already stuck
with ghc given the other extensions you use (TypeFamilies, PolyKinds,
TemplateHaskell).
Regards,
Adam
On Thu, May 15, 2014 at 1:38 PM, silvio
Hi Haskell,
I've been wondering if (.) is so cool in other languages why can't we make it even cooler in haskell. And went on to implement such a (.) based on multiparameter type classes and type families.
type family Output object action class Action object action where (.) :: object -> action -> Output object action
I'm not sure if this has been done before like this but i didn't find anything. I used Map as an example, and here is what I ended up with:
:m -Prelude import Prelude hiding ((.)) import Object import Object.Example import Data.Map hiding (size) let m = empty . [ 'f' := Just 1, 'o' := Just 2, 'o' := Nothing ] m fromList [('f',Just 1),('o',Nothing)] m . 'f' Just 1 m . size 2
I also have a pretty cool (almost) solution to the name collision problem.
Visit the project homepage for a more thorough explanation.
https://github.com/yokto/object
And to those who gonna hate on me because they like the (.) as function composition I have only this to say.
type instance Output (b -> c) (a -> b') = (a -> c) instance (b ~ b') => Action (b -> c) (a -> b') where f . g = f Prelude.. g
Have fun,
Silvio _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks it works. I tried it in Example.lhs, which does not import the
instance from Object.hs.
On Thu, May 15, 2014 at 3:22 PM, silvio
(read . show) 1 :: Double 1.0
actually that example works fine for me are you sure you copied it right. I.e. that you have b and b' both in both instances.
silvio

On Thu, May 15, 2014 at 07:38:29PM +0200, silvio wrote:
Hi Haskell,
I've been wondering if (.) is so cool in other languages why can't we make it even cooler in haskell. And went on to implement such a (.) based on multiparameter type classes and type families.
In what languages is (.) cool, and in what way? -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus In a hierarchy, every employee tends to rise to his level of incompetence. -- The Peter Principle

In what languages is (.) cool, and in what way?
Because depending on what is before it, what is behind it can have different meanings. For me this is one of the main points. I just don't like the name collision problem in Haskell. Take something like size for instance it is pretty clear what it means yet unless you have a type class that everybody knows about you can use it on only one thing. And even if you have a simple type class some object might want to return an Int and some other might want to return an Integer. With (.) being from a multiparameter typeclass you can define for each object what it means without any of them knowing about the others. And you are not even limited to, let's call them, 'labels' like size. You can also use any other Type you want like the key of a database object or as in my example a Map. Silvio

On Thu, May 15, 2014 at 11:37:40PM +0200, silvio wrote:
In what languages is (.) cool, and in what way?
Because depending on what is before it, what is behind it can have different meanings. For me this is one of the main points. I just don't like the name collision problem in Haskell. Take something like size for instance it is pretty clear what it means yet unless you have a type class that everybody knows about you can use it on only one thing. And even if you have a simple type class some object might want to return an Int and some other might want to return an Integer. With (.) being from a multiparameter typeclass you can define for each object what it means without any of them knowing about the others. And you are not even limited to, let's call them, 'labels' like size. You can also use any other Type you want like the key of a database object or as in my example a Map.
So, slightly simplified you want to: Firstly, a notation where you put the first argument before the function/method? [1,2,3] . length -> 3 Secondly, mimic the multilayered namespaces that is commonly found in mainstream imperative OO languages? [1,2,3] . length -> 3::Int aPieceOfString . length -> 120.0::Double Just trying to understand what problem you are actually trying to solve. I've *never* thought of (.) being powerful in OO languages, mostly because I don't really think the dot is what makes an OO language. /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus What gets measured, gets done. -- Tom Peters

Firstly, a notation where you put the first argument before the function/method?
[1,2,3] . length -> 3
Secondly, mimic the multilayered namespaces that is commonly found in mainstream imperative OO languages?
[1,2,3] . length -> 3::Int aPieceOfString . length -> 120.0::Double
Just trying to understand what problem you are actually trying to solve. I've *never* thought of (.) being powerful in OO languages, mostly because I don't really think the dot is what makes an OO language.
That's essentially it. I see that people on this thread where thinking more along the lines of inheritance. So let me add that it shouldn't be difficult to add the instances you want for your child object and then make a default instance which reverts to the parent object. It's a bit of a problem for updating stuff in a functional way since you can never be sure if a method is ment to return an object or if this is supposed to be an update. But for things in IO/STM/... it should be fine. Silvio

On Fri, May 16, 2014 at 12:47:40AM +0200, silvio wrote:
Firstly, a notation where you put the first argument before the function/method?
[1,2,3] . length -> 3
Secondly, mimic the multilayered namespaces that is commonly found in mainstream imperative OO languages?
[1,2,3] . length -> 3::Int aPieceOfString . length -> 120.0::Double
Just trying to understand what problem you are actually trying to solve. I've *never* thought of (.) being powerful in OO languages, mostly because I don't really think the dot is what makes an OO language.
That's essentially it. I see that people on this thread where thinking more along the lines of inheritance. So let me add that it shouldn't be difficult to add the instances you want for your child object and then make a default instance which reverts to the parent object. It's a bit of a problem for updating stuff in a functional way since you can never be sure if a method is ment to return an object or if this is supposed to be an update. But for things in IO/STM/... it should be fine.
Excellent, then at least understand what you are after. I was confused by the ensuing discussion, because it so quickly moved away from what I thought you were really proposing. To be honest I've more often missed Haskell's (.) when programming in C/C++/C# than the other way around ;) /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay

Magnus, did you notice the Alan Kay quote that was generated for your sig?
Serendipitous. :-)
Haskell subsumes a great deal of semantics from many programming models.
This is not to say that it is necessarily a productive end-tool
replacement, but many have discovered that it is a great language to build
such tools with.
Cheers,
Darren
On May 15, 2014 4:00 PM, "Magnus Therning"
On Fri, May 16, 2014 at 12:47:40AM +0200, silvio wrote:
Firstly, a notation where you put the first argument before the function/method?
[1,2,3] . length -> 3
Secondly, mimic the multilayered namespaces that is commonly found in mainstream imperative OO languages?
[1,2,3] . length -> 3::Int aPieceOfString . length -> 120.0::Double
Just trying to understand what problem you are actually trying to solve. I've *never* thought of (.) being powerful in OO languages, mostly because I don't really think the dot is what makes an OO language.
That's essentially it. I see that people on this thread where thinking more along the lines of inheritance. So let me add that it shouldn't be difficult to add the instances you want for your child object and then make a default instance which reverts to the parent object. It's a bit of a problem for updating stuff in a functional way since you can never be sure if a method is ment to return an object or if this is supposed to be an update. But for things in IO/STM/... it should be fine.
Excellent, then at least understand what you are after. I was confused by the ensuing discussion, because it so quickly moved away from what I thought you were really proposing.
To be honest I've more often missed Haskell's (.) when programming in C/C++/C# than the other way around ;)
/M
-- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus
I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, May 16, 2014 at 01:35:20AM +0200, Darren Grant wrote:
Magnus, did you notice the Alan Kay quote that was generated for your sig? Serendipitous. :-)
Well spotted, I didn't notice it. Serendipitous indeed!
Haskell subsumes a great deal of semantics from many programming models. This is not to say that it is necessarily a productive end-tool replacement, but many have discovered that it is a great language to build such tools with.
I'm convinced it IS a productive replacement in a surprising number of cases. It's just so irritating how entrenched the use of C/C++ is in the circles I move :( /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay

Well for instance in game development we cover a number of different
computational and creative roles. Being able to design languages that serve
game development easily is a plus, or creating a solid backend
infrastructure. The general tool is often a poor fit.
And sometimes computational systems just have to be extremely efficient,
especially on lowest common denominator targets. This is another good place
for a DSL or some sort of automatic code generation, in which case Haskell
can become like lisp on steroids for spitting out code consumed elsewhere.
Cheers,
Darren
On May 15, 2014 10:21 PM, "Magnus Therning"
On Fri, May 16, 2014 at 01:35:20AM +0200, Darren Grant wrote:
Magnus, did you notice the Alan Kay quote that was generated for your sig? Serendipitous. :-)
Well spotted, I didn't notice it. Serendipitous indeed!
Haskell subsumes a great deal of semantics from many programming models. This is not to say that it is necessarily a productive end-tool replacement, but many have discovered that it is a great language to build such tools with.
I'm convinced it IS a productive replacement in a surprising number of cases. It's just so irritating how entrenched the use of C/C++ is in the circles I move :(
/M
-- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus
I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay

On 16/05/2014, at 9:37 AM, silvio wrote:
In what languages is (.) cool, and in what way?
Because depending on what is before it, what is behind it can have different meanings.
That's not cool, that's majorly problematic. Ad hoc polymorphism is not good for readability.
For me this is one of the main points. I just don't like the name collision problem in Haskell. Take something like size for instance it is pretty clear what it means yet unless you have a type class that everybody knows about you can use it on only one thing.
For the person WRITING the code, this is a pain in the backside. For the person READING the code, it is great blessing. In Java, foo.size() could literally do ANYTHING. In Smalltalk, "x value" might be simply extracting a slot from an object or it might be invoking an arbitrarily complex operation with arbitrary side effects or (in at least one Smalltalk) it might be a special kind of synchronisation, and it's not hard to end up in situations where all three are in play. Note that the dot as such actually plays no significant role in OO. Common Lisp and Ada both can do dynamic dispatch using ordinary function call syntax. Indeed, Common Lisp shows an pretty horrible and not very principled restriction in the dotty view of the world: the dynamic call (draw Picture Canvas) can dispatch on Picture, or Canvas, or both, depending on what best suits your problem, whereas picture.Draw(canvas) can only dispatch on picture.

For the person WRITING the code, this is a pain in the backside. For the person READING the code, it is great blessing.
Acutely, I think dot notation is great to read.
In Java, foo.size() could literally do ANYTHING. In Smalltalk, "x value" might be simply extracting a slot from an object or it might be invoking an arbitrarily complex operation with arbitrary side effects or (in at least one Smalltalk) it might be a special kind of synchronisation, and it's not hard to end up in situations where all three are in play.
I don't see how a polymorphic (.) changes anything. If the output type which is decided by the input types is 'IO a' then it can do anything if it is not IO then it can't. Just like in any other Haskell function. I concede that doku is something I yet have to think about. But that's just a question of representing the info that is already there in a readable way. silvio
participants (17)
-
adam vogt
-
Albert Y. C. Lai
-
Alberto G. Corona
-
Alexander Berntsen
-
Arjun Comar
-
Benno Fünfstück
-
Brandon Allbery
-
Darren Grant
-
David Thomas
-
Erik Hesselink
-
John Meacham
-
Kyle Marek-Spartz
-
Magnus Therning
-
MigMit
-
Richard A. O'Keefe
-
Sam Caldwell
-
silvio