Re: [Haskell-cafe] Data.Time

2011-07-04 Thread Ashley Yakeley
On Mon, 2011-07-04 at 10:38 +0300, Yitzchak Gale wrote:
  Leap second data is there too, so it should be possible to create a
  Data.Time.Clock.TAI.LeapSecondTable from it.
 
 No, unfortunately. There is a place in the data structure
 for leap second information, but no live Olson
 file has every populated it AFAIK.

Have a look at the right/UTC timezone, I think leap-second data is
represented there. But zdump right/UTC does not give you the TAI time.
Quite the opposite, it gives you the UTC time if your clock is set to
TAI.

-- 
Ashley Yakeley


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


Re: [Haskell-cafe] Data.Time

2011-07-03 Thread Ashley Yakeley

On 2011-07-02 14:03, Yitzchak Gale wrote:

Not exactly. A TimeZone in Data.Time doesn't really
represent a time zone - it represents a specific clock setting
in a time zone.


I still regret this! I should have called it TimeOffset or somesuch.


To get a TimeZoneSeries, representing a time zone with
all of its known clock changes throughout history and some
years into the future, use the timezone-olson package[2] to
read an Olson time zone file. On Linux and Mac OS X
systems, Olson time zone files are available in the directory
/usr/share/zoneinfo.


Leap second data is there too, so it should be possible to create a 
Data.Time.Clock.TAI.LeapSecondTable from it.


Also, it might be worth creating an OS-specific package that dealt with 
the filepaths for you, so for instance you could read in a 
TimeZoneSeries given a time zone name such as America/Los_Angeles.


--
Ashley Yakeley

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


Re: [Haskell-cafe] Fwd: Data.Time

2011-07-02 Thread Ashley Yakeley

On 2011-07-02 13:22, Yitzchak Gale wrote:

Ashley, heads up! I am CCing you on this message because
I think a problem has been found with Data.Time.Format.


Thanks Yitzchak.


when you think that this is not a parseable date:
2011/1/30 (because the month must be padded by zeros).


Hmm, that does seem wrong. The C API allows that to be
parsed using the format %Y/%m/%d, since the leading zero
for %m and %d are optional when parsing.
See, for example,
http://pubs.opengroup.org/onlinepubs/009695399/functions/strptime.html


This was fixed in time-1.2.0.5. From the haddock for parseTime:

Supports the same %-codes as formatTime, including %-, %_ and %0 
modifiers.


With ghci:

Prelude System.Locale Data.Time parseTime defaultTimeLocale 
%Y/%-m/%-d 2011/1/30 :: Maybe Day

Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package time-1.2.0.5 ... linking ... done.
Just 2011-01-30

--
Ashley Yakeley

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


Re: [Haskell-cafe] Fwd: Data.Time

2011-07-02 Thread Ashley Yakeley

On 2011-07-02 16:35, Yitzchak Gale wrote:


It is important to note that this works differently than the usual
strptime behavior, though. For example, %m in Data.Time is
an alias for %0m, whereas %m in strptime means the
same as %-m in Data.Time (optional leading zero).


I made some changes from the C lib behaviour for consistency. In C, %m 
means %0m in strftime and %-m in strptime. I decided to make it 
%0m consistently. Also, at least in glibc, the %# modifier does not 
consistently convert to lower case. In Data.Time it does.


--
Ashley Yakeley

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


[Haskell-cafe] Re: Re: instance Eq (a - b)

2010-04-19 Thread Ashley Yakeley
Why is a function that gets a bunch of strict ByteStrings out of a lazy
one exposed?

In any case, it sounds like a similar situation to (==) on Float and
Double. There's a mismatch between the Haskellish desire for a law on
(==), and the convenient desire for -0.0 == 0.0, or for exposing
toChunks. Which one you prefer depends on your attitude. My point is not
so much to advocate for the Haskellish viewpoint than to recognise the
tension in the design. Float and Double are pretty ugly anyway from a
Haskell point of view, since they break a bunch of other desirable
properties for (+), (-) and so on.

The theoretical reason for using floating point rather than fixed point
is when one needs relative precision over a range of scales: for other
needs one should use fixed point or rationals. I added a Fixed type to
base, but it doesn't implement the functions in the Floating class and I
doubt it's as fast as Double for common arithmetic functions.

It would be possible to represent the IEEE types in a Haskellish way,
properly revealing all their ugliness. This would be gratifying for us
purists, but would annoy those just trying to get some numeric
calculations done.

-- 
Ashley Yakeley


On Mon, 2010-04-19 at 15:32 -0400, Edward Kmett wrote:

 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 ash...@semantic.org
 wrote:
 
 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
 
 
 
 ___
 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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-17 Thread 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 decidable equality in Haskell 
(which Oleg claims that everyone knows ;).


I don't know off the top of my head what the class member for Compact 
should be.  I'd guess it should have a member search :: (a - Bool) - a 
with the specificaiton that p (search p) = True iff p is True from some 
a. But I'm not sure if this is correct or not.  Maybe someone know knows 
more than I do can claify what the member of the Compact class should be.


http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/ 


Here's a first attempt, which works when I tried comparing values of 
type ((Integer - Bool) - Bool). It needs some generalisation, however. 
I want to be able to write these:


  instance (Countable a,Countable b) = Countable (a,b)
  instance (Countable c,Compact b) = Compact (c - b)

...


