[Haskell-cafe] Re: [Haskell] pros and cons of static typing and side effects ?

2005-08-11 Thread Bernard Pope
[Moved to the Haskell cafe]

It's Friday afternoon here so I thought I'd join in the fun.

On Thu, 2005-08-11 at 23:01 -0400, [EMAIL PROTECTED] wrote:

> While you can't be certain that once your code typechecks, it's bug-free
> (though that does often happen), you can be almost guaranteed that if
> your code typechecks after a refactoring, the refactoring didn't
> introduce any bugs.  

(I tend to agree with ajb's sentiment, but I'll play the devil's
advocate anyway). Perhaps we can reach a fixed point of violent
agreement?

I'm a bit concerned with "can't be certain" on the one hand, and
"_almost_ guaranteed", on the other. 

I guess there are nuances to be explored here, and it is all about
degree of confidence.

Sometimes I have high confidence in my refactoring, like introducing a
state monad. Other times I have much less confidence, like swapping the
order of arguments in numerical calculations.

However, if it weren't for static type checking then I would be much
less game to even _try_ introducing a state monad in my code in the
first place. (Maybe that's just me). Another colleague of mine gave the
opinion that one of the reasons higher-order code is less common in
Prolog than Haskell is that in Prolog does not have static type checking
(it's just one factor out of many). It seems to me like static type
checking has the capacity to make some refactorings much less heroic
than they would be in the non-static setting.

That's my "log on the fire" for today.

Bernie.

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


Re: [Haskell-cafe] Functional dependencies and type inference

2005-08-11 Thread Iavor Diatchki
Hello,

On 8/11/05, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

> ... Here is a boiled down version, much simpler to
> understand.
> 
> module Proxy where
> 
> class Dep a b | a -> b
> instance Dep Char Bool
> 
> foo :: forall a. a -> (forall b. Dep a b => a -> b) -> Int
> foo x f = error "urk"

Should this really be valid?  It seems that because 'b' is determined
by 'a' we should not be allowed to quantify over 'b' without
quantifying over 'a'. I think we can view the class 'Dep' as a
function on types, that is defined by the instances.  Then the above
type is:
a -> (a -> Dep a) -> Int
and it seems that the quantification over 'b' is non-sensical.

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


Re: [Haskell-cafe] Re: Creating a Haskell app to do crosstabs

2005-08-11 Thread Bulat Ziganshin
Hello Peter,

Thursday, August 11, 2005, 1:18:54 PM, you wrote:
PS>  > afaik Spirit is modeled after ParseC (parsing combinators)
PS>  > haskell library and Phoenix was needed for this library
PS>  > because parser combinators require lazy functional language to
PS>  > work :)

PS> Just a minor nit: the Phoenix library has nothing to do with
PS> parsing. It's basically a collection of expression templates
PS> which save you a lot of time when it comes to writing glue code.

Phoenix is a part of Spirit, though


-- 
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] pros and cons of static typing and side effects ?

2005-08-11 Thread Mark Carroll
The previous comments make sense to me. The lots-of-unit-tests aspect of
static typing I find really useful, far exceeding any BDSM cost. If I'm
engaging in exploratory programming, the type inference combined with the
ability to write 'error "armadillo"' in stubs for values I can't be
bothered to generate right now really works conveniently for me.

Although I agree that lots-of-lists is very handy in early prototyping, I
don't feel at all constrained by using homogeneous lists, although very
occasionally I may use existential types, and the way I write programmes
is exactly to think in advance and then write the code: to do otherwise
just wastes my time because then the code doesn't work in some confusing
way and I have to do that thinking I postponed to figure out why - or, if
it does work, I have to think about it to satisfy myself that appearances
aren't deceiving.

I'm not quite sure what macros would look like in Haskell, but I've not
missed those either. In Lisp I would tend to use them for things that
involved changing the values of variables, but that's not really a
Haskellish thing to be doing anyway. Mind you, I learned Lisp after
learning ML, so to some extent I was thinking in ML when writing in Lisp.
Alas, dead-tree versions of "On Lisp" are hard to come by affordably, but
I am now trying to learn more about what I might have missed about Lisp.

I find monads useful because I find it a helpful debugging aid for
functions to be quite clear about what side effects they may want to
have.

I posted this to Haskell-Cafe instead of the main Haskell list, because
I'm rambling a bit. Puzzled Haskell-Cafe readers may like to check
http://www.mail-archive.com/haskell@haskell.org/msg17009.html

-- Mark

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


RE: [Haskell-cafe] Functional dependencies and type inference

2005-08-11 Thread Simon Peyton-Jones
Einar

Good question.  This is a more subtle form of the same problem as I
described in my last message.  In fact, it's what Martin Sulzmann calls
"the critical example".  Here is a boiled down version, much simpler to
understand.

module Proxy where

class Dep a b | a -> b
instance Dep Char Bool

foo :: forall a. a -> (forall b. Dep a b => a -> b) -> Int
foo x f = error "urk"

bar :: (Char -> Bool) -> Int
bar g = foo 'c' g


You would think this should be legal, since bar is just an instantation
of foo, with a=Char and b=Bool.  But GHC rejects it.  Why?

GHC looks at the call to foo (in bar's RHS), and instantiates it with
a=Char.  That tells it that the second argument should have type
(forall b. Dep Char b => Char -> b)
But it doesn't!  It has type (Char -> Bool).  And to GHC these are not
the same types.

You may say that they *should* be the same types.  The crispest way I
know to explain why it arguably should be rejected is to try translating
the program into System F (which is what GHC actually does).  Then the
RHS of bar looks like

bar (g::Char->Bool) = foo {Char} 'c' (...???...)

The {Char} is the type argument to foo.  But what can we pass for
(...???...)?.   We must pass a polymorphic function, with type
forall b. Dep Char b -> Char -> b
But all we have is g::Char->Bool.  And System F has no way to connect
the two.


Well, that's the problem anyway.  I can think of three "solutions":
- Reject such programs (GHC's current solution)
- Abandon compilation via System F
- Extend System F

I'm working on the third of these, with Martin, Manuel, and Stephanie.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Einar Karttunen
| Sent: 15 July 2005 13:48
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] Functional dependencies and type inference
| 
| Hello
| 
| I am having problems with GHC infering functional dependencies related
| types in a too conservative fashion.
| 
| > class Imp2 a b | a -> b
| > instance Imp2 (Foo a) (Wrap a)
| >
| >
| > newtype Wrap a = Wrap { unWrap :: a }
| > data Foo a = Foo
| > data Proxy (cxt :: * -> *)
| >
| > foo :: Imp2 (ctx c) d => Proxy ctx -> (forall a b. (Imp2 (ctx a) b)
=> a -> b) -> c -> d
| > foo p f x = f x
| 
| The type of "foo (undefined :: Proxy Foo)" is inferred as
| "forall c. (forall a b. (Imp2 (Foo a) b) => a -> b) -> c -> Wrap c"
| which shows the outmost functional dependence is working fine. ctx
| is carried to the inner Imp2.
| 
| However "foo (undefined :: Proxy Foo) Wrap" will fail complaining that
| 
| Couldn't match the rigid variable `b' against `Wrap a'
|   `b' is bound by the polymorphic type `forall a b. (Imp2 (ctx a)
b) => a -> b'
| at :1:0-32
|   Expected type: a -> b
|   Inferred type: a -> Wrap a
| In the second argument of `foo', namely `Wrap'
| 
| My guess is that GHC cannot see that the functional dependency
| guarantees that there are no instances which make the inferred
| type invalid. Any solutions to this problem?
| 
| 
| - Einar Karttunen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Functional dependenices in class declarations

2005-08-11 Thread Simon Peyton-Jones
It's intentional.

Consider this data type declaration

data B b = MkT (A a b)

Should that be accepted?  The only thing it could possibly mean would be

data B b = MkT (forall a. A a b)

and I suppose that might possibly be useful.  But in this case you're
also saying that "a" determines "b".  But you can hardly say *forall* a,
if the choice of a determines the (fixed by context) b.

These functional dependencies are tricky things.   Martin Sulzmann and I
wrote a paper about some of the trickiness
(http://research.microsoft.com/%7Esimonpj/Papers/fd-chr/index.htm), and
we're working on a journal version.


My wild guess is that you are trying to convert an O-O idiom into
Haskell, and that's led you to a rather strange program.  Maybe there's
another way to do it.

Simon


| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Frank
| Sent: 08 August 2005 18:17
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] Functional dependenices in class declarations
| 
| In ghc 6.4 (fine work - many gratulations to all who did it!) it is
| permitted
| to have type parameters which are reachable (7.4.3.1 context of type
| signatures).
| I tried the following:
| 
| module TypeDependencies where
| 
| class A a b | a -> b
| 
| class (A a b) => B b  where
| op :: a -> a
| 
| x :: A a b => a -> a
| x = id
| 
| Which compiles fine for the function x, but does complain
| "not in scope: type variable 'a' " for the class (A a b) => B b.
| 
| Is this an intentional restriction that 'reachable' type variables are
only
| permitted in type definitions, but not in classes? or do I
misunderstand
| something?
| 
| Any help appreciated!
| Andrew Frank
| 
| 
| ___
| 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] Re: Creating a Haskell app to do crosstabs

2005-08-11 Thread Peter Simons
Bulat Ziganshin writes:

 > afaik Spirit is modeled after ParseC (parsing combinators)
 > haskell library and Phoenix was needed for this library
 > because parser combinators require lazy functional language to
 > work :)

Just a minor nit: the Phoenix library has nothing to do with
parsing. It's basically a collection of expression templates
which save you a lot of time when it comes to writing glue code.
Binding arguments of arbitrary function objects is something
Phoenix can do, for example. Spirit works well with that library
because both were written by the same author, but they aren't
really related.

You are right, though, that Spirit was influenced by Haskell
quite a bit. As a matter of fact, it was Spirit's author -- Joel
de Guzman -- who made me aware of Haskell when he posted some
example source code on the mailing list back then; I think it was
the usual implementation of Quicksort. I distinctly remember that
I couldn't believe my eyes when I saw that. ;-)

Peter

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


Re: [Haskell-cafe] Creating a Haskell app to do crosstabs

2005-08-11 Thread Andy Elvey

Greg Buchholz wrote:


Andy Elvey wrote:
 

a) Using Haskell to read a delimited file (with column-headings) into a 
columnar or tabular data-structure -
   


   Parsec (http://www.cs.uu.nl/~daan/parsec.html) is a great parsing
library in Haskell.


Greg Buchholz

   

Hi  Greg - thanks very much for this! 
 
  I'll check Parsec out - thanks for the link -


- Andy

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


Re: [Haskell-cafe] Creating a Haskell app to do crosstabs

2005-08-11 Thread Andy Elvey

Bulat Ziganshin wrote:




btw, afaik Spirit is modeled after ParseC (parsing combinators)
haskell library and Phoenix was needed for this library because parser
combinators require lazy functional language to work :) 
 

Hi Bulat - thanks for this! 

 I didn't know that about Phoenix.  Certainly both Spirit and Phoenix 
are very good, and the developers of those libraries are excellent. 

( I'm just a contributor of a couple of examples, although the s/f 
Spirit page lists me as a dev!  :-)  ) 


 -  Andy


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