[Haskell-beginners] Return type from class method

Thomas Jakway tjakway at nyu.edu
Sat Oct 7 22:30:27 UTC 2017


You could hide Prelude and define it yourself in a different module but 
that would be a pretty bad idea.  Everyone who wanted to use it would 
have to import your module qualified and refer to it as MyModule.+, 
which defeats the point of making it (+) and not `myAdditionFunction` in 
the first place.

Haskell deliberately doesn't allow overloading.  Having (+) return 
something other than Num would be extremely confusing.


On 10/07/2017 05:07 AM, PATRICK BROWNE wrote:
> Hi,
> Is there a way rewriting the definition of (+) so that testPlusArg 
> returns a (Moving Double). My current intuition is that the signature 
> [(+)  ::  a -> a  -> a] says that the type should be the same as the 
> arguments. And indeed (:t testPlus) confirms this. But the type of  
> testPlusArg is a Double.
>  Can I make it (Moving Double) ?
> Thanks,
> Pat
>
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE TypeSynonymInstances #-}
> module Moving where
> data  Time  = Time Double
> type Moving v  = Time -> v
>
> class  Number a where
>  (+)  ::  a -> a  -> a
>
> instance Number  (Moving Double) where
>  (+) a b = \t -> ((a t) Prelude.+ (b t))
>
> a,b ::  Moving Double
> a (Time x) = 2.0
> b (Time x) = 2.0
> testPlus ::(Moving Double)
> testPlus = (a Moving.+ b)
> testPlusArg = (a Moving.+ b) (Time 2.0)
>
> This email originated from DIT. If you received this email in error, 
> please delete it from your system. Please note that if you are not the 
> named addressee, disclosing, copying, distributing or taking any 
> action based on the contents of this email or attachments is 
> prohibited. www.dit.ie <http://www.dit.ie/>
>
> Is ó ITBÁC a tháinig an ríomhphost seo. Má fuair tú an ríomhphost seo 
> trí earráid, scrios de do chóras é le do thoil. Tabhair ar aird, mura 
> tú an seolaí ainmnithe, go bhfuil dianchosc ar aon nochtadh, aon 
> chóipeáil, aon dáileadh nó ar aon ghníomh a dhéanfar bunaithe ar an 
> ábhar atá sa ríomhphost nó sna hiatáin seo. www.dit.ie 
> <http://www.dit.ie/>
>
> Tá ITBÁC ag aistriú go Gráinseach Ghormáin – DIT is on the move to 
> Grangegorman <http://www.dit.ie/grangegorman>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20171007/06ba76a3/attachment.html>


More information about the Beginners mailing list