{-# LANGUAGE FlexibleInstances #-}
module Compact where

  import Data.List
  import Data.Maybe
  import Prelude

  class Countable a where
countPrevious :: a - Maybe a

  countDown :: (Countable a) = a - [a]
  countDown a = case countPrevious a of
Just a' - a':(countDown a')
Nothing - []

  instance Countable () where
countPrevious () = Nothing

  instance Countable Bool where
countPrevious True = Just False
countPrevious False = Nothing

  instance Countable Integer where
countPrevious 0 = Nothing
countPrevious a | a  0 = Just (- a - 1)
countPrevious a = Just (- a)

  instance (Countable a) = Countable (Maybe a) where
countPrevious = fmap countPrevious

  class Compact a where
search :: (a - Bool) - Maybe a
forsome :: (a - Bool) - Bool
forsome = isJust . search

  forevery :: (Compact a) = (a - Bool) - Bool
  forevery p = not (forsome (not . p))

  instance (Compact a) = Compact (Maybe a) where
search mab = if mab Nothing
 then Just Nothing
 else fmap Just (search (mab . Just))

  prepend :: (Countable c) = b - (c - b) - c - b
  prepend b cb c = case countPrevious c of
Just c' - cb c'
Nothing - b

  find_i :: (Countable c) = ((c - Bool) - Bool) - c - Bool
  find_i cbb = let
b = forsome(cbb . (prepend True)) in
prepend b (find_i (cbb . (prepend b)))

  instance (Countable c) = Compact (c - Bool) where
forsome cbb = cbb (find_i cbb)
search cbb = if forsome cbb then Just(find_i cbb) else Nothing

  instance (Compact a,Eq b) = Eq (a - b) where
p == q = forevery (\a - p a == q a)

  class (Compact a,Countable a) = Finite a where
allValues :: [a]

  finiteSearch :: (Finite a) = (a - Bool) - Maybe a
  finiteSearch p = find p allValues

  instance Compact () where
search = finiteSearch

  instance Finite () where
allValues = [()]

  instance Compact Bool where
search = finiteSearch

  instance Finite Bool where
allValues = [False,True]

  instance (Finite a) = Finite (Maybe a) where
allValues = Nothing:(fmap Just allValues)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-17 Thread Ashley Yakeley

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-17 Thread Ashley Yakeley

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Ashley Yakeley
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 instances of equality manage to have a Eq instance.  The other 
 data types one has an (partial) equivalence relation in mind but it goes 
 unwritten.
 
 But in my dependently typed world we don't have partial values so there 
 are no bottoms to worry about; maybe these ideas don't carry over 
 perfectly.

It's an interesting approach, though, since decided equality seems to
capture the idea of full value fairly well.

I'm currently thinking along the lines of a set V of Platonic values,
while Haskell names are bound to expressions that attempt to calculate
these values. At any given time during the calculation, an expression
can be modelled as a subset of V. Initially, it's V, as calculation
progresses it may become progressively smaller subsets of V.

Saying a calculation is bottom is to make a prediction that cannot in
general be decided. It's to say that the calculation will always be V.
If it ever becomes not V, it's a partial value. If it ever becomes a
singleton, it's a complete value.

On the other hand, this approach may not help with strict vs. non-strict
functions.

-- 
Ashley Yakeley

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Ashley Yakeley

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 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).


A Haskellish solution would be to implement Eq so that it compares the 
bits of the representations of Float and Double, thus -0.0 /= 0.0, NaN 
== NaN (if it's the same NaN). But this might surprise people expecting 
IEEE equality, which is probably almost everyone using Float or Double.


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


[Haskell-cafe] Re: Nomic game in Haskell

2010-04-15 Thread Ashley Yakeley

On 2010-04-15 14:00, Dan Piponi wrote:


(A neutral third party will have to implement Board.)


data Three a b c where
{
  MkThree :: Three () () ()
}

type Board a b c d e f g h i =
 Either (Three a b c)
 (Either (Three d e f)
 (Either (Three g h i)
 (Either (Three a d g)
 (Either (Three b e h)
 (Either (Three c f i)
 (Either (Three a e i)
 (Either (Three c e g)
 )))

Player 2 wins, I think.

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


[Haskell-cafe] Re: Nomic game in Haskell

2010-04-15 Thread Ashley Yakeley

On 2010-04-15 17:39, Dan Piponi wrote:


In the service of readability we could also define:

data X = X
data O


In that case we'd want

  type Three a b c = (a,b,c)

...which is simpler than my GADT.

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


[Haskell-cafe] instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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

Of course, it's not perfect, since empty types are finite but not 
Bounded. One can nevertheless make them instances of Bounded with 
undefined bounds, and have enumFrom and friends always return the empty 
list.


It seems one should also be able to write

  instance (Bounded a,Enum a) = Traversable (a - b) where ???

But this turns out to be curiously hard.

--
Ashley Yakeley

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


Re: [Haskell-cafe] instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley
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 instance, Bool.

-- 
Ashley Yakeley

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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

  instance (Finite a,Eq a) = Traversable (a - b) where
 sequenceA afb = fmap lookup
   (sequenceA (fmap (\a - fmap (b - (a,b)) (afb a)) allValues))
  where
   lookup :: [(a,b)] - a - b
   lookup (a,b):_ a' | a == a' = b
   lookup _:r a' = lookup r a'
   lookup [] _ = undefined

  instance Finite () where
allValues = [()]

  data Nothing

  instance Finite Nothing where
allValues = []

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley
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 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.

-- 
Ashley Yakeley

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 type.


For this reason I recommend fast and loose reasoning:
http://www.cs.nott.ac.uk/~nad/publications/danielsson-et-al-popl2006.html

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley
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

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 fine.

Of course, sometimes we may want to add _additional_ information 
concerning bottom, such as strictness.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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. They're very useful.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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, so it doesn't need to evaluate it. g waits 
forever trying to evaluate its function, not knowing it doesn't need it.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

Ivan Lazar Miljenovic wrote:

Ashley Yakeley ash...@semantic.org 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 instance, Bool.


You didn't make such a restriction; you wanted it for _all_ function types.


That's OK. There are lots of ways of writing computationally expensive 
things in Haskell. If you really want to compare two functions over 
Word32, using my (==) is no more computationally expensive than any 
other way.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 differently. f is smart enough to know that its
argument doesn't matter, so it doesn't need to evaluate it. g waits
forever trying to evaluate its function, not knowing it doesn't need it.


Hence they are distinct functions,


They are distinct Haskell functions, but they represent the same moral 
function.



and should not be determined to be equal by an equality instance.


I don't see why not. It doesn't break the expected Eq laws of 
reflexivity, symmetry, transitivity. Also, it supports this law:


  if f == g = True, then f x == g x = True

... in exactly the same way that it supports reflexivity, that is, fast 
and loose ignoring bottom.



A compiler will not transform g into f
because said distinction is important and part of the definition of a
function.


I'm not seeing this implication as part of the semantics of (==).

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 calculate 
values, because your calculation would never terminate (or similar 
condition).


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 fact proper values are not just subsets of values but are also
quotients.

thus (-0.0) and 0.0 denote the same proper value even though they are
represented by different Haskell values.


The trouble is, there are functions that can distinguish -0.0 and 0.0. 
Do we call them bad functions, or are the Eq instances for Float and 
Double broken?


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Ashley Yakeley

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 undefined nor (0.0/0.0) are proper values

In fact proper values are not just subsets of values but are also
quotients.

thus (-0.0) and 0.0 denote the same proper value even though they are
represented by different Haskell values.


The trouble is, there are functions that can distinguish -0.0 and 0.0.
Do we call them bad functions, or are the Eq instances for Float and
Double broken?


Worse, this rules out values of types that are not Eq.

--
Ashley Yakeley

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


[Haskell-cafe] Re: a way to convert partial functions to functions with Maybe's

2010-04-13 Thread Ashley Yakeley

On 2010-04-13 03:02, Ozgur Akgun wrote:


I want a function to generate func1Fixed, given func1.


Don't do that, it's unHaskellish. Bottom is for non-termination (which 
you absolutely cannot catch) plus some other conditions to be treated 
similarly.


If the implementer of func1 decided to return pseudo-non-termination, 
that's what you get.


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


Re: [Haskell-cafe] Cabal, GHC and Preprocessors

2010-04-12 Thread Ashley Yakeley
On Mon, 2010-04-12 at 06:51 +0100, Malcolm Wallace wrote:
 Even without that, it may be possible to get what you want, using
 -pgmPcpphs -optP-cpp -optP-ansi
 that is, to override ghc's addition of -traditional with -ansi.   
 However I'm not sure exactly what order the preprocessor arguments  
 will reach cpphs - in a choice between -traditional and -ansi, it is  
 the last one on the cpphs commandline that will take effect.

This worked in my .cabal file:

cpp-options: --cpp -ansi
ghc-options: -pgmPcpphs

Thanks!

-- 
Ashley Yakeley

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


[Haskell-cafe] Cabal, GHC and Preprocessors

2010-04-11 Thread Ashley Yakeley

I want identifier concatenation in Haskell. For instance:

  #define CDecl(n) = class C_##n a where { f_##n :: a };

  CDecl(1)
  CDecl(2)
  CDecl(3)

(Actual motivator involves generating by type kind.)

I have no trouble switching on CPP, but this doesn't work.

The trouble is, GHC uses gcc for preprocessing, and it passes 
-traditional which switches this off. There doesn't seem to be a flag 
to override this.


I've tried replacing the GHC preprocessor with cpphs using -pgmP, but 
GHC passes include files using -include, while cpphs only accepts 
--include.


I've tried telling Cabal to use cpphs, but even if you rename the source 
file to .cpphs, it will still use GHC's gcc preprocessor rather than 
cpphs. In any case, it's not clear how to tell Cabal to pass --hashes to 
cpphs.


I've tried using Template Haskell instead, but you can't easily splice 
identifiers, only expressions, types and top-level declarations.


--
Ashley Yakeley

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


[Haskell-cafe] Re: GSOC idea: Haskell JVM bytecode library

2010-03-30 Thread Ashley Yakeley

Alexandru Scvortov wrote:
 I'm thinking of writing a library for 

analyzing/generating/manipulating JVM
bytecode.  To be clear, this library would allow one to load and work with JVM 
classfiles; it wouldn't be a compiler, interpretor or a GHC backend.


You might be interested in http://semantic.org/jvm-bridge/. It's a bit 
bit-rotted, though.


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


[Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-30 Thread Ashley Yakeley

Edward Kmett wrote:
Of course, you can argue that we already look at products and coproducts 
through fuzzy lenses that don't see the extra bottom, and that it is 
close enough to view () as Unit and Unit as Void, or go so far as to 
unify Unit and Void, even though one is always inhabited and the other 
should never be.


The alternative is to use _consistently_ fuzzy lenses and not consider 
bottom to be a value. I call this the bottomless interpretation. I 
prefer it, because it's easier to reason about.


In the bottomless interpretation, laws for Functor, Monad etc. work. 
Many widely-accepted instances of these classes fail these laws when 
bottom is considered a value. Even reflexivity of Eq fails.


Bear in mind bottom includes non-termination. For instance:

  x :: Integer
  x = x + 1

  data Nothing
  n :: Nothing
  n = seq x undefined

x is bottom, since calculation of it doesn't terminate, but one cannot 
write a program even in IO to determine that x is bottom. And if Nothing 
is inhabited with a value, does n have that value? Or does the 
calculation to find which value n is not terminate, so n never gets a value?


I avoid explicit undefined in my programs, and also hopefully 
non-termination. Then the bottomless interpretation becomes useful, for 
instance, to consider Nothing as an initial object of Hask particularly 
when using GADTs.


I also dislike Void for a type declared empty, since it reminds me of 
the C/C++/C#/Java return type void. In those languages, a function of 
return type void may either terminate or not, exactly like Haskell's ().


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


[Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-30 Thread Ashley Yakeley

Ashley Yakeley wrote:

Edward Kmett wrote:
Of course, you can argue that we already look at products and 
coproducts through fuzzy lenses that don't see the extra bottom, and 
that it is close enough to view () as Unit and Unit as Void, or go so 
far as to unify Unit and Void, even though one is always inhabited and 
the other should never be.


The alternative is to use _consistently_ fuzzy lenses and not consider 
bottom to be a value. I call this the bottomless interpretation. I 
prefer it, because it's easier to reason about.


In the bottomless interpretation, laws for Functor, Monad etc. work. 
Many widely-accepted instances of these classes fail these laws when 
bottom is considered a value. Even reflexivity of Eq fails.


Worse than that, if bottom is a value, then Hask is not a category! Note 
that while undefined is bottom, (id . undefined) and (undefined . id) 
are not.


That's a fuzzy lens...

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


[Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-30 Thread Ashley Yakeley

wagne...@seas.upenn.edu wrote:
Forgive me if this is stupid--I'm something of a category theory 
newbie--but I don't see that Hask necessarily has an initial object in 
the bottomless interpretation. Suppose I write


data Nothing2

Then if I understand this correctly, for Nothing to be an initial 
object, there would have to be a function f :: Nothing - Nothing2, 
which seems hard without bottom.


 This is a difference between Hask and
 Set, I guess: we can't write down the empty function.

Right. It's an unfortunate limitation of the Haskell language that one 
cannot AFAIK write this:


 f :: Nothing - Nothing2;
 f n = case n of
 {
 };

However, one can work around it with this function:

 never :: Nothing - a
 never n = seq n undefined;

Of course, this workaround uses undefined, but at least never has the 
property that it doesn't return bottom unless it is passed bottom.


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


[Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-30 Thread Ashley Yakeley

wagne...@seas.upenn.edu wrote:
I believe I was claiming that, in the absence of undefined, Nothing and 
Nothing2 *aren't* isomorphic (in the CT sense).


Well, this is only due to Haskell's difficulty with empty case 
expressions. If that were fixed, they would be isomorphic even without 
undefined.


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


[Haskell-cafe] Re: Haskell.org re-design

2010-03-28 Thread Ashley Yakeley

Christopher Done wrote:

On 28 March 2010 22:54, Don Stewart d...@galois.com wrote:

This looks great!

What are the implementation details of having this go live?

   * Ashley: would you be able to e.g. install an index.html like this,
 and hang the wiki under it?
   * How do we allow editing (by trusted users?)


I've emailed Ashley about sorting this out. I'll stick to the way it's
currently done, wikimedia template for the home page. I'll just make
the index page a special case somehow or make a new index file to pull
the necessary bits from the wiki database. Let's go, Ashley!


Is the front page a wiki page?

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


[Haskell-cafe] Re: Haskell.org re-design

2010-03-28 Thread Ashley Yakeley

Christopher Done wrote:

On 28 March 2010 23:32, Ashley Yakeley ash...@semantic.org wrote:

There was a big competition for the logo, with this blind Condorcet voting
and everything, and this is the shape that was picked. But it kind of ran
out of steam before colours were decided upon. So I just copied the colours
from the Haskell Platform logo...


Sure. Maybe the colours are great, I don't know. But I can't get them
to work very well, personally.


No, you're right, they're ugly colours IMO.


On 28 March 2010 23:25, Ashley Yakeley ash...@semantic.org wrote:

Is the front page a wiki page?


By the looks of it, yes. If you go to 'Edit this page', you can see
that it's made out of wikimedia templates. But that's just a guess.


I meant, in the redesign, is the intent to make the front page a wiki 
page, or a special static page?


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


[Haskell-cafe] Re: [ANN] text 0.7, fast Unicode text

2009-12-15 Thread Ashley Yakeley

Bryan O'Sullivan wrote:
The new 0.7 release of the text package 
http://hackage.haskell.org/package/text adds support for Unicode I/O, 
using either the new locale-aware Handle code in 6.12 or a fallback on 
older releases.


Details: 
http://www.serpentine.com/blog/2009/12/15/data-text-0-7-gains-io-support/


How do you pack Unicode codepoints into Word16? Do you use UTF-16?

Supposing -

  s = \x010A60\x010A61 -- Old South Arabian script
  t = pack s

Is (unpack t) the same as s? What is (length t)?

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


[Haskell-cafe] Re: [ANN] text 0.7, fast Unicode text

2009-12-15 Thread Ashley Yakeley

Cetin Sert wrote:

http://corsis.sourceforge.net/img/csharp-6.png
http://corsis.sourceforge.net/img/csharp-6.pngo__O!?


That's just C# string literals. In Haskell, '\x010A60' '\x010A61', but 
in C#, '\x010A' '6' '0' '\x010A' '6' '1'.


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


[Haskell-cafe] Re: systemtimmetypeable: Workaround for lack of deriveable data instance in either System.Time or Data.Time.

2009-10-21 Thread Ashley Yakeley
Data.Fixed (in base) has been updated with Data instances in HEAD. When
that's released, I'll release time-extra that will contain Data
instances. I've got it all ready to go.

The reason Data instances are in time-extras is that the time library
must be Haskell 98, while Data instances require Rank2.

-- Ashley

On Wed, 2009-10-21 at 11:15 -0500, Thomas Hartman wrote:
 update:
 
 on haskell reddit, dons suggested simply patching time. reasonable
 enough, but I hit a glitch where the Data.Fixed (in base lib) was
 missing a Data instance, and gave up when I couldn't find the source
 repo for base. Is this simply part of ghc?
 
 Anyways, that instance seems to be added in ghc 6.12 so probably a non
 issue now or closer to it.
 
 http://www.haskell.org/ghc/dist/current/docs/html/libraries/base/Data-Fixed.html
 
 also, aavogton #haskell suggested
 
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=11009#a11009
 
 as a workaround for people using time on happstack earlier than 6.12,
 probably nicer than the MyTime hack I created though it comes with a
 bit more baggage.
 
 I haven't upgraded to 6.12 but I would suggest that time now be made
 Data Generics friendly if it hasn't already, since this is probably a
 very simple change and would be helpful to happstack. If no one has
 time to do this I'll try to get around to it when I upgrade to 6.12.
 
 Also wouter swierstra suggested that standalone deriving (
 http://www.haskell.org/ghc/docs/latest/html/users_guide/deriving.html#stand-alone-deriving
 ) could be helpful in this case but I'm not sure why, or even whether
 this was for data-izing data.time or system.time or both.
 
 Given all this I won't be uploading anything to hackage, and hopefully
 the base libs + time will be data friendly soon enough.
 
 thomas.
 
 2009/10/19 Thomas Hartman tphya...@gmail.com:
  At
 
  http://osdir.com/ml/haskell-cafe@haskell.org/2009-10/msg00197.html
 
  I griped that the lack of Data-Derivable time values was causing me
  headache in happstack.
 
  In the proposed cabal package
 
  http://patch-tag.com/r/tphyahoo/systemtimetypeable/snapshot/current/content/pretty/systemtimetypeable.cabal
 
  I submit a workaround that, while probably not the ideal thing, has
  proved helpful to me.
 
  Basically, I use the type MyTime, which is data-deriveable, when
  working with Macid in happstack; and convert from System.Time and/or
  Data.Time with the accompanying utility functions when necessary.
  Perhaps the utility functions are useful on their own as well. I found
  it surprisingly hard to get from Data.Time values to System.Time
  values.
 
  Anyways, I am interested in what others think and, of course, patches
  and suggestions welcome.
 
  thomas.
 
 

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


Re: [Haskell-cafe] Re: Are GADTs what I need?

2009-07-14 Thread Ashley Yakeley
On Mon, 2009-07-13 at 23:20 -0700, Jason Dagit wrote:
  data EqualType a b where
MkEqualType :: EqualType t t
 
 Is there any reason to prefer this over:
 data EqualType a b where
   MkEqualType :: EqualType a a

They're exactly the same. Yours just looks a bit left-biased, that's
all.

-- 
Ashley Yakeley

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


[Haskell-cafe] Re: Are GADTs what I need?

2009-07-13 Thread Ashley Yakeley

Ryan Ingram wrote:


data Type a where
   TInt :: Type Int
   TBool :: Type Bool
   TChar :: Type Char
   TList :: Type a - Type [a]
   TFun :: Type a - Type b - Type (a - b)


Type here is what I call a simple type witness. Simple type witnesses 
are useful because they can be compared by value, and if they have the 
same value, then they have the same type.


So you can write this:

  data EqualType a b where
MkEqualType :: EqualType t t

  matchWitness :: Type a - Type b - Maybe (EqualType a b)
  matchWitness TInt TInt = Just MkEqualType
  matchWitness TBool TBool = Just MkEqualType
  matchWitness TChar TChar = Just MkEqualType
  matchWitness (TList w1) (TList w2) = do
MkEqualType - matchWitness w1 w2
return MkEqualType
  matchWitness (TFun wa1 wb1) (TFun wa2 wb2) = do
MkEqualType - matchWitness wa1 wa2
MkEqualType - matchWitness wb1 wb2
return MkEqualType
  matchWitness _ _ = Nothing

Now whenever you match some value with MkEqualType, the compiler will 
infer the identity of the two types. See my witness package:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/witness

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


[Haskell-cafe] Re: Wiki user accounts

2009-06-18 Thread Ashley Yakeley

I wrote:
Rules for usernames are the same as rules for particle titles, 


erm, article titles

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


[Haskell-cafe] Re: Wiki user accounts

2009-06-16 Thread Ashley Yakeley

Maurí­cio wrote:

Maybe OpenID could help with spam problems without
the need for manual intervention:

   http://www.mediawiki.org/wiki/Extension:OpenID


Nope, can't install it on this version.
http://haskell.org/haskellwiki/Special:Version

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


[Haskell-cafe] Re: Wiki user accounts

2009-06-16 Thread Ashley Yakeley

I wrote:

OK, so who wants to create accounts? What are your haskell.org usernames?


Anyone else? Gwern? Philippa?

--
Ashley Yakeley

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


[Haskell-cafe] Re: Wiki user accounts

2009-06-16 Thread Ashley Yakeley

OK, the people listed here have been given the ability to create accounts:

http://haskell.org/haskellwiki/?title=Special%3AListusersgroup=createaccount

I'm willing to hand this ability out to pretty much anyone who seems 
unlikely to be a spammer.


To create an account, go to the login page. 
http://haskell.org/haskellwiki/Special:Userlogin


You should see five text boxes instead of two. Enter the desired 
username, and the person's email, and click on the by email button. 
You do not need to enter a password.


Rules for usernames are the same as rules for particle titles, so the 
first character cannot be a lower-case letter (actually, it will get 
folded to upper-case). But spaces are OK.


If you want to let people know that you can do this for them, add your 
email address here:


http://haskell.org/haskellwiki/HaskellWiki:New_accounts

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


[Haskell-cafe] Logo

2009-06-15 Thread Ashley Yakeley

Thomas Davie wrote:
We had a lot of fun deciding Haskell's new logo, and while I don't 
agree with the final result, it would be nice if we could now start 
consistently using it.  With that in mind, I realised that the Haskell 
Platform's logo is totally different, and did a quick mock up of a 
version reflecting the current Haskell logo.  It needs someone with the 
original vector graphics to have a play and improve it a little bit, but 
hopefully you'll se a concept you like.


I rather like the fact that the Haskell Platform logo is distinct from 
the Haskell logo. I think it helps prevent confusion (even though the 
Platform logo is based on one of the Haskell logo competition entrants).


http://haskell.org/haskellwiki/Haskell_Platform

By the way, when I came to replace the Haskell logo on the wiki site, 
since the colours had not and still have not been officially decided on, 
I just picked the same colours as the Haskell Platform logo. So for the 
time being, there is a visual link between the two logos.


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


[Haskell-cafe] Re: Fwd: Logo

2009-06-15 Thread Ashley Yakeley

Robert Greayer wrote:

For anyone concerned the Hackage icon
(http://hackage.haskell.org/favicon.ico) is still the old blue lambda,
not the sparkling new icon (http://haskell.org/favicon.ico).


That's on a different machine. See 
http://haskell.org/haskellwiki/Haskell.org_domain for which machine does 
what.


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


[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Ashley Yakeley

Miguel Mitrofanov wrote:
Suppose I want to create a specific monad as a combination of monad 
transformers - something like StateT smth1 (ReaderT smth2 Identity). 
As you can see, each transformer is parametrized with a type of kind *. 
I want to abstract these parameters, so that instead of StateT smth... 
I can write something like


Zip (ConsT StateT (ConsT ReaderT NilT)) (ConsA smth1 (ConsA smth2 NilA)) 
Identity


and it would be a type isomorphic to the first one. I mean, I want 
(ConsT StateT (ConsT ReaderT NilT)) to be a separate entity of fixed 
kind, so that I can, say, create a class instance for it or something.


I'd be quite happy if list length appears as a separate parameter, like

Zip (Succ (Succ Zero)) (ConsT ...

I would NOT be happy with something like

Zip (List_2 StateT ReaderT) (Arg_2 smth1 smth2)

If haskell had polymorphic kinds, I'd be able to do it easily; 
unfortunately, it doesn't have them.


I think the type families extension can do this.

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


[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Ashley Yakeley

Miguel Mitrofanov wrote:
First, it seems to me that using type families would require some other 
extensions. Multi-parameter type classes are OK, but, in my experience, 
the road from them to the darkness of undecidable instances is quite 
short, and I don't feel very safe on these grounds.


Actually, you can use type families without using classes or instances 
at all.


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


[Haskell-cafe] Re: Wiki user accounts

2009-06-14 Thread Ashley Yakeley

Gwern Branwen wrote:

This runs on MediaWiki, right? How about adding a CAPTCHA for account
registrations?

http://www.mediawiki.org/wiki/Extension:ConfirmEdit


See http://haskell.org/haskellwiki/Special:Version

ConfirmEdit would require an upgrade.


This is the ideal solution. But it requires an update of the machine 
from an old Red Hat distro (RHEL AS release 3 update 9) to something a 
bit more modern, like Debian 5.0 or Ubuntu Server 9.04.


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


[Haskell-cafe] Re: Wiki user accounts

2009-06-14 Thread Ashley Yakeley

Gwern Branwen wrote:

 Presumably Ashley is busy.

Yes. Average request rate is about one each day; I tend to do them in a 
lump about once a week.



One solution would be to have Ashley re-enable user registrations.
This has been suggested before, but no one knows how bad the spam
would be.


Basically, someone was creating thousands of accounts automatically. It 
seems likely this will happen again.



Another solution would be to sysop a few users to
admin/bureaucrat, so that even if a few are inactive or away, the rest
can handle requests.


What would the process be?

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


[Haskell-cafe] Re: Type equality proof

2009-03-19 Thread Ashley Yakeley

Martijn van Steenbergen wrote:

Ashley Yakeley wrote:

Have a look at these:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/witness
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/open-witness


Ah, nice! It seems most we came up with is already in there. Even Any 
which I use in my project but didn't think of putting in the package is 
there. No use anymore for a new package now, I guess. On the other hand, 
I can't find the comm, trans, coerce, subst and resp. Would it be an 
idea to add those to your package?


Well, trans is the same as (.), if you import Control.Category. But by 
and large you don't need those functions. You just match MkEqualType 
where you need it. Since matchWitness returns (Maybe (EqualType a b)), 
you can do this easily with do notation. For instance:


do
  MkEqualType - matchWitness a1 b1
  MkEqualType - matchWitness a2 b2
  return MkEqualType

Current code is in darcs here:
http://code.haskell.org/witness/
http://code.haskell.org/open-witness/

They now target base 4.0.

Also, my paper that explains it:
http://semantic.org/stuff/Open-Witnesses.pdf

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


[Haskell-cafe] Re: Type equality proof

2009-03-18 Thread Ashley Yakeley

Martijn van Steenbergen wrote:

Olá café,

With the recent generic programming work and influences from 
type-dependent languages such as Agda, the following data type seems to 
come up often:



data (a :=: a') where
  Refl :: a :=: a


Everyone who needs it writes their own version; I'd like to compile a 
package with this data type and related utilities, if such a package 
doesn't exist already (I couldn't find one). Below is what I have so 
far; I'd much appreciate it if you added your ideas of what else the 
package should contain.


Have a look at these:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/witness
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/open-witness

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


[Haskell-cafe] Re: Haskell Logo Voting has started!

2009-03-17 Thread Ashley Yakeley

There are larger versions of most of them here:
http://www.haskell.org/haskellwiki/Haskell_logos/New_logo_ideas

30 should probably have been split up by typeface.

My votes: 68, 58, 59, 30, 6, 61, 3, 37, 34, 36, rest.

I had trouble choosing between my top four.

Note that votes cannot be modified after being cast.

Probably I'll be the one to update most appearances on haskell.org once 
we have a winner, though I think the logo appears in a number of places 
around the web.


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


[Haskell-cafe] Re: Uploading files to the wiki

2009-03-16 Thread Ashley Yakeley

Wouter Swierstra wrote:
I can't manage to upload files to the Haskell wiki. I've tried different 
browsers, different internet connections, different machines, different 
operating systems, and different user accounts - all without success. Is 
this a new anti-spam measure?


This is slightly annoying. I was looking to release the next 
Monad.Reader on the wiki. Thanks for any advice,


It turns out that both PHP and Apache have limits on file uploads. The 
PHP limit was set to 2MiB, and there was also a PHP-specific Apache 
configuration that limited POSTs to 0.5MiB. So Apache responded to this 
upload with a 413 error. MediaWiki (perhaps wisely) does not add its own 
upload limit, though it does issue a warning confirmation for files 
bigger than 150KiB.


I've set both limits to 20MiB, and switched off MediaWiki's warning. 
I've uploaded Wouter's file to [[Image:TMR-Issue13.pdf]].


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


[Haskell-cafe] Re: Haskell-Wiki Account registration

2009-03-14 Thread Ashley Yakeley

Henning Thielemann wrote:


How long will the Wiki account registration be disabled? Would it be 
possible to ask a question, that real Haskellers could easily answer, 
but a spambot cannot? E.g. What's Haskell's surname?


It will be re-enabled when an appropriate extension to MediaWiki is 
installed.


An appropriate extension will be installed when MediaWiki is upgraded to 
a version that supports that.


MediaWiki will be upgraded when PHP and MySQL are upgraded.

MySQL cannot easily be upgraded on the existing distribution (RHEL AS 3 
update 9 with Linux 2.4.21), as various other packages depend on the 
current version. MySQL will be upgraded when we have a more up-to-date 
distribution (for instance, Debian 4.0).

http://haskell.org/pipermail/haskell/2009-January/020916.html

We will have a more up-to-date distribution when a new machine takes 
over from the existing machine at Yale.


I don't know when anyone will have a new machine.

This is an overview of which machine does what:
http://haskell.org/haskellwiki/Haskell.org_domain

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


[Haskell-cafe] Re: Does anybody dislike implicit params as much asI do?

2009-03-14 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

I think they have a useful place in propagating semi-global
configuration information without imposing huge syntactic overhead.


Right, for instance,

  type MyMonad a = (?env :: Env) = IO a

No lift needed!

I was hoping to use IPs to do OO-style implicit type conversion from a 
derived type to base type. For instance:


  type Base = forall a. ((?f1 :: Int) = a) - a

  field1 :: Base - Int
  field1 b = b ?f1

  type Derived = forall a. ((?f1 :: Int, ?f2 :: String) = a) - a

  d :: Derived
  d x = let {?f1 = 3;?f2 = Hello} in x

  f1d :: Int
  f1d = field1 d

Annoyingly, GHC objects to the field1 d application.

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


Re: [Haskell-cafe] Logo Preferences

2009-03-09 Thread Ashley Yakeley
On Mon, 2009-03-09 at 10:08 +, Sebastian Sylvan wrote:

 But the point is that you shouldn't need to rank every single logo,
 just the ones you care about and then you leave the rest at the
 default rank.

You'll also want to rank the popular ones even if you don't like them.

-- 
Ashley Yakeley


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


[Haskell-cafe] Logo Preferences

2009-03-08 Thread Ashley Yakeley

Eelco Lempsink wrote:

The list with options can be found here (for now): 
http://community.haskell.org/~eelco/poll.html  Notice that some (very) 
similar logos are grouped as one option (thanks to Ian Lynagh) All 
submissions compete, so that still makes more than a 100 options!


The voting system we'll use is the Condorcet Internet Voting System 
(http://www.cs.cornell.edu/andru/civs.html).


So ranking all 100+ items on the Condorcet ballot is a bit of a daunting 
task. However, if we get a rough idea of the favourites, we can each cut 
down a bit on the work.


For instance, suppose 82 and 93 are very popular. You might not like 
either of them, but it's worth ranking them on your ballot (after the 
ones you do like) if you have a preference between them. But there's 
less need to rank the ones no-one likes.


I'm currently liking

30 (specifically, 30.7)
58
61 (specifically, the second image)
62

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


[Haskell-cafe] Re: ANN: leapseconds-announced-2009

2009-01-17 Thread Ashley Yakeley
On Sun, 2009-01-18 at 00:34 -0500, Bjorn Buckwalter wrote:
 Thanks for the pointer. My source is the Earth Orientation Parameter
 (EOP) data at http://www.celestrak.com/SpaceData/; specifically I
 autogenerate the module from
 http://www.celestrak.com/SpaceData/eop19620101.txt. Probably looks
 more complicated than necessary but I'm parsing the file anyway for
 other purposes.

With tz, though, you could discover the table at run-time and so be more
likely to be up to date.

-- 
Ashley Yakeley

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


[Haskell-cafe] Re: [Haskell] HaskellWiki Upgrade Aborted

2009-01-11 Thread Ashley Yakeley

Duncan Coutts wrote:

The machine is running RHEL AS 3 update 9 with Linux 2.4.21.


We really need to upgrade the whole thing. Not an easy job given the
range of stuff being run on there by lots of different people.


It might be easier to move the services to another machine, preferably 
running Debian 4.0 (like both monk and nun). I'm not sure how much this 
can be done gradually.


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


[Haskell-cafe] Logos of Other Languages

2008-12-19 Thread Ashley Yakeley

I browsed around a bit for logos from other languages...

Python
http://www.python.org/images/python-logo.gif
The snake pair is visually interesting while still remaining simple. 
The typeface is unusual and yet clean and humanistic. The logo is only 
slightly marred by the TM. Overall, elegant and appealing. A.


Caml
http://caml.inria.fr/styles/modern/title-en.gif
This is actually more of a heading than a logo: it continues to the 
right edge of the page to close the oval. The typeface is readable, but 
the text is a bit verbose, spelling out The Caml Language with a 
visual nod to its ML roots. B+.


Ruby
http://www.ruby-lang.org/images/logo.gif
An ordinary book typeface with an ordinary picture of an ordinary ruby. 
And the strapline A Programmer's Best Friend is vague and uninspired. 
Bland, but at least inoffensive. C.


Perl
http://upload.wikimedia.org/wikipedia/en/e/e0/Programming-republic-of-perl.png
I'm not sure if this is the Perl logo or O'Reilly's Perl logo, but 
it's ugly, busy, difficult to read and a bit obscure. The title 
PROGRAMMING REPUBLIC OF also lends an air of snotty pretension. D.


Apple Dylan
http://osteele.com/projects/images/Dylan.logo-thumb.png
Arty, abstract, vaguely Hermitian, but a bit corporate. Easy to make a 
website favicon from, but the actual word Dylan is not strictly 
included. A-.


All of these get one thing right that the current and most of the 
proposed Haskell logos do not: they don't make any reference to the 
syntax of the language itself. Doing so seems to miss the point of a 
logo: it's supposed to appeal visually, rather than semantically. So I'd 
like to see some submissions that don't use lambdas.


--
Ashley Yakeley
Seattle, WA

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


[Haskell-cafe] Re: Logos of Other Languages

2008-12-19 Thread Ashley Yakeley

George Pollard wrote:

This is why I like Cale's mountain (which incorporates a sneaky
lambda ;P). A mountain peak/summit/apex also has nice connotations!

http://haskell.org/haskellwiki/Haskell_logos/New_logo_ideas#Cale_Gibbard


I think it would be better without the lambda. In fact, many of the 
logos would be improved simply by removing all trace of lambdas and 
other syntactical elements.


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


[Haskell-cafe] Re: deleting spam on the wiki

2008-12-05 Thread Ashley Yakeley
You can blank the page but you cannot delete it. I'll delete the pages
and block the user/IP address later today.

-- Ashley

On Fri, 2008-12-05 at 15:37 +, Duncan Coutts wrote:

 Who is able to delete wiki spam?
 
 http://haskell.org/haskellwiki/?title=Special:Contributionstarget=Tomso123
 
 All the pages created by this user appear to be spam (check the google
 translation) so the account should probably be deleted too.
 
 As I understand it, any registered user can revert changes to a page:
 http://www.haskell.org/haskellwiki/Help:Editing
 
 However if a registered user creates new spam pages then other ordinary
 registered users cannot revert that change.
 
 Is there some way of reporting spam pages to the appropriate people that
 I missed?
 
 Duncan
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Fun with type functions

2008-12-03 Thread Ashley Yakeley

Simon Peyton-Jones wrote:


can you tell us about the most persuasive, fun application
you've encountered, for type families or functional dependencies?


I'm using them to provide witnesses to lenses.

Given two lenses on the same base type, I want to compare them, and if 
they're the same lens, know that they have the same view type.


  data Lens base view = MkLens
  {
-- lensWitness :: ???,
lensGet :: base - view,
lensPut :: base - view - base
  };

How do I compare Lens base view1 and Lens base view2, and match up 
view1 and view2?


The difficulty is that my witnesses are monomorphic, while a lens may be 
polymorphic. For instance, the lens corresponding to the fst function:


  fstLens :: Lens (a,b) a;
  fstLens = MkLens
  {
lensGet = fst,
lensPut = \(_,b) a - (a,b)
  };

I only want to generate one open witness for fstLens, but what is its type?

This is where type functions come in. I have a type family TF, and a 
basic set of instances:


  type family TF tf x;

  data TFIdentity;
  type instance TF TFIdentity x = x;

  data TFConst a;
  type instance TF (TFConst a) x = a;

  data TFApply (f :: * - *);
  type instance TF (TFApply f) x = f x;

  data TFMatch;
  type instance TF TFMatch (f a) = a;

  data TFMatch1;
  type instance TF TFMatch1 (f a b) = a;

  data TFCompose tf1 tf2;
  type instance TF (TFCompose tf1 tf2) x = TF tf1 (TF tf2 x);

I create a new witness type, that witnesses type functions:

  import Data.Witness;

  data TFWitness w x y where
  {
MkTFWitness :: w tf - TFWitness w x (TF tf x);
  };

  instance (SimpleWitness w) = SimpleWitness (TFWitness w x) where
  {
matchWitness (MkTFWitness wtf1) (MkTFWitness wtf2) = do
{
  MkEqualType - matchWitness wtf1 wtf2;
  return MkEqualType;
};
  };

So for my lens type, I want a witness for the type function from base to 
view:


  data Lens base view = MkLens
  {
lensWitness :: TFWitness IOWitness base view,
lensGet :: base - view,
lensPut :: base - view - base
  };

For our fst lens, I can now generate a witness for the function from 
(a,b) to a.


  fstWitness :: IOWitness TFMatch1;
  fstWitness - newIOWitness; -- language extension

  fstLens :: Lens (a,b) a;
  fstLens = MkLens
  {
lensWitness = MkTFWitness fstWitness,
lensGet = fst,
lensPut = \(_,b) a - (a,b)
  };

I can now compare two lenses like this:

  get1put2 :: Lens base view1 - Lens base view2 - base - Maybe base;
  get1put2 lens1 lens2 b = do
  {
MkEqualType - matchWitness (lensWitness lens1) (lensWitness lens2);
return (lensPut lens2 b (lensGet lens1 b));
  };

(Actually, I'm doing something a bit more useful than get1put2.)

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


[Haskell-cafe] Ubuntu Haskell

2008-10-11 Thread Ashley Yakeley

Don Stewart wrote:

* Arch now has 609 Haskell packages in AUR.


Have you thought about doing this for Ubuntu? If you know how to 
automatically generate packages, you could set up a PPA (private package 
archive) on Launchpad.


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


[Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-15 Thread Ashley Yakeley

Tom Hawkins wrote:


data Expr :: * - * where
  Const :: a - Term a
  Equal :: Term a - Term a - Term Bool


Your basic problem is this:

  p1 :: Term Bool
  p1 = Equal (Const 3) (Const 4)

  p2 :: Term Bool
  p2 = Equal (Const yes) (Const no)

p1 and p2 have the same type, but you're not going to be able to compare 
them unless you can compare an Int and a String. What do you want p1 == 
p2 to do?


If you want to just say that different types are always non-equal, the 
simplest way is to create a witness type for your type-system. For instance:


  data MyType a where
IntType :: MyType Int
StringType :: MyType String

Now you'll want to declare MyType as a simple witness:

  instance SimpleWitness MyType where
matchWitness IntType IntType = Just MkEqualType
matchWitness StringType StringType = Just MkEqualType
matchWitness _ _ = Nothing

You'll need to include a witness wherever parameter types cannot be 
inferred from the type of the object, as well as an Eq dictionary:


  data Term :: * - * where
Const :: a - Term a
Equal :: Eq a = MyType a - Term a - Term a - Term Bool

Now you can do:

  instance Eq a = Eq (Term a) where
(Const p1) == (Const p2) = p1 == p2
(Equal w1 p1 q1) (Equal w2 p2 q2) = case matchWitness w1 w2 of
   MkEqualType - (p1 == p2)  (q1 == q2)
   _ - False -- because the types are different
_ == _ = False

Note: I haven't actually checked this. Use cabal install witness to 
get SimpleWitness and EqualType.


--
Ashley Yakeley



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


[Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-15 Thread Ashley Yakeley

Ryan Ingram wrote:


There are many papers that talk about using GADTs to reify types in
this fashion to allow safe typecasting.  They generally all rely on
the base GADT, TEq; every other GADT can be defined in terms of
TEq and existential types.


Ah, yes. See my paper Witnesses and Open Witnesses
http://semantic.org/stuff/Open-Witnesses.pdf

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


[Haskell-cafe] Re: haskell core definition

2008-09-08 Thread Ashley Yakeley

Vlad Skvortsov wrote:
Also, how do I demangle the names? It seems that, for example,  
'base:GHC.Base.ZC' is a (:) function on strings, but where how am I 
supposed to figure that out?
#!/usr/bin/perl
# Written by Ashley Yakeley 2003
# All rights to the public

while ()
{
s/_/ /g;
s/\w+/decode($)/eg;
print;
}

sub commas
{
local($i) = @_;
if ($i == 0)
{
return ;
}
elsif ($i == 1)
{
return  ;
}
else
{
return , x ($i - 1);
}
}

sub decode
{
local($s) = @_;
my $a=;
while ($s =~/([^zZ]*)([zZ].*)/)
{
$a.=$1;
if ($2 =~/([zZ][A-Za-z])(.*)/)
{
{
$a.=(,last if $1 =~/ZL/;
$a.=),last if $1 =~/ZR/;
$a.=[,last if $1 =~/ZM/;
$a.=],last if $1 =~/ZN/;
$a.=:,last if $1 =~/ZC/;
$a.=Z,last if $1 =~/ZZ/;

$a.=z,last if $1 =~/zz/;
$a.=,last if $1 =~/za/;
$a.=|,last if $1 =~/zb/;
$a.=^,last if $1 =~/zc/;
$a.='$',last if $1 =~/zd/;
$a.==,last if $1 =~/ze/;
$a.=,last if $1 =~/zg/;
$a.=#,last if $1 =~/zh/;
$a.=.,last if $1 =~/zi/;
$a.=,last if $1 =~/zl/;
$a.=-,last if $1 =~/zm/;
$a.=!,last if $1 =~/zn/;
$a.=+,last if $1 =~/zp/;
$a.=',last if $1 =~/zq/;
$a.=\\,last if $1 =~/zr/;
$a.=/,last if $1 =~/zs/;
$a.=*,last if $1 =~/zt/;
$a.=_,last if $1 =~/zu/;
$a.=%,last if $1 =~/zv/;
$a.=???;
}
$s = $2;
}
elsif ($2 =~/Z([0-9]+)T(.*)/)
{
$a.=(.commas($1).);
$s = $2;
}
elsif ($2 =~/Z([0-9]+)H(.*)/)
{
$a.=(#.commas($1).#);
$s = $2;
}
elsif ($2 =~/Z([0-9]+)U(.*)/)
{
$a.=chr($1);
$s = $2;
}
else
{
$a.=???.$2;
$s = ;
}
};
return $a.$s;
};___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Top Level -

2008-09-07 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
Suppose I am writing something that I intend to be used as part of a 
plug-in that is reloaded in different forms again and again. And I see 
module K which does something I want, so I use it. It so happens that K 
uses M, which has a -. If I knew that using K in my plug-in would cause 
a memory leak, I would avoid doing so; but since the whole point of - 
is to avoid making the need for some state visible in the API.


The results from the - in M will only be stored once for the life of 
the RTS, no matter how many times your plug-ins are reloaded.


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


[Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
But it's limited to the initialisers. An IORef holding an Integer 
isn't much memory, and it only ever gets leaked once.



It happens every time you load and unload, surely?


No. An initialiser is only ever run once per run of the RTS.

Also I thought this was a general discussion with Data.Unique as a 
concrete example; something else might leak substantially more memory. 
Your witnesses stuff would leak one Integer per module, wouldn't it?


It would leak one Integer per IOWitness initialiser for the run of the RTS.

Finally, any memory leak at all can be unacceptable in some contexts. 
It's certainly not something we should just dismiss as oh, it's only 
small.


Since it's of the order of the number of uniquely identified 
initialisers, it's arguably not a memory leak so much as a static 
overhead. The only way to get a continuous leak is to load and unload an 
endless stream of _different_ modules, each with their own initialisers.


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


[Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
I would call it a leak if something that is no longer being used cannot 
be reclaimed. The endless stream of different modules is possible in 
long-running systems where the code being run evolves or changes over 
time (e.g. something like lambdabot, which runs user-provided code).


This might be fixable with an option to the dynamic load function.

Let us say a module M has a number of top-level - of the form

  val - exp

The set of ACIO expressions exp is the static initialisers of M. The 
RTS must note when each static initialiser is run, and cache its result 
val. Let's call this cache of vals the static results cache of M.


When M is loaded, and a static results cache for M already exists, then 
it will be used for the vals of M.


It is the static results cache that might leak.

Let us have an flag to the dynamic load function, to mark the static 
results cache of M as freeable. If the static results cache is 
freeable, then it will be deleted when M is unloaded (and M is not part 
of the main program).


If you pass True for this flag, your code is unsafe if all of the following:

* M has static initialisers
* M will be loaded again after unloading
* Values from M will be stored elsewhere in the program.

If you pass False for this flag, your code will continuously leak memory 
if you continuously load modules


* that are all different
* that contain static initialisers

There may also have to be some way to specify how to apply the flag to 
dependencies as well.


In general I'm way beyond my knowledge of the RTS, so I may have 
something Very Wrong here. I don't think hs-plugins implements unloading 
 at all currently.


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


[Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
The set of ACIO expressions exp is the static initialisers of M. 
The RTS must note when each static initialiser is run, and cache its 
result val. Let's call this cache of vals the static results cache 
of M.


When M is loaded, and a static results cache for M already exists, 
then it will be used for the vals of M.


This sounds reachable to me, and therefore static overhead and not a 
leak.


You can call it what you like, but it's still unacceptable behaviour, 
particularly since clients of M will have no way of telling from its API 
that it will happen.


That what will happen?

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-05 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

Sounds plausible, although dynamic relocations do slow down linking.

Unloading is another interesting problem. Are we allowed to re-run -
if the module that contained it is unloaded and then reloaded? I'm not
quite sure what the conditions for allowing a module to be unloaded
in general should be, though.


Interesting question. I suppose it's allowable if the guarantees 
attached to the ACIO type imply that it would not be possible to tell 
the difference.


I think this means that all values of types, including newtypes, 
belonging to the module must be unreachable before unloading. Consider 
Data.Unique as a separate loadable module. It's loaded, and various 
Unique values are obtained. But Unique is just a newtype of Integer, and 
comparison between Uniques doesn't use code from Data.Unique. This might 
be difficult to track as once the newtype is boiled away, the code is 
basically dealing with Integers, not Uniques.


I really don't know enough about the RTS to know. The alternative would 
be to keep all initialised values when the module is unloaded. I'm 
guessing this is more feasible.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-05 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

Ashley Yakeley wrote:


I really don't know enough about the RTS to know. The
alternative would be to keep all initialised values
when the module is unloaded. I'm guessing this is more
feasible.


Easier, but a guaranteed memory leak.


But it's limited to the initialisers. An IORef holding an Integer isn't 
much memory, and it only ever gets leaked once.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-04 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

I talked to Don about this and you're right, that doesn't happen.
However
he also confirmed that it does load modules a second time if they are
in the main program as well as the plugin, and it would be difficult to
merge the static and dynamic versions of the module.


Oh dear. To fix this, I suppose the RTS would have to be able to keep 
track of all static initialisers. But it shouldn't otherwise affect 
program optimisation.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-04 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

Oh dear. To fix this, I suppose the RTS would have to be able to
keep track of all static initialisers. But it shouldn't otherwise
affect program optimisation.


What would the RTS actually do?


I don't know enough about the RTS to say. I imagine initialisers would 
have to be marked in object files, so the RTS could link them separately 
when dynamically loading. The RTS would also keep a list of initialisers 
in the main program.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
In any case, what I'm trying to establish below is that it should be a 
safety property of - that the entire module (or perhaps mutually 
recursive groups of them?) can be duplicated safely - with a new name, 
or as if with a new name - and references to it randomly rewritten to 
the duplicate, as long as the result still type checks.


That's not acceptable. This would cause Unique to break, as its MVar 
would be created twice. It would also mean that individual Unique and 
IOWitness values created by - would have different values depending on 
which bit of code was referencing them. It would render the extension 
useless as far as I can see.


It also introduces odd execution scopes again. In order for - to work, 
it must be understood that a given - initialiser in a given module in a 
given version of a given package will execute at most once per RTS. But 
your restriction breaks that.


It's worth mentioning that the current Data.Unique is part of the 
standard base library, while hs-plugins is rather experimental. 
Currently Data.Unique uses the NOINLINE unsafePerformIO hack to create 
its MVar. If hs-plugins duplicates that MVar, that's a bug in 
hs-plugins. It's up to a dynamic loader to get initialisation code correct.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

David Menendez wrote:

Isn't that what we have right now? Typeable gives you a TypeRep, which
can be compared for equality. All the introspection stuff is in Data.


Oh, yes, you're right.

--
Ashley Yakeley

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:
That's not acceptable. This would cause Unique to break, 
as its MVar would be created twice. It would also mean 
that individual Unique and IOWitness values created by
- would have different values depending on which bit 
of code was referencing them. It would render the extension

useless as far as I can see.


The result wouldn't typecheck if two Unique values that now pointed to
the two different modules were compared.


I don't understand. If the dynamic loader were to load the same package 
name and version, and it duplicated the MVar, then Unique values would 
have the same type and could be compared.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

David Menendez wrote:

On Wed, Sep 3, 2008 at 2:53 AM, Ashley Yakeley [EMAIL PROTECTED] wrote:

It's worth mentioning that the current Data.Unique is part of the standard
base library, while hs-plugins is rather experimental. Currently Data.Unique
uses the NOINLINE unsafePerformIO hack to create its MVar. If hs-plugins
duplicates that MVar, that's a bug in hs-plugins. It's up to a dynamic
loader to get initialisation code correct.


Data.Unique describes itself as experimental and non-portable. The
Haskell 98 report includes NOINLINE, but also states that environments
are not required to respect it. So hs-plugins wouldn't necessarily be
at fault if it didn't support Data.Unique.


I found this:

To solve this the hs-plugins dynamic loader maintains state storing a 
list of what modules and packages have been loaded already. If load is 
called on a module that is already loaded, or dependencies are attempted 
to load, that have already been loaded, the dynamic loader ignores these 
extra dependencies. This makes it quite easy to write an application 
that will allows an arbitrary number of plugins to be loaded.

http://www.cse.unsw.edu.au/~dons/hs-plugins/hs-plugins-Z-H-6.html

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

I am suggesting that this duplication process, whether conducted by the
dynamic loader or something else, should behave as if they did not have
the same package name or version.

This is certainly a valid transformation for Data.Unique, I am simply
saying that it should be a valid transformation on any module.


So if I dynamically load module M that uses base, I will in fact get a 
completely new and incompatible version of Maybe, IO, [], Bool, Char 
etc. in all the type-signatures of M?


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:
I think it treats them as compatible, using the fact that 
Data.Typeable returns the same type reps (which was why I initially

mentioned Data.Typeable in this thread). This is fine for normal
modules. There's a bit of description in the Dynamic Typing section of
http://www.cse.unsw.edu.au/~dons/hs-plugins/hs-plugins-Z-H-5.html#node_s
ec_9

It's clearly the wrong thing to do for Data.Unique and any anything
else that might use -; but if there are no such types in the interface
of the plugin, then it won't matter. I can't see how to make it
safe to pass Data.Unique etc across a plugin interface without
severely restricting the possible implementation strategies for
a plugin library and its host.


I think it's bad design for a dynamic loader to load a module more than 
once anyway. It's a waste of memory, for a start. We already know that 
hs-plugins won't for modules it already loaded itself (apparently it 
crashes the RTS), and I suspect it doesn't at all.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-03 Thread Ashley Yakeley

Sittampalam, Ganesh wrote:

In compiled code module boundaries don't necessarily exist. So how
do you relink the loaded code so that it points to the unique copy
of the module?


hs-plugins loads modules as single .o files, I believe.


It crashes the RTS of the plugins loader, which is based on ghci, which
is built around loading modules independently. I believe there's a
separate RTS running at the top level of the program which has no
knowledge of the plugin loader.


Two RTSs? Are you quite sure? How would GC work?

The loader is a binding to the GHC runtime system's dynamic linker, 
which does single object loading. GHC also performs the necessary 
linking of new objects into the running process.

http://www.cse.unsw.edu.au/~dons/hs-plugins/hs-plugins-Z-H-2.html#node_sec_4

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
I have a feeling it might be non-trivial; the dynamically loaded bit of 
code will need a separate copy of the module in question, since it might 
be loaded into something where the module is not already present.


Already the dynamic loader must load the module into the same address 
space and GC, i.e. the same runtime. So it should be able to make sure 
only one copy gets loaded.


What is the status of dynamic loading in Haskell? What does hs-plugins 
do currently?


Well, the safety of - being run twice in the Data.Unique case is based 
around the two different Data.Unique types not being compatible.


Right. The only code that can construct Unique values is internal to 
Data.Unique.


Let's 
suppose some other module uses a -, but returns things based on that - 
that are some standard type, rather than a type it defines itself. Is 
module duplication still safe?


In this case, duplicate modules of different versions is as safe as 
different modules. In other words, this situation:


  mypackage-1.0 that uses -
  mypackage-2.0 that uses -

is just as safe as this situation:

  mypackage-1.0 that uses -
  otherpackage-1.0 that uses -

The multiple versions issue doesn't add any problems.

Well, let me put it this way; since I don't like -, and I don't 
particularly mind Typeable, I wouldn't accept IOWitness as an example of 
something that requires - to implement correctly, because I don't see 
any compelling feature that you can only implement with -.


Why don't you like -? Surely I've addressed all the issues you raise? 
Multiple package versions does not actually cause any problems. 
Capabilities would be really nice, but the right approach for that is to 
create a new execution monad. There is an obligation regarding dynamic 
loading, but it looks like dynamic loading might need work anyway.


Since this is a matter of aesthetics, I imagine it will end with a list 
of pros and cons.


There's some unsafety somewhere in both Typeable and IOWitnesses, and in 
both cases it can be completely hidden from the user - with Typeable, 
just don't let the user define the typeOf function at all themselves. 


It's worse than that. If you derive an instance of Typeable for your 
type, it means everyone else can peer into your constructor functions 
and other internals. Sure, it's not unsafe, but it sure is ugly.


Sometimes you want to do witness equality tests rather than type 
equality tests. For instance, I might have a foo exception and a 
bar exception, both of which carry an Int. Rather than create new 
Foo and Bar types, I can just create a new witness for each.


This is precisely what newtype is designed for, IMO. We don't need 
another mechanism to handle it.


It's not what newtype is designed for. Newtype is designed to create 
usefully new types. Here, we're only creating different dummy types so 
that we can have different TypeRep values, which act as witnesses. It's 
the TypeReps that actually do the work.


It would be much cleaner to declare the witnesses directly.

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
Well, the question of whether multiple copies of a module are ok is 
still open, I guess - as you say later, it seems perfectly reasonable 
for two different versions of Data.Unique to exist, each with their own 
types and global variables - so why not two copies of the same version, 
as long as the types aren't convertible? My feeling is that the the 
execution of - needs to follow the Data.Typeable instances - if the two 
types are the same according to Data.Typeable, then there must only be 
one - executed.


They will be different types if they are in different package versions. 
Thus they could have different instances of Typeable. But why do we care 
about Typeable?


So another question following on from that is what happens if there 
isn't any datatype that is an essential part of the module - with 
Unique, it's fine for there to be two -s, as long as the Uniques aren't 
compared. Does this kind of safety property apply elsewhere? It feels to 
me that this is something ACIO (or whatever it would be called after 
being changed) needs to explain.


In the internal implementation of Unique, there must be only one MVar 
constructed with - per Unique type, i.e. per package version. This will 
work correctly, since values of Unique types from different package 
versions have different types, and thus cannot be compared.


Unique values constructed at top level by - will also be unique and 
will work correctly.


  ua - newUnique
  ub - newUnique

Here ua == ub will evaluate to False.

I'd rather use Data.Typeable for this, and make sure (by whatever 
mechanism, e.g. compiler-enforced, or just an implicit contract) that 
the user doesn't break things with dodgy Typeable instances.


You don't think that's rather ugly: a class that needs special 
deriving behaviour? I'd actually like to get rid of all special-case 
deriving: it should be for newtypes only.


Implicit contract is worse. I really shouldn't be able to write coerce 
without referring to something marked unsafe or foreign. Have we 
stopped caring about soundness?


In addition, one can only have one Typeable instance per type. By 
contrast, one can create multiple IOWitness values for the same type. 
For example, one can very easily create a system of open exceptions for 
IO, with an IOWitness value for each exception type, witnessing to the 
data that the exception carries.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
Right, but they might be the same package version, if one is a 
dynamically loaded bit of code and the other isn't.


OK. It's up to the dynamic loader to deal with this, and make sure that 
initialisers are not run more than once when it loads the package into 
the RTS. The scopes and names are all well-defined. How hard is this?


My question was actually about what happens with some different library 
that needs -; how do we know whether having two -s is safe or not?


I don't understand. When is it not safe?

No, it seems like the right way to do introspection to me, rather than 
adding some new mechanism for describing a datatype as your paper

suggests.


Aesthetic arguments are always difficult. The best I can say is, why are 
some classes blessed with a special language-specified behaviour? It 
looks like an ugly hack to me. We have a class with a member that may be 
 safely exposed to call, but not safely exposed to define. How is this 
the right way?


By contrast, top-level - is straightforward to understand. Even the 
scope issues are not hard. It's safe, it doesn't privilege a class with 
special and hidden functionality, it doesn't introspect into types, and 
it allows individual unique values rather than just unique instances per 
type. And it also allows top-level IORefs and MVars.



We could arrange for the class member of Typeable to be called unsafe


We could, but it's not actually unsafe to call as such. It's only unsafe 
to implement. And if we're going the implicit contract route, we have to 
resort to unsafe functions to do type representation. It's not 
necessary, and seems rather against the spirit of Haskell.


Time was when people would insist that unsafePerformIO wasn't Haskell, 
though perhaps useful for debugging. Now we have all these little unsafe 
things because people think they're necessary, and there's an implicit 
contract forced on the user not to be unsafe. But it turns out that 
they're not necessary.


I don't see what the point of multiple values is, I'm afraid. A single 
instance of Typeable is fine for doing type equality tests.


Sometimes you want to do witness equality tests rather than type 
equality tests. For instance, I might have a foo exception and a bar 
exception, both of which carry an Int. Rather than create new Foo and 
Bar types, I can just create a new witness for each.


Or if I want, I can create a dictionary of heterogeneous items, with 
IOWitness values as keys. Then I can do a top-level - to declare keys 
in this dictionary. Now I've got OOP objects.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-31 Thread Ashley Yakeley

Ganesh Sittampalam wrote:

On Sat, 30 Aug 2008, Ashley Yakeley wrote:

OK. Let's call it top-level scope. Haskell naturally defines such a 
thing, regardless of processes and processors. Each top-level - would 
run at most once in top-level scope.


If you had two Haskell runtimes call by C code, each would have its 
own memory allocator and GC; IORefs, Uniques and thunks cannot be 
shared between them; and each would have its own top-level scope, even 
though they're in the same process.


That sounds more feasible - though it does constrain a plugin 
architecture (in which Haskell code can dynamically load other Haskell 
code) to cooperate with the loading RTS and not load multiple copies of 
modules; this might make linking tricky.


This is a good idea anyway. It's up to the dynamic loading architecture 
to get this right.


There's also the problem Duncan 
Coutts mentioned about loading multiple versions of the same module - 
what are the semantics of - in relation to that?


If they are different versions, they ought to be considered different 
modules with different names. Thus, Unique in base-3.0.2.0 ought to be a 
different type than Unique in base-4.0. Thus any top-level initialisers 
ought to be considered different and be run separately.


What's the current static behaviour? What happens if I link with 
packages B  C, which link with different versions of A?


Also, it's no use for mediating access to a resource or library that can 
only be accessed once, right? In fact, even without the problem of two 
Haskell runtimes in one process this can't work, since some library in 
another language might also choose to access that resource or library.


What applications does this leave beyond Data.Unique and Random?


So far we've just looked at declaring top-level IORefs and MVars.

By declaring top-level values of type IOWitness, you can generate open 
witnesses to any type, and thus solve the expression problem. See my 
open witness library and paper:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/open-witness
http://semantic.org/stuff/Open-Witnesses.pdf

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
If you want to standardise a language feature, you have to explain its 
behaviour properly. This is one part of the necessary explanation.


To be concrete about scenarios I was considering, what happens if:

 - the same process loads two copies of the GHC RTS as part of two 
completely independent libraries? For added complications, imagine that 
one of the libraries uses a different implementation instead (e.g. Hugs)


 - one Haskell program loads several different plugins in a way that 
allows Haskell values to pass across the plugin boundary


How do these scenarios work with use cases for - like (a) Data.Unique 
and (b) preventing multiple instantiation of a sub-library?


That's a good question. But before you propose these scenarios, you must 
establish that they are sane for Haskell as it is today.


In particular, would _local_ IORefs work correctly? After all, the 
memory allocator must be global in some sense. Could you be sure that 
different calls to newIORef returned separate IORefs?


Perhaps this is the One True Global Scope: the scope in which refs from 
newIORef are guaranteed to be separate. It's the scope in which values 
from newUnique are supposed to be different, and it would also be the 
scope in which top-level - would be called at most once.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Philippa Cowderoy wrote:

Talking of which, we really ought to look at an IO typeclass or two (not
just our existing MonadIO) and rework the library ops to use it in
Haskell'. You're not the only one to want it, and if it's not fixed this
time it may never get fixed.


This could allow both the best of both worlds, as we could have a monad 
that one couldn't create global variables for, and a monad for which one 
could.


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


[Haskell-cafe] Re: Calling Lockheed, Indra, Thales, Raytheon

2008-08-30 Thread Ashley Yakeley

Paul Johnson wrote:
This is a strange question, I know, but is there anyone working in any 
of the above companies on this mailing list?


Everyone will no doubt be wondering what they have in common.  I'm 
afraid I can't discuss that.


Air Traffic Control?

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
Every single call to newIORef, across the whole world, returns a 
different ref.


How do you know? How can you compare them, except in the same Haskell 
expression?


The same one as a previous one can only be returned 
once the old one has become unused (and GCed).


Perhaps, but internally the IORef is a pointer value, and those pointer 
values might be the same. From the same perspective, one could say that 
every single call to newUnique across the whole world returns a 
different value, but internally they are Integers that might repeat.


It's the scope in which values from newUnique are supposed to be 
different, and it would also be the scope in which top-level - would 
be called at most once.


I don't really follow this. Do you mean the minimal such scope, or the 
maximal such scope? The problem here is not about separate calls to 
newIORef, it's about how many times an individual - will be executed.


Two IO executions are in the same global scope if their resulting 
values can be used in the same expression. Top-level - declarations 
must execute at most once in this scope.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Ashley Yakeley wrote:
I don't really follow this. Do you mean the minimal such scope, or the 
maximal such scope? The problem here is not about separate calls to 
newIORef, it's about how many times an individual - will be executed.


Two IO executions are in the same global scope if their resulting 
values can be used in the same expression. Top-level - declarations 
must execute at most once in this scope.


Better:

Two newIORef executions are in the same global scope if their 
resulting refs can be used in the same expression. Top-level - 
declarations must execute at most once in this scope.


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
How do the implementers of Data.Unique know that they musn't let them be 
serialised/deserialised? What stops the same rule from applying to 
Data.Random?


Unique values should be no more deserialisable than IORefs.

Is it the functionality of Data.Unique that you object to, or the fact 
that it's implemented with a global variable?


If the former, one could easily build Unique values on top of IORefs, 
since IORef is in Eq. Thus Data.Unique is no worse than IORefs (ignoring 
hashability, anyway).


If the latter, how do you recommend implementing Data.Unique? 
Implementing them on IORefs seems ugly. Or should they just be a 
primitive of the platform, like IORefs themselves?


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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-08-30 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
How can they be the same unless the memory management system is broken? 
I consider different pointers on different machines or in different 
virtual address spaces different too; it's the fact that they don't 
alias that matters.


But the actual pointer value might repeat.

every single call to newUnique across the whole world returns a 
different value, but internally they are Integers that might repeat.


The thing about pointers is that they are managed by the standard 
behaviour of memory allocation. This isn't true of Integers.


But it could be. A global variable allows us to do the same thing as the 
memory allocator, and allocate unique Integers just as the allocator 
allocates unique pointer values.


Now you can say that the same pointer value on different machines is 
different pointers; equally, you can say the same Integer in Unique on 
different machines is different Uniques: it's the fact that they don't 
alias that matters.


In fact this point suggests an implementation for Data.Unique that 
should actually be safe without global variables: just use IORefs for 
the actual Unique values. IORefs already support Eq, as it happens. That 
gives you process scope for free,


Isn't this rather ugly, though? We're using IORefs for something that 
doesn't involve reading or writing to them. Shouldn't there be a more 
general mechanism?


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


  1   2   3   >