Re: [Haskell-cafe] Is take behaving correctly?

2007-09-13 Thread rahn



pref_eq k xs ys = take k xs == take k ys



This seems to be a straightforward implementation with good properties.



Actually, no, at least not if implemented naively.


I choosed this example, since I stumbled on this question last week.  
Reputable mathematicians doing combinatorics on words are using  
exactly this definition! (Karhumäki, Harju) There are others (Holub),  
that use the (to the computer scientist) nicer(?)


pref_eq 0 _  _  = True
pref_eq _ _  [] = False
pref_eq _ [] _  = False
pref_eq k (x:xs) (y:ys) = x == y  pref_eq (k-1) xs ys

And as you guess it, there are lemmata (and probably theorems), that  
hold for one of the definitions only... Later, the mathematicians  
agree upton to call the first version pref_eq and the second  
pref_eq_proper.


And yes, you are right, just to change the behavior of take would not  
solve this issue. My topic was really more like



don't leap into coding a function before you know what it means


as you pointed out with nice words :-) This is not the main topic of  
the thread (is this true?) but we are in a cafe, so from time to time  
one adds some cents...


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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Jules Bean

Neil Mitchell wrote:

Hi


A more serious point is that in some cases we might want take to
underapproximate, or zip to truncate (or tail [] = [] ?). I don't
think there's
always a clear library choice here.


I have a zipWithEq function I often use, which crashes if the zip'd
lists aren't equal. I also have tailSafe which does the tailSafe [] =
[] behaviour. I created a hackage package safe for the tailSafe
function and others, http://www-users.cs.york.ac.uk/~ndm/safe/ . If
anyone wants to extend that with deliberately unsafe functions, such
as zipWithUnsafe, zipUnsafe, takeUnsafe etc, I'd be happy to accept a
patch. If not, I'll probably do it myself at some point in the
(potentially distant) future.


Of course we have tailSafe in the standard library (if I correctly 
understand what you mean) as drop 1 and headSafe as take 1.


I've rather got used to the exact details of head/tail, take/drop and 
zip but I agree it's a bit arbitrary: counterintuitive until you learn 
which is which and which is what.


Although I appluad the semantics of the safe package, I'm not delighted 
with the idea of replacing our concise elegant standard library names 
with uglyAndRatherLongCamelCaseNamesThatCouldBePerlOrEvenJava though. 
Conciseness of expression is a virtue.


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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Neil Mitchell
Hi

 Although I appluad the semantics of the safe package, I'm not delighted
 with the idea of replacing our concise elegant standard library names
 with uglyAndRatherLongCamelCaseNamesThatCouldBePerlOrEvenJava though.
 Conciseness of expression is a virtue.

They aren't that long - merely an extra 4 characters over the standard
one to indicate what the specific semantics are. If you can think of
better names, then I'm happy to make use of them.

Thanks

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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Jules Bean

Neil Mitchell wrote:

Hi


Although I appluad the semantics of the safe package, I'm not delighted
with the idea of replacing our concise elegant standard library names
with uglyAndRatherLongCamelCaseNamesThatCouldBePerlOrEvenJava though.
Conciseness of expression is a virtue.


They aren't that long - merely an extra 4 characters over the standard
one to indicate what the specific semantics are. If you can think of
better names, then I'm happy to make use of them.


No, they're not, and it wasn't intended as a slight against your naming 
choice. I don't have a better suggestion.


