On Sep 7, 2012 2:00 AM, "Edward Z. Yang" @
mit.edu > wrote:
>
> Haskell already does this, to some extent, in the design of imprecise
> exceptions. But note that bottom *does* have well defined behavior, so
> these "optimizations" are not very desirable.
They're not *usually* desirable, but when
I have no plans to do such a thing anytime soon, but is there a way to tell
GHC to allow nasal demons to fly if the program forces bottom? This mode of
operation would seem to be a useful optimization when compiling a program
produced by Coq or similar, enabling various transformations that can tur
e/order-statistics<http://hackage.haskell.org/package/order-statistics>
>
> Cheers,
> Gershom
>
> On 9/1/12 3:26 PM, David Feuer wrote:
>
>> The median function in the hstats package uses a naive O(n log n)
>> algorithm. Is there another package pr
The median function in the hstats package uses a naive O(n log n)
algorithm. Is there another package providing an O(n) option? If not,
what would it take to get the package upgraded?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.hask
On Thu, Aug 16, 2012 at 9:53 AM, Felipe Almeida Lessa
wrote:
> If you import qualified then adding functions will never break anything.
If the language is changed (without possibility of breakage, I
believe) so that names declared in a module shadow imported names,
incompatibility can only arise
Where are pragmas treated like comments?
On Aug 16, 2012 6:14 AM, "Björn Peemöller"
wrote:
> Dear cafe,
>
> I'm experimenting with extending the parser for a Haskell-like language
> by module pragmas. The parser is written using parser combinators.
>
> Currently, I adapted the lexer to ignore whi
s a. ~P(a)) v Q
> {a is not free in Q}
> exists a. (~P(a) v Q)
> {implication = not-or}
> exists a. (P(a) -> Q)
>
> These steps are all equivalencies, valid in both directions.
>
> On Wed, Aug 15, 2012 at 9:32 AM, David Feuer wrote:
>
>> On Aug 15, 2012 3:2
On Aug 15, 2012 3:21 AM, "wren ng thornton" wrote:
> It's even easier than that.
>
> (forall a. P(a)) -> Q <=> exists a. (P(a) -> Q)
>
> Where P and Q are metatheoretic/schematic variables. This is just the
usual thing about antecedents being in a "negative" position, and thus
flipping as yo
In Unix, at least, "check, then act" is generally considered unwise:
1. Something can go wrong between checking and acting.
2. You might not be checking the right thing(s). In this case, the fact
that the file exists is not useful if you don't have permission to execute
it. You may not be able to
Has anyone used existential types to represent items on a schedule in a
scheduled lazy data structure?
On Aug 11, 2012 4:15 AM, wrote:
>
> > data A = A deriving Show
> > data B = B deriving Show
> > data C = C deriving Show
> >
> > data Foo = forall a. Show a => MkFoo a (Int -> Bool)
> >
> > inst
It looks to me like Wadler made a typo. Even great minds like his slip up
like that sometimes. However, I do have some comments below on your code.
On Aug 9, 2012 8:53 PM, "Stayvoid" wrote:
> I tried to implement it in Haskell:
> (I'm a newbie. I guess it's possible to write a better version.)
>
So I was thinking about a mutable array of tuples, but to avoid allocating
tuples to modify their fields, I guess I really want an immutable array of
tuples of STRefs. Just how much less efficient is this than a plain mutable
array? might it even make sense to use parallel mutable arrays? The thoug
Is it really so bad to use an explicit let when you need mutually recursive
bindings?
On Aug 8, 2012 1:51 PM, "Martijn Schrage" wrote:
> On 08-08-12 19:01, Simon Hengel wrote:
>
> On Wed, Aug 08, 2012 at 12:22:39PM -0400, David Feuer wrote:
>
> Changing scoping rule
-- Forwarded message --
From: David Feuer
Date: Wed, Aug 8, 2012 at 12:22 PM
Subject: Re: [Haskell-cafe] 'let' keyword optional in do notation?
To: Martijn Schrage
Changing scoping rules based on whether things are right next to each
other? No thanks.
On Wed, Aug 8,
Where by "nearly double", of course, I really mean "nearly triple".
I'm a little tired.
David
On Sun, Aug 5, 2012 at 5:37 AM, David Feuer wrote:
> Unfortunately, I doubt it can. That algorithm reduces the number of
> comparisons a good bit, but the asy
g-pairwise-sums
>
> Heinrich
>
> Am 04.08.2012 20:47, schrieb David Feuer:
>>
>> I realized my algorithm is insane. The correct way to sort [a*b|a<-A,
>> b<-B] is clearly to sort A and B, then for each a in A construct
>> either map (a*) B or map (a*) (reverse
stead: http://hackage.haskell.org/package/vector
>
> On Sat, Aug 4, 2012 at 11:23 AM, David Feuer wrote:
>
>> I'm writing a toy program (for a SPOJ problem--see
>> https://www.spoj.pl/problems/ABCDEF/ ) and the profiler says my
>> performance problem is that I'm
ave managed to solve the problem within the
time limit using the same approach I've taken (I believe), but mine is
taking too long. Any suggestions? Do I need to do something insane
like sorting in an STUArray?
David Feuer
___
Haskell-Cafe
___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Night. An owl flies o'er rooftops. The moon sheds its soft light upon
the trees.
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
See comments below.
On Sun, May 12, 2002, David Feuer wrote:
> On Sun, May 12, 2002, Emre Tezel wrote:
> > Hi all,
> >
> > I recently bought Simon Thompson's Haskell book. I have been doing the
> > exercises while I read on. There are couple questions that I ca
ompose l
f::Int -> Float
f x = fromIntegral x
g::String -> Int
g = read
h::Int -> String
h x = take x "123456789"
main = do
putStrLn "hello!"
print $ compose (End (\x -> "Foo!")) 3
print $ compose (Comp f (Comp g (End h))) 4
--
Nig
On Sun, Apr 07, 2002, Konst Sushenko wrote:
> This one helped. Thanks.
>
> 'reduction' was the key word that made it clear for me. It is not that left
>associated (++) reconstructs the list once and again (although one can say that) it
>is just that to return the head from the recursive invocat
the following are calculated:
[]++[1]
[1]++[2]
[1,2]++[3]
[1,2,3]++[4]
Since l1++l2 takes order length(l1), each concatenation takes more time
than the previous one (linearly), so the total time for all of them is
quadratic.
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
t; a bit?)
Sorting is probably easiest if you use the standard sort function. I'm
still kind of interested in whether anyone has done work on which
purely-functional sorts are efficient, and particularly which ones are
efficient in GHC.
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Thu, Mar 07, 2002, Michael Ruth wrote:
> Hello,
>
> I am pretty new to Functional programming, and I am having the following
> problem.
>
> I need to sort a list of dates provided in an input file. One date per
> line.. day month year is the order. And each is represented by integers
> se
On Sat, Feb 23, 2002, Jan-Willem Maessen wrote:
> David Feuer <[EMAIL PROTECTED]> writes:
> > I seem to remember an article about functional graph algorithms using
> > extra-lazy arrays. Anyone know if these arrays have appeared in any
> > mainstream implement
I seem to remember an article about functional graph algorithms using
extra-lazy arrays. Anyone know if these arrays have appeared in any
mainstream implementation?
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org
> From: Joe <[EMAIL PROTECTED]>
> Does anybody with their elbows in the
> code think variable interpolation and/or
> multi-line strings are good/doable ideas?
Can't say I have my elbows in the code, but I think that
multi-line strings could be useful. I'm not sure what I
think about variable
> From: Thomas Hallgren <[EMAIL PROTECTED]>
> David Feuer wrote:
>
> >Has anyone written an efficient purely-functional
> >implementation of unification (for type checking)?
> >
> Well, if you have ever used hbc or nhc, you have used
type chec
> From: "Cagdas Ozgenc" <[EMAIL PROTECTED]>
>
> Greetings.
>
> In section 4.1 of Haskell Report for 98:
>
> It is indicated that (->) has kind * -> *-> * and
> t1 -> t2 is equivalent to type (->) t1 t2
>
> Does this make (->) a type constructor? Is this an
attempt to unify
> functions and dat
Has anyone written an efficient purely-functional
implementation of unification (for type checking)? If
not, what makes it difficult to solve the problem in that
way?
David Feuer
This message has been brought to you by the letter alpha and the number pi
ensions become list comprehensions
do notation is restricted to IO
numbers are not overloaded: 4,5,6::Integer and 4.0,5.0,6.0::Float
This kind of multi-level system would allow beginner's an easy
introduction without forcing people who know what they're doing to
remember
The paper I am reading uses the following in an instance declaration for
parsers:
p >>= f = Parser (\cs -> concat [parse (f a) cs' |
(a,cs') <- parse p cs])
Isn't this the same as
p >>= f = Parser (\cs ->
[(a',cs'') | (a,cs') <- parse p cs,
p 160 300 3 -1 roll 0 360 arc 300 div 1 1 sethsbcolor
fill}for grestore 0 -60 rmoveto}def 72 500 n(This message has been)m
(brought to you by the)m(letter alpha and the number pi.)m(David Feuer)
m([EMAIL PROTECTED])m showpage
___
Haskell-Cafe mailing list
ed at link time?
--
/Times-Bold 40 selectfont/n{moveto}def/m{gsave true charpath clip 72
400 n 300 -4 1{dup 160 300 3 -1 roll 0 360 arc 300 div 1 1 sethsbcolor
fill}for grestore 0 -60 rmoveto}def 72 500 n(This message has been)m
(brought to you by the)m(letter alpha and the number pi.)m(David Feuer
0 selectfont/n{moveto}def/m{gsave true charpath clip 72
400 n 300 -4 1{dup 160 300 3 -1 roll 0 360 arc 300 div 1 1 sethsbcolor
fill}for grestore 0 -60 rmoveto}def 72 500 n(This message has been)m
(brought to you by the)m(letter alpha and the number pi.)m(David
0 360 arc 300 div 1 1 sethsbcolor
fill}for grestore 0 -60 rmoveto}def 72 500 n(This message has been)m
(brought to you by the)m(letter alpha and the number pi.)m(David Feuer)
m([EMAIL PROTECTED])m showpage
___
Haskell-Cafe mailing list
[EMAIL PROTECT
I'm wondering why Haskell doesn't support Scheme-like cond statements or a
pattern matching predicate.
cond
c1->v1
c2->v2
or possibly
cond
| c1 -> v1
| c2 -> v2
...
would translate as
case () of
_ | c1 -> v1
| c2 -> v2
|
also, it seems t
(sorry to mess up mail threading, but I couldn't properly reply to the
message the way I'm using email right now--broken mail clients)
>Recently, however, there has been some interest in using named instance
>declarations in other ways, so perhaps we will see features like this
>creeping into fut
I am curious about a couple things regarding instance declarations.
1. Why can't they be hidden in module imports/exports? Is this an
implementation issue (I guess I could see it as a problem with the
dictionary-passing approach...)? It seems kind of bad that instances are
not allowed to overl
40 matches
Mail list logo