Re: [Haskell-cafe] Overloading

2013-03-10 Thread MigMit

On Mar 10, 2013, at 11:47 AM, Peter Caspers pcaspers1...@gmail.com wrote:

 Thank you all for your answers, this helps a lot. To clarify my last point ...
 
 Also again, taking this way I can not provide several constructors taking 
 inputs of different types, can I ?
 Sorry, didn't get what you mean here.
 
 In C++ it is perfectly normal to have overloaded functions like
 
 f : Int - Int - Int
 f : Int - Char - Int
 
 in coexistence, because the compiler can infer (at compile time) what 
 function to call by looking at the arguments types.
 
 In Haskell I think this is not possible simply due to the flexibility given 
 by partial function application, i.e.
 
 f 5
 
 would not be well defined any more, it could be Int - Int or Char - Int.

Well, that's what typeclasses are for.

class F a where f :: Int - a - Int

instance F Int where f = ...
instance F Char where f = ...

ghci :t f 5
ghci f 5 :: (F a) = a - Int
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread ok


 In C++ it is perfectly normal to have overloaded functions like

 f : Int - Int - Int
 f : Int - Char - Int

Something that may not be obvious about Haskell is that
Haskell does NOT have overloaded functions/operators at all.

More precisely, for any identifier and any point in a
Haskell module, there is at most ONE definition of that
identifier that is in scope at that point.

More precisely, we can think of a function has having
two parts: an *interface* which specifies its type and zero
or more *implementations* which specify its behaviour, all
of which must have types that match or are special cases
of that interface.
For any identfier and any point in a Haskell module,
there is at most one INTERFACE for that identifier that
is in scope at that point, so there is no possible doubt
about the type of that identifier.

As an example, the standard Prelude has *one* interface
for +, namely
(+) :: Num t = t - t - t
and it offers a number of implementations of + (in
'instance' declarations) for various types.
There are additional implementations in other modules,
but they all must have types that are instances of this one.

I don't believe that partial (Curried) application has
anything to do with it.  Torsors would need multiparameter
type classes so that
 g + t :: t
 t - t :: g
and so on, but Haskell originally didn't have multiparameter
type classes.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Peter Caspers



In C++ it is perfectly normal to have overloaded functions like

f : Int - Int - Int
f : Int - Char - Int

Something that may not be obvious about Haskell is that
Haskell does NOT have overloaded functions/operators at all.


thanks, this was the core of my question. So by example, if I define a 
Date type as


data Date = Date Int deriving Show

representing a date by its serial number and want two constructors 
(conditions are only examples here)


-- smart constructor with serialNumber
date serialNumber
 | serialNumber  0 = Date serialNumber
 | otherwise = error (invalid serialNumber  ++ show serialNumber)

-- smart constructor with day month year
date2 day month year
| month = 1  month =12 = undefined
| otherwise = error (invalid month  ++ show month)

there is no way of naming both functions date (instead of date2 above, 
which compiles), right ? I still think the basic reason is that


date 5

would then either refer to the first constructor (i.e. representing a 
date with serial number 5) or a partial application of the second
constructor (i.e. representing a function taking month and year and 
returning the date 5th month, year).


If this is the case, what would be the natural Haskell way of organizing 
the smart constructors ? Just number them as above ? Or naming them

dateFromSerialNumber, dateFromDayMonthYear ?

Or would you do it differently from the start ?

Thank you
Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Daniel Trstenjak

Hi Peter,

 -- smart constructor with serialNumber
 date serialNumber
  | serialNumber  0 = Date serialNumber
  | otherwise = error (invalid serialNumber  ++ show serialNumber)

Instead of raising an error it's more secure to return a Maybe value.

date :: Int - Maybe Date
date serialNumber
   | serialNumber  0 = Just $ Date serialNumber
   | otherwise= Nothing

 -- smart constructor with day month year
 date2 day month year
 | month = 1  month =12 = undefined
 | otherwise = error (invalid month  ++ show month)

