Because it is the most utilitarian way to get a bunch of strict ByteStrings
out of a lazy one.
Yes it exposes an implementation detail, but the alternatives involve an
unnatural amount of copying.
-Edward Kmett
On Sat, Apr 17, 2010 at 6:37 PM, Ashley Yakeley wrote:
> Ketil Malde wrote:
>
>> Do
I wrote:
class Compact a where
After reading Luke Palmer's message I'm thinking this might not be the
best name.
--
Ashley Yakeley
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Ketil Malde wrote:
Do we also want to modify equality for lazy bytestrings, where equality
is currently independent of chunk segmentation? (I.e.
toChunks s1 == toChunks s2 ==> s1 == s2
but not vice versa.)
Why is toChunks exposed?
--
Ashley Yakeley
_
rocon...@theorem.ca wrote:
As ski noted on #haskell we probably want to extend this to work on
Compact types and not just Finite types
instance (Compact a, Eq b) => Eq (a -> b) where ...
For example (Int -> Bool) is a perfectly fine Compact set that isn't
finite and (Int -> Bool) -> Int has a
Ashley Yakeley writes:
> There's an impedance mismatch between the IEEE notion of equality
> (under which -0.0 == 0.0), and the Haskell notion of equality (where
> we'd want x == y to imply f x == f y).
Do we also want to modify equality for lazy bytestrings, where equality
is currently independ
On 2010-04-15 06:18, Nick Bowler wrote:
Your definitions seem very strange, because according to this, the
functions
f :: Double -> Double
f x = 1/x
and
g :: Double -> Double
g x = 1/x
are not equal, since (-0.0 == 0.0) yet f (-0.0) /= g (0.0).
There's an impedance mismatch b
On Apr 15, 2010, at 12:53 AM, rocon...@theorem.ca wrote:
I'd call them disrespectful functions, or maybe nowadays I might
call them
improper functions. The "good" functions are respectful functions or
proper functions.
There's no need to put these into a different class. The IEEE defined
On 03:53 Thu 15 Apr , rocon...@theorem.ca wrote:
> On Wed, 14 Apr 2010, Ashley Yakeley wrote:
>
> > On 2010-04-14 14:58, Ashley Yakeley wrote:
> >> On 2010-04-14 13:59, rocon...@theorem.ca wrote:
> >>
> >>> There is some notion of value, let's call it proper value, such that
> >>> bottom is n
On Thu, 2010-04-15 at 03:53 -0400, rocon...@theorem.ca wrote:
> Hmm, I guess I'm carrying all this over from the world of dependently
> typed programming where we have setoids and the like that admit equality
> relations that are not necessarily decidable. In Haskell only the
> decidable instan
On Wed, 14 Apr 2010, Ashley Yakeley wrote:
On 2010-04-14 14:58, Ashley Yakeley wrote:
On 2010-04-14 13:59, rocon...@theorem.ca wrote:
There is some notion of value, let's call it proper value, such that
bottom is not one.
In other words bottom is not a proper value.
Define a proper value to
On Thu, 15 Apr 2010, Maciej Piechotka wrote:
Are
f 0 = 1
f n = f (n - 1) + f (n - 2)
and
g 0 = 1
g n | n > 0 = g (n - 1) + g (n - 2)
| n < 0 = g (n + 2) - g (n + 1)
The same (morally) function?
Are:
f x = 2*x
and
f x = undefined
The same function
Try using the (x == y) ==> (f x =
On Wed, 2010-04-14 at 12:16 -0700, Ashley Yakeley wrote:
> On 2010-04-14 11:12, John Meacham wrote:
> > On Wed, Apr 14, 2010 at 02:07:52AM -0700, Ashley Yakeley wrote:
> >>> So the facts that
> >>> (1) f == g
> >>> (2) f undefined = 6
> >>> (3) g undefined = undefined
> >>> is not a problem?
> >>
>
On Apr 14, 2010, at 5:10 PM, Ashley Yakeley wrote:
Worse, this rules out values of types that are not Eq.
In principle, every type is an instance of Eq, because every type
satisfies the identity function. Unfortunately, you can't DERIVE
instances in general. As you are finding out... O
On 2010-04-14 14:58, Ashley Yakeley wrote:
On 2010-04-14 13:59, rocon...@theorem.ca wrote:
There is some notion of value, let's call it proper value, such that
bottom is not one.
In other words bottom is not a proper value.
Define a proper value to be a value x such that x == x.
So neither u
On 2010-04-14 13:59, rocon...@theorem.ca wrote:
There is some notion of value, let's call it proper value, such that
bottom is not one.
In other words bottom is not a proper value.
Define a proper value to be a value x such that x == x.
So neither undefined nor (0.0/0.0) are proper values
In
On Wed, 14 Apr 2010, Ashley Yakeley wrote:
On 2010-04-14 13:03, Alexander Solla wrote:
If you're willing to accept that distinct functions can represent the
same "moral function", you should be willing to accept that different
"bottoms" represent the same "moral value".
Bottoms should not be
On 2010-04-14 13:31, Alexander Solla wrote:
And yet you are trying to recover the semantics of comparing bottoms.
No, I don't think so.
--
Ashley Yakeley
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/h
On Apr 14, 2010, at 1:24 PM, Ashley Yakeley wrote:
Bottoms should not be considered values. They are failures to
calculate values, because your calculation would never terminate (or
similar condition).
And yet you are trying to recover the semantics of comparing bottoms.
___
On 2010-04-14 13:03, Alexander Solla wrote:
If you're willing to accept that distinct functions can represent the
same "moral function", you should be willing to accept that different
"bottoms" represent the same "moral value".
Bottoms should not be considered values. They are failures to calcu
On Apr 14, 2010, at 12:16 PM, Ashley Yakeley wrote:
They are distinct Haskell functions, but they represent the same
moral function.
If you're willing to accept that distinct functions can represent the
same "moral function", you should be willing to accept that different
"bottoms" repre
On 2010-04-14 11:12, John Meacham wrote:
On Wed, Apr 14, 2010 at 02:07:52AM -0700, Ashley Yakeley wrote:
So the facts that
(1) f == g
(2) f undefined = 6
(3) g undefined = undefined
is not a problem?
This is not a problem. f and g represent the same moral function, they
are just implemented di
On Wed, 14 Apr 2010, Ashley Yakeley wrote:
On 2010-04-14 03:41, rocon...@theorem.ca wrote:
For example (Int -> Bool) is a perfectly fine Compact set that isn't
finite
Did you mean "Integer -> Bool"? "Int -> Bool" is finite, but large.
Yes, I meant Integer -> Bool.
--
Russell O'Connor
On Wed, Apr 14, 2010 at 2:22 PM, Stefan Monnier
wrote:
> While we're here, I'd be more interested in a dirty&fast comparison
> operation which could look like:
>
> eq :: a -> a -> IO Bool
>
> where the semantics is "if (eq x y) returns True, then x and y are the
> same object, else they may be
Stefan Monnier wrote:
> While we're here, I'd be more interested in a dirty&fast comparison
> operation which could look like:
>
> eq :: a -> a -> IO Bool
>
> where the semantics is "if (eq x y) returns True, then x and y are the
> same object, else they may be different". Placing it in IO i
> Why isn't there an instance Eq (a -> b) ?
I guess it's because even for those cases where it can be written, it
will rarely be what you want to do, so it's better to require the
programmer to explicitly request a function-comparison than to risk
silently using such a costly operation when the pr
On Wed, Apr 14, 2010 at 02:07:52AM -0700, Ashley Yakeley wrote:
>> So the facts that
>> (1) f == g
>> (2) f undefined = 6
>> (3) g undefined = undefined
>> is not a problem?
>
> This is not a problem. f and g represent the same moral function, they
> are just implemented differently. f is smart e
On 2010-04-14 03:41, rocon...@theorem.ca wrote:
For example (Int -> Bool) is a perfectly fine Compact set that isn't
finite
Did you mean "Integer -> Bool"? "Int -> Bool" is finite, but large.
--
Ashley Yakeley
___
Haskell-Cafe mailing list
Haskell-Ca
On Wed, Apr 14, 2010 at 5:13 AM, Luke Palmer wrote:
> On Wed, Apr 14, 2010 at 4:41 AM, wrote:
>> As ski noted on #haskell we probably want to extend this to work on Compact
>> types and not just Finite types
>>
>> instance (Compact a, Eq b) => Eq (a -> b) where ...
>>
>> For example (Int -> Bool
On Wed, Apr 14, 2010 at 4:41 AM, wrote:
> As ski noted on #haskell we probably want to extend this to work on Compact
> types and not just Finite types
>
> instance (Compact a, Eq b) => Eq (a -> b) where ...
>
> For example (Int -> Bool) is a perfectly fine Compact set that isn't finite
> and (In
On Wed, 14 Apr 2010, Ashley Yakeley wrote:
Joe Fredette wrote:
this is bounded, enumerable, but infinite.
The question is whether there are types like this. If so, we would need a new
class:
class Finite a where
allValues :: [a]
instance (Finite a,Eq b) => Eq (a -> b) where
p ==
Ashley Yakeley schrieb:
Joe Fredette wrote:
this is bounded, enumerable, but infinite.
The question is whether there are types like this. If so, we would
need a new class:
I assume that comparing functions is more oftenly a mistake then
actually wanted. Say I have compared
f x == f y
and la
Ivan Lazar Miljenovic wrote:
Ashley Yakeley writes:
On Wed, 2010-04-14 at 16:11 +1000, Ivan Miljenovic wrote:
but the only way you can "prove" it in
Haskell is by comparing the values for the entire domain (which gets
computationally expensive)...
It's not expensive if the domain is, for ins
Jonas Almström Duregård wrote:
So the facts that
(1) f == g
(2) f undefined = 6
(3) g undefined = undefined
is not a problem?
This is not a problem. f and g represent the same moral function, they
are just implemented differently. f is smart enough to know that its
argument doesn't matter, s
Ketil Malde wrote:
(If you'd made clear from the start that when you say "Enum a, Bounded a"
you really mean "Bool", you might have avoided these replies that you
apparently find offensive.)
I don't mean Bool. There are lots of small finite types, for instance,
(), Word8, Maybe Bool, and so on
Ashley Yakeley writes:
>> Another practical consideration is that checking a function taking a
>> simple Int parameter for equality would mean 2^65 function evaluations.
>> I think function equality would be too much of a black hole to be
>> worth it.
> Oh FFS, _don't do that_.
I won't.
But yo
On 14 Apr 2010, at 09:39, Ashley Yakeley wrote:
> Thomas Davie wrote:
>> I guess this further reinforces my point though – we have a mixture of
>> places where we consider _|_ when considering laws, and places where we
>> don't consider _|_. This surely needs better defined somewhere.
>
> It'
Thomas Davie wrote:
I guess this further reinforces my point though – we have a mixture of places
where we consider _|_ when considering laws, and places where we don't consider
_|_. This surely needs better defined somewhere.
It's easy: don't consider bottom as a value, and the laws work fi
On 14 Apr 2010, at 09:35, Jonas Almström Duregård wrote:
>>> what about these?
>>> f,g :: Bool -> Int
>>> f x = 6
>>> g x = x `seq` 6
>>
>> As pointed out on #haskell by roconnor, we apparently don't care, this is a
>> shame... We only care that x == y => f x == g y, and x == y can't tell if
>>
On 14 Apr 2010, at 09:31, Ashley Yakeley wrote:
> On Wed, 2010-04-14 at 09:29 +0100, Thomas Davie wrote:
>> It isn't?
>>
>> fPrelude> fmap id (undefined :: IO ())
>> *** Exception: Prelude.undefined
>
> ghci is helpfully running the IO action for you. Try this:
>
> seq (fmap id (undefined :: I
>> what about these?
>> f,g :: Bool -> Int
>> f x = 6
>> g x = x `seq` 6
>
> As pointed out on #haskell by roconnor, we apparently don't care, this is a
> shame... We only care that x == y => f x == g y, and x == y can't tell if
> _|_ == _|_.
So the facts that
(1) f == g
(2) f undefined = 6
(3) g
On Wed, 2010-04-14 at 09:29 +0100, Thomas Davie wrote:
> It isn't?
>
> fPrelude> fmap id (undefined :: IO ())
> *** Exception: Prelude.undefined
ghci is helpfully running the IO action for you. Try this:
seq (fmap id (undefined :: IO ())) "not bottom"
--
Ashley Yakeley
__
On 14 Apr 2010, at 09:25, Ashley Yakeley wrote:
> Thomas Davie wrote:
>> Because we consider that the Functor laws must hold for all values in the
>> type (including bottom).
>
> This is not so for IO, which is an instance of Functor. "fmap id undefined"
> is not bottom.
It isn't?
fPrelude>
Thomas Davie wrote:
Because we consider that the Functor laws must hold for all values in the type
(including bottom).
This is not so for IO, which is an instance of Functor. "fmap id
undefined" is not bottom.
--
Ashley Yakeley
___
Haskell-Cafe ma
On Wed, 2010-04-14 at 01:21 -0700, Ashley Yakeley wrote:
> Maciej Piechotka wrote:
>
> > I guess that the fact that:
> > - It is costly.
>
> No, it's not. Evaluating equality for "Bool -> Int" does not take
> significantly longer than for its isomorph "(Int,Int)". The latter has
> an Eq instanc
Maciej Piechotka wrote:
I guess that the fact that:
- It is costly.
No, it's not. Evaluating equality for "Bool -> Int" does not take
significantly longer than for its isomorph "(Int,Int)". The latter has
an Eq instance, so why doesn't the former?
--
Ashley Yakeley
On 14 Apr 2010, at 09:17, Ashley Yakeley wrote:
> Thomas Davie wrote:
>> Certainly bottom is a value, and it's a value in *all* Haskell types.
>
> This is a matter of interpretation. If you consider bottom to be a value,
> then all the laws fail. For instance, (==) is supposed to be reflexive,
On Tue, 2010-04-13 at 23:03 -0700, Ashley Yakeley wrote:
> Why isn't there an instance Eq (a -> b) ?
>
>allValues :: (Bounded a,Enum a) => [a]
>allValues = enumFrom minBound
>
>instance (Bounded a,Enum a,Eq b) => Eq (a -> b) where
> p == q = fmap p allValues == fmap q allValues
>
Thomas Davie wrote:
Certainly bottom is a value, and it's a value in *all* Haskell types.
This is a matter of interpretation. If you consider bottom to be a
value, then all the laws fail. For instance, (==) is supposed to be
reflexive, but "undefined == undefined" is not True for almost any t
On 14 Apr 2010, at 09:12, Jonas Almström Duregård wrote:
>> f,g :: Bool -> Int
>> f x = 6
>> g x = 6
>>
>> We can in Haskell compute that these two functions are equal, without
>> solving the halting problem.
>
> what about these?
> f,g :: Bool -> Int
> f x = 6
> g x = x `seq` 6
As pointed ou
On 14 Apr 2010, at 09:08, Jonas Almström Duregård wrote:
>> f,g :: Bool -> Int
>> f x = 6
>> g x = 6
>>
>> We can in Haskell compute that these two functions are equal, without
>> solving the halting problem.
>
> Of course, this is the nature of generally undecidable problems. They
> are decid
> f,g :: Bool -> Int
> f x = 6
> g x = 6
>
> We can in Haskell compute that these two functions are equal, without solving
> the halting problem.
what about these?
f,g :: Bool -> Int
f x = 6
g x = x `seq` 6
/Jonas
2010/4/14 Thomas Davie :
>
> On 14 Apr 2010, at 09:01, Jonas Almström Duregård wr
> f,g :: Bool -> Int
> f x = 6
> g x = 6
>
> We can in Haskell compute that these two functions are equal, without solving
> the halting problem.
Of course, this is the nature of generally undecidable problems. They
are decidable in some cases, but not in general.
/Jonas
2010/4/14 Thomas Davie
Ketil Malde wrote:
Another practical consideration is that checking a function taking a
simple Int parameter for equality would mean 2^65 function evaluations.
I think function equality would be too much of a black hole to be
worth it.
Oh FFS, _don't do that_.
--
Ashley Yakeley
___
On 14 Apr 2010, at 09:01, Jonas Almström Duregård wrote:
>> But if one did start considering bottom to be a value, one would have to
>> distinguish different ones. For instance, (error "ABC") vs. (error
>> "PQR"). Obviously this is not finite.
>
> Nor is it computable, since it must distinguish
On 14 Apr 2010, at 08:29, Ashley Yakeley wrote:
> On Wed, 2010-04-14 at 08:13 +0100, Thomas Davie wrote:
>> Your instances of Finite are not quite right:
>>
>> bottom :: a
>> bottom = doSomethingToLoopInfinitely.
>>
>> instance Finite () where
>> allValues = [(), bottom]
>
> Bottom is not a va
> But if one did start considering bottom to be a value, one would have to
> distinguish different ones. For instance, (error "ABC") vs. (error
> "PQR"). Obviously this is not finite.
Nor is it computable, since it must distinguish terminating programs
from nonterminating ones (i.e. the halting pr
On Wed, 2010-04-14 at 08:13 +0100, Thomas Davie wrote:
> Your instances of Finite are not quite right:
>
> bottom :: a
> bottom = doSomethingToLoopInfinitely.
>
> instance Finite () where
> allValues = [(), bottom]
Bottom is not a value, it's failure to evaluate to a value.
But if one did star
Your instances of Finite are not quite right:
bottom :: a
bottom = doSomethingToLoopInfinitely.
instance Finite () where
allValues = [(), bottom]
instance Finite Nothing where
allValues = [bottom]
Though at a guess an allValuesExculdingBottom function is also useful, perhaps
the class should
Joe Fredette wrote:
this is bounded, enumerable, but infinite.
The question is whether there are types like this. If so, we would need
a new class:
class Finite a where
allValues :: [a]
instance (Finite a,Eq b) => Eq (a -> b) where
p == q = fmap p allValues == fmap q allValues
59 matches
Mail list logo