Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Ryan Ingram
So, the Haskell98 solution to this is:

class StringableList a where
 listToString :: [a] - String

-- now [a] is of the proper form; T = [], a is a type variable
instance StringableList a = Stringable [a] where
toString = listToString

-- now to make an instance for Stringable [Char]
-- we just make an instance for StringableList Char
instance StringableList Char where
listToString = id

I think FlexibleInstances just makes the compiler jump through these
hoops instead of you.

  -- ryan

On Wed, Oct 15, 2008 at 3:20 AM, George Pollard [EMAIL PROTECTED] wrote:

 I'm a little confused. Why is this allowed:

 data Blah = Blah

 instance Eq Blah where
 x == y = True

 But not this:

 class Stringable a where
 toString :: a - String

 instance Stringable [Char] where
 toString = id

 (Resulting in:)

 Illegal instance declaration for `Stringable [Char]'
 (All instance types must be of the form (T a1 ... an)
  where a1 ... an are distinct type *variables*
  Use -XFlexibleInstances if you want to disable this.)
 In the instance declaration for `Stringable [Char]'

 'Blah' isn't a type variable, is it? Is my brain just not working right
 today?

 ___
 Haskell-Cafe mailing list
 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


Re: [Haskell-cafe] List as input

2008-10-15 Thread Janis Voigtlaender

leledumbo wrote:

module Main where

import Data.List

-- quicksort of any list
qsort [] = []
qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs)

-- optimized quicksort, uses middle element as pivot
qsortOpt [] = []
qsortOpt x  = qsortOpt less ++ [pivot] ++ qsortOpt greater
  where
pivot = x !! ((length x) `div` 2)
less = filter (pivot) (delete pivot x)
greater = filter (=pivot) (delete pivot x)

main = do
  putStr Enter a list: 
  l - readLn
  print (qsortOpt l)
-- end of code

Why do I get

ERROR qsort.hs:17 - Unresolved top-level overloading
*** Binding : main
*** Outstanding context : (Read b, Show b, Ord b)


The compiler doesn't know what kind of list you are trying to read, 
sort, and print. Try something like:


(l::[Int]) - readLn

in the penultimate line.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Salsa: A .NET Bridge for Haskell

2008-10-15 Thread Manuel M T Chakravarty

Great!  Thanks for putting the code out!

Manuel

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


[Haskell-cafe] List as input

2008-10-15 Thread leledumbo

module Main where

import Data.List

-- quicksort of any list
qsort [] = []
qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs)

-- optimized quicksort, uses middle element as pivot
qsortOpt [] = []
qsortOpt x  = qsortOpt less ++ [pivot] ++ qsortOpt greater
  where
pivot = x !! ((length x) `div` 2)
less = filter (pivot) (delete pivot x)
greater = filter (=pivot) (delete pivot x)

main = do
  putStr Enter a list: 
  l - readLn
  print (qsortOpt l)
-- end of code

Why do I get

ERROR qsort.hs:17 - Unresolved top-level overloading
*** Binding : main
*** Outstanding context : (Read b, Show b, Ord b)

?

-- 
View this message in context: 
http://www.nabble.com/List-as-input-tp19987726p19987726.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread apfelmus
Janis Voigtlaender wrote:
 Derek Elkins wrote:

 Agreed.  I'm extremely tired of the I haven't heard this term therefore
 it must be 'scary' and complicated and beyond me attitude.  Such people
 need to stop acting like five year old children.
 
 Not that it has much to do with the debate, but the attitude you
 complain about is the exact opposite of the attitude of any five year
 old children that *I* know (well, my son primarily ;-).

Derek probably meant kids that are three quarters through school ... and
thus no longer interesting in anything. :(


Regards,
apfelmus

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


Re: [Haskell-cafe] Re: 2008-10-12 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread wren ng thornton

Simon Marlow wrote:

Don Stewart wrote:
 * GHC.Prim was moved,

Nobody should be importing GHC.Prim, use GHC.Exts instead.



This is oft declared, but as things stand I don't think it's a tenable 
position. If someone's bothering to dig as far as GHC.Exts then it's 
very likely they're trying to optimize numeric computations and for that 
there are a number of functions in GHC.Prim which are essential, in 
particular the fast conversion functions for numeric types[1]. If those 
were moved to GHC.Exts then I think many people would be more inclined 
to heed the advice.



[1] Of the many, these four especially: int2Double#, int2Float#, 
double2Float#, float2Double#. Though I'm sure the folks who work with 
Words would like to add to this list.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Flexible instances

2008-10-15 Thread Bulat Ziganshin
Hello Albert,

Wednesday, October 15, 2008, 7:51:06 AM, you wrote:

 Illegal instance declaration for `Stringable [Char]'
 (All instance types must be of the form (T a1 ... an)
  where a1 ... an are distinct type *variables*

 Just in case: n=0 for instance Eq Blah, i.e., T a1 ... an becomes T.

and [Char] = [] Char, where Char isn't type variable but constant


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread oleg

Lennart Augustsson wrote:
 I was just pointing out that the mechanism for doing the OO thing
 exists in Haskell too, albeit looking a little different.

Indeed there is a mechanism for doing OO in Haskell -- several of
them. Most of them have nothing to do with Existentials. In the 
OHaskell paper,

http://homepages.cwi.nl/~ralf/OOHaskell/

Ralf Laemmel has collected all known to us methods of doing OO in
Haskell. Incidentally, three years ago Lennart Augustsson described a
simple, Haskell98 method of emulating OO, without existentials. We
give him credit in footnote 4.

The OOHaskell paper then goes to demonstrate how to do *all* of the
known OO in Haskell, with all its inherent complexity: depth and width
subtyping, upcasting and safe downcasting, nominal and structural
subtyping, and the whole issue about covariant methods.

Derek Elkins wrote:
 In general, to encode OO you need quite a bit more than existentials.
 As you are probably aware, there was a cottage industry in the mid to
 late '90s working on encodings of OO languages into System F + foo
 calculi.  They just about gave up on a complete encoding until someone
 figured one out.  'turns out all you needed was recursive bounded
 existential quantification.

Not necessarily. Again, please see the OOHaskell paper. The full story
is that there are several encodings of objects -- using closures and
using existentials. The former are *far* simpler. ML-ART (which later
evolved in the 'O' of OCaml) chose the more complex encoding -- and
hence had to add equi-recursive types, existentials and universals to
Caml -- only because of a potential safety issue with closures. A
constructor of an object may invoke methods that may access fields
that are not initialized yet. This problem is present in all OO
languages, and the common `solution' is an admonition ``not to do
that''. Clearly Didier Remy has higher standards, and he went into
considerable pain to solve the problem. Incidentally, Haskell can
solve this problem in a simpler way. We critically rely on the fact
that all effects must be done in a monad. Therefore, in OOHaskell we
can safely use the simpler encoding for objects.

Regarding existentials, the web page
http://okmij.org/ftp/Computation/Existentials.html

demonstrates how to systematically eliminate existentials. In fact,
the object encoding via existentials can be easily transformed into
the encoding that uses only simple, first-order types. The web page
begs a question if there is ever any real need for existentials.

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


[Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Mauricio

Hi,

I'm wrapping a library where functions take
as parameters pointers to a few standard
structs (as, well, all C libraries). I
would like to ensure that only pointers of
correct structs are passed to those functions.
What is the Haskell way to do that? My
idea is to do something like this:

newtype SomeStruct = SomeStruct ()

and then

foreign import ccall my_function myfunction
  :: Ptr SomeStruct - IO int

Is that the proper way to do that?

Thanks,
Maurício

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


Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Bulat Ziganshin
Hello Vivek,

Wednesday, October 15, 2008, 3:39:54 PM, you wrote:

i think that practical answer is suggestion to use `case` instead:

case () of
 _ | x  5 - do abc
 def
 ...
 
   | x==5  - do ...
   
   | otherwise - do ...

it's pretty common pattern for haskell

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Bulat Ziganshin
Hello Mauricio,

Wednesday, October 15, 2008, 5:40:16 PM, you wrote:

 newtype SomeStruct = SomeStruct ()

data SomeStruct = SomeStruct

looks even simpler. you don't need to shell around () since you anyway
will not use its value :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Creighton Hogg
So in my quest to create bindings to BlueZ in Haskell, I've hit a bit
of a snag:  sockets programming.

In C, you can use the standard sockets library and just pass around
addresses as arrays of 6 bytes instead of arrays of 4 bytes like you
normally would.  The problem I'm having is that in Network.Socket,
there's no such wiggle room and you have to either provide a Word32 or
four Word32's to represent the address.

Is there a way around this that I just haven't seen, or should I write
a patch to Network to add an extra constructor to SockAddr and code to
handle it?

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


[Haskell-cafe] ICFP09: Call for Workshop Proposals

2008-10-15 Thread Matthew Fluet (ICFP Publicity Chair)
 CALL FOR WORKSHOP PROPOSALS
 ICFP 2009
 14th ACM SIGPLAN International Conference on Functional Programming
 31st August - 2nd September, 2009
Edinburgh, Scotland
   http://www.icfpconference.org/icfp2009

The 14th ACM SIGPLAN International Conference on Functional
Programming will be held in Edinburgh, Scotland from 31st August to
2nd September 2009.  ICFP provides a forum for researchers and
developers to hear about the latest work on the design,
implementations, principles, and uses of functional programming.

Proposals are invited for workshops to be affiliated with ICFP 2009
and sponsored by SIGPLAN.  These workshops should be more informal and
focused than ICFP itself, include sessions that enable interaction
among the workshop attendees, and be fairly low cost.  The preference
is for one-day workshops, but other schedules can also be considered.
The workshops themselves will be held between August 30th and
September 5th, as capacity allows.

--

Submission details
 Deadline for submission: 19th November 2008
 Notification of acceptance:  17th December 2008

Prospective workshop organisers are invited to submit a completed
workshop proposal form in plain text format to the ICFP 2009 workshop
co-chairs (Chris Stone and Mike Sperber), via email to
icfp09-workshops at cs.hmc.edu by 19th November 2008. Please note
that this is a firm deadline. Organisers will be notified if their
proposal is accepted by 17th December 2008, and if successful are
required to produce a final report after the workshop has taken place
that is suitable for publication in SIGPLAN Notices.

The proposal form is available at:

http://www.icfpconference.org/icfp2009/workshops/icfp09-workshops-form.txt

Further information about SIGPLAN sponsorship is available at:

http://acm.org/sigplan/sigplan_workshop_proposal.htm

--

Selection committee

The workshop proposals will be evaluated by a committee comprising the
following members of the ICFP 2009 organising committee, together with
the members of the SIGPLAN executive committee.

 Chris Stone Harvey Mudd CollegeWorkshops co-chair
 Mike SperberDeinProgramm   Workshops co-chair
 Graham Hutton   University of Nottingham   General Chair
 Andrew Tolmach  Portland State University  Program Chair
--

Further information

Any queries regarding ICFP 2009 workshop proposals should be addressed
to the workshops co-chairs (Chris Stone and Mike Sperber), via email
to icfp09-workshops at cs.hmc.edu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Stuart Cook
On Thu, Oct 16, 2008 at 12:53 AM, Bulat Ziganshin
[EMAIL PROTECTED] wrote:
 data SomeStruct = SomeStruct

You can even go one step further and do

  data SomeStruct

which will prevent you from accidentally trying to the dummy
constructor. However, you'll need

  {-# LANGUAGE EmptyDataDecls #-}

or the equivalent compiler flag to make it work, since it's not
Haskell 98 syntax.


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


[Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Simon Michael

Does that help?


It helps me a lot. I never clearly understood that there are these two 
different layout modes in my code (coddled by haskell-mode!) This will 
cut down some more guesswork. Thanks!


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


[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread John Lato
I'd like to thank everyone who replied to my OP, and also perhaps
clarify one point.  I wasn't trying to be argumentative or negative
about any work people have done to make Haskell approachable for OO
programmers (or any other programmers, for that matter).  I simply
wanted to know what others thought about one item that was misleading
to me in particular, and to see if others either agreed with me or had
similar experiences.

That being said, I know that it's a great deal of work to put together
a useful tutorial, and I appreciate every one I read.  Especially the
monad tutorials, of which it took a half dozen before I got it.

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread David Leimbach
On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED] wrote:

 I'd like to thank everyone who replied to my OP, and also perhaps
 clarify one point.  I wasn't trying to be argumentative or negative
 about any work people have done to make Haskell approachable for OO
 programmers (or any other programmers, for that matter).  I simply
 wanted to know what others thought about one item that was misleading
 to me in particular, and to see if others either agreed with me or had
 similar experiences.

 That being said, I know that it's a great deal of work to put together
 a useful tutorial, and I appreciate every one I read.  Especially the
 monad tutorials, of which it took a half dozen before I got it.


I've read a lot of the Monad tutorials, and I feel like I only get most of
it to be 100% honest.  The State Monad still boggles my mind a little bit.
 I understand what it's supposed to do and I get the idea about how it
works.  It's just that when I look at the implementation of = for it, I
want to crawl into a corner and nibble my fingers.

Ok, it's not that bad, but I'll admit I've gone cross-eyed a few times
trying to keep all that state in my head about what's REALLY going on there.
 Perhaps if it were pulled apart step by step I'd have a better
understanding.

I even tried to implement it once, and failed, however, I never seem to fail
to be able to *use* it if someone already implements it for me :-).  Kind of
like how I know how to operate a car, but I wouldn't trust driving one that
I built :-)

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


Re: [Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Jules Bean

Simon Michael wrote:

Does that help?


It helps me a lot. I never clearly understood that there are these two 
different layout modes in my code (coddled by haskell-mode!) This will 
cut down some more guesswork. Thanks!


There is a new indentation module which does much better at the 
indentation stuff:


http://kuribas.hcoop.net/haskell-indentation.el

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Lennart Augustsson
The (=) operation for the state monad can be implemented with no
understanding at all.
Just watch djinn make the code for it.  And djinn doesn't understand
the state monad, I promise. :)

  -- Lennart


2008/10/15 David Leimbach [EMAIL PROTECTED]:

 On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED] wrote:

 I'd like to thank everyone who replied to my OP, and also perhaps
 clarify one point.  I wasn't trying to be argumentative or negative
 about any work people have done to make Haskell approachable for OO
 programmers (or any other programmers, for that matter).  I simply
 wanted to know what others thought about one item that was misleading
 to me in particular, and to see if others either agreed with me or had
 similar experiences.

 That being said, I know that it's a great deal of work to put together
 a useful tutorial, and I appreciate every one I read.  Especially the
 monad tutorials, of which it took a half dozen before I got it.

 I've read a lot of the Monad tutorials, and I feel like I only get most of
 it to be 100% honest.  The State Monad still boggles my mind a little bit.
  I understand what it's supposed to do and I get the idea about how it
 works.  It's just that when I look at the implementation of = for it, I
 want to crawl into a corner and nibble my fingers.
 Ok, it's not that bad, but I'll admit I've gone cross-eyed a few times
 trying to keep all that state in my head about what's REALLY going on there.
  Perhaps if it were pulled apart step by step I'd have a better
 understanding.
 I even tried to implement it once, and failed, however, I never seem to fail
 to be able to *use* it if someone already implements it for me :-).  Kind of
 like how I know how to operate a car, but I wouldn't trust driving one that
 I built :-)
 Dave
 ___
 Haskell-Cafe mailing list
 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


Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Bulat Ziganshin
Hello David,

Wednesday, October 15, 2008, 7:16:09 PM, you wrote:

 I've read a lot of the Monad tutorials, and I feel like I only get
 most of it to be 100% honest.  The State Monad still boggles my
 mind a little bit.  I understand what it's supposed to do and I get
 the idea about how it works.  It's just that when I look at the
 implementation of = for it, I want to crawl into a corner and nibble my 
 fingers.

may be i can help? :)  all those pure monads imho is rather
straightforward - monad just carries some value inside (such as state,
environment, or data logged) and =, operations bind actions while
carrying this value hiddenly. only get/set operations interact with
this value while for =, operations the only requirement is to pas
input value into first operation, then pass value at the exit of first
operation and pass it to second one and finally return value returned
by second operation. smth like this:

for state monad every action has its own (imparative) result of type a
plus receives some State and returns some State:

type StateAction a  =  State - (a,State)

() :: StateAction a - StateAction b - StateAction ()
-- this means that  is operation on two actions which joins them and
-- return composed action

action1  action2  =
  -- Result of joining two actions is action again
  -- i.e. it has type State - ((),State)
  -- so we define it as a function which receives initial state
  -- and carries it through both actions sequentially
  -- finally returning state returned from last action
  \state0 - let (_,state1) = action1 state0
 (_,state2) = action2 state1
 in ((),state2)

then when we apply (action1  action2) to some state this is
calculated as action1 calculation performed on this state and then
action2 calculation pewrformed on the state returned from action1

if you are are easy with high-order functions, partial application and
carrying you should have no problems mastering monads


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Mitchell, Neil
Hi
 
I didn't understand Monads until I read this:
http://www.haskell.org/haskellwiki/Monads_as_Containers
 
It took me quite a long time to get them too, but slowly over time it
will sink in.
 
Thanks
 
Neil




From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of David Leimbach
Sent: 15 October 2008 4:16 pm
To: John Lato
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Re: What I wish someone had told
me...



On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED]
wrote:


I'd like to thank everyone who replied to my OP, and
also perhaps
clarify one point.  I wasn't trying to be argumentative
or negative
about any work people have done to make Haskell
approachable for OO
programmers (or any other programmers, for that matter).
I simply
wanted to know what others thought about one item that
was misleading
to me in particular, and to see if others either agreed
with me or had
similar experiences.

That being said, I know that it's a great deal of work
to put together
a useful tutorial, and I appreciate every one I read.
Especially the
monad tutorials, of which it took a half dozen before I
got it.



I've read a lot of the Monad tutorials, and I feel like I only
get most of it to be 100% honest.  The State Monad still boggles my
mind a little bit.  I understand what it's supposed to do and I get the
idea about how it works.  It's just that when I look at the
implementation of = for it, I want to crawl into a corner and nibble
my fingers.

Ok, it's not that bad, but I'll admit I've gone cross-eyed a few
times trying to keep all that state in my head about what's REALLY going
on there.  Perhaps if it were pulled apart step by step I'd have a
better understanding.  

I even tried to implement it once, and failed, however, I never
seem to fail to be able to *use* it if someone already implements it for
me :-).  Kind of like how I know how to operate a car, but I wouldn't
trust driving one that I built :-)

Dave


==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Linking and unsafePerformIO

2008-10-15 Thread wren ng thornton

Mauricio wrote:


What I actually want to use that way are build
time configs. For instance, 'isThisLibraryThreadSafe'
or 'maximumNumberOfBigObjects'. Actually, I don't
know why people allow build time options at all.
We always use the best set of options, and the
alternatives are there just to compel us to check
for them :)

Maurício


Why not just have a Haskell module (that defines a number of CAFs) be 
your build-time config? Unless there's an important reason to be using 
the FFI, this seems like a much simpler approach. Xmonad and Yi use a 
similar technique even for load-time constant configurations.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I do not want to be a bitch, but ghc-6.8.3 and haskell binary policy are really horrible.

2008-10-15 Thread Jules Bean

John Van Enk wrote:
Could you, perhaps, outline a little more of what you're trying to do? 
I'm having a hard time seeing what exactly you're doing, and why you 
can't use the package provided by your distribution.


We'd love to help you, but you're not being very clear with what your 
problem is.


As far as I can see, his problem was

cabal update  cabal upgrade

which seems like a sensible command to run, but actually isn't.

Jules

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


Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Daniel Fischer
Am Mittwoch, 15. Oktober 2008 13:39 schrieb Ramaswamy, Vivek:
 Hello All~

 I have just started with Haskell, and I must confess; I am in love with
 it.
 However one area that I am really confused about is indentation.
 Lets take a look at if-else if- else block.

 The way I understand it:
 {--}
 if something
  then do
   something 1
   something2
 else if nothing
  then do
   something3
   something4
 else do
  different
 {---}
 The code above gives out an error.  I have been programming in python
 and the above appears fine.
 But it does not work.
 What works is:
 if something
  then do
   something1
   something2
   else if
then do
 something3
 something4
 else do
  different

 I find the above scheme extremely confusing. I tried going to:

Not for long, it'll become natural pretty fast.


 http://en.wikibooks.org/wiki/Programming:Haskell_indentation after
 reading I am even more confused.
 Can somebody please explain how the Haskell indentation works?

 The else-if and else seem to be aligning up with then. They should be
 aligning with If in my opinion.

The then ... and the else ... branches are both part of the if-expression, 
so they have to be indented further than the if. Aligning something with 
the if ends the expression, so if the else is aligned with the if, 
there's an incomplete if-expression and something which should be an 
expression but isn't because it begins with else. 

The Layout rule is explained in the report: http://haskell.org/onlinereport/
informally in section 2.7, formally in section 9.3, perhaps that helps.


 Thanks in advance.


 Regards
 -Vivek Ramaswamy-

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


Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Jules Bean

Ramaswamy, Vivek wrote:

Hello All~

I have just started with Haskell, and I must confess; I am in love with it.

However one area that I am really confused about is indentation.

Lets take a look at if-else if- else block.


Important point 1.

There are two contexts in haskell programs. Layout and non-layout.

In a non-layout context you can do whatever you like with indentation. 
You can put the newlines wherever you want.


In practice, almost everyone uses layout for the 'top-level' of a 
module. That means that anything flush to the left margin starts a new 
declaration. However, making sure we are not flush to the left margin, 
the following are all fine



x = if True then 1 else 2
x = if True
 then 1
 else 2
x =
 if True
 then 1
 else 2

x =
   if True
  then 1
 else 2

because, layout is not relevant in expressions.


Now, do blocks are layout blocks. So what you really want us to look 
at is the use of if/then/else in do blocks.


x =
 do
  if True
  then (return 1)
  else (return 2)

The first line in the do block defines the left margin for this block. 
In this example, the first line is the if line, that defines the left 
margin. Since the then and the else are also both on the left 
margin, they are new statements. So, the layout interprets as:


do {if True; then (return 1); else (return 2)}

...which is a parse error, because a statement cannot begin with 'then' 
or 'else'.


any pattern of indentation which keeps the if expression indented 
further to the right will be OK, such as


x =
 do
  if True
   then (return 1)
else (return 2)

x =
 do
  if True
then (return 1)
   else (return 2)

..are both fine.

Does that help?

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


Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread David Menendez
On Wed, Oct 15, 2008 at 6:05 AM,  [EMAIL PROTECTED] wrote:

 Regarding existentials, the web page
http://okmij.org/ftp/Computation/Existentials.html

 demonstrates how to systematically eliminate existentials. In fact,
 the object encoding via existentials can be easily transformed into
 the encoding that uses only simple, first-order types. The web page
 begs a question if there is ever any real need for existentials.

We might justify existential types on performance grounds. Stream
fusion, for example, uses existentials to replace recursive types and
functions with non-recursive types and functions, which are simpler to
optimize.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread George Pollard
Thanks to all that replied (Derek  Ryan for the major understanding,
Albert  Luke also)*. I guess I was getting confused with the error
message:

 (All instance types must be of the form (T a1 ... an)

I was interpreting this with Stringable/Enum as T and [Char]/Blah as
a1. 

Now I have clarity! I shall have to follow up Iavor's lead on why this
*is*.

Thanks!

*[Silly email reply system; discussions on the internet should form an
acyclic directed graph, not a tree! This, incidentally, is why I'm
replying to myself.]



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread John Lato
 Albet Lai wrote:
 John Lato wrote:
 Are you advocating introducing existential types to beginning
 Haskellers?  I think something with the scary name existential
 quantification would greatly increase the head'splodin' on the
 learnin' slope.

 OOP(*) advocates introducing existential types to beginning programmers.

Yes, because they're required to get almost anything done in OOP
languages.  In general they are not required in Haskell.  I got a bit
carried away with rhetorical flourish, but my point wasn't so much
that beginners couldn't understand something as that something with
such specialized usage isn't necessary for new Haskellers, and is
likely to encourage bad habits from OOP-converts.


 The broken analogy between OOP interfaces and Haskell/Isabell type
 classes is there because some people insist that all languages should be
 like mainstream languages. You have heard it, even from reputable
 leaders and pioneers: if you know one language, picking up others
 should be easy, they just differ in syntax.


I have heard it, and I used to believe it.  Now I think it's only true
provided the one language you know is suitably advanced (and currently
non-existent, I think).

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


[Haskell-cafe] Re: 2008-10-12 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Simon Marlow

wren ng thornton wrote:

Simon Marlow wrote:

Don Stewart wrote:
 * GHC.Prim was moved,

Nobody should be importing GHC.Prim, use GHC.Exts instead.



This is oft declared, but as things stand I don't think it's a tenable 
position. If someone's bothering to dig as far as GHC.Exts then it's 
very likely they're trying to optimize numeric computations and for that 
there are a number of functions in GHC.Prim which are essential, in 
particular the fast conversion functions for numeric types[1]. If those 
were moved to GHC.Exts then I think many people would be more inclined 
to heed the advice.


GHC.Exts re-exports the whole of GHC.Prim.  There's no reason to import 
GHC.Prim at all.  Admittedly this isn't immediately obvious from the 
documentation, but it is there.  Hopefully in the future we can improve 
Haddock so that it'll be able to paste in the whole of GHC.Prim into the 
GHC.Exts documentation, and we can then hide GHC.Prim.


Cheers,
Simon

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


Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread Lennart Augustsson
What do you mean by need?  From a theoretical or practical perspective?
We don't need them from a theoretical perspective, but in practice I'd
rather use existentials than encodinging them in some tricky way.

On Wed, Oct 15, 2008 at 11:05 AM,  [EMAIL PROTECTED] wrote:
 The web page
 begs a question if there is ever any real need for existentials.

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


Re: [Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Creighton Hogg
On Wed, Oct 15, 2008 at 12:26 PM, Bryan O'Sullivan [EMAIL PROTECTED] wrote:
 On Wed, Oct 15, 2008 at 6:54 AM, Creighton Hogg [EMAIL PROTECTED] wrote:

 Is there a way around this that I just haven't seen, or should I write
 a patch to Network to add an extra constructor to SockAddr and code to
 handle it?

 Linux and Windows support Bluetooth sockets, but they have different
 ideas of what the address family is called (AF_BTH vs AF_BLUETOOTH).
 Less popular platforms are all over the map: some (Solaris) have no
 support, others (NetBSD) don't use sockets for Bluetooth. I don't
 think that a patch to Network.Socket is the way to go for this, since
 it won't be portable enough. Perhaps a Network.Bluetooth package is in
 order to hide all the platform-specific gunk.

Ah, I've only ever used Bluetooth on Linux and didn't realize how
different it was between platforms.  I think you're right, then, and a
Network.Bluetooth would be a good idea.

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


[Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Ramaswamy, Vivek
Hello All~

I have just started with Haskell, and I must confess; I am in love with
it.
However one area that I am really confused about is indentation.
Lets take a look at if-else if- else block.

The way I understand it:
{--}
if something
 then do 
  something 1
  something2
else if nothing
 then do 
  something3
  something4
else do 
 different
{---}
The code above gives out an error.  I have been programming in python
and the above appears fine.
But it does not work.
What works is: 
if something
 then do
  something1
  something2
  else if
   then do
something3
something4
else do
 different

I find the above scheme extremely confusing. I tried going to: 

http://en.wikibooks.org/wiki/Programming:Haskell_indentation after
reading I am even more confused.
Can somebody please explain how the Haskell indentation works?

The else-if and else seem to be aligning up with then. They should be
aligning with If in my opinion.

Thanks in advance.


Regards
-Vivek Ramaswamy-




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


[Haskell-cafe] Re: Multi-line string literals are both easy /and/elegant in Haskell

2008-10-15 Thread Simon Marlow

Don Stewart wrote:

mjm2002:

On 10/13/08, Andrew Coppin wrote:

Cool. Is there any progress on getting GHC to *not* freak out when you
ask it to compile a CAF containing several hundred KB of string literal? :-}

Yes and no. There's dons' compiled-constants pkg which has a solution:

  http://code.haskell.org/~dons/code/compiled-constants/

And the code below would do all the haskell-side work for importing
the data from C, but I'm not aware of a way to have ghc not freak out
if it has to compile a huge amount of static data.


Hiding  it inside an unboxed string constant?
i.e.


this be bits#

Or does GHC still freak?


This is the trick I use in Haddock and Alex, it should work fine.  I don't 
know why GHC should have any problems with larger string literals anyway, 
since they get compiled into


x = unpackCString ...#

if you have evidence to the contrary, please submit a bug report.  (lists 
of other things are a different matter, which we already have open bugs for).


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


Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread wren ng thornton

John Lato wrote:

Are you advocating introducing existential types to beginning
Haskellers?  I think something with the scary name existential
quantification would greatly increase the head'splodin' on the
learnin' slope.  Certainly there's a place for them, but I wouldn't
want to see new Haskell programmers habitually approach problems with
a first create a type class, then make an existential wrapper
mentality.  Which is exactly what I fear is the current situation.

Although my list example is far to shallow to make this point, it
seems to me that it's fairly likely that somebody faced with this
problem has had something go severely wrong at some earlier time.

Existentials are certainly useful, but isn't it also possible that,
for many cases, an alternative design exists which fits a functional
idiom better and doesn't face this issue at all?

John



I think one of the reasons more people don't highlight the differences 
is that, with all due respect, the differences are often too subtle for 
OOP programmers. That is, few OOP programmers are taught to think about 
type theory as deeply as is necessary to see why they're so 
different[1]. On the one hand, few programmers of any ilk are taught to 
think deeply about type theory so that's unfair to OOP. But on the other 
hand OO propaganda is rife with claims that the class/inheritance model 
of types is The One True Way(tm). I'm not saying this to be rude; there 
are many OO programmers who do know quite a bit about type theory. 
However, tutorials for OOP are full of indoctrination about how OO type 
systems are better than C. In my experience that tends to create 
OO-programmers who don't question the class/inheritance model or think 
about what other approaches would look like. Discussions where an OO 
type system is not assumed typically lead to talking past one another, 
as here[2]. The idea of defining allomorphic functions which don't use 
dynamic dispatch and don't use inheritance is difficult to explain 
without a lot of groundwork to undo OO assumptions.


That said, I agree it's a pernicious meme which does disservice to 
everyone. Though I'm not sure showing people Oleg's handiwork is a 
gentler introduction either ;)



[1] Consider, for example, the question of whether the arguments/value 
of a function should be covariant or contravariant in subclasses. Java 
got this wrong for arrays. Their answer seems intuitively right, but 
this is one area where intuitions are suspect.


[2] 
http://www.reddit.com/r/programming/comments/6xerq/why_type_classes_are_interesting/c054u5u


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Anton Tayanovskyy
Thanks for the portable solution.

I'd also like to know how is the following different from
-XFlexibleInstances with [Char]? Stronger, weaker, same thing?

{-# OPTIONS -XTypeSynonymInstances #-}

class Stringable a where
toString :: a - String

instance Stringable String where
 toString = id


--A

On Wed, Oct 15, 2008 at 10:16 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 So, the Haskell98 solution to this is:

 class StringableList a where
 listToString :: [a] - String

 -- now [a] is of the proper form; T = [], a is a type variable
 instance StringableList a = Stringable [a] where
toString = listToString

 -- now to make an instance for Stringable [Char]
 -- we just make an instance for StringableList Char
 instance StringableList Char where
listToString = id

 I think FlexibleInstances just makes the compiler jump through these
 hoops instead of you.

  -- ryan

 On Wed, Oct 15, 2008 at 3:20 AM, George Pollard [EMAIL PROTECTED] wrote:

 I'm a little confused. Why is this allowed:

 data Blah = Blah

 instance Eq Blah where
 x == y = True

 But not this:

 class Stringable a where
 toString :: a - String

 instance Stringable [Char] where
 toString = id

 (Resulting in:)

 Illegal instance declaration for `Stringable [Char]'
 (All instance types must be of the form (T a1 ... an)
  where a1 ... an are distinct type *variables*
  Use -XFlexibleInstances if you want to disable this.)
 In the instance declaration for `Stringable [Char]'

 'Blah' isn't a type variable, is it? Is my brain just not working right
 today?

 ___
 Haskell-Cafe mailing list
 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

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


Re: [Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Bryan O'Sullivan
On Wed, Oct 15, 2008 at 6:54 AM, Creighton Hogg [EMAIL PROTECTED] wrote:

 Is there a way around this that I just haven't seen, or should I write
 a patch to Network to add an extra constructor to SockAddr and code to
 handle it?

Linux and Windows support Bluetooth sockets, but they have different
ideas of what the address family is called (AF_BTH vs AF_BLUETOOTH).
Less popular platforms are all over the map: some (Solaris) have no
support, others (NetBSD) don't use sockets for Bluetooth. I don't
think that a patch to Network.Socket is the way to go for this, since
it won't be portable enough. Perhaps a Network.Bluetooth package is in
order to hide all the platform-specific gunk.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Yitzchak Gale
Derek Elkins wrote:
 In general, to encode OO...
 turns out all you needed was recursive bounded
 existential quantification.

Do you have a reference for that?

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


[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
 The instance selection for an interface is done at run-time and this is
 inherently necessary.  The instance (in a different sense) selection for
 type classes is almost always resolvable statically.  In Haskell 98

In both cases, the dispatch is inherently dynamic, and in both cases,
most dispatches can be resolved at compile-time with sufficient effort.
The actual percentage may be quite different, tho.
Implementation techniques are also fairly different, and the resulting
coding style is also very different, but the two concepts are
fundamentally very close to each other.


Stefan

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


[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
 leaders and pioneers: if you know one language, picking up others
 should be easy, they just differ in syntax.
 I have heard it, and I used to believe it.  Now I think it's only true
 provided the one language you know is suitably advanced (and currently
 non-existent, I think).

It all depends on what you consider as knowing a language.
After all, a Real Programmer can write Fortran in any programming language,


Stefan

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash

 The equivalent won't compile in Haskell, because the actual return
 type does matter, and *is determined by the calling code*.  Our
 fictional GetListOfData can't return a List or a Mylist depending on
 some conditional, in fact it can't explicitly return either one at
 all, because the actual type of the result, as determined by the
 caller, could be either one, or something else entirely (ignoring the
 IO bit for the time being).



I have had an  unresolved issue on my stack of Haskell vs Java that I wonder
if your observation explains.

If you notice  java generics has all sort of gotchas (e.g.
http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I somehow
don't see this discussion in Haskell.   I wonder if haskell's model of
letting the caller determine the result type has advantage in that you don't
have all the complexity you would have if you let the API determine their
types.

daryoush

On Wed, Oct 15, 2008 at 11:45 AM, Stefan Monnier
[EMAIL PROTECTED]wrote:

  The instance selection for an interface is done at run-time and this is
  inherently necessary.  The instance (in a different sense) selection for
  type classes is almost always resolvable statically.  In Haskell 98

 In both cases, the dispatch is inherently dynamic, and in both cases,
 most dispatches can be resolved at compile-time with sufficient effort.
 The actual percentage may be quite different, tho.
 Implementation techniques are also fairly different, and the resulting
 coding style is also very different, but the two concepts are
 fundamentally very close to each other.


Stefan

 ___
 Haskell-Cafe mailing list
 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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 11:56 -0700, Daryoush Mehrtash wrote:
 The equivalent won't compile in Haskell, because the actual
 return
 type does matter, and *is determined by the calling code*.
  Our
 fictional GetListOfData can't return a List or a Mylist
 depending on
 some conditional, in fact it can't explicitly return either
 one at
 all, because the actual type of the result, as determined by
 the
 caller, could be either one, or something else entirely
 (ignoring the
 IO bit for the time being).
 
 
 I have had an  unresolved issue on my stack of Haskell vs Java that I
 wonder if your observation explains.
 
 If you notice  java generics has all sort of gotchas (e.g.
 http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I
 somehow don't see this discussion in Haskell.   I wonder if haskell's
 model of letting the caller determine the result type has advantage in
 that you don't have all the complexity you would have if you let the
 API determine their types.

These look more like unfortunate interactions between generics and the
pre-existing Java language than anything else.  Covariance isn't really
an issue in Haskell, since Haskell lacks sub-typing; the various
unfortunate consequences of type erasure in Java are avoided by the fact
that Haskell types lack constructors, so the user never expects to be
able to conjure up a value of an unknown type.

jcc



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


[Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin
I like Parsec. I use it for everything. But it does have one irritating 
problem.


Consider the following parser:

 expressions = many1 expression

Suppose this is the top-level parser for my language. Now suppose the 
user supplies an expression with a syntax error half way through it. 
What I *want* to happen is for an error to be raised. What *actually* 
happens is that Parsec just ignores all input after that point. So if 
+ is not a valid token, but the user writes


 x = 1; y = 2; z = 3 + z; w = 4;

then what my program receives back is x = 1; y = 2; z = 3, as if 
everything parsed successfully. But actually it has ignored half the 
input! o_O


Does anybody know how to fix this irratiting quirk? I can see why it 
happens, but not how to fix it.


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


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote:

 Suppose this is the top-level parser for my language.

snip

 Does anybody know how to fix this irratiting quirk? I can see why it happens,
 but not how to fix it.
 

One of:

expressions = many1 (try expression | myFail)
  where myFail = {- eat your way to the next expression -}

or do a prepass splitting your input up into expressions and feed the 
individual expressions into Parsec.

Parsec's not designed to do error recovery as such, so it's something you 
need to work out how to handle if you need it.

-- 
[EMAIL PROTECTED]

'In Ankh-Morpork even the shit have a street to itself...
 Truly this is a land of opportunity.' - Detritus, Men at Arms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 20:22 +0100, Andrew Coppin wrote:
 I like Parsec. I use it for everything. But it does have one irritating 
 problem.
 
 Consider the following parser:
 
   expressions = many1 expression
 
 Suppose this is the top-level parser for my language.

I always wrap my top-level parsers in

  return const `ap` parser `ap` eof

to express that they have to match the entire input.  (This is a bit
easier if you supply the missing Applicative instance:

  const $ parser * eof

).  I think Parsec should either do this itself or tell you what the
un-consumed input tokens were, but it doesn't.

jcc


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


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote:

 Suppose this is the top-level parser for my language. Now suppose the user
 supplies an expression with a syntax error half way through it. What I *want*
 to happen is for an error to be raised. What *actually* happens is that Parsec
 just ignores all input after that point. So if + is not a valid token, but
 the user writes
 
  x = 1; y = 2; z = 3 + z; w = 4;
 
 then what my program receives back is x = 1; y = 2; z = 3

That'll teach me not to scan-read when I'm tired!

expressions = do es - many1 expression
 eof
 return es

-- 
[EMAIL PROTECTED]

Society does not owe people jobs.
Society owes it to itself to find people jobs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread brian
On Wed, Oct 15, 2008 at 2:22 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:
 So if + is not a valid token, but the user writes
  x = 1; y = 2; z = 3 + z; w = 4;
 then what my program receives back is x = 1; y = 2; z = 3

You said you expect one or more 'expression'. It looks as if your
expression can optionally be terminated by semicolon? Can you demand
semicolons at the ends of your expressions? Then, z = 3 would not
constitute a complete expression and an error would be raised.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin

Philippa Cowderoy wrote:

expressions = do es - many1 expression
 eof
 return es
  


Ah - so eof fails if it isn't the end of the input?

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


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote:

 Philippa Cowderoy wrote:
  expressions = do es - many1 expression
   eof
   return es

 
 Ah - so eof fails if it isn't the end of the input?
 

eof = notFollowedBy anyChar

(assuming I've got the identifiers right, that's the actual definition 
too)

-- 
[EMAIL PROTECTED]

Society does not owe people jobs.
Society owes it to itself to find people jobs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin

Philippa Cowderoy wrote:

On Wed, 15 Oct 2008, Andrew Coppin wrote:

  

Philippa Cowderoy wrote:


expressions = do es - many1 expression
 eof
 return es
  
  

Ah - so eof fails if it isn't the end of the input?




eof = notFollowedBy anyChar

(assuming I've got the identifiers right, that's the actual definition 
too)
  


OK, well that'll make it fail alright. Now I just gotta figure out how 
to get a sane error message out of it! ;-)


(The example I showed is very simple; real parsers generally aren't.)

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash
Would you please explain this a bit more:

the various
unfortunate consequences of type erasure in Java are avoided by the fact
that Haskell types lack constructors, so the user never expects to be
able to conjure up a value of an unknown type.

Thanks,

daryoush


On Wed, Oct 15, 2008 at 12:04 PM, Jonathan Cast
[EMAIL PROTECTED]wrote:

 On Wed, 2008-10-15 at 11:56 -0700, Daryoush Mehrtash wrote:
  The equivalent won't compile in Haskell, because the actual
  return
  type does matter, and *is determined by the calling code*.
   Our
  fictional GetListOfData can't return a List or a Mylist
  depending on
  some conditional, in fact it can't explicitly return either
  one at
  all, because the actual type of the result, as determined by
  the
  caller, could be either one, or something else entirely
  (ignoring the
  IO bit for the time being).
 
 
  I have had an  unresolved issue on my stack of Haskell vs Java that I
  wonder if your observation explains.
 
  If you notice  java generics has all sort of gotchas (e.g.
  http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I
  somehow don't see this discussion in Haskell.   I wonder if haskell's
  model of letting the caller determine the result type has advantage in
  that you don't have all the complexity you would have if you let the
  API determine their types.

 These look more like unfortunate interactions between generics and the
 pre-existing Java language than anything else.  Covariance isn't really
 an issue in Haskell, since Haskell lacks sub-typing; the various
 unfortunate consequences of type erasure in Java are avoided by the fact
 that Haskell types lack constructors, so the user never expects to be
 able to conjure up a value of an unknown type.

 jcc




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


Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Bulat Ziganshin
Hello Daryoush,

Wednesday, October 15, 2008, 10:56:39 PM, you wrote:

 If you notice  java generics has all sort of gotchas (e.g.
 http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I

large prob;em of OOP languages with generics is interaction between
those two types of polymorhism. covariant/contravariant typing is one
example. since Haskell lacks OOP classes, it doesn't have such
pronblem at all. overall, speaking, pure languages (pure OOP, pure FP,
pure LP) is much simpler than ones trying to combine OOP, FP and
everything else together. There Is Only One Way To Do It In Haskell ;)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Cairo and dialog oddities on Windows using glade.

2008-10-15 Thread Jefferson Heard
Maybe I'm doing something wrong.  I've created several dialog boxes in
Glade, and I'm calling Gtk.runDialog on them when a user clicks the
mouse in my main window.  On Linux, they work mostly right, but the
insertion point never shows in the Gtk.Entry areas and the dialog
itself comes up without any decoration.  In Windows, I cannot edit the
Entry areas at all.  I can click on the action buttons I added with
Gtk.Dialog.addButton.

Also, I'm getting an (Invalid matrix (matrix not invertible)) error
from Cairo in WIndows that I'm not getting in Linux, and all I can
think is that occasionally a rectangle width could be negative.  Would
that cause the error?


-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash
I am having hard time understanding this statement:

Haskell types lack constructors, so the user never expects to be
 able to conjure up a value of an unknown type.


I am not sure how say in a Java language a constructor can conjure up a
value of an unknown type.

daryoush

On Wed, Oct 15, 2008 at 12:55 PM, Bulat Ziganshin [EMAIL PROTECTED]
 wrote:

 Hello Daryoush,

 Wednesday, October 15, 2008, 10:56:39 PM, you wrote:

  If you notice  java generics has all sort of gotchas (e.g.
  http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I

 large prob;em of OOP languages with generics is interaction between
 those two types of polymorhism. covariant/contravariant typing is one
 example. since Haskell lacks OOP classes, it doesn't have such
 pronblem at all. overall, speaking, pure languages (pure OOP, pure FP,
 pure LP) is much simpler than ones trying to combine OOP, FP and
 everything else together. There Is Only One Way To Do It In Haskell ;)


 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]


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


[Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Simon Michael

I'm trying that one now. Thanks for the tip!

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


[Haskell-cafe] Cabal package with library and tests

2008-10-15 Thread Mauricio

Hi,

I'm writing a Cabal package, using main=defaultMain
in Setup.hs. It has a library, and I want to also
build a few executables so I can test the library.
How am I supposed to do that? My attempt was to
create 'executable' sections for those tests. However,
I don't know how to include the main library in the
modules used by those tests. I tried to insert my
own package in a 'build-depends' line, but that
didn't work.

Thanks for your tips,
Maurício

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


Re: [Haskell-cafe] Very silly

2008-10-15 Thread Tommy M. McGuire

Jason Dagit wrote:
On Mon, Oct 13, 2008 at 8:32 PM, Tommy M. McGuire [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:

Java (and presumably C#) generics are very much like a weakened
version of normal parametric polymorphism.

I'm curious, in what way are they weakened?


That's a good question. :-)

I picked up the idea while reading Java Generics and Collections, but I 
can no longer find the part that *gave* me the impression.  I suspect 
that it is due to the type erasure vs. array runtime typing issues.


It may be the case that basic generics are identical to plain parametric 
polymorphism, and that the wildcard expressions attempt to serve the 
same purpose (with considerable divergence) as type classes and 
existential types.  But I don't know since my brains have apparently 
turned to oatmeal.


--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal package with library and tests

2008-10-15 Thread Sean Leather
 I'm writing a Cabal package, using main=defaultMain
 in Setup.hs. It has a library, and I want to also
 build a few executables so I can test the library.
 How am I supposed to do that? My attempt was to
 create 'executable' sections for those tests. However,
 I don't know how to include the main library in the
 modules used by those tests. I tried to insert my
 own package in a 'build-depends' line, but that
 didn't work.


You might consider looking at the EMGM cabal file in the source.

  https://svn.cs.uu.nl:12443/viewvc/dgp-haskell/EMGM/

There are some things in there that support building a 'test' executable for
the library. Specifically, the flag -ftest builds the executable and
enables its build-depends. Since the 'test' flag is false by default, those
build-depends are not passed onto users who download EMGM from Hackage.

Note that the way it's done, Cabal will build the library and the executable
separately. From what I understand, there's no easy way to have an
executable depend on a library in the same Cabal config file. So, you're
actually building the library twice. We have a -fnolib flag for disabling
the library build to speed things up. To get this, you'd use -ftest
-fnolib.

If you want to support the 'test' argument to Cabal (e.g. runhaskell
Setup.lhs test or cabal test using cabal-install), you can find that code
in the Setup.lhs file from the source link above.

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


Re: [Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-15 Thread Henning Thielemann
Ryan Ingram schrieb:
 On Mon, Oct 13, 2008 at 2:04 AM, J. Garrett Morris
 [EMAIL PROTECTED] wrote:
 Indeed - MTL seems to have been rewritten at some point in the past to
 prefer exhaustive enumeration to overlap.
 
 Indeed, and I actually think this is a weakness of the current
 implementation.  Anyone who comes up with a new transformer that
 provides different functionality than what is there needs to
 explicitly provide all the relevant instances, instead of letting
 MonadTrans do its thing.

 I long thought that it is unnecessary use of type system extensions to
require multi-parameter type classes for simple monads and its
transformer versions. I thought it would be enough to have atomar monads
like ST, IO and Identity, and monads like State, Reader, Writer,
Continuation can be offered exclusively in the transforming variant.
(State s a) would have to be defined as (StateT s Identity a) instead.
This way MonadState, MonadReader and the other classes become
unnecessary. However, 'lift' remains important with this design.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Karl Mazurak

Yitzchak Gale wrote:

Derek Elkins wrote:

In general, to encode OO...
turns out all you needed was recursive bounded
existential quantification.


Do you have a reference for that?


I'm not sure if this is precisely what Derek had in mind, but Bruce, 
Cardelli, and Pierce did a comparison of various object encodings:


http://www.cis.upenn.edu/~bcpierce/papers/compobj.ps

It's been a while since I read that paper, but skipping to the end tells 
me that the approach with recursive types and bounded existentials was 
the only one to support method override, although it was less attractive 
on other fronts.


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


Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Dan Weston

I suspect that more has been done since 1997. Isn't that pre-Oleg?

Karl Mazurak wrote:

Yitzchak Gale wrote:

Derek Elkins wrote:

In general, to encode OO...
turns out all you needed was recursive bounded
existential quantification.


Do you have a reference for that?


I'm not sure if this is precisely what Derek had in mind, but Bruce, 
Cardelli, and Pierce did a comparison of various object encodings:


http://www.cis.upenn.edu/~bcpierce/papers/compobj.ps

It's been a while since I read that paper, but skipping to the end tells 
me that the approach with recursive types and bounded existentials was 
the only one to support method override, although it was less attractive 
on other fronts.





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


Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Henning Thielemann
George Pollard schrieb:
 I'm a little confused. Why is this allowed:
 
 data Blah = Blah

 instance Eq Blah where
 x == y = True
 
 But not this:
 
 class Stringable a where
 toString :: a - String

 instance Stringable [Char] where
 toString = id
 
 (Resulting in:)
 
 Illegal instance declaration for `Stringable [Char]'
 (All instance types must be of the form (T a1 ... an)
  where a1 ... an are distinct type *variables*
  Use -XFlexibleInstances if you want to disable this.)
 In the instance declaration for `Stringable [Char]'
 
 'Blah' isn't a type variable, is it? Is my brain just not working right
 today?

http://www.haskell.org/haskellwiki/List_instance

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


Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Evan Laforge
Here's what I have in one file:

-- | Parse the text of an event with the given parser @[EMAIL PROTECTED]
parse :: (Monad m) = P.CharParser () a - String - Derive.DeriveT m a
parse p text = do
(val, rest) - case P.parse (p_rest p)  text of
Left err - Derive.throw $
parse error on char  ++ show (P.sourceColumn (P.errorPos err))
++  of  ++ show text ++ :  ++ Seq.replace \n ; 
(show_error_msgs (Parsec.Error.errorMessages err))
Right val - return val
unless (null rest) $
Derive.warn $ trailing junk:  ++ show rest
return val

-- Contrary to its documentation, showErrorMessages takes a set of strings
-- for translation, which makes it hard to use.
show_error_msgs = Parsec.Error.showErrorMessages
or unknown parse error expecting unexpected end of input

p_rest :: P.GenParser tok st t - P.GenParser tok st (t, [tok])
p_rest p = do
val - p
rest - P.getInput
return (val, rest)



And this reminds me of something I was going to ask about: it would be
nice to fix either the documentation for showErrorMessages or the
implementation.  Preferably the implementation, because I can't see
the current implementation actually being useful for translation...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Repair to floating point enumerations?

2008-10-15 Thread Henning Thielemann
David Roundy schrieb:

 Why not look for a heuristic that gets the common cases right, rather
 than going with an elegant wrong solution? After all, these
 enumerations are most often used by people who neither care nor know
 how they're implemented, but who most likely would prefer if haskell
 worked as well as matlab, python, etc.

 Although MatLab has a lot of bad heuristics, they fortunately didn't
try to be too clever with respect to rounding errors. Floating point
enumerations have the same problems in MatLab as in all other languages.

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


Re: [Haskell-cafe] 2008-10-13 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Henning Thielemann
Don Stewart schrieb:

 numeric-prelude-0.0.4
 Easy:   Lanuage pragma

My question was still not answered: I used the non-existing pragma
LANGUAGE_HOW_CAN_WE_ENABLE - I hoped it would be ignored, but it was
parsed and made GHC fail. Why? Bug or feature?


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


Re: [Haskell-cafe] List as input

2008-10-15 Thread Toby Hutton
On Wed, Oct 15, 2008 at 5:44 PM, leledumbo [EMAIL PROTECTED] wrote:

 module Main where

 import Data.List

 -- quicksort of any list
 qsort [] = []
 qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs)

 -- optimized quicksort, uses middle element as pivot
 qsortOpt [] = []
 qsortOpt x  = qsortOpt less ++ [pivot] ++ qsortOpt greater
  where
pivot = x !! ((length x) `div` 2)
less = filter (pivot) (delete pivot x)
greater = filter (=pivot) (delete pivot x)

 main = do
  putStr Enter a list: 
  l - readLn
  print (qsortOpt l)
 -- end of code

I'm curious as to why taking the pivot from the middle is an
'optimized' version.  For this to be true you must be making some
assumptions about the contents of the list.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List as input

2008-10-15 Thread Dan Weston

Google median order statistic.

E.g. this is an interesting (and colorful) discussion:

http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/6-046JFall-2005/60D030CD-081D-4192-9FB5-C220116E280D/0/lec6.pdf

Toby Hutton wrote:

On Wed, Oct 15, 2008 at 5:44 PM, leledumbo [EMAIL PROTECTED] wrote:

module Main where

import Data.List

-- quicksort of any list
qsort [] = []
qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs)

-- optimized quicksort, uses middle element as pivot
qsortOpt [] = []
qsortOpt x  = qsortOpt less ++ [pivot] ++ qsortOpt greater
 where
   pivot = x !! ((length x) `div` 2)
   less = filter (pivot) (delete pivot x)
   greater = filter (=pivot) (delete pivot x)

main = do
 putStr Enter a list: 
 l - readLn
 print (qsortOpt l)
-- end of code


I'm curious as to why taking the pivot from the middle is an
'optimized' version.  For this to be true you must be making some
assumptions about the contents of the list.
___
Haskell-Cafe mailing list
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


Re: [Haskell-cafe] Re: Repair to floating point enumerations?

2008-10-15 Thread David Roundy
On Wed, Oct 15, 2008 at 11:25:57PM +0200, Henning Thielemann wrote:
 David Roundy schrieb:
 
  Why not look for a heuristic that gets the common cases right, rather
  than going with an elegant wrong solution? After all, these
  enumerations are most often used by people who neither care nor know
  how they're implemented, but who most likely would prefer if haskell
  worked as well as matlab, python, etc.
 
  Although MatLab has a lot of bad heuristics, they fortunately didn't
 try to be too clever with respect to rounding errors. Floating point
 enumerations have the same problems in MatLab as in all other languages.

I presume you say this because you haven't tried qusing matlab?  I
don't know what their algorithm is, but matlab gives:

 sprintf('%.20f\n', (0:0.1:0.3), 0.1*3, 0.1+0.1+0.1, 0.3)

ans =

0.
0.1555
0.19998335
0.29998890
0.30004441
0.30004441
0.29998890

from which you can clearly see that matlab does have special handling
for its [0,0.1..0.3] syntax.  For what it's worth, octave has the same
behavior:

octave:1 sprintf('%.20f\n', (0:0.1:0.3), 0.1*3, 0.1+0.1+0.1, 0.3)
ans = 0.
0.1555
0.20001110
0.29998890
0.30004441
0.30004441
0.29998890

I don't know what they're doing, but obviously they're doing something
clever to make this common case work.  They presumably use different
algorithms, since octave gives a different answer for the 0.2 than
matlab does.  Matlab's value here is actually less that 0.1 and it's
also less than 2*0.1, which is a bit odd.  Both agree that the final
element in the sequence is 0.3.

The point being that other languages *do* put care into how they
define their sequences, and I see no reason why Haskell should be
sloppier.

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


Re: [Haskell-cafe] 2008-10-13 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Don Stewart
schlepptop:
 Don Stewart schrieb:
 
  numeric-prelude-0.0.4
  Easy:   Lanuage pragma
 
 My question was still not answered: I used the non-existing pragma
 LANGUAGE_HOW_CAN_WE_ENABLE - I hoped it would be ignored, but it was
 parsed and made GHC fail. Why? Bug or feature?
 
 

Feature. {-# #-}  language-y pragmas are parsed now.

Check with GHC HQ for details.

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread wren ng thornton

Daryoush Mehrtash wrote:

I have had an  unresolved issue on my stack of Haskell vs Java that I wonder
if your observation explains.

If you notice  java generics has all sort of gotchas (e.g.
http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I somehow
don't see this discussion in Haskell.   I wonder if haskell's model of
letting the caller determine the result type has advantage in that you don't
have all the complexity you would have if you let the API determine their
types.



That gotcha about generics, is really a gotcha about arrays. If you 
replace List with [] in their example it'll compile just fine, though 
it can never work. The runtime happens to catch this particular error as 
an ArrayStoreException, but there are more convoluted examples that let 
you break the type system in all sorts of disturbing ways. As I said 
before, co-/contravariance is a Hard Concept(tm) where intuitions lie.



I think the big difference is that Haskell (similar to some non-Java OO 
languages) separates the notion of a value from the notion of associated 
functions. In Haskell we expect that the result of a function, say, is a 
value with an actual type-- the actual type needed by the caller in 
fact, perhaps constructed by a type-class dictionary passed down by the 
caller. Whereas in Java the result of a function is some stateful bundle 
of functions-- and whatever the type is, the callee returns the 
functions that can be used on it. This is highlighted in Haskell by type 
signatures like |Foo a = a|, sure the type of our result may have a 
bundle of associated functions, but we know that the result is really a 
value of type |a|, polymorphically if need be.


For simple object-like types that may not seem so different, but for 
container types the difference becomes readily apparent. In Java an 
interface needs to cement the collection and so you often see interfaces 
with different versions of the same function only offering/accepting 
different collections. There are some abstract classes or interfaces 
that try to expand on this to make things more polymorphic, but this 
perspective still can't escape certain problems...


For example, the fragile base class problem. One of my gripes about Java 
is that for some unfathomable reason, Iterators are not Iterable. More 
particularly, for iterators from library collections, I often cannot 
make them so[1]. In Haskell, since associated functions like iterator() 
are not part of the value but instead exist ethereally, we'd be free to 
give an instance for all Iterators making them Iterable.


This is the sort of problem that Pythonistas and Rubyists work around 
with monkey patching. Another example is, say we have an object that 
constructs a priority queue internally, and ultimately hands it off to 
the caller; this class doesn't actually care about the pqueue itself, 
though it doesn't treat it as a black box either. If someone comes up 
with a more efficient implementation of pqueues they can't just require 
it (via polymorphism) from that class, instead they need to go in and 
change the class that doesn't care[2].


In a sense, Haskell embraces the dread spectre of multiple inheritance. 
There are inheritance trees of type-class instances, but the association 
of these functions to datatypes is flat, and datatypes can always opt 
into additional type-classes. The diamond problem of C++ multiple 
inheritance goes away since values never inherit additional fields, 
however we do still have diamond problems of our own which 
OverlappingInstances and IncoherentInstances try to work around.


Type-classes do specify types in the API, they can even specify types in 
ways that Java interfaces cannot (e.g. |a - a - b| [3]). But the way 
they specify types, functional polymorphism vs inheritance, are 
radically different.




[1] Cf. Vector which uses an anonymous local class. In order to have 
Vectors that do return iterable iterators, we need to subclass Vector 
and override iterator() with an almost identical declaration that adds a 
method: public IteratorE iterator() { return this; }


[2] Potentially by subclassing, assuming the class doesn't have too many 
interdependencies. Or by using some defunctionalization pattern to mimic 
caller-directed polymorphism, especially if we want to reuse the same 
factory for multiple callers for whom different pqueues are more efficient.


[3] Java has only one top type: Object, and so it can't ensure this 
constraint. In some cases generics can be bent to fill this gap, but in 
others it's much harder, e.g. |class Foo a where foo :: Int - a|. 
OO-Languages like SmallTalk can better capture some of these because 
they treat classes as objects too, but there are still differences.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Kalashnikov

I'm supposed to write a function isPrime that checks whether or not a given
integer is a prime number or not. The function has to use recursion. The
only advice I was given, was to use a helper function.

I still have no clue how to do it :confused:

I'm new to Haskell by the way..please help..
-- 
View this message in context: 
http://www.nabble.com/Writing-a-function-isPrime-using-recursion.-tp20003309p20003309.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] List as input

2008-10-15 Thread Toby Hutton
On Thu, Oct 16, 2008 at 9:01 AM, Dan Weston [EMAIL PROTECTED] wrote:
 Google median order statistic.

 E.g. this is an interesting (and colorful) discussion:

 http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/6-046JFall-2005/60D030CD-081D-4192-9FB5-C220116E280D/0/lec6.pdf

Hrmm, maths and statistics definitely aren't a strong area for me, but
doesn't that PDF say on the second page that choosing i = 0 or i = n
or i = median is equally naive?  The rest of the document describes
other interesting methods for getting the pivot.

I couldn't follow the Wikipedia page on order statistics though.
Still, with no assumptions as to the contents of a list whatsoever,
when choosing 1 element to be the pivot, intuitively it makes no
difference which one you choose.  (Then again, I find statistical
analysis rarely is intuitive.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Bulat Ziganshin
Hello Kalashnikov,

Thursday, October 16, 2008, 2:41:05 AM, you wrote:

 I'm supposed to write a function isPrime that checks whether or not a given
 integer is a prime number or not. The function has to use recursion. The
 only advice I was given, was to use a helper function.

seems that russian institutes also started to teach haskell :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread wren ng thornton

Henning Thielemann wrote:

 I long thought that it is unnecessary use of type system extensions to
require multi-parameter type classes for simple monads and its
transformer versions. I thought it would be enough to have atomar monads
like ST, IO and Identity, and monads like State, Reader, Writer,
Continuation can be offered exclusively in the transforming variant.
(State s a) would have to be defined as (StateT s Identity a) instead.
This way MonadState, MonadReader and the other classes become
unnecessary. However, 'lift' remains important with this design.


Doing it that way removes the polymorphism that MonadState, MonadReader, 
etc offer to clients. For example, the backwards-state monad[1] is a 
MonadState but not a StateT (without extra plumbing). There are other 
examples which don't even change the semantics. It seems a shame to 
force these implementations to give different names for the same 
functions. Are MPTCs onerous? They'll be in haskell-prime afterall. Of 
course, the fundeps are another matter entirely...


[1] 
http://luqui.org/blog/archives/2008/08/10/mindfuck-the-reverse-state-monad/


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 13:01 -0700, Daryoush Mehrtash wrote:
 I am having hard time understanding this statement:
 
 Haskell types lack constructors, so the user never expects to
 be
 able to conjure up a value of an unknown type.
 
 I am not sure how say in a Java language a constructor can conjure up
 a value of an unknown type.

Well, that's the point.  It can't, in Haskell or in Java.  If you
understand that --- that you can't call the default constructor of a
class that is not statically known at compile time --- then there's no
`gotcha', in Haskell or Java.  The gotcha in Java is that every type
that actually exists does in fact have a default constructor, and every
type of the form SetT actually has a copy constructor, and so on.  But
if T isn't statically known at compile time, you can't call it, even
though it's guaranteed to exist.  In Java, even if I know nothing else
about a class T, I know that SetT has a copy constructor.  So I can
get into the habit of calling the SetT copy constructor, without
paying attention to whether T is statically known or not --- which
breaks when T is a generic parameter.

So Haskell lacks the `gotcha' because you never get into the bad habit
of assuming every type has a constructor in the first place.

jcc



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


Re: [Haskell-cafe] Monadic Floating Point [was: Linking and unsafePerformIO]

2008-10-15 Thread Ariel J. Birnbaum
On Wednesday 15 October 2008 05:21:04 John Dorsey wrote:
 Should all floating point numerals be in the IO Monad?

I'm deviating from the thread's topic, but I tend to agree with this one. 
Maybe not IO directly, but some kind of STM-style monad, at least (that is, 
FP operations are composable but ultimately they must be evaluated in IO).

Floating point operations, at least by IEEE754, depend on environmental 
settings like the current rounding mode. They may modify state, like the 
sticky bits that indicate an exception occurred. They may jump nonlocally if  
a trap handler has been enabled.

None of these help in making an expression like 
  (a + b) + c == a + (b + c) :: Bool
any more referentially transparent than
  getChar : getChar : [] :: [Char]
would be if it was legal.

Anyway, enough rant for tonight. Sorry for the hijack.
We now resume our regular transmissions.
-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Rewrite rules

2008-10-15 Thread George Pollard
Section 8.13.2 of the GHC manual[1] states:

 GHC keeps trying to apply the rules as it optimises the program. For
 example, consider:
 
 let s = map f
   t = map g
   in
   s (t xs)
 
 The expression s (t xs) does not match the rule map/map, but GHC
 will substitute for s and t, giving an expression which does match. If
 s or t was (a) used more than once, and (b) large or a redex, then it
 would not be substituted, and the rule would not fire.
 
The part I'm interested in here is (a); if an expression is used more
than one then it cannot be substituted for. Is there any way to work
around this or force it?

The reason I ask is that as a bit of fun (and inspired by Joachim
Breitner's blog post [2]) I was going to try writing a rewrite rule for
the first time. What I had in mind was this:

{-# RULES
 index cycled list forall list n. cycle list !! n =
list !! (n `mod` length list)
 #-}

However, in the case he has written about this won't fire, since the LHS
cannot be substituted as `cycle list` is used more than once:

 let rlist = cycle list
 print ( rlist !! (10^9), rlist !! 0 )

I can get it to fire again if I write it like this:

 {-# RULES
  !!/cycle forall list. (!!) (cycle list)  = (\n - list !! (n `mod` length 
 list))
  #-}

 ...
 
 let rlist = (!!) (cycle list)
 print (rlist (10^9), rlist 0)

But this is non-obvious and I'd rather have it fire in the first case
(i.e. when used naïvely). So, back to my question; is there a workaround
or force for this... or does it break too many things if done?

[1]
http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.html#id414792

[2]
http://www.joachim-breitner.de/blog/archives/308-guid.html


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Simon Michael
I'm pleased to announce the first release of hledger, a command-line 
accounting tool similar to John Wiegley's c++ ledger. hledger generates
simple ledger-compatible transaction  account balance reports from a 
plain text ledger file. It's simple to use, at least for techies.


This has been my learning Haskell project, but I think it's also 
useful. It is much less featureful than ledger, and not quite as fast, 
but it has the virtue of being fun for haskellers to hack on. I am 
documenting the code, the app is simple, and I'm not too far up the 
haskell learning curve, so I think other people learning haskell might 
enjoy a look. It is currently ~1100 lines of haskell excluding tests.


home: http://joyful.com/Ledger#hledger
hackage: 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hledger-0.1

darcsweb: http://joyful.com/darcsweb/darcsweb.cgi?r=hledger
darcs 2 repo: http://joyful.com/repos/hledger
haddock: http://joyful.com/repos/hledger/api-doc/

ledger home: http://newartisans.com/software/ledger.html
ledger manual (recommended): 
http://github.com/jwiegley/ledger/tree/master/doc/ledger.texi


My thanks to John Wiegley for help with compatibility and for his very 
useful ledger tool. I use it (and now, both of them) daily to track time 
and money. This is of course a hot topic around our planet. I hope you 
find it useful or intriguing.


Patches and feedback welcome!

Best,
-Simon

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


[Haskell-cafe] (OT) Humorous definition for fixed points?

2008-10-15 Thread Corey O'Connor
I was just reminded of one of the joke definitions of recursion:
recursion: see recursion.

Perhaps there is a similar one for fixed points?
To learn about fixed points find the fixed point of the process:
Given somebody learn about fixed points from them.

Course, my understanding of fixed points is poor and my jokes always
have poor delivery. So I'm sure somebody else can do better.

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


Re: [Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Don Stewart
simon:
 I'm pleased to announce the first release of hledger, a command-line 
 accounting tool similar to John Wiegley's c++ ledger. hledger generates
 simple ledger-compatible transaction  account balance reports from a 
 plain text ledger file. It's simple to use, at least for techies.
 

Awesome. Available in Arch Linux,

http://aur.archlinux.org/packages.php?ID=20762

Thanks for publishing this on hackage.

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


Re: [Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Jason Dagit
On Wed, Oct 15, 2008 at 5:01 PM, Simon Michael [EMAIL PROTECTED] wrote:

 I'm pleased to announce the first release of hledger, a command-line
 accounting tool similar to John Wiegley's c++ ledger. hledger generates
 simple ledger-compatible transaction  account balance reports from a plain
 text ledger file. It's simple to use, at least for techies.

 This has been my learning Haskell project, but I think it's also useful.
 It is much less featureful than ledger, and not quite as fast, but it has
 the virtue of being fun for haskellers to hack on. I am documenting the
 code, the app is simple, and I'm not too far up the haskell learning curve,
 so I think other people learning haskell might enjoy a look. It is currently
 ~1100 lines of haskell excluding tests.


Simon, I went straight to the code and skimmed over 4 or 5 modules and I
found your code enjoyable to read.  I think this is a nice collection of
code.

Good job!

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


Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread Antoine Latter
On Wed, Oct 15, 2008 at 5:55 PM, wren ng thornton [EMAIL PROTECTED] wrote:

 Doing it that way removes the polymorphism that MonadState, MonadReader, etc
 offer to clients. For example, the backwards-state monad[1] is a MonadState
 but not a StateT (without extra plumbing). There are other examples which
 don't even change the semantics. It seems a shame to force these
 implementations to give different names for the same functions. Are MPTCs
 onerous? They'll be in haskell-prime afterall. Of course, the fundeps are
 another matter entirely...



Slightly off topic - if you do make your backwards-state monad an
instance on MonadState be careful not to use
Control.Monad.State.Class.modify - executing this falls into a black
hole for the backwards-state monad.

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Derek Elkins
On Wed, 2008-10-15 at 14:45 -0400, Stefan Monnier wrote:
  The instance selection for an interface is done at run-time and this is
  inherently necessary.  The instance (in a different sense) selection for
  type classes is almost always resolvable statically.  In Haskell 98
 
 In both cases, the dispatch is inherently dynamic, and in both cases,
 most dispatches can be resolved at compile-time with sufficient effort.
 The actual percentage may be quite different, tho.
 Implementation techniques are also fairly different, and the resulting
 coding style is also very different, but the two concepts are
 fundamentally very close to each other.

Rewrite this code so that there is no run-time remnants of dynamic
dispatch, that is to say there is no run-time method look-up of any
sort.  You can assume that this plus an interface declaration for
IDrawable and two classes Square and Circle is the whole program.

int n = int.Parse(System.Console.ReadLine());
ListIDrawable drawables = new ListIDrawable();
for(int i = 0; i  n; ++i)
drawables.Add(new Square());
drawables.Add(new Circle());

foreach(IDrawable drawable in drawables)
drawable.Draw();

And exercise two:  Write a Haskell example using type classes and not
using existentials or polymorphic recursion where given the whole
program dispatch is inherently dynamic.

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Derek Elkins
On Wed, 2008-10-15 at 08:16 -0700, David Leimbach wrote:
 
 On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED] wrote:
 I'd like to thank everyone who replied to my OP, and also
 perhaps
 clarify one point.  I wasn't trying to be argumentative or
 negative
 about any work people have done to make Haskell approachable
 for OO
 programmers (or any other programmers, for that matter).  I
 simply
 wanted to know what others thought about one item that was
 misleading
 to me in particular, and to see if others either agreed with
 me or had
 similar experiences.
 
 That being said, I know that it's a great deal of work to put
 together
 a useful tutorial, and I appreciate every one I read.
  Especially the
 monad tutorials, of which it took a half dozen before I got
 it.
 
 
 I've read a lot of the Monad tutorials, and I feel like I only get most of 
 it to be 100% honest.

Maybe the problem isn't you, but what you are reading...
 

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


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Richard O'Keefe


On 16 Oct 2008, at 9:01 am, Daryoush Mehrtash wrote:
I am not sure how say in a Java language a constructor can conjure  
up a value of an unknown type.


... Class anUnknownClass;
Object anInstance;
anInstance = anUnknownClass.getConstructor().newInstance();

If you know that the constructor will require arguments of
types T1 and T2, and you have suitable values v1, v2,

anInstance =
  anUnknownClass.getConstructor(T1, T2).newInstance(v1, v2);

will do the job.


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


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Richard O'Keefe


On 16 Oct 2008, at 12:09 pm, Jonathan Cast wrote:
I am not sure how say in a Java language a constructor can conjure  
up

a value of an unknown type.


Well, that's the point.  It can't, in Haskell or in Java.  If you
understand that --- that you can't call the default constructor of a
class that is not statically known at compile time


If you understand that about Java, then you don't understand Java.
Java reflection means that compile-time types are backed up by
runtime objects belonging to Type in general, to Class if they
are class types.  It also means that you can discover the
default constructor by using aClass.getConstructor(), and you
can invoke it by using .newInstance().

If it were not possible to do this, Java would not get much
use out of its ability to load new classes at run time.

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


[Haskell-cafe] Re: ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Simon Michael

Thanks Jason! Glad you liked it.

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


Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
 Would you please explain this a bit more:

 the various unfortunate consequences of type erasure in Java are
 avoided by the fact that Haskell types lack constructors, so the user
 never expects to be able to conjure up a value of an unknown type.

Even if Haskell had Java-style constructors, it wouldn't be a problem,
since type classes exist independently from any object, so the code that
needs the constructor will simply receive it in the
corresponding dictionary.


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


Re: [Haskell-cafe] List as input

2008-10-15 Thread leledumbo

 The compiler doesn't know what kind of list you are trying to read,
sort, and print.

So, the type must be specific? Then why it's possible to call the sorting
function with any list?

 I'm curious as to why taking the pivot from the middle is an
'optimized' version.

Consider if it's used in a GUI program which calls the function when a
button is pressed. Often, users clicks the button more than once. If the
pivot is the first (or last) element, the second (and further) click will
cause worst case scenario to happen. OTOH, if the pivot is the middle
element, best case scenario will happen.
-- 
View this message in context: 
http://www.nabble.com/List-as-input-tp19987726p20007078.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Nathan Bloomfield
At the risk of doing someone's homework...
A naive solution is to do trial division by all integers from 2 up to sqrt
n.

{-
isPrime :: Integer - BoolisPrime n
 | n  2 = False
 | otherwise = f 2 n
 where f k n
  = if k  isqrt
 then True
 else undefined -- exercise for the reader
-}

and where
isqrt n returns floor (sqrt n)

Here, f is the helper function, and is only in scope inside the definition
of isPrime. This is a common haskell idiom- a helper function that is not
quite general purpose enough to be made a standalone function can be defined
on the fly and doesn't need a name or type signature.

You could fancy this up to make it more efficient. I've also seen
probabilistic functions that can handle huge numbers, but I can't remember
if they are recursive.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monadic Floating Point [was: Linking and unsafePerformIO]

2008-10-15 Thread Duncan Coutts
On Thu, 2008-10-16 at 01:24 +0200, Ariel J. Birnbaum wrote:
 On Wednesday 15 October 2008 05:21:04 John Dorsey wrote:
  Should all floating point numerals be in the IO Monad?
 
 I'm deviating from the thread's topic, but I tend to agree with this one. 
 Maybe not IO directly, but some kind of STM-style monad, at least (that is, 
 FP operations are composable but ultimately they must be evaluated in IO).
 
 Floating point operations, at least by IEEE754, depend on environmental 
 settings like the current rounding mode. They may modify state, like the 
 sticky bits that indicate an exception occurred. They may jump nonlocally if  
 a trap handler has been enabled.

It is an interesting question: can IEEE floating point be done purely
while preserving the essential features. I've not looked very far so I
don't know how far people have looked into this before.

Haskell currently only supports a subset of the IEEE FP api. One can
assume that that's mainly because the native api for the extended
features is imperative. But need it be so?

Rounding modes sound to me like an implicit parameter. Traps and
exception bits sound like the implementation mechanism of a couple
standard exception handling strategies. The interesting thing here is
that the exception handling strategy is actually an input parameter.

So part of the issue is a functional model of the FP api but the other
part is what compiler support would be needed to make a functional api
efficient. For example if the rounding mode is an implicit parameter to
each operation like + - * etc then we need some mechanism to make sure
that we don't have to actually set the FP rounding mode before each FP
instruction, but only at points where we know it can change, like
passing a new value for the implicit parameter, or calling into a thunk
that uses FP instructions.

There's also the issue that if the Float/Double operations take an
implicit parameter, can they actually be instances of Num? Is that
allowed? I don't know.

Duncan

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


Re: [Haskell-cafe] List as input

2008-10-15 Thread Brandon S. Allbery KF8NH

On 2008 Oct 16, at 0:53, leledumbo wrote:

The compiler doesn't know what kind of list you are trying to read,

sort, and print.

So, the type must be specific? Then why it's possible to call the  
sorting

function with any list?


A function may have a polymorphic type; this allows its actual type to  
be set by context.


A *program* must have fully determined types, which includes  
polymorphic functions whose calls provide enough context to determine  
the actual type at the call site.  If there isn't enough information  
to set a concrete type at the call, type inference fails.  This is  
what you get with strong typing.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread Kim-Ee Yeoh

re: the importance of existential-cleansing   

On the one hand, it's easy to concur that existentials are simpler
than the alternatives, the tortuous elimination of CC Shan's
translucent existential being a case in point.

And it's also easy to dismiss such caprice as a penchant for Houdinian
escape perversities.  

Then again, why not?  There may never be a real need for anything
particular at all, existentials notwithstanding.  Affirming that by
cracking open the shackles of icons and diabolical shibboleths is
arguably the only real need.


Lennart Augustsson wrote:
 
 What do you mean by need?  From a theoretical or practical perspective?
 We don't need them from a theoretical perspective, but in practice I'd
 rather use existentials than encodinging them in some tricky way.
 
 On Wed, Oct 15, 2008 at 11:05 AM,  [EMAIL PROTECTED] wrote:
 The web page
 begs a question if there is ever any real need for existentials.

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

-- 
View this message in context: 
http://www.nabble.com/Object-oriented-programming%2C-Haskell-and-existentials-tp19990499p20007420.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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