To increase type safety it's a good idea to use as much explicit data
types instead of Int values as possible:

data Month = January | ...

 If this is the case, what would be the natural Haskell way of
 organizing the smart constructors ? Just number them as above ? Or
 naming them
 dateFromSerialNumber, dateFromDayMonthYear ?

I would use the descriptive names but leave out the 'date', because you could 
still have:

import qualified Date

Date.fromSerialNumber



Greetings,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Peter Caspers

Hi Daniel,


Instead of raising an error it's more secure to return a Maybe value.

date :: Int - Maybe Date
date serialNumber
| serialNumber  0 = Just $ Date serialNumber
| otherwise= Nothing


yes, I understand (Maybe seems the equivalent of c++'s boost::optionalT).


-- smart constructor with day month year
date2 day month year
 | month = 1  month =12 = undefined
 | otherwise = error (invalid month  ++ show month)

To increase type safety it's a good idea to use as much explicit data
types instead of Int values as possible:

data Month = January | ...


ok, I will try to change my code in that direction. The idea is clear.


I would use the descriptive names but leave out the 'date', because you could 
still have:

import qualified Date

Date.fromSerialNumber



also clear, yes. I think I have a better starting point now. Not 
impossible that I will come back later with further questions :-)


Thank you for your help
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] To seq or not to seq, that is the question

2013-03-10 Thread Albert Y. C. Lai

On 13-03-08 11:53 PM, Edward Z. Yang wrote:

Are these equivalent? If not, under what circumstances are they not
equivalent? When should you use each?

 evaluate a  return b
 a `seq` return b
 return (a `seq` b)


Let a = div 0 0
(or whatever pure but problematic expression you like)
b can be the same as a or something else.

First assume IO. The 3rd one is distinguished by

main = m  return ()

where m is to be plugged in the 1st, 2nd, or 3rd. During IO execution, 
the 1st and 2nd throw an exception, the 3rd one does not.


The 2nd is distinguished by

main = evaluate m

During IO execution, the 2nd throws an exception, the 1st and 3rd do 
not. (m `seq` return () should also do the same.)


In practice, we seldom artificially evaluate or seq an IO action like 
that. And so, that distinction between the 1st and 2nd is seldom 
observed. But another difference matters more in practice:


main = head [] `seq` (a `seq` return b)

Two consecutive seqs is an instance where the impreciseness of imprecise 
exceptions kicks in. The compiler reserves the right to prefer either 
the empty-list exception or the divide-by-0 exception; perhaps even a 
difference choice at a different time. Whereas:


main = evaluate (head [])  (evaluate a  return b)

By virtue of IO's serializing  (and lack of unsafeInterleaveIO hehe), 
the exception thrown must be the empty-list one.


If the monad is not IO, then we cannot discuss evaluate. But we can be 
sure that different monads behave differently, and the difference 
involves =. Example:


import Control.Monad.State.Strict
a = div 0 0
b = whatever you like
main = print (evalState ((a `seq` return b)  return ()) ())
-- throws an exception

import Control.Monad.State.Lazy
a = div 0 0
b = whatever you like
main = print (evalState ((a `seq` return b)  return ()) ())
-- does not throw an exception

(Did you know: Control.Monad.State refers to the Lazy one.)

I leave the rest of the questions unanswered. Enough mind-bending for 
today! :)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Donn Cave
Peter Caspers pcaspers1...@gmail.com,

 data Month = January | ...
 
 ok, I will try to change my code in that direction. The idea is clear.

To whatever extent these algebraic data types do map to integer
values for your purposes, you can implement that by making Month an
instance of Enum.

Donn

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Richard A. O'Keefe

On 11/03/2013, at 12:10 AM, Peter Caspers wrote:

 thanks, this was the core of my question. So by example, if I define a Date 
 type as
 
 data Date = Date Int deriving Show
 
 representing a date by its serial number and want two constructors 
 (conditions are only examples here)
 
 -- smart constructor with serialNumber
 date serialNumber
 | serialNumber  0 = Date serialNumber
 | otherwise = error (invalid serialNumber  ++ show serialNumber)
 
 -- smart constructor with day month year
 date2 day month year
| month = 1  month =12 = undefined
| otherwise = error (invalid month  ++ show month)
 
 there is no way of naming both functions date (instead of date2 above, which 
 compiles), right ?

Right.
 I still think the basic reason is that
 
 date 5
 
 would then either refer to the first constructor (i.e. representing a date 
 with serial number 5) or a partial application of the second
 constructor (i.e. representing a function taking month and year and returning 
 the date 5th month, year).

I am having real trouble understanding why you think this.
Yes, for an *untyped* language, date 27 would not know whether
to return a date or a closure.  But Haskell is *not* an untyped
language.  The one-identifier-one-visible-interface rule is about
making a practical type inference algorithm.

I'm also having some trouble understanding why negative serial
numbers would be illegal.  Dates are a Z-torsor; to convert
integers to dates you have to choose an arbitrary origin.
My Dershowitz-and-Reingold-inspired Smalltalk calendar library
lets you use Julian day number (shifted by 0.5), modified Julian
day number, rata die, and ahargana.  I've been thinking of allowing
a fifth origin: COBOL's 0=31-Dec-1600.  serialNumber is a bad
name because the origin is arbitrary and the name does not reveal
what the origin is.

You can easily write

date :: Either Int (Int Int Int) - Date

date (Left days_since_epoch) = Date days_since_epoch
date (Right (year,month,day))
  | 1 = month  month = 12  1 = day 
day = days_in_month year month
= …
  | otherwise = error (bad date)

Or even set up your own interface type:

import System.Time  -- to get Month; pity Data.Time doesn't offer that.

data Date_Presentation
   = Julian_Day_Number Int
   | Modified_Julian_Day_Number Int
   | Rata_Die Int
   | Ahargana Int
   | Days_Since_COBOL_Epoch Int
   | Gregorian Int Month Int
   | Julian Int Month Int
   | Revised_Julian Int Month Int -- more accurate than Gregorian 

date :: Date_Presentation - Date

date (Julian_Day_Number j) = …
…
date (Revised_Julian y m d) = …

You will notice that this list offers 5 date presentations that
use a single number and three that use two numbers and a month name.
Overloading is no help with that!

 If this is the case, what would be the natural Haskell way of organizing the 
 smart constructors ? Just number them as above ? Or naming them
 dateFromSerialNumber, dateFromDayMonthYear ?

As noted above, there is NO unique serial number for a date
and NO unique day/month/year representation either.

Smalltalk-80 introduced baStudlyCaps namesThatIsNamesWithInternalCapitals
because it was implemented on a machine that used the ASCII 63
left arrow and up arrow instead of the ASCII 67 underscore and caret.
So it used the codepoint we associate with underscore for the assignment
symbol.  In C and C++ and SML and Haskell, we are allowed to use
underscores.  ThereisnoneedtorunyourwordstogetherOrUseInternalCaps.
Nobody_will_shoot_you_for_writing_readably.

You should probably take advantage of the module name and call your
functions
Date.from_julian_day_number :: Int - Date
Date.from_gregorian :: Int - Month - Int - Date

 Or would you do it differently from the start ?

One question is support for different calendars.

I would probably have a My_Date module that just offers
julian day number, modified julian day number, ahagarna,
rata die, and maybe a couple of other epochs.  I would
create nested modules My_Date.Gregorian, My_Date.Julian,
My_Date.Revised_Julian, My_Date.Mayan, and so on, so that
a new calendar could be supported by just plugging in a
new module, not by changing anything.

For something without so many alternatives, I might make a different choice.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe