Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont
I was under the impression that STM code needed to be in its own  
monad. I was looking at Control.Concurrent.STM.TChan, for example,  
where signatures like this exist:


newTChan :: STM (TChan a)   
readTChan :: TChan a - STM a
writeTChan :: TChan a - a - STM ()  

and then

newTChan :: STM (TChan a)   
readTChan :: TChan a - STM a
writeTChan :: TChan a - a - STM ()  


I guess I should give this another look, re-read the STM paper and  
check out your patch.


Regardless, simple is elegant and your Maybe solution is simple.

Thanks, Joel

On Nov 22, 2005, at 7:09 AM, Tomasz Zielonka wrote:


I am talking about Software Transactional Memory, which is in
Control.Concurrent.STM. I think you confused it with State
Transformer Monad.

In your case STM would allow you to wait simultaneously on (T)MVar and
(T)Chan. It would look like this:

logger :: TMVar () - IO ()
logger die =
join $ atomically $
(do x - readTChan parent
return $ do
putStrLn x
logger die)
`orElse`
(do takeTMVar die
return (return ()))


--
http://wagerlabs.com/





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


[Haskell-cafe] Re: Frag: a First Person Shooting game

2005-11-22 Thread Joel Reymont

Mun,

I hope this ushers the era of Haskell games! I, for one, was  
certainly looking for something like this.


Did you encounter any difficulties in your development because of  
Haskell?


Was lazy evaluation ever a problem?

Why did you choose Yampa to program the game entities? Did this give  
you a particular advantage?


Isn't your frame rate a bit low?

Thanks, Joel

On Nov 22, 2005, at 6:05 AM, Mun Hon Cheong wrote:


Frag is a 3D First Person Shooting game.

Features:

*Yampa, a domain-specific embedded language
 for the programming of hybrid systems that
 using the concepts of Functional Reactive
 Programming (FRP) was used to program the
 game entities.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Records

2005-11-22 Thread Antti-Juhani Kaijanaho
Tomasz Zielonka wrote:
 Aren't C and C++ space insensitive (except the preprocessor)?

Literally, yes, because the C and C++ compilers proper take preprocessor
tokens, not strings, as input, and hence do not see the whitespace at
all; the whitespace-sensitive tokenization having been completed by the
preprocessor.  But I think that's splitting hairs, so my answer is: not
in the sense I was using that word. I don't know in what sense you use it.

(In a totally space insensitive language, andy and and y would be
tokenized the same way.)

Personally, I don't see how A.x vs. A . x is much different from that.
When using . as an operator, I separate it by spaces from the other
stuff. (Personally, I would even expect A.x, where A is not a module
name, to be an error in 98-esque Haskell, but it isn't.)
-- 
Antti-Juhani
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 08:30:33AM +, Joel Reymont wrote:
 I was under the impression that STM code needed to be in its own  
 monad. I was looking at Control.Concurrent.STM.TChan, for example,  
 where signatures like this exist:
 
 newTChan :: STM (TChan a) 
 readTChan :: TChan a - STM a 
 writeTChan :: TChan a - a - STM ()  

The STM monad is where synchronisation operations are grouped
in transactions. You can use STM as a drop-in replacement for
traditional Control.Concurrent synchronisation primitives by
simply wrapping every single operation in an atomically block:

atomically :: STM a - IO a

For example, a drop-in replacement for Chan:

type Chan' a = TChan a

newChan' = atomically newTChan
readChan' c = atomically (readTChan c)
writeChan' c v = atomically (writeChan c v)

the types of these functions are:

newChan' :: IO (TChan a)
readChan' :: TChan a - IO a
writeChan' :: TChan a - a - IO ()

But it is only grouping more operations in a transaction that will let
you benefit from the wonders of STM :-)

 I guess I should give this another look, re-read the STM paper and  
 check out your patch.

You definitely should do it. It is a very rewarding read.

 Regardless, simple is elegant and your Maybe solution is simple.

But it also requires that you restructure your code, doesn't it?
I am not sure we understood each other here.

One way to restructure your code to enable smooth transition to the
(Chan (Maybe String)) idea would be to change the type of die request
from (MVar ()) to (IO ()). You could use

(dieVar, die) - do
dieVar - newEmptyMVar
return (dieVar, putMVar dieVar ())

where dieVar is used on the receiver side, and die is used on the
sender side. Then you could easily use a different notification
mechanism for logger:

let die = writeChan parent Nothing

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


Re: [Haskell-cafe] Records

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 10:39:22AM +0200, Antti-Juhani Kaijanaho wrote:
 Tomasz Zielonka wrote:
  Aren't C and C++ space insensitive (except the preprocessor)?
 (In a totally space insensitive language, andy and and y would be
 tokenized the same way.)

Ah, I was wrong, here are some examples:

int a;  inta;
+ + a;  ++a;
map int, listT  mapint,listT

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


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont

Tomasz,

I think it's much simpler than that. I just changed the trace  
function to send Just String down the channel. Whenever I send  
Nothing (from waitForChildren) the logger just exits. Simple change  
in two places, no need for MVars.


Did I miss anything? The program became much snappier, btw.

Joel

On Nov 22, 2005, at 8:53 AM, Tomasz Zielonka wrote:


Regardless, simple is elegant and your Maybe solution is simple.


But it also requires that you restructure your code, doesn't it?
I am not sure we understood each other here.

One way to restructure your code to enable smooth transition to the
(Chan (Maybe String)) idea would be to change the type of die  
request

from (MVar ()) to (IO ()). You could use

(dieVar, die) - do
dieVar - newEmptyMVar
return (dieVar, putMVar dieVar ())

where dieVar is used on the receiver side, and die is used on the
sender side. Then you could easily use a different notification
mechanism for logger:

let die = writeChan parent Nothing


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 09:03:55AM +, Joel Reymont wrote:
 I think it's much simpler than that. I just changed the trace  
 function to send Just String down the channel. Whenever I send  
 Nothing (from waitForChildren) the logger just exits. Simple change  
 in two places, no need for MVars.

 Did I miss anything?

Perhaps I did. I had an impression that these MVars where a pattern that
you use in other parts of your code. If this is only limited to the
logger code then it code could be probably simplified even further.

 The program became much snappier, btw.

Did it fix the problem?

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


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont
Yes in the sense that more than a few lines of code are now printed  
on Windows. Not in the sense of the topic of this thread but then it  
seems to be a Mac OSX-only issue.


Thanks, Joel

On Nov 22, 2005, at 9:14 AM, Tomasz Zielonka wrote:


The program became much snappier, btw.


Did it fix the problem?


--
http://wagerlabs.com/





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


Re[2]: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Bulat Ziganshin
Hello Joel,

Tuesday, November 22, 2005, 1:41:38 AM, you wrote:

JR logger h die =
JR  do empty - isEmptyChan parent
JR unless empty $ do x - readChan parent
JR   putStrLn x
JR   hPutStrLn h x
JR alive - isEmptyMVar die
JR when (alive || not empty) $ logger h die

can you just send Die message through the same Chan? it will be best
solution. you can even write:

logger h die =
 pid - forkIO (readMVar die  putChan parent DIE)
 go
 killThread pid
 where go = do x - readChan parent
   case x of
 DIE - return ()
 _ - do putStrLn x
 hPutStrLn h x
 go



or try something like this:

while isEmptyMVar
  while not isEmptyChan
x - readChan
...

JR I see clearly how using Maybe with getChanContents will work out
JR perfectly. I don't understand why the above code is inefficient to  
JR the point of printing just a few messages (out of hundreds) out on  
JR Windows. I would like to understand it to avoid such mistakes in the  
JR future.

is writing to channel and filling MVar done in different threads? if
so, second thread may just get much more attention. and may be your
code itself drive to this, for example because you are querying channel state
with the same frequency as state of MVar


ps: btw, for such sort of tasks like 'go' above i created control
structure repeat_whileM. with its help first code will become just:

logger h die =
  withThread (readMVar die  putChan parent DIE) $ do
repeat_whileM (readChan parent) (/=DIE) (\x - putStrLn x  hPutStrLn h x)

withThread code  =  bracket (forkIO code) killThread . const
  
repeat_whileM inp cond out = do
  x - inp
  if (cond x)
then do out x
repeat_whileM inp cond out
else return x

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] re-definition of '.'

2005-11-22 Thread Bulat Ziganshin
Hello Max,

Tuesday, November 22, 2005, 2:30:23 AM, you wrote:

 2) sequential functions application in OOP style:

 [1..100] .map (2*) .sum

ME Great proposal! And the only feature haskell will lack is computable go to!
ME And if we add both haskell would become the most expressive and
ME powerful programming language since INTERCAL

is the word OOP persuade so strange on you? two days above someone
wrote about the same operator, just with different name and i don't
see any critics from you or any other FP purists

you missed the key of my idea - because '.' syntax is so needed for
modules and records, we must either support this as special syntax
rules or invent some functional explanation for this syntax. i propose
just such explanations, while all other records proposals just say
this must become a special syntax



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-22 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 20:51 schrieb Henning Thielemann:
 On Mon, 21 Nov 2005, Wolfgang Jeltsch wrote:
 [...]

  Hmm, printing code on paper isn't good for the environment.

 But is quite the same argument for e-paper. :-)

I already thought about this.  But if your computer is turned on anyway (as 
usually is mine during my work time), it doesn't make any difference.

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


Re[2]: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Bulat Ziganshin
Hello Joel,

Tuesday, November 22, 2005, 12:03:55 PM, you wrote:

JR I think it's much simpler than that. I just changed the trace
JR function to send Just String down the channel. Whenever I send  
JR Nothing (from waitForChildren) the logger just exits. Simple change  
JR in two places, no need for MVars.

JR Did I miss anything? The program became much snappier, btw.

it is just the same i recommend to you in previous letter (sorry, i
don't read patch from Tomasz). it must work, at least the
close solution work in my own program :)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Wolfgang Jeltsch
Am Dienstag, 22. November 2005 07:33 schrieb David Menendez:
 Keean Schupke writes:
  Haskell already has static records (in H98)
 
  Dynamic records are addressed by the HList library, which uses
  extensions already present in GHC and Hugs (namely Multi-parameter
  type-classes and function-dependancies).

 Is this the case? Every implementation of HList that I've seen also uses
 overlapping and undecidable instances.

The paper about HList I have seen does explicitely say that the authors were 
finally able to avoid using overlapping instances.  I don't know about 
undecidable instances but I thought (and hope very much) that they don't need 
them too.

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


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 20:34 schrieb Max Eronin:
 On 11/21/05, David Roundy [EMAIL PROTECTED] wrote:
  class Coord a where
get_x :: a - Double
get_y :: a - Double
set_x :: Double - a - a
set_y :: Double - a - a

 I'd say this is a typical OO solution to the problem that doesn't exist

 Why do you need setters and getters for coordinate in purely
 functional language? Doesn't  data Coord = Coord Double Double,
 functional composition and monads solve problems in way better than
 inheritance?

 The most impressive feature of haskell for me, as a former OO-design
 patterns-UML is great programmer was that I don't have to and in fact
 must not use OO and inheritance and can write code that doesn't leave
 you guessing what exactly it is doing and what is not. And that the
 language forces you make good design decisions and doesn't let you
 make wrong ones. Inheritance  is no doubt one of the most sensless
 solutions for code reuse i have ever seen.

Yes, yes, yes! :-)

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


Re: Re[2]: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont

This is the approach that I went with, thanks.

On Nov 22, 2005, at 9:26 AM, Bulat Ziganshin wrote:


can you just send Die message through the same Chan? it will be best
solution. you can even write:


--
http://wagerlabs.com/





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


[Haskell-cafe] GHCi always optimizes?

2005-11-22 Thread Dusan Kolar

Hello all,

 My question is rather strange, maybe, even if simple:
Does ghci always translates with -O option set on?

 I've done some measurements on an application
using ghc and ghci.

ghc compiled with no opmitization = program running
real988m59.260s
user989m1.325s
sys 0m0.704s

ghc compiled with optimization set on = program running
real15m54.343s
user15m54.168s
sys 0m0.172s


ghci alaways:
951.97 secs, 7445117252 bytes (which is 15m51.97sec)

 To be honest, I don't mind ghci optimizes always
but saying it uses the same options as ghc is not
entirely true and, for optimization, it's quite painful
because one searches error where it is not. (/Understand,
I was wondering why program compiled by ghc crashes
and/or evaluates so long while running correctly
and fast in ghci./)


 Dusan

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


[Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Keean Schupke

If I have a function:

  f x y = add x y

and I want to type the function in isolation, then the type of 'add' is 
essentially carried in the environment... Lets say I want to make this 
type explicit in the type signature (where f is valid for any a where 
there is an add function on a - ignoring the class that Haskell would 
require for the overloading):


  add :: Int - Int - Int
  add :: Float - Float - Float

  f :: forall a . exists (add :: a - a - a) = a - a - a

or a step further:

  class Add a where
 add :: a - a - a
  instance Add Int where ...
  instance Add Float where ...

  f :: forall a . Add a = a - a - a

This seems to suggest:

   Add a == exists (add :: a - a - a)

Does this seem in any way right? It seems that the definition of 'f' 
does require the existance of 'add'. That is the definition is valid iff 
there exists a function called 'add' of the correct type. Also doesn't 
the existential quantifier stop you looking inside 'add' - obviously you 
cannot inspect the definition as it may not be defined (yet?), but 
presumably you can still apply 'add'.


   Regards,
   Keean.

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


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Keean Schupke
The HList code does not need overlapping-instances, however it does use 
undecidable
instances. This is not however bad like overlapping instances is. 
Overlapping instances
can break module independance (as in defining a new instance can change 
the meaning
of an existing class in modules that are already compiled). Undecidable 
instances merely
means the compiler is not capable of proving that the constraints 
terminate. In the
case of an HList they obviously do (where the constraint recursion is 
structurally over
the length of a list termination is obvious). This is more a weakness in 
the compiler rather

than some problem with the HList code.

   Keean.

Wolfgang Jeltsch wrote:


Am Dienstag, 22. November 2005 07:33 schrieb David Menendez:
 


Keean Schupke writes:
   


   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses
extensions already present in GHC and Hugs (namely Multi-parameter
type-classes and function-dependancies).
 


Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
   



The paper about HList I have seen does explicitely say that the authors were 
finally able to avoid using overlapping instances.  I don't know about 
undecidable instances but I thought (and hope very much) that they don't need 
them too.


Best wishes,
Wolfgang
___
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] records proposals list

2005-11-22 Thread Keean Schupke

My mistake, what you want is:

   (   mything .=. something
   .*. value .=. (27::Int)
   .*. logic .=. True
   .*. HNil )

Admittedly the label creation would benefit from some syntactic sugar to
reduce typing...

Keean.

Bulat Ziganshin wrote:


Hello Keean,

Monday, November 21, 2005, 6:56:06 PM, you wrote:

KS So you can do this now... with reasonable syntax, for example to
KS create an extensible record

KS (some thing .*. (27 :: Int) .*. True .*. HNil)

KS is a statically typed anonymous record.
  
it is not record, but heterogenous list, in my feel. record must be

indexed by field name, not by type name or position


 



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


Re: [Haskell-cafe] Records

2005-11-22 Thread Ketil Malde
Cale Gibbard [EMAIL PROTECTED] writes:

 This really isn't so bad in practice though. I've certainly never been
 confused by it. 

Well, what can I say?  Good for you?

 You'd have to go out of your way to construct a
 situation in which it's potentially confusing

No.

 There are much more important issues to deal with than this, really.

Like inventing as many new and wonderful symbolic operators as
possible!  Hey, why not allow quoted function names?  So that I can
defined a function f  different from f  ?  Or differentiate
(+4) from completely different  (+ 4), ( +4) and ( + 4) which
*obviously* are entirely differen things?

 might be relevant in the IOHCC, but not in ordinary programming.

So why not go for the Obfuscated Language Design Contest instead?

 In a sane language, small amounts of whitespace sensitivity are going
 to be around no matter what you do.

And if you already are using whitespace to separate words, surely the
logical (not to mention aesthetical) way forward would be to introduce
evene more whitespace sensitivity - here is the Holy Grail
  http://compsoc.dur.ac.uk/whitespace/index.php 

I don't understand why this isn't obvious to people who generally
appear fairly bright, but: introducing extension that turns working
programs into non-working ones is generally a bad idea.  Having it be
due to spacing habits around symbolic operators is worse.  That
spacing changes suddenly starts bringing very complex language
extensions into the picture, with an associated heap of
incomprehensible error messages is *not* a nice thing for anybody -
except, perhaps, the two academics who wrote the paper, and the three
academics who read it.



/rant

Okay, I'm being unfair here.  Haskell is an academic language, its
primary purpose is to produce papers, not software.  And as a mere
programmer, I'm in a minority.  I think Haskell is really cool, but I
don't really belong here, and I realize of course that my voice isn't
going to carry a lot of weight.

But IF there is a desire for Haskell to be used for Real Work, I think
there should be a certain degree of stability.  Taking the function
composition operator and turning it into record selection -- depending
on spacing, of course -- is, IMO, madness.

But good luck on those papers, and see you later, probably on the
Clean mailing lists. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Keean Schupke

Just a follow up to my last post ... The HList paper also presents a way of
removing overlapping instances from _any_ class. So infact support for 
overlapping
instances is no longer required - and this removes all the messy 
problems with

overlapping instances and functional dependancies.

The current HList source distribution runs in hugs with -98 +o only 
because of
lazyness on out part. All the occurances of overlapping instances can 
(will?) be

