On Mon, Nov 24, 2008 at 7:40 AM, Andrea Vezzosi <[EMAIL PROTECTED]> wrote:
> It's more natural to consider the cross product of no sets to be [[]] so
> your crossr becomes:
>
> crossr [] = [[]]
> crossr (x:xs) = concat (map (\h ->map (\t -> h:t) (crossr tail)) hd
Ops, hd and tail should be x and
It's more natural to consider the cross product of no sets to be [[]] so
your crossr becomes:
crossr [] = [[]]
crossr (x:xs) = concat (map (\h ->map (\t -> h:t) (crossr tail)) hd)
which we can rewrite with list comprehensions for conciseness:
crossr [] = [[]]
crossr (x:xs) = [ a:as | a <- x, a
On 11/23/08 13:52, Luke Palmer wrote:
2008/11/23 Larry Evans <[EMAIL PROTECTED]>:
http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product
of two lists. That attached does the same but then
used cross on 3 lists. Naturally, I thought use of
News about Haskell on Arch Linux
* Arch now has 734 Haskell packages now
* That’s an increase of 29 new packages in the last 8 days!
* 3.6 new Haskell releases are occuring each day.
Noteworthy,
* haskell-hledger-0.2: “A ledger-compatible text-based accounting tool.”
I was trying to create a typeclass for an abstract Stack class, and ran
into some problems. The following 'works' fine:
{-# OPTIONS_GHC -XEmptyDataDecls -XFlexibleContexts
-fno-monomorphism-restriction #-}
module Stack where
data Void
class Stack s where
push_ :: s a r -> b -> s b (s a r
Alexey Khudyakov wrote:
But this bring question what "the right thing" is? If locale is UTF8 or system
support unicode some other way - no problem, just encode string properly.
Problem is how to deal with untanslatable characters. Skip? Replace with
question marks? Anything other? Probably we nee
On 23/11/2008, at 9:18 PM, Robin Green wrote:
It occurs to me that garbage collection can be seen as some kind of
dual of laziness. Laziness means deferring the creation of values
until
later in the future (or even never).
A program optimisation might also have the same effect (of avoiding
hledger is a minimal haskell clone of John Wiegley's "ledger" text-based
accounting tool (http://newartisans.com/software/ledger.html). hledger
generates ledger-compatible register & balance reports from a plain text
ledger file, and demonstrates a functional implementation of ledger.
For
mor
> No, I believe it wouldn't. The left-biased tree cannot distinguish
> where parentheses have been used from where HSE inserted its own left
> fixities. For instance, if we have the expressions
>
> xs ++ ys ++ zs
> (xs ++ ys) ++ zs
>
> Then HSE will return something like (I'm using strings for the
On Mon, Nov 24, 2008 at 12:39 AM, Niklas Broberg
<[EMAIL PROTECTED]> wrote:
>> I want this information to be used somehow when creating the Template
>> Haskell AST, so that the operators used have the correct fixities. If
>> I use HSE for parsing Haskell expressions, then I want it to tell me
>> wh
> "Robin" == Robin Green <[EMAIL PROTECTED]> writes:
Robin> It occurs to me that garbage collection can be seen as some
Robin> kind of dual of laziness. Laziness means deferring the
Robin> creation of values until later in the future (or even
Robin> never). Garbage collection m
It occurs to me that garbage collection can be seen as some kind of
dual of laziness. Laziness means deferring the creation of values until
later in the future (or even never). Garbage collection means eagerly
destroying data created in the past, and reclaiming the memory used by
it, before some ot
2008/11/23 Larry Evans <[EMAIL PROTECTED]>:
> http://www.muitovar.com/monad/moncow.xhtml#list
>
> contains a cross function which calculates the cross product
> of two lists. That attached does the same but then
> used cross on 3 lists. Naturally, I thought use of
> fold could generalize that to
http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product
of two lists. That attached does the same but then
used cross on 3 lists. Naturally, I thought use of
fold could generalize that to n lists; however,
I'm getting error:
{-- cut here
Com
BTW, the documentation of catch is bad: the example
catch (openFile f ReadMode)
(\e -> hPutStr stderr ("Couldn't open "++f++": " ++ show e))
does not type check. Is this a known "bug" or shall I report it anywhere?
Regards,
Martin.
Ross Mellgren schrieb:
I think catch is now basica
On Sun, 2008-11-23 at 16:41 +0100, Manlio Perillo wrote:
> Claus Reinke ha scritto:
> > [...]
> >>> 2. It still wouldn't work for the OpenGL package on Windows, because
> >>> the configure scripts require a Unix-style built environment
> >>> (MinGW/MinSys or Cygwin).
> >>
> > [...]
> > - they need
Claus Reinke ha scritto:
[...]
2. It still wouldn't work for the OpenGL package on Windows, because
the configure scripts require a Unix-style built environment
(MinGW/MinSys or Cygwin).
[...]
- they need to install MinGW/MSys
- then they can do cabal install OpenGL
Does cabal support pre
On Sun, 2008-11-23 at 09:24 -0500, Jeff Heard wrote:
> Duncan, what kind of help do you need on the Haskell Platform install?
> I have access to VMs running windows XP and Vista.
The haskell-platform meta-package is here:
darcs get http://code.haskell.org/haskell-platform/
This specifies the lis
thannks very much!!
--
Thanks & Regards
Changying Li
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Duncan, what kind of help do you need on the Haskell Platform install?
I have access to VMs running windows XP and Vista.
On Sun, Nov 23, 2008 at 8:12 AM, Duncan Coutts
<[EMAIL PROTECTED]> wrote:
> On Sun, 2008-11-23 at 08:00 -0500, Paul L wrote:
>> On 11/23/08, Duncan Coutts <[EMAIL PROTECTED]>
> On Sun, Nov 23, 2008 at 8:23 AM, John A. De Goes <[EMAIL PROTECTED]> wrote:
>> Though many see it as "losing" information, I agree wholeheartedly with your
>> proposal to change the AST.
>>
>> It's better to have an AST that conveys less information, but truthfully,
>> than to have an AST that pu
On Sun, 2008-11-23 at 08:00 -0500, Paul L wrote:
> On 11/23/08, Duncan Coutts <[EMAIL PROTECTED]> wrote:
> >> 2. It still wouldn't work for the OpenGL package on Windows, because
> >> the configure scripts require a Unix-style built environment
> >> (MinGW/MinSys or Cygwin).
> >
> > Yes, building i
It turns out that there is at least a (partial) solution to my
quasiquote problem. Template Haskell's "reify" function can be used to
find an operator's fixity, although it seems not for all cases.
However, for the purposes of this discussion, suppose I can write a
function
userFixity :: String ->
On Sun, 2008-11-23 at 12:30 +, Claus Reinke wrote:
> >> >> It's sad to see the OpenGL binding being dropped from GHC binary
> >> >> installers starting from 6.10. Though this issue has been brought up
> >> >> and discussed before, I'm sure a lot of people who based their work on
> >> >> OpenGL
On 11/23/08, Duncan Coutts <[EMAIL PROTECTED]> wrote:
>> 2. It still wouldn't work for the OpenGL package on Windows, because
>> the configure scripts require a Unix-style built environment
>> (MinGW/MinSys or Cygwin).
>
> Yes, building it requires mingw/msys, but with it cabal install opengl
> rea
>> It's sad to see the OpenGL binding being dropped from GHC binary
>> installers starting from 6.10. Though this issue has been brought up
>> and discussed before, I'm sure a lot of people who based their work on
>> OpenGL would share the same sympathy.
>
> $ cabal install OpenGL
Nice except
On Sat, Nov 22, 2008 at 9:46 AM, Changying Li <[EMAIL PROTECTED]> wrote:
> Hi.
> I read 'write yourself a scheme in 48 hours' and try to modify its code.
> now part of code is :
>
> parseList :: Parser LispVal
> parseList = liftM List $ sepEndBy parseExpr spaces
><|> do char '('
>
On Sat, 2008-11-22 at 23:34 -0500, Paul L wrote:
> On 11/22/08, Don Stewart <[EMAIL PROTECTED]> wrote:
> > ninegua:
> >> Hi everyone,
> >>
> >> It's sad to see the OpenGL binding being dropped from GHC binary
> >> installers starting from 6.10. Though this issue has been brought up
> >> and discuss
Hello Alexey,
Sunday, November 23, 2008, 10:20:47 AM, you wrote:
> And this problem related not only to IO. It raises whenever strings cross
> border between haskell world and outside world. Opening files with unicode
> names, execing, etc.
this completely depends on libraries, and ghc-bundled i
29 matches
Mail list logo