The problem I was really trying to point at, but didn't express at all 
well, was that a proliferation of similar functions with slightly 
different names (like Conor's four versions of zipWith) doesn't make a 
very elegant library API. It's nicer to settle on a smaller number of 
primitives. I don't actually have a solution that I think is good for 
the head/tail/take/drop issue :-(


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


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Stephane Bortzmeyer
On Thu, Sep 13, 2007 at 12:23:33AM +,
 Aaron Denney [EMAIL PROTECTED] wrote 
 a message of 76 lines which said:

 the characters read and written should correspond to the native
 environment notions and encodings.  These are, under Unix,
 determined by the locale system.

Locales, while fine for things like the language of the error messages
or the format to use to display the time, are *not* a good solution
for things like file names and file contents.

Even on a single Unix machine (without networking), there are
*several* users. Using the locale to find out the charset used for a
file name won't work if these users use different locales.

Same thing for file contents. The charset used must be marked in the
file (XML...) or in the metadata, somehow. Otherwise, there is no way
to exchange files or even to change the locale (if I switch from
Latin1 to UTF-8, what do my files become?)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Bulat Ziganshin
Hello Stefan,

Thursday, September 13, 2007, 4:40:17 AM, you wrote:

 I'm pretty sure Hugs does the right thing.  NHC is probably broken. In
 any case, we already have hGetBuf / hPutBuf in the standard base
 libaries for raw binary IO, so code that uses getChar for bytes really
 has no excuse.  We can and should fix the bug.

are you ever heard about backward compatibility? :/

-- 
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: getting crazy with character encoding

2007-09-13 Thread Andrea Rossato
On Thu, Sep 13, 2007 at 11:07:03AM +0200, Stephane Bortzmeyer wrote:
 On Thu, Sep 13, 2007 at 12:23:33AM +,
  Aaron Denney [EMAIL PROTECTED] wrote 
  a message of 76 lines which said:
 
  the characters read and written should correspond to the native
  environment notions and encodings.  These are, under Unix,
  determined by the locale system.
 
 Locales, while fine for things like the language of the error messages
 or the format to use to display the time, are *not* a good solution
 for things like file names and file contents.
 
 Even on a single Unix machine (without networking), there are
 *several* users. Using the locale to find out the charset used for a
 file name won't work if these users use different locales.

Yes indeed. And I find it a real mess. And I don't see any way out.

 Same thing for file contents. The charset used must be marked in the
 file (XML...) or in the metadata, somehow. Otherwise, there is no way
 to exchange files or even to change the locale (if I switch from
 Latin1 to UTF-8, what do my files become?)

Ok, you are perfectly right, but we live in an imperfect world and we
must come up with a solution. In my case I'm developing this prompt
for xmonad and a Chinese user wants directory and file names to be
correctly displayed. What else can I do but using locale technologies?
This is something I don't know.

The code below is not perfect but it works to some extent.
Nonetheless, if you have 2 users using an iso-8859-1 locale the first
and utf-8 one the second, non ascii characters in file names of the
first users will produce invalid character sequences for the second
users. The reverse will work, though.

I'm still puzzled and still find the thread title appropriate.

Thanks for your kind attention.

Andrea

The locale aware version of the previous code (needs hsc2hs)

{-# OPTIONS -fglasgow-exts #-}
import Prelude hiding (catch)
import System.Process
import System.IO
import Control.Monad
import System.Directory
import Foreign
import Foreign.C
import Data.Char
import Control.Exception

runProcessWithInput cmd args input = do
  (pin, pout, perr, ph) - runInteractiveProcess cmd args Nothing Nothing
  hPutStr pin input
  hClose pin
  output - hGetContents pout
  when (output==output) $ return ()
  hClose pout
  hClose perr
  waitForProcess ph
  return output

main = do
  setupLocale
  l - fmap lines $ runProcessWithInput /bin/bash [] ls ab*\n
  l' - mapM fromLocale l
  l'' - mapM toLocale l'
  putStrLn (show l')
  mapM_ putStrLn l''
  mapM_ (putStrLn . show . length) l'


-- This code comes from John Meacham's HsLocale
-- http://repetae.net/john/repos/HsLocale/
toLocale :: String - IO String
toLocale s = catch (stringToBytes s = return . map (chr . fromIntegral))
   (const $ return invalid character sequence)

fromLocale :: String - IO String
fromLocale s = bytesToString (map (fromIntegral . ord) s) 
  `catch` \_ -  return invalid character sequence 

stringToBytes :: String - IO [Word8]
stringToBytes cs = (withIConv  UTF-32 $ \ic - convertRaw ic cs) 

bytesToString :: [Word8] - IO String
bytesToString xs =  (withIConv UTF-32  $ \ic -  convertRaw ic xs) = 
return . f where
f ('\65279':xs) = xs   -- discard byte order marker
f xs = xs

newtype IConv = IConv (#type intptr_t)
deriving(Num,Eq,Show)

foreign import ccall unsafe iconv.h iconv_open
  iconv_open :: Ptr CChar - Ptr CChar - IO IConv
foreign import ccall unsafe iconv.h iconv_close
  iconv_close :: IConv - IO CInt
foreign import ccall unsafe iconv.h iconv 
  iconv :: IConv - Ptr (Ptr CChar) - Ptr CSize - Ptr (Ptr CChar) - Ptr 
CSize - IO CInt

withIConv :: String - String - (IConv - IO a) - IO a 
withIConv to from action = bracket open close action where
close ic = throwErrnoIfMinus1_ iconv_close (iconv_close ic)
open = throwErrnoIfMinus1 iconv_open iopen
iopen = do
withCAString to $ \to - do
withCAString from $ \from - do
iconv_open to from

convertRaw :: (Storable a, Storable b) = IConv - [a] - IO [b]
convertRaw ic xs = do 
with (fromIntegral $ sizeOf (head xs) * length xs) $ \inptrSz - do
withArray xs $ \arr - do  
with (castPtr arr) $ \inptr - do
allocaBytes (1024) $ \outptr - do
with outptr $ \outptrptr - do
with 1024 $ \outptrSz - do
let outSz = fromIntegral $ sizeOf $ unsafePerformIO (peek outptr) 
let 
go = do 
ret - iconv ic inptr inptrSz (castPtr outptrptr) outptrSz 
err - getErrno
case (ret,err) of
(-1,_) | err == e2BIG - do
oz - peek outptrSz
x - peekArray ((1024 - fromIntegral oz) `div` outSz) 
(castPtr outptr) 
poke outptrptr outptr
poke outptrSz 1024
y - go
return $ x ++ y
(-1,_) - throwErrno iconv
(_,_) - do
oz - peek outptrSz
peekArray ((1024 

Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Ketil Malde
On Thu, 2007-09-13 at 09:56 +0100, Jules Bean wrote:
 Neil Mitchell wrote:
  Hi
  
  Although I appluad the semantics of the safe package, I'm not delighted
  with the idea of replacing our concise elegant standard library names
  with uglyAndRatherLongCamelCaseNamesThatCouldBePerlOrEvenJava though.
  Conciseness of expression is a virtue.
  
  They aren't that long - merely an extra 4 characters over the standard
  one to indicate what the specific semantics are. If you can think of
  better names, then I'm happy to make use of them.
 
 No, they're not, and it wasn't intended as a slight against your naming 
 choice. I don't have a better suggestion.

Isn't there sort of a tradition for 'unsafe' to mean dangerous
territory, beyond mere domain limitations for functions, so to call this
'safe' may be a bit misleading? 

Similarly, I expect foo and foo' to be equivalent, except for strictness
properties, but perhaps an underscore could be used for slightly
different behaviors (interpretations, as it were)?  tail_ or zip_,
anyone?

-k

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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Pepe Iborra


On 13/09/2007, at 0:06, Don Stewart wrote:


ok:
In Monad.Reader 8, Conrad Parker shows how to solve the Instant  
Insanity
puzzle in the Haskell type system.  Along the way he  
demonstrates very

clearly something that was implicit in Mark Jones' Type Classes with
Functional Dependencies paper if you read it very very carefully  
(which
I hadn't, but on re-reading it is there).  That is, Haskell types  
plus

multiparameter type classes plus functional dependencies is a logic
programming language.  In fact it is a sufficiently powerful  
language to

emulate any Turing machine calculation as a type checking problem.

So we have

C++ : imperative language whose type system is a Turing-complete
  functional language (with rather twisted syntax)

Haskell: functional language whose type system is a Turing-
  complete logic programming language (with rather twisted
  syntax)

Since not all Turing machines halt, and since the halting problem is
undecidable, this means not only that some Haskell programs will make
the type checker loop forever, but that there is no possible meta-
checker that could warn us when that would happen.

I've been told that functional dependencies are old hat and there is
now something better.  I suspect that better here means worse.


Better here means better -- a functional language on the type  
system,

to type a functional language on the value level.

-- Don


For a taste, see Instant Insanity transliterated in this functional  
language:


http://hpaste.org/2689

NB: it took me 5 minutes, and that was my first piece of coding ever  
with Type families



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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Neil Mitchell
Hi

 Similarly, I expect foo and foo' to be equivalent, except for strictness
 properties, but perhaps an underscore could be used for slightly
 different behaviors (interpretations, as it were)?  tail_ or zip_,
 anyone?

There are 4 variants of tail:

tail :: [a] - [a] -- normal
tailDef :: [a] - [a] - [a] -- returns the first argument on []
tailMay :: [a] - Maybe [a] -- returns a Nothing
tailNote :: String - [a] - [a] -- crashes, but with a helpful message
tailSafe :: [a] - [a] -- returns [] on []

tail_ would not be a good name!

Thanks

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


Re: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Ketil Malde
On Wed, 2007-09-12 at 17:40 -0700, Stefan O'Rear wrote:
 On Thu, Sep 13, 2007 at 12:23:33AM +, Aaron Denney wrote:
  Unfortunately, at this point it is a well entrenched bug, and changing
  the behaviour will undoubtedly break programs.
 ...
  There should be another system for getting the exact bytes in and 
  out (as Word8s, say, rather than Chars), 

 I'm pretty sure Hugs does the right thing.

..which makes me wonder what the right thing actually is?

Since IO on Unix (or at least on Linux) consists of bytes, I don't see
how a Unicode-only interface is ever going to do the 'right thing' for
all people.

One possible solution might be to have IO functions deal with [Word8]
instead of [Char]. If string and character constants were polymorphic,
Char and String made aliases for byte-based types, and a new type
introduced for Unicode characters, it might even be possible to fix
without breaking absolutely all legacy code.

But even this would probably only fix the Unix side of things.

-k

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


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Aaron Denney
On Thu, Sep 13, 2007 at 11:07:03AM +0200, Stephane Bortzmeyer wrote:
 On Thu, Sep 13, 2007 at 12:23:33AM +,
  Aaron Denney [EMAIL PROTECTED] wrote 
  a message of 76 lines which said:
 
  the characters read and written should correspond to the native
  environment notions and encodings.  These are, under Unix,
  determined by the locale system.
 
 Locales, while fine for things like the language of the error messages
 or the format to use to display the time, are *not* a good solution
 for things like file names and file contents.

I never claimed it was a good system, merely that it was the system.
Yes, serious applications should use byte oriented I/O and explicitly
manage character sets when necessary.  STDIO in general and terminal
interaction in particular should use the locale selected by the user.

 Even on a single Unix machine (without networking), there are
 *several* users. Using the locale to find out the charset used for a
 file name won't work if these users use different locales.
 
 Same thing for file contents. The charset used must be marked in the
 file (XML...) or in the metadata, somehow.

For file system and network access, the justification is a bit more
clouded, but the interfaces there _should not_ be character interfaces.
Character interfaces are _lies_; Word8s are what actually get passed,
and trying to treat them as unicode characters with any fixed mapping
breaks.  At best we get an extremely leaky abstraction.

Filesystems are not uniform across systems, yet Haskell tries to present
a uniform view that manages to capture exactly no existing system.

File contents (almost) everywhere are streams of bytes (ignoring, say,
old record-based OSes, palm databases, and mac resource forks etc.)
Almost all file systems use a hierarchical directory system, but with
significant differences.  Under unixes the names are NUL-terminated
bytestrings that can't contain slashes.  New Macs and Windows have
specific character encodings (UTF-8, and UTF-16, respectively).  DOS,
old Macs, and windows have multiple roots and various directory
seperators and forbidden characters.

Trying to specify some API that is usable for robust programs that work
on any of these is hard.  I'd actually have preferred that the standard
didn't even try, and instead provided system-specific annexes.
Then an external library that was freer to evolve could try to solve
the problem of providing a uniform interface that would not defy
platform expectations.

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


RE: Re[2]: [Haskell-cafe] Basic FFI with GHC

2007-09-13 Thread Simon Peyton-Jones
|  So, after more searching on the internet and some RTFM, I think I
|  found my answer, and it seems to work, but I don't know if it's the
|  right answer to generalize from.
|
| i have added your recipe to http://www.haskell.org/haskellwiki/FFI_cook_book

Thank you Bulat.

There's also a GHC page about the FFI here:
http://haskell.org/haskellwiki/GHC/Using_the_FFI

It seems reasonable to have two: one generic to Haskell and one specific to GHC.

- But it would make sense to add a pointer from the generic one to the GHC one
- And perhaps some of the material on the GHC page is actually generic,
and should be moved?

Simon

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


[Haskell-cafe] Re: help getting happy

2007-09-13 Thread Simon Marlow

Greg Meredith wrote:

Haskellians,

The code pasted in below causes Happy to return parE when invoked with 
happy rparse.y -i . Is there anyway to get Happy to give me just a wee 
bit more info as to what might be causing the parE (which i interpret a 
'parse error').


Please grab a more recent version of Happy from darcs:

  http://darcs.haskell.org/happy

the parE thing was a bug in the error handling introduced in the last 
release.  You'll need Cabal-1.2 in order to build the latest Happy.


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


Re[4]: [Haskell-cafe] Basic FFI with GHC

2007-09-13 Thread Bulat Ziganshin
Hello Simon,

Thursday, September 13, 2007, 2:12:18 PM, you wrote:

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

 There's also a GHC page about the FFI here:
 http://haskell.org/haskellwiki/GHC/Using_the_FFI

this page, despite its name, is only about dealing with Visual C++ via
DLLs. it's cookbook-style material, although rather long to be merged
with former page

 It seems reasonable to have two: one generic to Haskell and one specific to 
 GHC.
 - But it would make sense to add a pointer from the generic one to the GHC one

done

 - And perhaps some of the material on the GHC page is actually generic,
 and should be moved?

current ghc material is step-by-step recipe of implementing one particular
application and i think that another description should be written if
we want split it into ghc-specific and common parts

moreover, i bet that there are not too much non-ghc FFI users, so it
will be hard and almost useless to work on such splitting :(


-- 
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: Is take behaving correctly?

2007-09-13 Thread Jeff Polakow
Hello,
 
 There are 4 variants of tail:
 
 tail :: [a] - [a] -- normal
 tailDef :: [a] - [a] - [a] -- returns the first argument on []
 tailMay :: [a] - Maybe [a] -- returns a Nothing
 tailNote :: String - [a] - [a] -- crashes, but with a helpful message
 tailSafe :: [a] - [a] -- returns [] on []
 
Is there a reason for not having

tailM :: Monad m = [a] - m [a]

which, at least for me, is much more useful?

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Neil Mitchell
Hi

 Is there a reason for not having

 tailM :: Monad m = [a] - m [a]

 which, at least for me, is much more useful?

No, that probably is a much more sensible choice. Patches welcome :)

Thanks

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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Lutz Donnerhacke
* Neil Mitchell wrote:
 There are 4 variants of tail:

 tail :: [a] - [a] -- normal
 tailDef :: [a] - [a] - [a] -- returns the first argument on []
 tailMay :: [a] - Maybe [a] -- returns a Nothing
 tailNote :: String - [a] - [a] -- crashes, but with a helpful message
 tailSafe :: [a] - [a] -- returns [] on []

From the logical point of view tailMay is the right one.
It pushes the error handling to the caller programm.

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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Neil Mitchell
Hi

 From the logical point of view tailMay is the right one.
 It pushes the error handling to the caller programm.

 tail = fromJust . tailMay

The error messages suffer:

tail [] = error: fromJust Nothing

That's why I supplied tailNote, where tailNote foo broke its
invariant! [] gives the message error: tail [], foo broke its
invariant!

Thanks

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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Jules Bean

Jeff Polakow wrote:


Hello,
 
  There are 4 variants of tail:

 
  tail :: [a] - [a] -- normal
  tailDef :: [a] - [a] - [a] -- returns the first argument on []
  tailMay :: [a] - Maybe [a] -- returns a Nothing
  tailNote :: String - [a] - [a] -- crashes, but with a helpful message
  tailSafe :: [a] - [a] -- returns [] on []
 
Is there a reason for not having

tailM :: Monad m = [a] - m [a]



Monads are not an (elegant, or deliberate) abstraction of failure.

Jules

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


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Ketil Malde
On Thu, 2007-09-13 at 13:56 +0100, Neil Mitchell wrote:
  tail = fromJust . tailMay
 
 The error messages suffer [..]
 That's why I supplied tailNote

Still, given tailMay, we have:

tailDef xs   = maybe xs id . tailMay
tailNote msg = tailDef (error msg)
tailSafe = tailDef []
tail = tailNote tail: empty list

which I suppose was Lutz's point?

(My rather ugly preference is to #define tail so that an error message
contains source code location.)

-k


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


Re: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Stefan O'Rear
On Thu, Sep 13, 2007 at 12:06:15PM +0200, Ketil Malde wrote:
 On Wed, 2007-09-12 at 17:40 -0700, Stefan O'Rear wrote:
  On Thu, Sep 13, 2007 at 12:23:33AM +, Aaron Denney wrote:
   Unfortunately, at this point it is a well entrenched bug, and changing
   the behaviour will undoubtedly break programs.
  ...
   There should be another system for getting the exact bytes in and 
   out (as Word8s, say, rather than Chars), 
 
  I'm pretty sure Hugs does the right thing.
 
 ..which makes me wonder what the right thing actually is?
 
 Since IO on Unix (or at least on Linux) consists of bytes, I don't see
 how a Unicode-only interface is ever going to do the 'right thing' for
 all people.

I never said it was Unicode-only.

hGetBuf / hPutBuf - Raw Word8 access
getChar etc   - Uses locale info

Stefan


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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Pepe Iborra
For a taste, see Instant Insanity transliterated in this functional  
language:


http://hpaste.org/2689



I thought I'd better paste here the code for Instant Insanity with  
Type Families. Otherwise it will vanish in a short time.

I took the opportunity to clean it up a bit.

Although AT are not a supported feature, the code works in a 6.8.1  
snapshot.
But note that you cannot actually see the solution, as there is no  
way to ask

GHCi to display the normalized types.

My favorite bit is:
*  type instance Map f Nil = Nil
*  type instance Map f (x:::xs) = Apply f x ::: Map f xs

\begin{code}
  import Prelude hiding (all, flip, map, filter)
  u = undefined

  data R  -- Red
  data G  -- Green
  data B  -- Blue
  data W  -- White

  data Cube u f r b l d

  type CubeRed = Cube R R R R R R
  type CubeBlue = Cube B B B B B B
  type Cube1 = Cube B G W G B R
  type Cube2 = Cube W G B W R R
  type Cube3 = Cube G W R B R R
  type Cube4 = Cube B R G G W W

  data True
  data False

  type family And b1 b2
  type instance And True  True = True
  type instance And True  False= False
  type instance And False True = False
  type instance And False False= False

  data Nil
  data Cons x xs
  data x ::: xs
  infixr 5 :::

  type family ListConcat l1 l2
  type instance ListConcat Nil l = l
  type instance ListConcat (x:::xs) ys = x:::(ListConcat xs ys)

  type family Apply f a

  data Rotation
  data Twist
  data Flip
  type instance Apply Rotation (Cube u f r b l d) = Cube u r b l f d
  type instance Apply Twist(Cube u f r b l d) = Cube f r u l d b
  type instance Apply Flip (Cube u f r b l d) = Cube d l b r f u

  type family Map f xs
  type instance Map f Nil = Nil
  type instance Map f (x:::xs) = Apply f x ::: Map f xs

  type family Filter f xs
  type instance Filter f Nil = Nil
  type instance Filter f (x:::xs) = AppendIf (Apply f x) x (Filter f  
xs)


  type family AppendIf b x ys
  type instance AppendIf True x ys  = x ::: ys
  type instance AppendIf False x ys = ys

  type family MapAppend f xs
  type instance MapAppend f Nil = Nil
  type instance MapAppend f (x:::xs) = ListConcat (x:::xs) (Map f  
(x:::xs))


  type family MapAppend2 f xs
  type instance MapAppend2 f Nil = Nil
  type instance MapAppend2 f (x:::xs)  = ListConcat (x:::xs)  
(MapAppend f (Map f (x:::xs)))


  type family MapAppend3 f xs
  type instance MapAppend3 f Nil = Nil
  type instance MapAppend3 f (x:::xs) = ListConcat xs (MapAppend2 f  
(Map f (x:::xs)))



  data Orientations
  type instance Apply Orientations c = MapAppend3 Rotation (
   MapAppend2 Twist (
   MapAppend Flip (c:::Nil)))
  type family NE x y
  type instance NE R R = False
  type instance NE R G = True
  type instance NE R B = True
  type instance NE R W = True
  type instance NE G R = True
  type instance NE G G = False
  type instance NE G B = True
  type instance NE G W = True
  type instance NE B R = True
  type instance NE B G = True
  type instance NE B B = False
  type instance NE B W = True
  type instance NE W R = True
  type instance NE W G = True
  type instance NE W B = True
  type instance NE W W = False

  type family All l
  type instance All Nil = True
  type instance All (False ::: xs) = False
  type instance All (True ::: xs)  = All xs

  type family Compatible c1 c2
  type instance Compatible (Cube u1 f1 r1 b1 l1 d1) (Cube u2 f2 r2  
b2 l2 d2) =

  All (NE f1 f2 ::: NE r1 r2 ::: NE b1 b2 ::: NE l1 l2)

  type family Allowed c cs
  type instance Allowed c Nil = True
  type instance Allowed c (y ::: ys) = And (Compatible c y) (Allowed  
c ys)


  type family Solutions cs
  type instance Solutions Nil = (Nil ::: Nil)
  type instance Solutions (c ::: cs) = AllowedCombinations (Apply  
Orientations c) (Solutions cs)


  type family AllowedCombinations os sols
  type instance AllowedCombinations os Nil = Nil
  type instance AllowedCombinations os (s ::: sols) =
  ListConcat (AllowedCombinations os sols) (MatchingOrientations  
os s)


  type family MatchingOrientations os sol
  type instance MatchingOrientations Nil sol = Nil
  type instance MatchingOrientations (o ::: os) sol =
  AppendIf (Allowed o sol) (o:::sol) (MatchingOrientations os sol)

  type Cubes = (Cube1 ::: Cube2 ::: Cube3 ::: Cube4 ::: Nil)
  solution = u :: Solutions Cubes

\end{code}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread David Roundy
On Thu, Sep 13, 2007 at 06:49:59AM -0700, Stefan O'Rear wrote:
 On Thu, Sep 13, 2007 at 12:06:15PM +0200, Ketil Malde wrote:
  On Wed, 2007-09-12 at 17:40 -0700, Stefan O'Rear wrote:
   On Thu, Sep 13, 2007 at 12:23:33AM +, Aaron Denney wrote:
Unfortunately, at this point it is a well entrenched bug, and changing
the behaviour will undoubtedly break programs.
   ...
There should be another system for getting the exact bytes in and 
out (as Word8s, say, rather than Chars), 
  
   I'm pretty sure Hugs does the right thing.
  
  ..which makes me wonder what the right thing actually is?
  
  Since IO on Unix (or at least on Linux) consists of bytes, I don't see
  how a Unicode-only interface is ever going to do the 'right thing' for
  all people.
 
 I never said it was Unicode-only.
 
 hGetBuf / hPutBuf - Raw Word8 access
 getChar etc   - Uses locale info

The problem is that the type of openFile and getArgs is wrong, so there's
no right way to get a Handle (other than stdin) to read from in the first
place, unless we're willing to allow the current weird behavior of treating
a [Char] as [Word8].
-- 
David Roundy
Department of Physics
Oregon State University


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


[Haskell-cafe] Memory leak or wrong use of Array ?

2007-09-13 Thread L.Guo
Hi MailList Haskell-Cafe:

I am tring to solve Project Euler problem 70.
And write some code. (will at the end of this mail)
And, I run the code in GHCi.

The problem is that, when the input is 1,000,000, it works 
fine, when the input is up to 10,000,000, the memory GHCi 
used increase very fast and did not stop.

Is this a memory leak ? or, is there some mis-understand 
about array ?

Regards
--
-- Mudules :
import Data.Array.IO
import Foreign ( unsafePerformIO )
-- Codes :
p070_solve = putStrLn . show $ solutionOf 1000
  where
isPerm a b = sort (show a) == sort (show b)
phis n = unsafePerformIO $ do
arr - newArray (2,n) (False,1/1) :: Fractional t = IO (IOArray Int 
(Bool,t))
mapM_ (sieve arr n) [2..n]
factors - getElems arr
return . map (\(n,(b,f)) - (n,floor $ toRational n*f)) $ zip [2..n] 
factors
  where
sieve arr ubound p = do
(b,o) - readArray arr p
if b then return () else
  mapM_ (update arr (toRational p)) . takeWhile (=ubound) $ 
iterate (+p) p
update arr p i = do
(_,o) - readArray arr i
writeArray arr i (True,o*(p-1)/p)
solutionOf = snd . minimum
   . map (\(n,phi)-(toRational n / toRational phi,n))
   . filter (uncurry isPerm) . phis
--
L.Guo
2007-09-14

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


[Haskell-cafe] Re: help getting happy

2007-09-13 Thread Greg Meredith
Simon,

Cheers. i solved the problem before i saw your email. The Happy i got was a
result of invoking

port install happy

What's the drift between macports and happy versions? Is there a way of
using Happy without being on or even near the cutting edge of development?

Best wishes,

--greg

On 9/13/07, Simon Marlow [EMAIL PROTECTED] wrote:

 Greg Meredith wrote:
  Haskellians,
 
  The code pasted in below causes Happy to return parE when invoked with
  happy rparse.y -i . Is there anyway to get Happy to give me just a wee
  bit more info as to what might be causing the parE (which i interpret a
  'parse error').

 Please grab a more recent version of Happy from darcs:

http://darcs.haskell.org/happy

 the parE thing was a bug in the error handling introduced in the last
 release.  You'll need Cabal-1.2 in order to build the latest Happy.

 Cheers,
 Simon




-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
505 N 72nd St
Seattle, WA 98103

+1 206.650.3740

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


Re: [Haskell-cafe] Re: help getting happy

2007-09-13 Thread Paul Brown
On 9/13/07, Greg Meredith [EMAIL PROTECTED] wrote:
 Cheers. i solved the problem before i saw your email. The Happy i got was a
 result of invoking

 port install happy

 What's the drift between macports and happy versions? Is there a way of
 using Happy without being on or even near the cutting edge of development?

You can freely intermix bits and pieces installed via port and via
traditional (e.g., runghc Setup.hs install or make install) means,
provided that you have the paths set up properly.

-- 
[EMAIL PROTECTED]
http://mult.ifario.us/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Andrew Coppin

Jules Bean wrote:
I'm not delighted with the idea of replacing our concise elegant 
standard library names with 
uglyAndRatherLongCamelCaseNamesThatCouldBePerlOrEvenJava though. 
Conciseness of expression is a virtue.


I, on the other hand, I'm not delighted with names such as Eq and 
Ord. (Would it be *so* hard to write Equal and Ordered?) This is 
one of the main things I'd have done differently if I'd designed 
Haskell... not that anybody is too bothered. ;-)


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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Don Stewart
 Better here means better -- a functional language on the type  
 system,
 to type a functional language on the value level.
 
 -- Don
 
 For a taste, see Instant Insanity transliterated in this functional  
 language:
 
 http://hpaste.org/2689
 
 NB: it took me 5 minutes, and that was my first piece of coding ever  
 with Type families

Wow. Great work! 

The new age of type hackery has dawned.

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


[Haskell-cafe] MonadGL - Partitioning effects without giving up type inference

2007-09-13 Thread Jules Bean

The OpenGL bindings which come bundled with ghc are a really great
example of how even an almost-literal port of a C API can still
be easier to work with in haskell than it is in C, because of the
benefits of type inference and powerful abstractions. Even the
ability to mapM_ is a tool to make C programmers envious, and there
are useful combinators like preservingMatrix to guarantee pairing of
pushes and pops.

Because the bindings are ported over using the FFI, all the GL calls
are in the IO monad. GL is build around state machines, so it's not at
all surprising to end up in some kind of state monad. However, we find
that the type system is not powerful enough to distinguish between

myActionWhichOnlyMakesGLCalls :: IO ()

and

myActionWhichMixesGLAndIO :: IO ()

It would be much nicer if the type-system could distinguish the two.
One case in point is that an arbitrary IO action can modify IORefs,
and it would be nice to have actions whose type guaranteed that they
didn't do that.

It's fairly simple to imagine something like the following:


 {-# OPTIONS -fglasgow-exts #-}

(extensions are only for deriving (Monad), it's not important)


 newtype GL a = GL { runGL :: IO a } deriving (Monad)

 unsafeIOToGL :: IO a - GL a
 unsafeIOToGL = GL

The intention here of course is that we export 'runGL' which is safe,
having type GL a - IO a, but don't export unsafeIOToGL.

Then we have lots of functions which are imported via the FFI and
end up with IO types, here is a trival example:

 _foo :: IO ()
 _foo = putStrLn OpenGL!

And we embed them into the GL monad. No other module can corrupt our
GL monad because we don't export unsafeIOToGL.

 foo :: GL ()
 foo = unsafeIOToGL _foo

As far as it goes, this technique is absolutely fine. We end up being
able to write actions entirely in the GL monad:

*Main :t do { foo ; foo ; foo }
do { foo ; foo ; foo } :: GL ()

...as well as actions which mix general IO and GL calls :

*Main :t do { runGL foo ; putStrLn Not a GL call ; runGL foo }
do { runGL foo ; putStrLn Not a GL call ; runGL foo } :: IO ()

The point of this message is actually to get rid of those annoying
'runGL' calls. When writing an IO action I want to be able to freely
intermix IO and GL calls. When writing a GL-only action, I want to
only use GL calls. And I want the type system to enforce that; and
ideally, infer it too.

So we define a type-class for monad which can perform GL :

 class Monad m = MonadGL m where
 runMonadGL :: m a - IO a
 embedGL:: GL a - m a

And we write an instance for IO:

 instance MonadGL IO where
 runMonadGL = id
 embedGL= runGL

Now we are able to bind our FFI call _foo slightly differently:

 foo' :: MonadGL m = m ()
 foo' = embedGL foo

This is interesting because, although we know that IO is in fact
the only instance of MonadGL, there might in principle be others.
(For example, GL is itself an instance of MonadGL if you put
runMonadGL = runGL and embedGL = id). The type signature for foo'
guarantees that it will run in *any* MonadGL, and therefore can't
use any IO-specific effects, only the GL ones.

Now we get the automatic type inference we want:

*Main :t do { foo' ; foo' ; foo' }
do { foo' ; foo' ; foo' } :: (MonadGL t) = t ()

This only performs GL actions, no IO.

*Main :t do { foo' ; putStrLn Normal ; foo' }
do { foo' ; putStrLn Normal ; foo' } :: IO ()

The single IO call here forces the type to IO, but we are not
required to put noisy 'runGL's in front of every GL call.

This technique is quite scalable in that you can have any number
of MonadFoos representing different librarys with different kinds
of state, and (as long as you don't mind the modest blow-up
in type signature size) you get, for an arbitrary action, a
type signature which pins down precisely what kinds of side-effect
the action can have.

It would, however, be a real pain to run through all the 'foreign'
calls in the rather large GL library and add appropriate wrappers
of the form 'embedGL . unsafeIOToGL'. Definitely a job for
an automated tool.

Incidentally, I don't believe this technique has any performance
implication at all. The newtypes are all erased at compile time.

Any comments? I'm sure this has been shown before but I don't
remember where.

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


Re: [Haskell-cafe] haskell and reflection

2007-09-13 Thread Don Stewart
lgreg.meredith:
Haskellians,
 
Am i wrong in my assessment that the vast majority of reflective machinery
is missing from Haskell? Specifically,
 
  * there is no runtime representation of type available for programmatic
representation

  * there is no runtime representation of the type-inferencing or checking
machinery

  * there is no runtime representation of the evaluation machinery

  * there is no runtime representation of the lexical or parsing machinery

So there is library support for all of this, in various forms:

* lexer, parser, type checker, evaluator:
ghc-api
hs-plugins

* lexer, parser, pretty printer
many parser libs (Language.Haskell, Template Haskell)

* runtime type representation
Data.Typeable

* reflecting code to data:
Data.Generics

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


[Haskell-cafe] Vital for real Haskell?

2007-09-13 Thread Peter Verswyvelen
I showed Vital (http://www.cs.kent.ac.uk/projects/vital) to some 
teachers at my university and they where really enthousiastic.


IMHO the Haskell community needs something like this, but for *real* 
Haskell (preferable with extensions), and not using Java...


Is any work being done on something like this?

Thanks,
Peter



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


Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-13 Thread J. Garrett Morris
I believe that rnf from the Control.Parallel.Strategies library
shipped with GHC 6.6.1 is equivalent to deepSeq, as in:

x `deepSeq` yis equivalent to   rnf x `seq` y

Isn't it?

 /g

On 9/12/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:
 Thanks for all the info.

 It's really good news that code coverage is now part of the GHC compiler!

 Any more info on that deep seq? I can't find it in the libraries that come
 with GHC 6.6.1. It seems to be part of Control.Strategies.DeepSeq of HXT.
 This is a separate download?

 Intuitively, I would say deep seq forces strict evaluation of the complete
 graph of its first argument? Is this correct?

 Peter

 -Original Message-
 From: Don Stewart [mailto:[EMAIL PROTECTED]
 Sent: Tuesday, September 11, 2007 10:11 PM
 To: Peter Verswyvelen
 Cc: Neil Mitchell; Haskell-Cafe
 Subject: Re: [Haskell-cafe] Building production stable software in Haskell

 bf3:
  Well, I actually meant more something like the imperative equivalences
  of code coverage tools and unit testing tools, because I've read
  rumors that in Haskell, unit testing is more difficult because lazy
  evaluation will cause the units that got tested to be evaluated

 We have full control over evaluation though, with bang patterns, seq and
 deep seq.

 Generally unit testing is generalised to property testing with QuickCheck,
 though.

 For code coverage, combined with testing, use HPC, the program coverage tool

 now in GHC head.

 -- Don

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



-- 
The man who'd introduced them didn't much like either of them, though
he acted as if he did, anxious as he was to preserve good relations at
all times. One never knew, after all, now did one now did one now did
one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Peter Verswyvelen
This is all very cool stuff, but sometimes I wander if it isn't possible 
to drop the special languages for fiddling with types, and introduce 
just a single language which has no types, only raw data from which you 
can built your own types (as in the old days when we used macro 
assemblers ;-), but the language has two special keywords: static and 
dynamic, where code annotated with static runs in the compiler domain, 
and code annotated with dynamic runs in application domain. Of course, 
I don't know much about this, so this idea might be totally insane ;-) 
Probably this is impossible because of the halting problem or something...


Pete

Don Stewart wrote:
Better here means better -- a functional language on the type  
system,

to type a functional language on the value level.

-- Don
  
For a taste, see Instant Insanity transliterated in this functional  
language:


http://hpaste.org/2689

NB: it took me 5 minutes, and that was my first piece of coding ever  
with Type families



Wow. Great work! 


The new age of type hackery has dawned.

-- Don
___
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] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Derek Elkins
On Thu, 2007-09-13 at 11:12 -0700, Don Stewart wrote:
  Better here means better -- a functional language on the type  
  system,
  to type a functional language on the value level.
  
  -- Don
  
  For a taste, see Instant Insanity transliterated in this functional  
  language:
  
  http://hpaste.org/2689
  
  NB: it took me 5 minutes, and that was my first piece of coding ever  
  with Type families
 
 Wow. Great work! 
 
 The new age of type hackery has dawned.

Is the type level functional language non-strict? (Is there a flag that
will allow non-terminating associated type programs?)

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


Re: [Haskell-cafe] MonadGL - Partitioning effects without giving up type inference

2007-09-13 Thread Derek Elkins
On Thu, 2007-09-13 at 19:34 +0100, Jules Bean wrote:

 
 Any comments? I'm sure this has been shown before but I don't
 remember where.

The Monad Transformer Library essentially does this, the types you get
are along the lines of:

foo :: (Monad m, MonadState s m, MonadReader r m) = m Int

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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread ok

I wrote:

Since not all Turing machines halt, and since the halting problem is
undecidable, this means not only that some Haskell programs will make
the type checker loop forever, but that there is no possible meta-
checker that could warn us when that would happen.


On 13 Sep 2007, at 4:27 pm, Stefan Holdermans wrote:
Do not forget that both functional dependencies and associated  
types come with syntactic restrictions that are there just to  
tame the Turing completeness, i.e., to guarantee that type  
checking will actually terminate.


I don't know anything about associated types, so can't comment on those.
But on the subject of functional dependencies, you and the author of the
article in Monad.Reader 8 *cannot* both be right, because the whole
point of that article is to explain how to program in the type system,
using, amongst other things, conditionals and recursion, in such a way
that a Turing machine can surely be simulated.  If there is some
restriction to guarantee termination, then those techniques can't work.




Admittedly, it's my experience that whenever one wants to do  
something interesting (and here I mean interesting in a way that  
you would probably label as rather twisted ;-)), one has to  
bypass these restrictions (and, hence, allow for potentially  
undecidable instances).


Ah, now we have it.  To quote Conrad Parker:
This tutorial uses the Haskell98 type system extended with
multi-parameter typeclasses and undecidable instances.
We need to enable some GHC extensions to play with this type- 
hackery:

$ ghci -fglasgow-exts -fallow-undecidable-instances

That is the combination I'm talking about.

Now, I haven't really worked with associated types (or, for that  
matter, associated type synonyms), but my hope is that, when using  
those, turning off the checks is needed less often. We'll see.


If you hope that, then we probably agree more than you might think.
My point is that the combination exists and is being explained so that
people can use it, and that the result is comparable in C++.  (Imagine
Dame Edna Everage saying I mean that in a loving way, possums.)

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


[Haskell-cafe] haskell on llvm?

2007-09-13 Thread brad clawsie
has anyone ever considered using llvm as a infrastructure for haskell
compilation? it wold seem people are looking at building frontends for
scheme, ocaml, etc. i don't know if an alternate backend is
appropriate, but it would seem to be an interesting way to aggregate
the best thinking for various optimizations over a more diverse group
of developers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Thomas Schilling
On Fri, 2007-09-14 at 10:42 +1200, ok wrote:
 I wrote:
  Since not all Turing machines halt, and since the halting problem is
  undecidable, this means not only that some Haskell programs will make
  the type checker loop forever, but that there is no possible meta-
  checker that could warn us when that would happen.
 
 On 13 Sep 2007, at 4:27 pm, Stefan Holdermans wrote:
  Do not forget that both functional dependencies and associated  
  types come with syntactic restrictions that are there just to  
  tame the Turing completeness, i.e., to guarantee that type  
  checking will actually terminate.
 
 I don't know anything about associated types, so can't comment on those.
 But on the subject of functional dependencies, you and the author of the
 article in Monad.Reader 8 *cannot* both be right, because the whole
 point of that article is to explain how to program in the type system,
 using, amongst other things, conditionals and recursion, in such a way
 that a Turing machine can surely be simulated.  If there is some
 restriction to guarantee termination, then those techniques can't work.
 
 
  Admittedly, it's my experience that whenever one wants to do  
  something interesting (and here I mean interesting in a way that  
  you would probably label as rather twisted ;-)), one has to  
  bypass these restrictions (and, hence, allow for potentially  
  undecidable instances).
 
 Ah, now we have it.  To quote Conrad Parker:
  This tutorial uses the Haskell98 type system extended with
  multi-parameter typeclasses and undecidable instances.
  We need to enable some GHC extensions to play with this type- 
 hackery:
  $ ghci -fglasgow-exts -fallow-undecidable-instances
 
 That is the combination I'm talking about.
 
  Now, I haven't really worked with associated types (or, for that  
  matter, associated type synonyms), but my hope is that, when using  
  those, turning off the checks is needed less often. We'll see.
 
 If you hope that, then we probably agree more than you might think.
 My point is that the combination exists and is being explained so that
 people can use it, and that the result is comparable in C++.  (Imagine
 Dame Edna Everage saying I mean that in a loving way, possums.)

The type system doesn't help you avoid writing non-terminating programs,
so i see no problem with it being possible giving programmers the power
to express and check more complex properties of their programs -- as
long as type-checking remains sound.  From a practical standpoint,
non-terminating type checks are just as much a bug as non-terminating
library functions.  Type systems need more thought anyways, so why not
make sure it's terminating, too?  The other extreme is to use dependent
types everywhere, but this has a bit more drastic consequences to the
accessibility and practicality of the language.

I don't think this will become a mainstream tool any time soon, but it
may turn out to be very valuable to library authors.  We also shouldn't
forget that this is a brand-new feature and requires proper evaluation;
how better could this be achieved than by having it included as an
optional feature in a mature and well-used compiler?  I am glad that
Haskellers try to integrate theory and practice that nicely.

/ Thomas

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


Re: [Haskell-cafe] haskell on llvm?

2007-09-13 Thread Thomas Schilling
On Thu, 2007-09-13 at 15:58 -0700, Don Stewart wrote:
 clawsie:
  has anyone ever considered using llvm as a infrastructure for haskell
  compilation? it wold seem people are looking at building frontends for
  scheme, ocaml, etc. i don't know if an alternate backend is
  appropriate, but it would seem to be an interesting way to aggregate
  the best thinking for various optimizations over a more diverse group
  of developers.
 
 People are definitely interested in it. Needs some people with compiler
 experience and GHC experience to tackle it seriously, I suspect.

Reading and writing llvm files could also be useful to
prototype/implement compiler passes using Haskell.

/ Thomas

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


Re: [Haskell-cafe] haskell on llvm?

2007-09-13 Thread Thomas Schilling
On Thu, 2007-09-13 at 15:55 -0700, brad clawsie wrote:
 has anyone ever considered using llvm as a infrastructure for haskell
 compilation? it wold seem people are looking at building frontends for
 scheme, ocaml, etc. i don't know if an alternate backend is
 appropriate, but it would seem to be an interesting way to aggregate
 the best thinking for various optimizations over a more diverse group
 of developers.

I applied for Google Summer of Code with the suggestion to write a
library to generate (and compile) LLVM code (not my idea in the first
place, but I liked it), but it didn't get into the top 9 (i.e., funded)
projects.  It's certainly not a bad idea, but the immediate use to the
community would admittedly not be too great.  Targeting an existing
Haskell compiler would probably be doable, but I am unsure what the big
advantages would be.  Many optimizations implemented for llvm are more
high-level in nature and wouldn't make much sense for Haskell compilers,
since translating to llvm would lose some information, and Haskell,
being a lazy language, requires/enables non-standard transformations.
Haskell-compilers currently require better low-level optimizations
(instruction scheduling, register allocation, maybe memory locality
optimazitions).  I'm not up to date with how well llvm scores in these
areas, but last time I checked it was slower than ghc, and ghc already
isn't too great at this kind of stuff (compared to icc).

I could however see some applications of an llvm-generation library for
DSLs that require high performance, and currently have to invoke gcc at
runtime.

/ Thomas

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


RE: [Haskell-cafe] Vital for real Haskell?

2007-09-13 Thread Tim Docker
Pivotal was/is Vital's successor:

 http://www.cs.kent.ac.uk/projects/pivotal/

However, it's not clear from the website how alive the project is. I'd
love to see a robust implementation of something like this.

Tim 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Peter Verswyvelen
Sent: Friday, 14 September 2007 5:16 AM
To: Haskell-Cafe
Subject: [Haskell-cafe] Vital for real Haskell?

I showed Vital (http://www.cs.kent.ac.uk/projects/vital) to some
teachers at my university and they where really enthousiastic.

IMHO the Haskell community needs something like this, but for *real*
Haskell (preferable with extensions), and not using Java...

Is any work being done on something like this?

Thanks,
Peter



___
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] getting crazy with character encoding

2007-09-13 Thread John Meacham
On Wed, Sep 12, 2007 at 05:19:22PM +0200, Andrea Rossato wrote:
 And so it's my job to convert it in what I need. Luckily I've just
 discovered (and now I'm reading) some of John Meacham's code on
 locale. This is going to be very helpful (unfortunately I don't see
 Licenses coming with HsLocale, but if I'm reading correctly there is
 something like this in Riot - and this was BSD3 released).

it is BSD3. in general, pretty much everything I write is BSD3 except
for large projects as a whole which get GPL=2. Though I am more than
happy to BSD3 any incidentally useful parts of my projects that others
would find useful.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Manuel M T Chakravarty

Pepe Iborra wrote,
For a taste, see Instant Insanity transliterated in this functional 
language:


http://hpaste.org/2689



I thought I'd better paste here the code for Instant Insanity with Type 
Families. Otherwise it will vanish in a short time.

I took the opportunity to clean it up a bit.


Thanks!

Although AT are not a supported feature, the code works in a 6.8.1 
snapshot.
But note that you cannot actually see the solution, as there is no way 
to ask

GHCi to display the normalized types.


Just to complete transferring the discussion from the ephemeral 
hpaste to the mailing list.  My response to the lack of being able 
to display normalised types was that GHC actually goes to 
considerable trouble to preserve the original (non-normalised types) 
for error messages and other output, as this usually makes these 
messages easier to understand (eg, you usually rather like String 
than [Char] in an error message).


However, to debug your type-level programs (or to abuse the type 
checker as an evaluator) this is clearly inconvenient.  So, the plan 
is to add a ghci command that given a type will print its normal 
form.  On hpaste, Pepe also suggested a flag to instruct the 
compiler to generally print normalised instead of unnormalised 
types.  However, I think a form of eval for types on the command 
line is the most direct way of experimenting with type families and 
debugging type-level programs.


Manuel

PS: And, no, you won't be able to set breakpoints in type-level
programs...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Manuel M T Chakravarty

Derek Elkins wrote,

On Thu, 2007-09-13 at 11:12 -0700, Don Stewart wrote:
Better here means better -- a functional language on the type  
system,

to type a functional language on the value level.

-- Don
For a taste, see Instant Insanity transliterated in this functional  
language:


http://hpaste.org/2689

NB: it took me 5 minutes, and that was my first piece of coding ever  
with Type families
Wow. Great work! 


The new age of type hackery has dawned.


Is the type level functional language non-strict? (Is there a flag that
will allow non-terminating associated type programs?)


The associated type theory is only concerned with terminating (aka 
strongly normalising) sets of type instances.  For a strongly 
normalising calculus, it does not matter whether you use eager or 
non-strict evaluation.


However, there is of course a flag to diable the check for 
termination and to give up on decidable type checking.[1]  It's the 
same flag as for type classes: -fallow-undecidable-instances
(Equations of type families, or type-level functions, are introduced 
with the keywords type instance, so the option name still makes 
sense.)


FWIW, the evaluation strategy in this case is right now fairly 
eager, but it is a little hard to characterise.  If the application 
of a type family needs to be normalised to proceed with unification, eg,


  [a] ~ F (G Int)

then F (G Int) will be eagerly evaluated (ie, first G Int, and then 
(F result of G Int).  However, type-level data constructors (ie, 
type constructors are non-strict); eg,


  [a] ~ [F Int]

will result in the substitution [F Int/a].  And you can use cyclic 
bindings:


  a ~ F a

However, they must have a finite solution, as we still only admit 
finite types; eg, the following definition of F would be fine:


  type family F a
  type instance F a = Int

but

  type family F a
  type instance F a = [a]

will give you one of these cannot construct infinite type: a ~ [a] 
messages.  This makes it a bit like Id/pH's lenient evaluation.


Manuel

[1] This is GHC after all, it tries to gently nudge you in the right
direction, but if you insist, it happily let's you drill
arbitrarily large holes in your foot.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadGL - Partitioning effects without giving up type inference

2007-09-13 Thread Stuart Cook
On 9/14/07, Jules Bean [EMAIL PROTECTED] wrote:
   {-# OPTIONS -fglasgow-exts #-}

 (extensions are only for deriving (Monad), it's not important)

If that's the case, you should be able to write (assuming GHC 6.6+)

  {-# LANGUAGE GeneralizedNewtypeDeriving #-}

though I don't know how well other implementations support it.


 Incidentally, I don't believe this technique has any performance
 implication at all. The newtypes are all erased at compile time.

One potential slowdown is the added typeclass polymorphism (for
MonadGL); hopefully the compiler is clever enough to eliminate
dictionary passing/lookup.


 Any comments? I'm sure this has been shown before but I don't
 remember where.

I'm not aware of any GL-specific explanation, but I think the trick of
using monad classes as a capability system has been around for a
while. (In the folklore, you might say.)

Using classes for transparent lifting seems to come up in discussions
of the standard library's I/O functions. Writing liftIO everywhere
is just as painful as runGL.


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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Stefan O'Rear
On Fri, Sep 14, 2007 at 11:05:34AM +1000, Manuel M T Chakravarty wrote:
 Just to complete transferring the discussion from the ephemeral hpaste to 
 the mailing list.  My response to the lack of being able to display 
 normalised types was that GHC actually goes to considerable trouble to 
 preserve the original (non-normalised types) for error messages and other 
 output, as this usually makes these messages easier to understand (eg, you 
 usually rather like String than [Char] in an error message).

That's what they always say, but IME GHC's unpredictable mixing of
expanded and unexpanded form is more confusing than a straight
macro-expansion would be.  What are the motivating examples (ideally I'd
like a mailing list thread or paper citation)?

Stefan


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


Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Thomas Conway
On 9/14/07, Thomas Schilling [EMAIL PROTECTED] wrote:
 The type system doesn't help you avoid writing non-terminating programs,
 so i see no problem with it being possible giving programmers the power
 to express and check more complex properties of their programs -- as
 long as type-checking remains sound.  From a practical standpoint,
 non-terminating type checks are just as much a bug as non-terminating
 library functions.  Type systems need more thought anyways, so why not
 make sure it's terminating, too?  The other extreme is to use dependent
 types everywhere, but this has a bit more drastic consequences to the
 accessibility and practicality of the language.

While I love all the exceedingly cool type hackery, I also like the
compiler to terminate.

Some people in this forum may be old enough to remember Turbo Prolog.
It did mode inference (i.e. data-flow analysis) on programs, but
unfortunately it didn't always terminate. So what you got was a hung
compiler, leaving you to guess what it was about your [quite possibly
correct] program that caused the analysis to loop.

With C++ templates, the problem is addressed by having a limit to the
depth of the call stack for template evaluation. I recall with Forte
5, there was no flag to let you increase  the depth, so at one point
we had to do something like

if (0) {
  // Horrible nasty expression to force the evaluation of some of the
 // the lower parts of the template stack
}

This works because (at least in Forte 5, and probably most
implementations) template instantiations are hash-consed.

I would *much* rather have a simpler type system, than a compiler
which might not terminate.

cheers,
T.
-- 
Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Aaron Denney
On 2007-09-13, Stefan O'Rear [EMAIL PROTECTED] wrote:
 In any case, we already have hGetBuf / hPutBuf in the standard base
 libaries for raw binary IO, so code that uses getChar for bytes really
 has no excuse.

Except, of course, that hGetBuf and hPutBuf are
(a) allocating the memory for the buffers is a pain (does it require the
FFI?)
(b) are something of a pain to use, requiring explicitly managing what's
valid in these buffers (though a wrapper only need be written once)
(c) while in the standard base libraries are not in the report or
library report.  i.e. there's no guarantee that a conforming Haskell
implementation will have them.  It'd be silly for an implementation to
not support them, of course, but...

The ByteString library at least fixes (a) and (b).

-- 
Aaron Denney
--

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


[Haskell-cafe] Clarification Please

2007-09-13 Thread PR Stanley

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in Haskell:
5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty 
list and singleton lists are already sorted, and 
any other list is sorted by merging together the 
two lists that result from sorting the two halves of the list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.

	Create a halve function - okay, that's fairly 
straightforward. The rest, I'm afraid, is a 
little obscure. I'm not looking for the solution; 
I'd like to work that out for meself. However, 
I'd  really appreciate some clues as to the general structure of the algorithm.

Much obliged,
Paul

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


Re: [Haskell-cafe] Clarification Please

2007-09-13 Thread Michael Vanier
Define a merge function that merges two sorted lists into a sorted list containing all the elements 
of the two lists.  Then define the msort function, which will be recursive.


Mike

PR Stanley wrote:

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in 
Haskell:

5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty list and singleton lists 
are already sorted, and any other list is sorted by merging together the 
two lists that result from sorting the two halves of the list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.

Create a halve function - okay, that's fairly straightforward. The 
rest, I'm afraid, is a little obscure. I'm not looking for the solution; 
I'd like to work that out for meself. However, I'd  really appreciate 
some clues as to the general structure of the algorithm.

Much obliged,
Paul

___
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] Clarification Please

2007-09-13 Thread PR Stanley
I'm not sure. We start with one list and also, 
perhaps I should have mentioned that I have a 
merge function which takes two sorted lists with 
similar, now, what do they call it, similar 
orientation? and merges them into one sorted list.

e.g. merge [1, 4,] [2, 3]
[1,2,3,4]
Cheers, Paul
At 04:02 14/09/2007, you wrote:
Define a merge function that merges two sorted 
lists into a sorted list containing all the 
elements of the two lists.  Then define the 
msort function, which will be recursive.


Mike

PR Stanley wrote:

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in Haskell:
5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty 
list and singleton lists are already sorted, 
and any other list is sorted by merging 
together the two lists that result from sorting 
the two halves of the list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.
Create a halve function - okay, that's 
fairly straightforward. The rest, I'm afraid, 
is a little obscure. I'm not looking for the 
solution; I'd like to work that out for 
meself. However, I'd  really appreciate some 
clues as to the general structure of the algorithm.

Much obliged,
Paul
___
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] Clarification Please

2007-09-13 Thread Michael Vanier
OK, you have the split function, and you have the merge function, and now you have to define the 
msort function.  First write down the base cases (there are two, as you mention), which should be 
obvious.  Then consider the remaining case.  Let's say you split the list into two parts.  Then what 
would you do?


Mike

PR Stanley wrote:
I'm not sure. We start with one list and also, perhaps I should have 
mentioned that I have a merge function which takes two sorted lists with 
similar, now, what do they call it, similar orientation? and merges them 
into one sorted list.

e.g. merge [1, 4,] [2, 3]
[1,2,3,4]
Cheers, Paul
At 04:02 14/09/2007, you wrote:
Define a merge function that merges two sorted lists into a sorted 
list containing all the elements of the two lists.  Then define the 
msort function, which will be recursive.


Mike

PR Stanley wrote:

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in 
Haskell:

5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty list and singleton 
lists are already sorted, and any other list is sorted by merging 
together the two lists that result from sorting the two halves of the 
list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.
Create a halve function - okay, that's fairly straightforward. 
The rest, I'm afraid, is a little obscure. I'm not looking for the 
solution; I'd like to work that out for meself. However, I'd  really 
appreciate some clues as to the general structure of the algorithm.

Much obliged,
Paul
___
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] Clarification Please

2007-09-13 Thread Krzysztof Kościuszkiewicz
On Fri, Sep 14, 2007 at 03:45:02AM +0100, PR Stanley wrote:

 5. Using merge, define a recursive function
 msort :: (Ord a) = [a] - [a]
 that implements merge sort, in which the empty 
 list and singleton lists are already sorted, and 
 any other list is sorted by merging together the 
 two lists that result from sorting the two halves of the list separately. :
 Hint: first define a function
 ¬halve :: [a] - [([a], [a])]
 ¬that splits a list into two halves whose length differs by at most one.

Split the input list using halve, sort both halves (as merge requires lists to
be sorted) and merge them into output list...

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
Simplicity is the ultimate sophistication -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe