[Haskell-cafe] Object oriented haskell.

adam vogt vogt.adam at gmail.com
Thu May 15 19:17:58 UTC 2014


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 <silvio.frischi at gmail.com> 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
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list