removed from the source if it becomes an important issue (most of them are
in auxilliary definitions that are not in the paper, like Show for HList.

If you program in the completely non overlapping instances model, then 
compiler

support for deriving TTypeable would be nice, or compiler support for a type
level equality constraint (TypeEq could become a built-in). But just to 
make it clear - compiler
support for this is not necessary, you just define instances of 
TTypeable for all your datatypes.
There is a template-haskell library that can automatically derive 
TTypeable for any datatype

as well.

   Keean.

David Menendez wrote:


Keean Schupke writes:

 


   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses 
extensions already present in GHC and Hugs (namely Multi-parameter 
type-classes and function-dependancies).
   



Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
 



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


Re: [Haskell-cafe] Records

2005-11-22 Thread Keean Schupke
Just my 2p worth... If I were designing a language I would not have used 
the '.' like Haskell does. One problem is that ascii does not support 
enough symbols (Hmm, PL1 here we come). I guess my vote would go to 
keeping the '.' as is to not break existing programs, and using a 
different symbol for record access and qualified names... however '.' 
works well for DNS names:


   [EMAIL PROTECTED] -- function composition (people are used to reading the @ 
backwards due to emails)

   M.f -- qualified naming...
   f?f -- record access...

really needs more symbols... of course the problem then becomes entering 
them on a normal keyboard.


   Keean.

Ketil Malde wrote:


Cale Gibbard [EMAIL PROTECTED] writes:

 


This really isn't so bad in practice though. I've certainly never been
confused by it. 
   



Well, what can I say?  Good for you?

 


You'd have to go out of your way to construct a
situation in which it's potentially confusing
   



No.

 


There are much more important issues to deal with than this, really.
   



Like inventing as many new and wonderful symbolic operators as
possible!  Hey, why not allow quoted function names?  So that I can
defined a function f  different from f  ?  Or differentiate
(+4) from completely different  (+ 4), ( +4) and ( + 4) which
*obviously* are entirely differen things?

 


might be relevant in the IOHCC, but not in ordinary programming.
   



So why not go for the Obfuscated Language Design Contest instead?

 


In a sane language, small amounts of whitespace sensitivity are going
to be around no matter what you do.
   



And if you already are using whitespace to separate words, surely the
logical (not to mention aesthetical) way forward would be to introduce
evene more whitespace sensitivity - here is the Holy Grail
 http://compsoc.dur.ac.uk/whitespace/index.php 


I don't understand why this isn't obvious to people who generally
appear fairly bright, but: introducing extension that turns working
programs into non-working ones is generally a bad idea.  Having it be
due to spacing habits around symbolic operators is worse.  That
spacing changes suddenly starts bringing very complex language
extensions into the picture, with an associated heap of
incomprehensible error messages is *not* a nice thing for anybody -
except, perhaps, the two academics who wrote the paper, and the three
academics who read it.



/rant

Okay, I'm being unfair here.  Haskell is an academic language, its
primary purpose is to produce papers, not software.  And as a mere
programmer, I'm in a minority.  I think Haskell is really cool, but I
don't really belong here, and I realize of course that my voice isn't
going to carry a lot of weight.

But IF there is a desire for Haskell to be used for Real Work, I think
there should be a certain degree of stability.  Taking the function
composition operator and turning it into record selection -- depending
on spacing, of course -- is, IMO, madness.

But good luck on those papers, and see you later, probably on the
Clean mailing lists. 


-k
 



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


Re: [Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Adrian Hey
On Tuesday 22 Nov 2005 10:39 am, Keean Schupke wrote:
 If I have a function:

f x y = add x y

 and I want to type the function in isolation, then the type of 'add' is
 essentially carried in the environment...

I am no expert in type theory so I'm probably about to get way
out of my depth, but isn't this what principal typings are all
about (as distinct from principal types). Maybe a look at type
system CT would be useful too.

 http://www2.dcc.ufmg.br/~camarao/CT/

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


Re: [Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Keean Schupke
Excellent link thanks! Not quite what I was thinking of - but definitely 
related.
I'll give it a read and see if they want to existentially quantify 
environments...


   Keean.

Adrian Hey wrote:


On Tuesday 22 Nov 2005 10:39 am, Keean Schupke wrote:
 


If I have a function:

  f x y = add x y

and I want to type the function in isolation, then the type of 'add' is
essentially carried in the environment...
   



I am no expert in type theory so I'm probably about to get way
out of my depth, but isn't this what principal typings are all
about (as distinct from principal types). Maybe a look at type
system CT would be useful too.

http://www2.dcc.ufmg.br/~camarao/CT/

Regards
--
Adrian Hey
 



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


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-22 Thread Daniel Fischer
Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy:

May I suggest

endBy anyToken semi ? -- optionally replace semi by char ';', if you don't 
want to skip whitespace

I think this is what you want --- stop at the first semicolon.

If you want to ignore just a final semicolon, you might use

endBy anyToken (optional semi  eof),

if you want to stop at the last semicolon, whatever comes thereafter, you have 
a problem, you'd need long lookahead.

Cheers,
Daniel


 Thanks for your solution. However, when I try this,

  str1 :: Parser String
 str1 = do str - many anyToken
notFollowedBy' semi
  return str
 
  notFollowedBy' :: Show a = GenParser tok st a - GenParser tok st ()
  notFollowedBy' p  = try $ join $  do  a - try p
  return
  (unexpected (show a)) |
   return (return ())
   run:: Show a = Parser a - String - IO()
 
   run p input
 
  = case (parse p  input) of
 
  Left err - do {putStr parse error at  ;print err}
 
  Right x - print

 When I compile, it still displays ; at the end of the string.

   Parser run str1 Hello ;
   Hello ;

 The reason, as I think, because anyToken accepts any kind of token, it
 considers ; as token of its string. Thus, it does not understand
 notFollowedBy' ???

 Do you have any ideas about this ??? Thanks.

 On 11/19/05, Andrew Pimlott [EMAIL PROTECTED] wrote:
  On Sat, Nov 19, 2005 at 06:43:48PM -0500, Sara Kenedy wrote:
   str1 :: Parser String
   str1 = do {str - many anyToken; notFollowedBy semi; return str}
  
   However, when I compile, there is an error.
  
   ERROR Test.hs:17 - Type error in application
   *** Expression : notFollowedBy semi
   *** Term   : semi
   *** Type   : GenParser Char () String
   *** Does not match : GenParser [Char] () [Char]
 
  The problem is that notFollowedBy has type
 
  notFollowedBy  :: Show tok = GenParser tok st tok - GenParser tok
  st ()
 
  ie, the result type of the parser you pass to notFollowedBy has to be
  the same as the token type, in this case Char.  (The reason for this
  type is obscure.)  But semi has result type String.  You could fix the
  type error by returning a dummy Char:
 
  str1 = do {str - many anyToken
; notFollowedBy (semi  return undefined)
; return str}
 
  I think this will even work; however notFollowedBy is a pretty
  squirrelly function.  There was a discussion about it:
 
  http://www.haskell.org/pipermail/haskell/2004-February/013621.html
 
  Here is a version (which came out of that thread) with a nicer type,
  that probably also works more reliably (though I won't guarantee it):
 
  notFollowedBy' :: Show a = GenParser tok st a - GenParser tok st ()
  notFollowedBy' p  = try $ join $  do  a - try p
return (unexpected (show a))
|
return (return ())
 
  Andrew

 ___
 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] How to use notFollowedBy function in Parsec

2005-11-22 Thread Daniel Fischer
Am Dienstag, 22. November 2005 14:51 schrieben Sie:
 Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy:

 May I suggest

 endBy anyToken semi ? -- optionally replace semi by char ';', if you


Oops, I confused endBy and manyTill !! Also below. 
And since maybe there isn't any semicolon, I'd say

manyTill anyToken (semi {- try semi, perhaps -} | eof)

 don't want to skip whitespace

 I think this is what you want --- stop at the first semicolon.

 If you want to ignore just a final semicolon, you might use

 endBy anyToken (optional semi  eof),

 if you want to stop at the last semicolon, whatever comes thereafter, you
 have a problem, you'd need long lookahead.

 Cheers again,
 Daniel

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


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-22 Thread Sara Kenedy
Hello,
I run as follows:

simple::Parser String
simple = do manyTill anyToken (semi | eof)

run:: Show a = Parser a - String - IO()

run p input

= case (parse p  input) of

Left err - do {putStr parse error at  ;print err}

Right x - print x


ParsecLanguage :load Test.hs
Type checking
ERROR Test.hs:21 - Type error in application
*** Expression : semi | eof
*** Term   : semi
*** Type   : GenParser Char () String
*** Does not match : GenParser a b ()

Do you know what happens? Thank you.

On 11/22/05, Daniel Fischer [EMAIL PROTECTED] wrote:
 Am Dienstag, 22. November 2005 14:51 schrieben Sie:
  Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy:
 
  May I suggest
 
  endBy anyToken semi ? -- optionally replace semi by char ';', if you
 

 Oops, I confused endBy and manyTill !! Also below.
 And since maybe there isn't any semicolon, I'd say

 manyTill anyToken (semi {- try semi, perhaps -} | eof)

  don't want to skip whitespace
 
  I think this is what you want --- stop at the first semicolon.
 
  If you want to ignore just a final semicolon, you might use
 
  endBy anyToken (optional semi  eof),
 
  if you want to stop at the last semicolon, whatever comes thereafter, you
  have a problem, you'd need long lookahead.
 
  Cheers again,
  Daniel


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


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-22 Thread Daniel Fischer
Am Dienstag, 22. November 2005 15:58 schrieben Sie:
 Hello,
 I run as follows:

 simple::Parser String
 simple = do manyTill anyToken (semi | eof)

 run:: Show a = Parser a - String - IO()

 run p input

   = case (parse p  input) of

   Left err - do {putStr parse error at  ;print err}

   Right x - print x


 ParsecLanguage :load Test.hs
 Type checking
 ERROR Test.hs:21 - Type error in application
 *** Expression : semi | eof
 *** Term   : semi
 *** Type   : GenParser Char () String
 *** Does not match : GenParser a b ()

 Do you know what happens? Thank you.


Aye, | takes two parsers of the same type, so we'd need

manyTill anyToken ((semi  return () ) | eof)
or
manyTill anyToken (semi | (eof  return dummy String))

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


Re: [Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Wolfgang Jeltsch
Am Dienstag, 22. November 2005 11:39 schrieb Keean Schupke:
 [...]

 This seems to suggest:

 Add a == exists (add :: a - a - a)

Doesn't exists normally quantify over types and not over values?

 [...]

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


Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Keean Schupke
This function is already in the HList library (well early versions 
anyway)... I dont think
this is in the current distribution. Its  a generic constructor  
wrapper. For example:


hMarkAll Just hlist

   class HList l = HMarkAll c l m | c l - m where
  hMarkAll :: (forall a . a - c a) - l - m
   instance HMarkAll c HNil HNil where
  hMarkAll _ _ = HNil
   instance HMarkAll c l m = HMarkAll c (HCons e l) (HCons (c e) m) where
  hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)

   Keean.

Joel Reymont wrote:


Credit goes to Cale:

class (HList l, HList p) = HLPU p l | p - l, l - p where
puHList :: p - PU l

instance HLPU HNil HNil where
puHList HNil = lift HNil

instance (HList l, HLPU p l) = HLPU (HCons (PU e) p) (HCons e l) where
puHList (HCons pe l) =
wrap (\(a, b) - HCons a b,
  \(HCons a b) - (a, b))
  (pair pe (puHList l))


On Nov 10, 2005, at 2:04 PM, Joel Reymont wrote:


Folks,

I'm having trouble creating a pickler for HLists and would  
appreciate a solution.


The code for (HCons e HNil) works fine but I get an error trying to  
implement puHList for (HCons e l) where l is supposed to be (HCons  e 
...), i.e. another HList.


Bar.hs:21:37:
Couldn't match the rigid variable e' against PU e'
`e' is bound by the instance declaration at Bar.hs:17:0

Expected type: HCons (PU e) l Inferred type: HCons e l
In the first argument of puHList', namely l'

In the second argument of pair', namely (puHList l)'

Failed, modules loaded: none.



--
http://wagerlabs.com/





___
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] using of data types as kinds

2005-11-22 Thread Bulat Ziganshin
Hello ,

in the HCAR GHC team wrote On the type system front, we hope to ...
Allow you to use data types as kinds, in a manner similar to Tim
Sheard▓s Omega language. can someone point me where i can read about
this?

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Keean Schupke

Wolfgang Jeltsch wrote:


This seems to suggest:

   Add a == exists (add :: a - a - a)
   



Doesn't exists normally quantify over types and not over values?
 

It is quantifying over types, it is saying there exists a type a - a 
- a that has

at least one value we will call add...

I think the important point is that the existential is a pair of (proof, 
proposition)
which through curry-howard-isomorphism is (value in set, set). Here we 
are saying that
there is a set of functions with the type a - a - a ... for the 
existential to be satisfied
there must be one called add. Consider this as an assumption placed on 
the environment

by the function.

   Keean.

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


Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Joel Reymont

Keean,

I sort of gave up on HList for the time being since I found easier  
ways to solve my problem.


Mainly, I could not estimate the impact it would have on run-time  
performance of my code and GHC not being able to compile the code was  
not a good indication. Simon PJ fixed that error since.


My idea was to, basically, create my own record sans labels. I wanted  
to specify picklers and default values for each field instead. I have  
over 250 records, though, and some have over 10 fields. There is a  
lot of sharing of fields between the records but I still think this  
is too much for GHC to handle.


Can you venture a guess on runtime performance of such code?

Thanks, Joel


On Nov 22, 2005, at 4:07 PM, Keean Schupke wrote:


hMarkAll Just hlist

   class HList l = HMarkAll c l m | c l - m where
  hMarkAll :: (forall a . a - c a) - l - m
   instance HMarkAll c HNil HNil where
  hMarkAll _ _ = HNil
   instance HMarkAll c l m = HMarkAll c (HCons e l) (HCons (c e)  
m) where

  hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Keean Schupke
That all depends... In theory all the HList stuff happens at compile 
time, and what you are left with is normal function application... Of 
course compilers arn't that good yet, but as a reasonable idea, consider 
just that value level... Most of the extra work is the packing/unpacking 
of pairs (,). I have used HList for database schemas like the Cow 
example database (see attached) with no problems. The DB code includes 
code to generate the database from this Schema so is doesn't need to 
be entered twice, and it also typechecks the database against the schema 
in a one-way extensional manner on program start. The performance of the 
DB app is good, better than with scripting languages like perl/python, 
and type-safe.

This code uses records made from HLists (see the paper for examples).

   Keean.


Joel Reymont wrote:


Keean,

I sort of gave up on HList for the time being since I found easier  
ways to solve my problem.


Mainly, I could not estimate the impact it would have on run-time  
performance of my code and GHC not being able to compile the code was  
not a good indication. Simon PJ fixed that error since.


My idea was to, basically, create my own record sans labels. I wanted  
to specify picklers and default values for each field instead. I have  
over 250 records, though, and some have over 10 fields. There is a  
lot of sharing of fields between the records but I still think this  
is too much for GHC to handle.


Can you venture a guess on runtime performance of such code?

Thanks, Joel


On Nov 22, 2005, at 4:07 PM, Keean Schupke wrote:


hMarkAll Just hlist

   class HList l = HMarkAll c l m | c l - m where
  hMarkAll :: (forall a . a - c a) - l - m
   instance HMarkAll c HNil HNil where
  hMarkAll _ _ = HNil
   instance HMarkAll c l m = HMarkAll c (HCons e l) (HCons (c e)  m) 
where

  hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)



--
http://wagerlabs.com/







{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module Lib.Relational.FamDb where

import Char
import Lib.ODBC.Types
import Lib.TIR.HList
import Lib.TIR.HTypeGHC
import Lib.TIR.HRecord
import Lib.Relational.Types as SQL

---
-- Foot and Mouth Database

famdb :: (FarmerTable:*:FarmTable:*:AnimalTable:*:ContaminatedTable:*: HNil)
famdb = (farmerTable.*.farmTable.*.animalTable.*.contaminatedTable.*.HNil)

---
-- Domains

newtype DFarmerId = DFarmerId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DFarmerName = DFarmerName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DFarmId = DFarmId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DFarmName = DFarmName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DFarmCounty = DFarmCounty String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DAnimalId = DAnimalId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DAnimalName = DAnimalName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
data DAnimalType = Cow | Sheep deriving (Show,Eq)
newtype DAnimalPrice = DAnimalPrice Float deriving (Show,Eq,ToSqlType SqlNumeric,FromSqlType SqlNumeric)
data DCntdType = BSE | FM deriving (Show,Eq)

instance FromSqlType SqlVarchar DAnimalType where
   fromSqlType _ s = case (map toLower s) of
  cow - Just Cow
  sheep - Just Sheep
  _ - Nothing
 
instance ToSqlType SqlVarchar DAnimalType where
   toSqlType Cow = SqlTyped (SqlExpressionConst $ sqlShow cow )
   toSqlType Sheep = SqlTyped (SqlExpressionConst $ sqlShow sheep )

instance FromSqlType SqlVarchar DCntdType where
	fromSqlType _ s = case (map toLower s) of
		bse - Just BSE
		fm - Just FM
		_ - Nothing

instance ToSqlType SqlVarchar DCntdType where
	toSqlType BSE = SqlTyped (SqlExpressionConst $ sqlShow BSE )
	toSqlType FM = SqlTyped (SqlExpressionConst $ sqlShow FM )

---
-- Farmer table

data FarmerId = FarmerId deriving Show
data FarmerName = FarmerName deriving Show

type FarmerTable = Table (
	FarmerId :=: Attribute DFarmerId SqlInteger :*:
	FarmerName :=: Attribute DFarmerName SqlVarchar :*:
	HNil)	

farmerTable :: FarmerTable
farmerTable =  newTable Farmer (
	FarmerId .=. Attribute (attr { attrName=farmerid, attrType=SERIAL }) .*.
	FarmerName .=. Attribute (attr { attrName=name, attrSize=20 }) .*.
	HNil)

---
-- Farm table

data FarmId = FarmId deriving Show
data FarmName = FarmName deriving Show
data FarmCounty = FarmCounty deriving 

RE: [Haskell-cafe] using of data types as kinds

2005-11-22 Thread Simon Peyton-Jones
Read about Omega!  

I have not written anything about what I plan to do in GHC, but basically it 
amounts to allowing you to use a data type as a kind.  Busy doing GADTs and 
impredicativity at the moment though

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of
| Bulat Ziganshin
| Sent: 22 November 2005 15:41
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] using of data types as kinds
| 
| Hello ,
| 
| in the HCAR GHC team wrote On the type system front, we hope to ...
| Allow you to use data types as kinds, in a manner similar to Tim
| Sheard▓s Omega language. can someone point me where i can read about
| this?
| 
| --
| Best regards,
|  Bulat  mailto:[EMAIL PROTECTED]
| 
| 
| 
| ___
| 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] using of data types as kinds

2005-11-22 Thread Greg Woodhouse


--- Simon Peyton-Jones [EMAIL PROTECTED] wrote:

 Read about Omega!  
 

I will.

 Busy doing GADTs and impredicativity at the moment though
 

Impredicativity?


===
Gregory Woodhouse  [EMAIL PROTECTED]


Interaction is the mind-body problem of computing.

--Philip Wadler











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


Re: [Haskell-cafe] GHCi always optimizes?

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 11:07:07AM +0100, Dusan Kolar wrote:
 To be honest, I don't mind ghci optimizes always
 but saying it uses the same options as ghc is not
 entirely true and, for optimization, it's quite painful
 because one searches error where it is not.

I think the real source of your problem is that GHCi will load a
compiled .o file if it's up to date wrt.  the source files. When you
load modules, watch the messages printed by GHCi. Skipping means
loading the .o file, Compiling means that the module will be compiled
and interpreted by GHCi.

Anyway, it's strange that you are experiencing crashes.  IIRC, there
were problems if you mixed modules compiled with different levels of
optimisation in the same program, but I am not sure it still happens.

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


[Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Joel Reymont

Is there a shorter way to write the if-then-else part below?

--
tryTakeSeat :: [Word8] - Word8 - ScriptState (Maybe Word8)
tryTakeSeat _ _ =
do ...
   if (cmdType cmd) /= (CmdSitError Server)
  then return $ Just seat_num
  else return Nothing
--

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Arjan van IJzendoorn

Is there a shorter way to write the if-then-else part below?
   if (cmdType cmd) /= (CmdSitError Server)
  then return $ Just seat_num
  else return Nothing


return $ if cmdType cmd /= CmdSitError Serv
then Just seat_num else Nothing

Arjan

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


Re: [Haskell-cafe] Records

2005-11-22 Thread Sven Panne
I think this discussion has reached a point where it is of utmost importance 
to re-read Wadler's Law of Language Design, a law so fundamental to 
computer science that it can only be compared to quantum dynamics in physics:

   http://www.informatik.uni-kiel.de/~mh/curry/listarchive/0017.html

:-)

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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Arjan van IJzendoorn [EMAIL PROTECTED] writes:

 Is there a shorter way to write the if-then-else part below?
if (cmdType cmd) /= (CmdSitError Server)
   then return $ Just seat_num
   else return Nothing

 return $ if cmdType cmd /= CmdSitError Serv
   then Just seat_num else Nothing

return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Greg Woodhouse


--- Sven Panne [EMAIL PROTECTED] wrote:

 I think this discussion has reached a point where it is of utmost
 importance 
 to re-read Wadler's Law of Language Design, a law so fundamental to
 
 computer science that it can only be compared to quantum dynamics in
 physics:
 
http://www.informatik.uni-kiel.de/~mh/curry/listarchive/0017.html
 
 :-)
 
 Cheers,
S.

To be honest, I haven't followed the entire records thread (at least
not yet), but I don't know that it's fair to say that we've been
focusing entirely (or nearly so) on lexical issues. I'll grant you that
there's an awful lot of that going on, but unless I'm missin something
obvious, support for a record data type isn't even a purely syntactic
issue. If records are to be supported, they need to have semantics, and
it's not obvious to me how this is to be done in a functional language.

That being said, this is a matter of some interest to me, primarily
because I've been thinking about how to go about using Haskell with
(not necessarily relational) databases, and it seems awkward to use a
tuple or heterogenous list in a context where new attributes can be
added to existing data. Now, of course, that's a puzzle in it's own
right: How on earth can you achieve anything like referential
transparency here? 


===
Gregory Woodhouse  [EMAIL PROTECTED]


Interaction is the mind-body problem of computing.

--Philip Wadler











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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Henning Thielemann


On Tue, 22 Nov 2005, Matthias Neubauer wrote:


Arjan van IJzendoorn [EMAIL PROTECTED] writes:


Is there a shorter way to write the if-then-else part below?
   if (cmdType cmd) /= (CmdSitError Server)
  then return $ Just seat_num
  else return Nothing


return $ if cmdType cmd /= CmdSitError Serv
then Just seat_num else Nothing


return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num


Because I often need it, I'm used to use my private function 'toMaybe'

return $ toMaybe (cmdType cmd /= CmdSitError Serv) seat_num
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Sven Panne
Am Dienstag, 22. November 2005 19:30 schrieb Greg Woodhouse:
 To be honest, I haven't followed the entire records thread (at least
 not yet), but I don't know that it's fair to say that we've been
 focusing entirely (or nearly so) on lexical issues. I'll grant you that
 there's an awful lot of that going on, but unless I'm missin something
 obvious, support for a record data type isn't even a purely syntactic
 issue. [...]

I definitely didn't want to offend anybody, and I'm sure that there have been 
quite a few good (non-syntactical) proposals, but to be honest: They vanished 
in a sea of syntactic discussions, at least for me, and I couldn't follow the 
whole thread closely due to a lack of time. Hopefully somebody writes up the 
relevant points and proposals in a condensed form...

As an aside, such heated syntactical discussions come up at least once a year 
on the Haskell lists for almost a decade now, and I think it is a good time 
to remind people about the law then... :-)

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


Re: [Haskell-cafe] Existential quantification of environments.

2005-11-22 Thread Wolfgang Jeltsch
Am Dienstag, 22. November 2005 17:19 schrieben Sie:
 Wolfgang Jeltsch wrote:
 This seems to suggest:
 
 Add a == exists (add :: a - a - a)
 
 Doesn't exists normally quantify over types and not over values?

 It is quantifying over types, it is saying there exists a type a - a - a
 that has at least one value we will call add...

It says that there exists a value add.  With quantifying over types I meant 
something like this:

exists a. some type using the type variable a

This is how forall in GHC and Hugs looks like.

 [...]

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


Re[2]: [Haskell-cafe] using of data types as kinds

2005-11-22 Thread Bulat Ziganshin
Hello Greg,

Tuesday, November 22, 2005, 8:24:41 PM, you wrote:
 Busy doing GADTs and impredicativity at the moment though
 

GW Impredicativity?

just in the case you don't have time to read HCAR ;) some excerpt from
there:


2.1  The Glasgow Haskell Compiler



There is lots more in the works:

We are planning to use darcs (6.6) instead of CVS for GHC. 

On the type system front, we hope to extend GHC’s higher-rank type
system to incorporate impredicative types:
http://research.microsoft.com/~simonpj/papers/boxy/, 

fix the GADT implementation to work nicely with type classes, 

Allow you to use data types as kinds, in a manner similar to Tim
Sheard’s Omega language. 

We are planning to release GHC 6.6 some time in the next six months.
This will include the parallel version of GHC. 


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] using of data types as kinds

2005-11-22 Thread Bulat Ziganshin
Hello Simon,

Tuesday, November 22, 2005, 8:17:38 PM, you wrote:

SPJ I have not written anything about what I plan to do in GHC, but
SPJ basically it amounts to allowing you to use a data type as a
SPJ kind.  Busy doing GADTs and impredicativity at the moment though

Simon, i can't download file

http://research.microsoft.com/~simonpj/papers/boxy/boxy-pldi.ps.gz

reffered at http://research.microsoft.com/~simonpj/papers/boxy/


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Bulat Ziganshin
Hello Matthias,

Tuesday, November 22, 2005, 9:17:57 PM, you wrote:

MN return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num

return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

must also work :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] using of data types as kinds

2005-11-22 Thread kyra

Bulat Ziganshin wrote:


Hello Simon,

Tuesday, November 22, 2005, 8:17:38 PM, you wrote:

SPJ I have not written anything about what I plan to do in GHC, but
SPJ basically it amounts to allowing you to use a data type as a
SPJ kind.  Busy doing GADTs and impredicativity at the moment though

Simon, i can't download file

http://research.microsoft.com/~simonpj/papers/boxy/boxy-pldi.ps.gz

reffered at http://research.microsoft.com/~simonpj/papers/boxy/


 


Google gives http://www.cis.upenn.edu/~dimitriv/boxy/boxy.ps
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 10:15:15PM +0300, Bulat Ziganshin wrote:
 Tuesday, November 22, 2005, 9:17:57 PM, you wrote:
 
 MN return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num
 
 return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)
 
 must also work :)

But it won't.
I have made this mistake too in the past ;-)

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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Joel Reymont

Why wouldn't Bulat's version work?

I don't think it will work for me either way as I'm returning m  
(Maybe Int) where m is my own monad. It seems that folks assumed that  
m itself was the maybe monad. Unless I'm mistaken the code below  
won't work otherwise.


On Nov 22, 2005, at 8:50 PM, Tomasz Zielonka wrote:


On Tue, Nov 22, 2005 at 10:15:15PM +0300, Bulat Ziganshin wrote:



return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

must also work :)


But it won't.
I have made this mistake too in the past ;-)


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Bulat Ziganshin [EMAIL PROTECTED] writes:

 Hello Matthias,

 Tuesday, November 22, 2005, 9:17:57 PM, you wrote:

 MN return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num

 return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

 must also work :)

Only if seat_num is of type () ... :-)

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Yitzchak Gale
 Is there a shorter way to write the if-then-else part below?
 
 --
 tryTakeSeat :: [Word8] - Word8 - ScriptState (Maybe Word8)
 tryTakeSeat _ _ =
 do ...
if (cmdType cmd) /= (CmdSitError Server)
   then return $ Just seat_num
   else return Nothing
 --

tryTakeSeat _ _ = runMaybeT $ do
   ...
   guard $ cmdType cmd /= CmdSitError Server
   return seat_num

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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Joel Reymont [EMAIL PROTECTED] writes:

 I don't think it will work for me either way as I'm returning m
 (Maybe Int) where m is my own monad. It seems that folks assumed that
 m itself was the maybe monad. Unless I'm mistaken the code below
 won't work otherwise.

There are two monads involved. The outer return injects into your m
monad. That's all there is for your m.

Then there is the inner stuff. Because the constructor of the inner
expressions, your Maybes, is an instance of MonadPlus, you can use all
the nice stuff there is for MonadPlus.

I'd usually write it like this ...

  return $ do
guard (cmdType cmd /= CmdSitError Serv) 
return seat_num

In case the guard fails, you'll get back mzero (Nothing in your
case).

And then there is also mplus to handle alternatives ...

-Matthias


 On Nov 22, 2005, at 8:50 PM, Tomasz Zielonka wrote:

 On Tue, Nov 22, 2005 at 10:15:15PM +0300, Bulat Ziganshin wrote:

 return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

 must also work :)

 But it won't.
 I have made this mistake too in the past ;-)

 --
 http://wagerlabs.com/





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


-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-22 Thread Scherrer, Chad
Albert Lai [EMAIL PROTECTED] writes:

 I offer a simpler, more direct, and pre-existing correspondence
between a functional 
 programming construct and unix pipes:

Maybe my point wasn't clear. Of course this idea of comparing lazy
evaluation to Unix pipes is very old (long before July 2004, I'm sure).
The point I'm making is that there is an old idea that may be underused.
We use ($) all over the place, but if there are a lot of them (and
especially if they are spread over several lines) it becomes awkward to
read the whole thing backward to trace through the function from
beginning to end. In these cases, it's much simpler to use 

(\|) = flip ($) -- (#) seems to me too pretty for other purposes to use
it here.
infixl 0 \| -- Again, why can't this be negative or Fractional??

What I'm asking is really a question of pedagogy and style. This style
seems reasonable to me. OTOH, there are some reasons not to do things in
this way. Maybe any function big enough to benefit from writing it this
way should be broken up anyway. Or maybe getting used to this style
where the laziness is right in your face could make it more difficult
for people to learn to reason through less obvious laziness. I'm really
trying to figure out whether this approach is worth pursuing, rather
than imply that this is a completely original idea.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad Transformer question

2005-11-22 Thread Fan Wu
Hi Haskell gurus,

I'm learning Haskell now and here I'm quite puzzled over some code
about Monad Transformers. The code is like:


   type NDS a = StateT ProblemState [] a

   getVar :: Var - NDS (Maybe Value)
   getVar v = do vs - gets vars
 return $ lookup v vs


What puzzles me is that, I think the Monad of the do block shall be
the NDS (Maybe Value) in declaration, but the type of gets is

gets :: (MonadState s m) = (s - a) - m a

So gets returns a Monad of type m ([] is this case), which seems to
be different from NDS (Maybe Value), but GHC does not complain about
it.


If I comment out the type declaration of getVar :: Var - NDS (Maybe
Value) and let GHC interpret the type, then the type of getVar is
like:

getVar :: (MonadState ProblemState m) = Var - m (Maybe Value)

So does it mean StateT ProblemState m and the m as in MonadState
ProblemState m is the same thing?

I guess I must missed something when trying to understand the Monad
Transformers. Please give me some insights.

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


Re: [Haskell-cafe] Monad Transformer question

2005-11-22 Thread Andrew Pimlott
On Tue, Nov 22, 2005 at 05:26:00PM -0700, Fan Wu wrote:
type NDS a = StateT ProblemState [] a
 
getVar :: Var - NDS (Maybe Value)
getVar v = do vs - gets vars
  return $ lookup v vs
 
 
 What puzzles me is that, I think the Monad of the do block shall be
 the NDS (Maybe Value) in declaration, but the type of gets is
 
 gets :: (MonadState s m) = (s - a) - m a
 
 So gets returns a Monad of type m ([] is this case), which seems to
 be different from NDS (Maybe Value), but GHC does not complain about
 it.
 
 
 If I comment out the type declaration of getVar :: Var - NDS (Maybe
 Value) and let GHC interpret the type, then the type of getVar is
 like:
 
 getVar :: (MonadState ProblemState m) = Var - m (Maybe Value)
 
 So does it mean StateT ProblemState m and the m as in MonadState
 ProblemState m is the same thing?

No!  Check out the instance:

instance (Monad m) = MonadState s (StateT s m) where ...

So you can see that the m in MonadState ProblemState m is actually
StateT ProblemState m' where m' is the inner monad, [] in your case.
So a correct type for gets as you use it is

gets :: (ProblemState - a) - MonadState ProblemState [] a

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


Re: Re[2]: [Haskell-cafe] re-definition of '.'

2005-11-22 Thread Max Eronin
 is the word OOP persuade so strange on you?

No, my brain exploded by the examples and proposed rules made me look so
When it is exploding I often start acting funnily. And I was fortunate
enough not to begin biting the dogs and scratching the cats after an
attempt to predict an order of application with two different (but not
so) operators that bubble arguments left to right and then throw them
backward and over again.
bow-wow
Something like PLEASE READ OUT statement in INTERCAL.

There was nothing about OOP in my posting (as well as in yours).

 see any critics from you or any other FP purists

Not sure I see what you mean by 'FP purists' in the context of Haskell language
But whatever -, Haskell is still a pure language, isn't it?
Looks like now it's time to change this inadvertence. Let it be
impure, vulgar, dirty and scripting!

And you are absolutely right. I missed the key of your idea. My brain
is erupted, you know... :(


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


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 09:07:29PM +, Joel Reymont wrote:
 Why wouldn't Bulat's version work?

Because Int /= ()

when :: (Monad m) = Bool - m () - m ()

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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 02:09:40PM -0800, Scherrer, Chad wrote:
 (\|) = flip ($) -- (#) seems to me too pretty for other purposes to use
 it here.
 infixl 0 \| -- Again, why can't this be negative or Fractional??

I have a ? operator that does the same thing. Next time I use it I'll
check if \| looks better.

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


[Haskell-cafe] Records vs HList

2005-11-22 Thread David Menendez
Keean Schupke writes:

 David Menendez wrote:
 
 Chris Kuklewicz writes:
 
 Would the record system describe at
 http://lambda-the-ultimate.org/node/view/1119
 also be convertable into System Fw, GHC's existing, strongly-typeed
 intermediate language. ?
 
 Probably. Daan's current implementation uses MLF, which I believe is
 system F implemented for ML.
 
 (We're talking about the system in Daan Leijen's paper, Extensible
 Records With Scoped Labels. Good stuff.)

 You can change the project and update operators in the HList library
 to behave in exactly this way. At the moment they are constrained to
 not allow multiple identical labels in records. If this kind of
 access is considered useful, I can add it to the HList distribution.

This is true. I've implemented a small subset of HList that's able to
emulate Daan's three record operators using only fundeps and undecidable
instances.

*Main let r = foo .=. Bar .*. emptyRecord
*Main r
Record{foo=Bar}
*Main let r2 = foo .=. () .*. r  
*Main r2
Record{foo=(),foo=Bar}
*Main r2 .!. foo
()
*Main (r2 .-. foo) .!. foo
Bar

(This is actually *more* powerful than the system described in Daan's
paper, because labels are first class.)

While this is a testament to the power of Haskell's extended type-class
system, I'm not sure that it can replace a dedicated record system. In
his paper, Daan describes how to implement the records such that field
lookups take O(log n) or even O(1) time. HList can't do better than
O(n).

Of course, in the absence of a powerful record system, HList is the way
to go. Rather than decide on a new record system sight unseen, let's
implement them using HList and see how they feel.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe