Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask

On 11/11/2010 5:21 PM, Ketil Malde wrote:

Richard O'Keefeo...@cs.otago.ac.nz  writes:


it is often desirable to have the same field names
for many records in the same module.




very much so, this is currently possible, with the restriction that
the field names must have the same type modulo the record it is 
selecting on.


what is disirable is that this restriction be lifted.


I'm not sure that it is desirable to have many records in the
same module in the first place.




this should really be a choice of the programmer.


One possibility might be to allow mulitple module definitions in the
same file, making it easier to wrap each record in its own module
without running into a Java-like forest of files.



a module represents a compilation unit which happens to be a file, in 
haskell it also represents a name space and a means for control of that 
namespace. Compilation units and name space management are orthoganal 
issues although obviously connected. SML for example manages the name 
space with Functors and does not explicitly name the compilation units, 
haskell names the compilation units i.e. modules, but I have had some 
thoughts along the same lines, myself, more on this later ..



discussion of the haskell record system and syntax has a long history, 
just a quick search ...


http://www.mail-archive.com/hask...@haskell.org/msg17725.html
http://www.haskell.org/pipermail/haskell-prime/2006-March/000836.html
http://www.mail-archive.com/hask...@haskell.org/msg13394.html
http://www.mail-archive.com/hask...@haskell.org/msg20516.html

in 2003

http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

I quote

Haskell lacks a serious record system. (The existing mechanism for 
named fields in data types was always seen as a stop-gap measure.) At 
the 1999 Haskell Workshop, Mark Jones and Simon Peyton Jones proposed a 
more fully-fledged record system, closely modelled on the TRex system 
implemented in Hugs. But Simon never got around to implementing it in 
GHC. Why not? Mainly because the implementation cost turned out to be 
relatively high.


.. in the intervening years we have GADTS, type families, associated 
types tec ... but with respect to records what has changed ?



In my mind, the feature that I most wish for, and what haskell lacks is 
the ability to manage the module name space with respect to record label 
names. Yes, I often want to define a record with the same label name at 
a different type.


many languages have a construct with record which unqualifies the 
names introduced by the record definition, those names being implicitly 
qualified when defined. Haskell label names are implicitly unqualified.


I have often thought that a minimal extension to Haskell compatible with 
the current record system that could ameliorate the situation would be


data Foo = Foo { label1 :: Int, label2 :: String } qualified

where such a qualified data declaration would hide labels label1 and 
label2, making the available only as Foo.label1, Foo.label2., etc


where we have a qualified record we should be able to unqualify it as

import data Foo

or rename it

import data Foo qualified as Bar

which would introduces Bar.label1, Bar.label2

etc.

None of the above is incompatible with the current record system and 
introduces no new keywords. This proposal solely addresses the issue of 
name space management.




(I've proposed this before, and although I don't remember the specifics,
ISTR the response being mostly negative.)

-k


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 12:53 AM, Jesse Schalken
jesseschal...@gmail.com wrote:
 I have had a look at hs-plugins, but it is unclear how to derive a simple
 pair of functions `(a - b) - ByteString` and `ByteString - Either
 ParseError (a - b)`, for example, from the functionality it provides, if it
 is possible at all. I guess such a thing requires thorough digging into the
 depths of GHC, (or maybe even LLVM if
 an architecture independent representation is sought, but I don't know
 enough to say.). Perhaps this is more a question for those interested and
 knowledgable in Haskell compilation (and, to some extent, decompilation).
 If not Haskell, are there any languages which provide a simple serialization
 and deserialization of functions?

As far as I know, GHC has no support for this.  There are issues with
the idea that will come out pretty fast, such as:

(1) Those cannot be pure functions, because it differentiate
denotationally equal functions.  So it would have to be at least (a -
b) - IO ByteString.
(2) What if you tried to serialize a filehandle or an FFI Ptr?

But my answers are Ok and Then you get a runtime error,
respectively.  It is by no means impossible, IIRC Clean does it.   I
think it's pretty dumb that we don't have support for this yet.
Purely functional languages have a unique disposition to be very good
at this.  But oh well, there aren't enough tuits for everything.

A more elaborate answer to (2) is you get a runtime error when you
try to *use* the thing that was impossible to serialize.  This makes
sure that you don't get an error if you are trying to serialize \x -
const x a_filehandle_or_something, which is just the identity
function.

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 1:34 AM, John Lask jvl...@hotmail.com wrote:
 On 11/11/2010 5:21 PM, Ketil Malde wrote:

 Richard O'Keefeo...@cs.otago.ac.nz  writes:

 it is often desirable to have the same field names
 for many records in the same module.


 very much so, this is currently possible, with the restriction that
 the field names must have the same type modulo the record it is selecting
 on.

 what is disirable is that this restriction be lifted.

Haskell has a wonderful history of being careful to consider both
sides of a restriction.  One one hand, a restriction can make it
harder to write something you want to write.  On the other hand, a
restriction can provide properties that make it easy to transform and
reason about your program.

So I am not ready to accept your claim that this is desirable without
further justification.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 1:41 AM, Luke Palmer lrpal...@gmail.com wrote:
 On Thu, Nov 11, 2010 at 1:34 AM, John Lask jvl...@hotmail.com wrote:
 On 11/11/2010 5:21 PM, Ketil Malde wrote:

 Richard O'Keefeo...@cs.otago.ac.nz  writes:

 it is often desirable to have the same field names
 for many records in the same module.


 very much so, this is currently possible, with the restriction that
 the field names must have the same type modulo the record it is selecting
 on.

 what is disirable is that this restriction be lifted.

 Haskell has a wonderful history of being careful to consider both
 sides of a restriction.  One one hand, a restriction can make it
 harder to write something you want to write.  On the other hand, a
 restriction can provide properties that make it easy to transform and
 reason about your program.

 So I am not ready to accept your claim that this is desirable without
 further justification.

Sorry for the self-reply.  I just want to clarify, I didn't mean to
write off your well-thought-out message with this simple comment.  I
was just drawing attention to the duality of restrictions.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Alberto G. Corona
There are some straighforward tricks using the package eval (or hint)l.

This is more or less the idea in pseudocode:

type FuncExpr= String

data F a = F FuncExpr a

apply (F _ f) x= f x

instance Show (F a) where show (F str _)= str

instance Read (F a) where read (F str f)= eval f = F str



2010/11/11 Jesse Schalken jesseschal...@gmail.com

 Is it possible to serialize and deserialize a function to/from binary form,
 perhaps using Data.Binary, for example? What about an IO action? If so, is
 there a way the serialized representation could be architecture-independent?

 I have been shown how useful it can be to store functions inside data
 structures, and while looking at data serialization for the purpose of
 persistence I wondered since functions are just values in Haskell, why
 can't we persist them, too?.

 To me the idea has interesting implications. For example, an arbitrary
 program could simply be represented by a serialization of `IO ()`. In fact,
 you could load any program into memory from a file and use
 Control.Concurrent.forkIO to run it, and later kill it, giving you the
 beginnings of an operating environment. If such a serialization
 is architecture independent then to my understanding you have the beginnings
 of a virtual machine. You could break your program into pieces and store
 them in a database and load them when needed, or even pull updates to each
 piece individually from down the web etc, enabling interesting methods of
 software distribution. It would make very cool stuff possible.

 I have had a look at hs-plugins, but it is unclear how to derive a simple
 pair of functions `(a - b) - ByteString` and `ByteString - Either
 ParseError (a - b)`, for example, from the functionality it provides, if it
 is possible at all. I guess such a thing requires thorough digging into the
 depths of GHC, (or maybe even LLVM if
 an architecture independent representation is sought, but I don't know
 enough to say.). Perhaps this is more a question for those interested and
 knowledgable in Haskell compilation (and, to some extent, decompilation).

 If not Haskell, are there any languages which provide a simple
 serialization and deserialization of functions?

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


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Alberto G. Corona
nstance Read (F a) where read str= eval str = F str

sorry

2010/11/11 Alberto G. Corona agocor...@gmail.com

 There are some straighforward tricks using the package eval (or hint)l.

 This is more or less the idea in pseudocode:

 type FuncExpr= String

 data F a = F FuncExpr a

 apply (F _ f) x= f x

 instance Show (F a) where show (F str _)= str

 instance Read (F a) where read (F str f)= eval f = F str



 2010/11/11 Jesse Schalken jesseschal...@gmail.com

  Is it possible to serialize and deserialize a function to/from binary
 form, perhaps using Data.Binary, for example? What about an IO action? If
 so, is there a way the serialized representation could
 be architecture-independent?

 I have been shown how useful it can be to store functions inside data
 structures, and while looking at data serialization for the purpose of
 persistence I wondered since functions are just values in Haskell, why
 can't we persist them, too?.

 To me the idea has interesting implications. For example, an arbitrary
 program could simply be represented by a serialization of `IO ()`. In fact,
 you could load any program into memory from a file and use
 Control.Concurrent.forkIO to run it, and later kill it, giving you the
 beginnings of an operating environment. If such a serialization
 is architecture independent then to my understanding you have the beginnings
 of a virtual machine. You could break your program into pieces and store
 them in a database and load them when needed, or even pull updates to each
 piece individually from down the web etc, enabling interesting methods of
 software distribution. It would make very cool stuff possible.

 I have had a look at hs-plugins, but it is unclear how to derive a simple
 pair of functions `(a - b) - ByteString` and `ByteString - Either
 ParseError (a - b)`, for example, from the functionality it provides, if it
 is possible at all. I guess such a thing requires thorough digging into the
 depths of GHC, (or maybe even LLVM if
 an architecture independent representation is sought, but I don't know
 enough to say.). Perhaps this is more a question for those interested and
 knowledgable in Haskell compilation (and, to some extent, decompilation).

 If not Haskell, are there any languages which provide a simple
 serialization and deserialization of functions?

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



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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Stephen Tetley
 If not Haskell, are there any languages which provide a simple serialization
 and deserialization of functions?

Napier88 was a persistent language that also had higher-order
functions. I've no experience other than reading about it but as its
persistence was orthogonal persistence I'd expect HOFs to be
persistent. The implementation of Napier88 produced a substantial
runtime / persistent store that was used for other languages - I think
one was Persistent Haskell, certainly one was Staple which was a
higher order language.

Tycoon2 was a similar persistent language - it was heavily influenced
by ML so potentially it had HOFs.

PolyML has a persistent store, though this may have been just for the
top-level to freeze bindings I've no idea whether it supported
serializing HOFs.

Clean supports serialized HOFs as does Oz, see the paper below. Kali
Scheme supported migration of running code between networked computers
- as it was a Scheme I'd expect it to be higher order (the migration
would mandate serialization).


http://www-systems.cs.st-andrews.ac.uk/wiki/Napier88
http://www.polyml.org/FAQ.html
http://www.st.cs.ru.nl/papers/2003/verm2003-LazyDynamicIO.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Thomas Davie

On 11 Nov 2010, at 08:36, Luke Palmer wrote:

 On Thu, Nov 11, 2010 at 12:53 AM, Jesse Schalken
 jesseschal...@gmail.com wrote:
 I have had a look at hs-plugins, but it is unclear how to derive a simple
 pair of functions `(a - b) - ByteString` and `ByteString - Either
 ParseError (a - b)`, for example, from the functionality it provides, if it
 is possible at all. I guess such a thing requires thorough digging into the
 depths of GHC, (or maybe even LLVM if
 an architecture independent representation is sought, but I don't know
 enough to say.). Perhaps this is more a question for those interested and
 knowledgable in Haskell compilation (and, to some extent, decompilation).
 If not Haskell, are there any languages which provide a simple serialization
 and deserialization of functions?
 
 As far as I know, GHC has no support for this.  There are issues with
 the idea that will come out pretty fast, such as:
 
(1) Those cannot be pure functions, because it differentiate
 denotationally equal functions.  So it would have to be at least (a -
 b) - IO ByteString.

I don't think I agree, I didn't see a rule f == g = serialise f == serialise g 
anywhere.

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Gábor Lehel
I agree with the people who want to decouple the dot-syntax from TDNR
itself. To quote myself from the publicly-editable wiki page:

This might be a really dumb question, but is there any reason TDNR
needs to be tied to a new syntax for function application? It seems
strange to me to have one syntax for left-to-right function
application without TDNR, and then another for right-to-left
application with it. I would much rather gain TDNR for the existing
syntax, and then maybe introduce the dot operator as a separate option
if people want it, which I don't. The reason I don't is that (.) as
composition and ($) already work in one direction, which is the same
direction (`foo . bar . baz $ bla` and `foo $ bar $ baz $ bla` are
interchangeable), and while in a vacuum I might even prefer the
opposite direction which (.)-as-application uses, it is much more
important to be consistent. We have a vast body of functions already
written and designed to be convenient with the existing direction:
functions are generally of the form `f :: (what to do) - (what to do
it with) - (result)`, which lends itself well to partial
application/currying and chaining in the existing direction, but not
the other one. (Object oriented languages which use the dot operator
indeed also use the reverse order for their methods, with the object
first and the action second.) Also, reading expressions where
different parts work in different directions is very confusing. The
one major exception which works in the other direction is monadic
bind, (=), which I think was a (minor) mistake, and indeed I
frequently end up using (=) instead. Anyway, executive summary: TDNR
yea, dot operator nay.

Some further thoughts.

I would have TDNR apply only in cases where:
- The functions are all imported from different modules (so you can't
define overlapping names within the same module);
- All of the functions have an explicit type signature;
- The ambiguity can be resolved by looking at the type of the first
(taking currying into account, only) parameter of each function and,
looking at the type constructors from the outside in, comparing only
type constructors which are concrete types, rather than type variables
(with or without constraints). E.g.:
-- f :: Int - [...] and f :: Char - [...] could be resolved;
-- f :: Foo Int - [...] and f :: Foo Char - [...] could be resolved;
-- f :: Foo a - [...] and f :: Bar b - [...] could be resolved;
-- f :: Num a = a - [...] and f :: IsString b = b - [...] could
*not* be resolved (even if it is known that the argument type doesn't
satisfy both constraints);
-- f :: a Int - [...] and f :: b Char - [...] could *not* be
resolved (though I'm less sure about this one).
-- Going by the above, neither Foo nor Bar can be type functions.
-- With more than two functions, each possible pair has to meet the conditions.

I don't have any well-articulated arguments to support this idea, yet;
it mainly just feels right. My intuition for TDNR is that it has no
connection to semantics, and it is not intended as a means of defining
an interface: it is merely a syntactic convenience. If you want to
define an interface, use a type class. TDNR would be a convenience for
the case where you have imported multiple modules using a function of
the same name with obviously different types (whether the functions do
similar or different things is beside the point). Comparing to C++
(though it's unlikely to help my case to mention that language here,
but whatever), I feel that type classes : TDNR :: virtual functions :
static overloading.

And, in any case, as a language extension nobody would be forced to
use it if they don't like it. (I personally would find it very
useful). I think the fact that language extensions need to meet (much)
lesser criteria than changes to the language standard itself is
plainly evidenced by the existence of IncoherentInstances, which
nobody in their right mind would ever consider standardizing (or, for
that matter, ever enabling).


On Wed, Nov 10, 2010 at 10:59 AM, John Smith volderm...@hotmail.com wrote:
 Type-directed name resolution, as originally proposed for Haskell', has now
 been proposed for GHC. Obvious benefits of this are that conflicting
 function names from imported modules can be used without qualification
 (verbose) or pseudo-Hungarian renaming (verbose, and requires that you
 control the source, and perform the same renaming in all dependencies). This
 is important for both readability and programming in the large, particularly
 where records are concerned, as the duplicate name problem cannot be
 alleviated with typeclasses, and it is often desirable to have the same
 field names for many records in the same module.

 http://hackage.haskell.org/trac/ghc/ticket/4479
 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Gábor Lehel
2010/11/11 Gábor Lehel illiss...@gmail.com:
 I agree with the people who want to decouple the dot-syntax from TDNR
 itself. To quote myself from the publicly-editable wiki page:

 This might be a really dumb question, but is there any reason TDNR
 needs to be tied to a new syntax for function application? It seems
 strange to me to have one syntax for left-to-right function
 application without TDNR, and then another for right-to-left
 application with it. I would much rather gain TDNR for the existing
 syntax, and then maybe introduce the dot operator as a separate option
 if people want it, which I don't. The reason I don't is that (.) as
 composition and ($) already work in one direction, which is the same
 direction (`foo . bar . baz $ bla` and `foo $ bar $ baz $ bla` are
 interchangeable), and while in a vacuum I might even prefer the
 opposite direction which (.)-as-application uses, it is much more
 important to be consistent. We have a vast body of functions already
 written and designed to be convenient with the existing direction:
 functions are generally of the form `f :: (what to do) - (what to do
 it with) - (result)`, which lends itself well to partial
 application/currying and chaining in the existing direction, but not
 the other one. (Object oriented languages which use the dot operator
 indeed also use the reverse order for their methods, with the object
 first and the action second.) Also, reading expressions where
 different parts work in different directions is very confusing. The
 one major exception which works in the other direction is monadic
 bind, (=), which I think was a (minor) mistake, and indeed I
 frequently end up using (=) instead. Anyway, executive summary: TDNR
 yea, dot operator nay.

 Some further thoughts.

 I would have TDNR apply only in cases where:
 - The functions are all imported from different modules (so you can't
 define overlapping names within the same module);
 - All of the functions have an explicit type signature;
 - The ambiguity can be resolved by looking at the type of the first
 (taking currying into account, only) parameter of each function and,
 looking at the type constructors from the outside in, comparing only
 type constructors which are concrete types, rather than type variables
 (with or without constraints). E.g.:
 -- f :: Int - [...] and f :: Char - [...] could be resolved;
 -- f :: Foo Int - [...] and f :: Foo Char - [...] could be resolved;
 -- f :: Foo a - [...] and f :: Bar b - [...] could be resolved;
 -- f :: Num a = a - [...] and f :: IsString b = b - [...] could
 *not* be resolved (even if it is known that the argument type doesn't
 satisfy both constraints);
 -- f :: a Int - [...] and f :: b Char - [...] could *not* be
 resolved (though I'm less sure about this one).
 -- Going by the above, neither Foo nor Bar can be type functions.
 -- With more than two functions, each possible pair has to meet the 
 conditions.

I forgot to mention: some kind of similar criteria should probably
apply to the function where 'f' is used (again going by the above
examples) and/or its argument as well. E.g. it should not be possible
to define g a = f a and have f be resolved by TDNR when g is used
(even if all of the in-scope functions with the name 'f' meet the
previous criteria), because TDNR is not duck typing.



 I don't have any well-articulated arguments to support this idea, yet;
 it mainly just feels right. My intuition for TDNR is that it has no
 connection to semantics, and it is not intended as a means of defining
 an interface: it is merely a syntactic convenience. If you want to
 define an interface, use a type class. TDNR would be a convenience for
 the case where you have imported multiple modules using a function of
 the same name with obviously different types (whether the functions do
 similar or different things is beside the point). Comparing to C++
 (though it's unlikely to help my case to mention that language here,
 but whatever), I feel that type classes : TDNR :: virtual functions :
 static overloading.

 And, in any case, as a language extension nobody would be forced to
 use it if they don't like it. (I personally would find it very
 useful). I think the fact that language extensions need to meet (much)
 lesser criteria than changes to the language standard itself is
 plainly evidenced by the existence of IncoherentInstances, which
 nobody in their right mind would ever consider standardizing (or, for
 that matter, ever enabling).


 On Wed, Nov 10, 2010 at 10:59 AM, John Smith volderm...@hotmail.com wrote:
 Type-directed name resolution, as originally proposed for Haskell', has now
 been proposed for GHC. Obvious benefits of this are that conflicting
 function names from imported modules can be used without qualification
 (verbose) or pseudo-Hungarian renaming (verbose, and requires that you
 control the source, and perform the same renaming in all dependencies). This
 is important for both readability and programming in 

Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Max Rabkin
On Thu, Nov 11, 2010 at 11:25, Bob tom.da...@gmail.com wrote:
 I don't think I agree, I didn't see a rule f == g = serialise f == serialise 
 g anywhere.

The rule a == b = f a == f b is called referential transparency (for
denotational equality, not Eq) and is (perhaps the most important)
part of what is meant by purely functional.

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


Re: [Haskell-cafe] Splittable random numbers

2010-11-11 Thread Richard Senington
I got hold of, and looked through the paper suggested in the root of 
this thread Pseudo random trees in Monte-Carlo 
http://portal.acm.org/citation.cfm?id=1746034, and based upon this
I have thrown together a version of the binary tree based random number 
generator suggested.


I would like to point out that I do not know very much about random 
number generators, the underlying mathematics or any subsequent papers 
on this subject, this is just a very naive implementation based upon 
this one paper.


As a question, the following code actually generates a stream of numbers 
that is more random than I was expecting, if anyone can explain why I 
would be very interested.


import System.Random

data LehmerTree = LehmerTree {nextInt :: Int,
  leftBranch :: LehmerTree,
  rightBranch :: LehmerTree}

instance Show LehmerTree where
  show g = LehmerTree, current root = ++(show $ nextInt g)

mkLehmerTree :: Int-Int-Int-Int-Int-Int-LehmerTree
mkLehmerTree aL aR cL cR m x0 = innerMkTree x0
  where
mkLeft x = (aL * x + cL) `mod` m
mkRight x = (aR * x + cR) `mod` m
innerMkTree x = let l = innerMkTree (mkLeft x)
r = innerMkTree (mkRight x)
in LehmerTree x l r

mkLehmerTreeFromRandom :: IO LehmerTree
mkLehmerTreeFromRandom = do gen-getStdGen
let a:b:c:d:e:f:_ = randoms gen
return $ mkLehmerTree a b c d e f

instance RandomGen LehmerTree where
  next g = (fromIntegral.nextInt $ g, leftBranch g)
  split g = (leftBranch g, rightBranch g)
  genRange _ = (0, 2147483562) -- duplicate of stdRange



test :: IO()
test = do gen-mkLehmerTreeFromRandom
  print gen
  let (g1,g2) = split gen
  let p = take 10 $ randoms gen :: [Int]
  let p' = take 10 $ randoms g1 :: [Int]
  -- let p'' = take 10 $ randoms g2 :: [Float]
  print p
  print p'
  -- print p''


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Dan Doel
On Thursday 11 November 2010 4:25:46 am Thomas Davie wrote:
 I don't think I agree, I didn't see a rule f == g = serialise f ==
 serialise g anywhere.

That equal things can be substituted for one another is one of the fundamental 
ideas of equality (the other is that anything is equal to itself). In fact, in 
second order logic, equality can be *defined* as (roughly):

  (x = y) means (forall P. P x - P y)

That is, x is equal to y if all predicates satisfied by x are also satisfied 
by y. Using this, one can derive other typical laws for equality. Transitivity 
is pretty easy, but surprisingly, even symmetry can be gotten:

  If P z is z = x, using substitution we get x = x - y = x,
  and x = x is trivially true.

And of course, we also get congruence:

  Given a function f, let P z be f x = f z,
  substitution yields f x = f x - f x = f y,
  where f x = f x is again trivial.

The equality that people typically expect to hold for Haskell expressions is 
that two such expressions are equal if they denote the same thing, as Max 
said. Expressions with function type denote mathematical functions, and so if 
we have something like:

  serialize :: (Integer - Integer) - String

it must be a mathematical function. Further, its arguments will denote 
functions, to, and equality on mathematical functions can be given point-wise:

  f = g iff forall x. f x = g x

Now, here are two expressions with type (Integer - Integer) that denote equal 
functions:

  \x - x + x
  \x - 2 * x

So, for all this to work out, serialize must produce the same String for both 
of those. But in general, it isn't possible to decide if two functions are 
point-wise equal, let alone select a canonical representative for each 
equivalence class of expressions that denote a particular function. So there's 
no feasible way to implement serialize without breaking Haskell's semantics.

How making serialize :: (Integer - Integer) - IO String solves this? Well, 
that's another story.

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


[Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Hi,

I'm having a few problems with cabals build-type configure on windows, 
especially with the packages curl and pcre-light. Both fail either with:


* Missing C library: pcre
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Printing of asynchronous exceptions to stderr

2010-11-11 Thread Simon Marlow

On 10/11/2010 17:52, Mitar wrote:

Hi!

On Wed, Nov 10, 2010 at 4:16 PM, Simon Marlowmarlo...@gmail.com  wrote:

The right way to fix it is like this:


Optimist. ;-)


  let run = unblock doSomething `catches` [
Handler (\(_ :: MyTerminateException) -  return ()),
Handler (\(e :: SomeException) -  putStrLn $ Exception:  ++
show e)
  ] `finally` (putMVar terminated ())
  nid- block $ forkIO run


In 6.12.3 this does not work (it does not change anything, I hope I
tested it correctly) because finally is defined as:

a `finally` sequel =
   block (do
 r- unblock a `onException` sequel
 _- sequel
 return r
   )


Oh, good point!  I must have tested it with 7.0.  So this is indeed 
something that is fixed by the new async exceptions API: finally itself 
doesn't raise async exceptions inside a mask.


To fix this with GHC 6.12.3 you'd have to avoid finally and do it manually:

  let run = do
r - (unblock doSomething `catches` [
Handler (\(_ :: MyTerminateException) - return ()),
Handler (\(e :: SomeException) - putStrLn $ 
Exception:  ++ show e)

  ]) `onException` sequel
sequel
where sequel = putMVar terminated ()

Now *that* works - I tested it with 6.12.3 this time.

Cheers,
Simon





You see that unblock there? So it still unblocks so that second
exception is delivered immediately after catches handles the first
exception?

But I agree that your explanation for what is happening is the correct
one. Better than my hanging threads at the end. And with my throwIO
approach I just override MyTerminateException with ThreadKilled.


Mitar


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Sjoerd Visscher
 The equality that people typically expect to hold for Haskell expressions is 
 that two such expressions are equal if they denote the same thing, as Max 
 said. Expressions with function type denote mathematical functions, and so if 
 we have something like:
 
  serialize :: (Integer - Integer) - String
 
 it must be a mathematical function. Further, its arguments will denote 
 functions, to, and equality on mathematical functions can be given point-wise:
 
  f = g iff forall x. f x = g x
 
 Now, here are two expressions with type (Integer - Integer) that denote 
 equal 
 functions:
 
  \x - x + x
  \x - 2 * x
 
 So, for all this to work out, serialize must produce the same String for both 
 of those. 

What I'm wondering is if it would actually break things if serialize would not 
produce the same String for these functions. The reasoning above is used 
regularly to shoot down some really useful functionality. So what would go 
wrong if we chose to take the practical path, and leave aside the theoretical 
issues?

Also, the above two functions might not be exactly denotationally equal if the 
type is (Float - Float), or the speed or memory use might be different. Could 
it not be that requiring them to be equal could just as well break things?

greetings,
Sjoerd Visscher




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


[Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Hi,

I'm having a few problems with cabals build-type configure on windows, 
especially with the packages curl and pcre-light. Both fail either with:


configure: error: curl libraries not found, so curl package cannot 
be built


Configuring pcre-light-0.4...
cabal: Missing dependency on a foreign library:
* Missing C library: pcre

Both libraries (pcre3.dll and libcurl.dll) are in my PATH variable, and 
I can build other non-haskell-applications which are using these via 
mingws gcc compiler. But still, somehow cabal seems unable to find them. 
Using the recommanded --extra-include-dirs and --extra-lib-dirs 
won't help either. Or is cabal looking for different files than those 
two .dlls?


Can anyone help me on this? Did anyone manage to build curl/pcre-light 
on windows?


My current configuration is MinGW/msys with gcc 4.5, ghc 6.12.3, 
cabal-install 0.8.2, cabal 1.8.0.6. libcurl.dll and pcre.dll are the 
latest builds from the official webpages.



Thanks for any Help,
Nils


PS: Sorry for the previous (incomplete) mail.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Opportunity for Haskell porting to java at RD labs in Bay Area, CA

2010-11-11 Thread Atze Dijkstra
Hi All,

UHC (http://www.cs.uu.nl/wiki/UHC) has a Java backend. It works but further 
development currently does not have high priority.

cheers,

On  10 Nov, 2010, at 21:03 , aditya siram wrote:

 Googling haskell java integration brings up a number of references
 to Lambada. Is this project still alive?
 -deech
 
 On Wed, Nov 10, 2010 at 4:16 PM, Tom Davies tgdav...@gmail.com wrote:
 
 On 11/11/2010, at 7:42 AM, Padma wrote:
 
 We are looking for a entry level Haskell programmer who has experience in 
 porting from Haskell to java. Please contact me by Email or you can call me 
 at 408-207-9367.
 
 You could look at CAL/OpenQuark -- https://github.com/levans/Open-Quark -- 
 which is essentially Haskell 98 for the JVM.
 
 There would still be a porting exercise, because CAL has less syntactic 
 sugar and fewer libraries (and doesn't have the GHC extensions you may use), 
 but it has good (though verbose) Java interoperability.
 
 Tom
 
 ___
 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


- Atze -

Atze Dijkstra, Department of Information and Computing Sciences. /|\
Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \
Tel.: +31-30-2534118/1454 | WWW  : http://www.cs.uu.nl/~atze . /--|  \
Fax : +31-30-2513971  | Email: a...@cs.uu.nl  /   |___\



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


Re: [Haskell-cafe] Gödel' s System T

2010-11-11 Thread Petr Pudlak
Thanks Dan, the book is really interesting, all parts of it. It looks 
like I'll read the whole book.


  Best regards,
  Petr

On Wed, Nov 10, 2010 at 05:21:16PM -0500, Dan Doel wrote:

On Wednesday 10 November 2010 1:42:00 pm Petr Pudlak wrote:

I was reading the paper Total Functional Programming [1]. I
encountered an interesting note on p. 759 that primitive recursion in a
higher-order language allows defining much larger set of function than
classical primitive recursion (which, for example, cannot define
Ackermann's function). And that this is studied in in Gödel's System T.
It also states that this larger set of primitive functions includes all
functions whose totality can be proved in first order logic.

I was searching the Internet but I couldn't find a resource (a paper, a
book) that would explain this in detail, give proofs etc. I'd be happy
if someone could give me some directions.


Girard's book, Proofs and Types, has some stuff on System T. A translation is
freely available:

 http://www.paultaylor.eu/stable/Proofs+Types.html

Skimming, it looks like he gives an argument that T can represent all
functions that are provably total in Peano arithmetic.

The rest of the book is also excellent.

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


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Gábor Lehel
On Thu, Nov 11, 2010 at 12:22 PM, Sjoerd Visscher sjo...@w3future.com wrote:
 The equality that people typically expect to hold for Haskell expressions is
 that two such expressions are equal if they denote the same thing, as Max
 said. Expressions with function type denote mathematical functions, and so if
 we have something like:

  serialize :: (Integer - Integer) - String

 it must be a mathematical function. Further, its arguments will denote
 functions, to, and equality on mathematical functions can be given 
 point-wise:

  f = g iff forall x. f x = g x

 Now, here are two expressions with type (Integer - Integer) that denote 
 equal
 functions:

  \x - x + x
  \x - 2 * x

 So, for all this to work out, serialize must produce the same String for both
 of those.

 What I'm wondering is if it would actually break things if serialize would 
 not produce the same String for these functions. The reasoning above is used 
 regularly to shoot down some really useful functionality. So what would go 
 wrong if we chose to take the practical path, and leave aside the theoretical 
 issues?

Yeah, my sense -- but correct my if I'm reading the original post
incorrectly -- is that the whole thing with function equality is a
distraction and not really relevant here.

It is true that (a) per Luke Palmer, if we could serialize equal
functions to equal representations then we could we could decide
whether two pure functions were equal, which (if not done in the IO
monad) would(?) break purity; and (b) per Dan Doel, if we wanted to
implement our serialization in a way so that equal functions get equal
representations, we couldn't do it, because it's an impossible
problem.

But these sort of cancel each other out, because (a) it's an
impossible problem, and (b) we don't want to do it.

A function which does x+x would simply be serialized as doing x+x,
and a function which does x*2 would be serialized as doing x*2, and
when deserialized the resulting functions would continue to do those
things, and it would be completely agnostic and indifferent as to
whether or not they are in fact equal.

Obviously there are questions here with regards to the functions which
the to-be-serialized function makes use of -- should they be
serialized along with it? Required to be present when it is
deserialized? Is it OK for the function to do something different when
it is loaded compared to when it was stored if its environment is
different, or not OK?


 Also, the above two functions might not be exactly denotationally equal if 
 the type is (Float - Float), or the speed or memory use might be different. 
 Could it not be that requiring them to be equal could just as well break 
 things?

 greetings,
 Sjoerd Visscher




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




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Stephen Tetley
Do you have the headers installed as well as the dlls?

For headers, MSys will have a search path of at least these two directories

msys\1.0\local\include
MinGW\include
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 07:04:16PM +1030, John Lask wrote:
 it is often desirable to have the same field names
 for many records in the same module.

 very much so, this is currently possible, with the restriction that
 the field names must have the same type modulo the record it is
 selecting on.
 
 what is disirable is that this restriction be lifted.

Why on earth? I thought that the motivation for this feature was
simply to deal with naming conflicts with _unrelated_ records from
_unrelated_ modules without having to resort to qualified names. But I
can't see why someone would use the same accessor name for unrelated
records in a single module. And if the records are related (and the
field is conceptually the same for the records), then you can use a
type class to overload the accessor name in a controlled fashion.

So why would you ever need to reuse the same field name in the same
module?


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Jesse Schalken
2010/11/11 Gábor Lehel illiss...@gmail.com

 Obviously there are questions here with regards to the functions which
 the to-be-serialized function makes use of -- should they be
 serialized along with it? Required to be present when it is
 deserialized? Is it OK for the function to do something different when
 it is loaded compared to when it was stored if its environment is
 different, or not OK?


I would have say Yes, No, No. At the moment, when you serialise data
structure A which references data structure B which references data
structure C, using Data.Binary for example, the whole lot (A, B, and C) gets
serialised, so that the resulting deserialization of A is
denotationally equivalent to the original, regardless of the environment. I
don't see why this shouldn't be the case for functions also.

So a serialized function should include all its direct and indirect callees.
This might result in potentially simple functions ending up enormous when
serialized, simply because the call graph, including all it's libraries and
their libraries etc, is that size, but such would be pure function
serialization.

This raises the question of what is left. The assembled machine code? For
the architecture of the serializer or of the deserializer? Or LLVM IR
for architecture independence? C--? Core? I don't know, but it would be
awesome for the serialized representation to be both low-level and
architecture independent, then having it JIT compiled when it is
deserialized. To me, this means a virtual machine, which I guess is what you
need when you want fast mobile code, but I'm just musing here as I know
little about programming language implementation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Michael Snoyman
On Thu, Nov 11, 2010 at 2:24 PM, Lauri Alanko l...@iki.fi wrote:
 On Thu, Nov 11, 2010 at 07:04:16PM +1030, John Lask wrote:
 it is often desirable to have the same field names
 for many records in the same module.

 very much so, this is currently possible, with the restriction that
 the field names must have the same type modulo the record it is
 selecting on.

 what is disirable is that this restriction be lifted.

 Why on earth? I thought that the motivation for this feature was
 simply to deal with naming conflicts with _unrelated_ records from
 _unrelated_ modules without having to resort to qualified names. But I
 can't see why someone would use the same accessor name for unrelated
 records in a single module. And if the records are related (and the
 field is conceptually the same for the records), then you can use a
 type class to overload the accessor name in a controlled fashion.

 So why would you ever need to reuse the same field name in the same
 module?

data PetOwner
data FurnitureOwner

data Cat = Cat { owner :: PetOwner }
data Chair = Chair { owner :: FurnitureOwner }

Just the first thing that came to mind, this kind of thing comes up
often enough to be an irritant. I'm not sure whether or not TDNR is a
good solution to the problem, just pointing out a use case.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Gábor Lehel
On Thu, Nov 11, 2010 at 2:15 PM, Jesse Schalken jesseschal...@gmail.com wrote:
 2010/11/11 Gábor Lehel illiss...@gmail.com

 Obviously there are questions here with regards to the functions which
 the to-be-serialized function makes use of -- should they be
 serialized along with it? Required to be present when it is
 deserialized? Is it OK for the function to do something different when
 it is loaded compared to when it was stored if its environment is
 different, or not OK?

 I would have say Yes, No, No. At the moment, when you serialise data
 structure A which references data structure B which references data
 structure C, using Data.Binary for example, the whole lot (A, B, and C) gets
 serialised, so that the resulting deserialization of A is
 denotationally equivalent to the original, regardless of the environment. I
 don't see why this shouldn't be the case for functions also.
 So a serialized function should include all its direct and indirect callees.
 This might result in potentially simple functions ending up enormous when
 serialized, simply because the call graph, including all it's libraries and
 their libraries etc, is that size, but such would be pure function
 serialization.
 This raises the question of what is left. The assembled machine code? For
 the architecture of the serializer or of the deserializer? Or LLVM IR
 for architecture independence? C--? Core? I don't know, but it would be
 awesome for the serialized representation to be both low-level and
 architecture independent, then having it JIT compiled when it is
 deserialized. To me, this means a virtual machine, which I guess is what you
 need when you want fast mobile code, but I'm just musing here as I know
 little about programming language implementation.

I'm not an expert here either, I'll just note that LLVM is only
platform independent to a degree. Or rather, I believe the situation
is that it *is* architecture independent, but it doesn't abstract
anything else besides the architecture -- so if you have any other
differences, it's not going to work. LLVM IR doesn't do #ifdefs.

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





-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Am 11.11.2010 13:41, schrieb Stephen Tetley:

Do you have the headers installed as well as the dlls?

For headers, MSys will have a search path of at least these two directories

msys\1.0\local\include
MinGW\include


Is there an environment variable for this? As I said, I tried using 
--extra-include-dirs with MinGW\include.

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


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Stephen Tetley
On 11 November 2010 13:21, Nils Schweinsberg m...@n-sch.de wrote:


 Is there an environment variable for this? As I said, I tried using
 --extra-include-dirs with MinGW\include.

I'm not sure about an environment variable. Adding the MinGW\ prefix
looks wrong, you may have to experiment with paths and forward or back
slash separators a bit. I can't remember which convention (Windows)
cabal uses.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Malcolm Wallace

I'll just note that LLVM is only
platform independent to a degree. Or rather, I believe the situation
is that it *is* architecture independent, but it doesn't abstract
anything else besides the architecture


In particular, imagine how you might serialise a Haskell function  
which is an FFI binding to some external platform-specific library  
(e.g. Posix, Win32, Gtk+, WPF), such that you could save it on a  
Windows machine, copy to Linux or Mac, and start it running again.


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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 03:17:39PM +0200, Michael Snoyman wrote:
 data PetOwner
 data FurnitureOwner
 
 data Cat = Cat { owner :: PetOwner }
 data Chair = Chair { owner :: FurnitureOwner }

These are clearly related uses, so as I said, you can use a type class
to overload the accessor name in a controlled fashion.


{-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}

data PetOwner
data FurnitureOwner

data Cat = Cat { catOwner :: PetOwner }
data Chair = Chair { chairOwner :: FurnitureOwner }

class Owned a b | a - b where
  owner :: a - b
  
instance Owned Cat PetOwner where  
  owner = catOwner
  
instance Owned Chair FurnitureOwner where
  owner = chairOwner


(You can also use associated type families for the same effect.)


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Gábor Lehel
On Thu, Nov 11, 2010 at 2:29 PM, Malcolm Wallace malcolm.wall...@me.com wrote:
 I'll just note that LLVM is only
 platform independent to a degree. Or rather, I believe the situation
 is that it *is* architecture independent, but it doesn't abstract
 anything else besides the architecture

 In particular, imagine how you might serialise a Haskell function which is
 an FFI binding to some external platform-specific library (e.g. Posix,
 Win32, Gtk+, WPF), such that you could save it on a Windows machine, copy to
 Linux or Mac, and start it running again.

...and FFI imports are something you definitely can't serialize, so
that's one case where you either have it say call the linked-in
function with the name 'whatever' and hope it's the same one, or just
disallow it entirely.



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




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Michael Snoyman
On Thu, Nov 11, 2010 at 3:10 PM, Lauri Alanko l...@iki.fi wrote:
 On Thu, Nov 11, 2010 at 03:17:39PM +0200, Michael Snoyman wrote:
 data PetOwner
 data FurnitureOwner

 data Cat = Cat { owner :: PetOwner }
 data Chair = Chair { owner :: FurnitureOwner }

 These are clearly related uses, so as I said, you can use a type class
 to overload the accessor name in a controlled fashion.


 {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}

 data PetOwner
 data FurnitureOwner

 data Cat = Cat { catOwner :: PetOwner }
 data Chair = Chair { chairOwner :: FurnitureOwner }

 class Owned a b | a - b where
  owner :: a - b

 instance Owned Cat PetOwner where
  owner = catOwner

 instance Owned Chair FurnitureOwner where
  owner = chairOwner


 (You can also use associated type families for the same effect.)

Well, it's not exactly the same. For example:

myCat = Cat { owner = michael }

versus

myCat = Cat { catOwner = michael }

Not to mention that with TDNR, there is much less typing involved: no
need to declare a type class, declare instances, export the type
class.

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Stephen Tetley
On 11 November 2010 13:10, Lauri Alanko l...@iki.fi wrote:


 {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}

 data PetOwner
 data FurnitureOwner

 data Cat = Cat { catOwner :: PetOwner }
 data Chair = Chair { chairOwner :: FurnitureOwner }

 class Owned a b | a - b where
  owner :: a - b

 instance Owned Cat PetOwner where
  owner = catOwner

 instance Owned Chair FurnitureOwner where
  owner = chairOwner


This is fairly onerous for people who are programming to an outside
schema (i.e. a relational database) as it leads to boiler plate along
two axes - data type definitions plus class definitions for accessors.

I don't like the details current TDNR proposal, but if improved
records are never going to happen, TDNR has benefit for this
situation.

Incidentally there is now a member of the ML family with a
sophisticated record system - MLPolyR:
http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Miguel Mitrofanov



11.11.2010 16:53, Stephen Tetley пишет:

On 11 November 2010 13:10, Lauri Alankol...@iki.fi  wrote:


{-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}

data PetOwner
data FurnitureOwner

data Cat = Cat { catOwner :: PetOwner }
data Chair = Chair { chairOwner :: FurnitureOwner }

class Owned a b | a -  b where
  owner :: a -  b

instance Owned Cat PetOwner where
  owner = catOwner

instance Owned Chair FurnitureOwner where
  owner = chairOwner


This is fairly onerous for people who are programming to an outside
schema (i.e. a relational database) as it leads to boiler plate along
two axes - data type definitions plus class definitions for accessors.

I don't like the details current TDNR proposal, but if improved
records are never going to happen, TDNR has benefit for this
situation.


That's kinda the point, it can work the other way: ugly solution like TDNR can 
prevent improved records from ever appearing.


Incidentally there is now a member of the ML family with a
sophisticated record system - MLPolyR:
http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Gábor Lehel
On Thu, Nov 11, 2010 at 2:59 PM, Miguel Mitrofanov
miguelim...@yandex.ru wrote:


 11.11.2010 16:53, Stephen Tetley пишет:

 On 11 November 2010 13:10, Lauri Alankol...@iki.fi  wrote:

 {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses,
 FunctionalDependencies #-}

 data PetOwner
 data FurnitureOwner

 data Cat = Cat { catOwner :: PetOwner }
 data Chair = Chair { chairOwner :: FurnitureOwner }

 class Owned a b | a -  b where
  owner :: a -  b

 instance Owned Cat PetOwner where
  owner = catOwner

 instance Owned Chair FurnitureOwner where
  owner = chairOwner

 This is fairly onerous for people who are programming to an outside
 schema (i.e. a relational database) as it leads to boiler plate along
 two axes - data type definitions plus class definitions for accessors.

 I don't like the details current TDNR proposal, but if improved
 records are never going to happen, TDNR has benefit for this
 situation.

 That's kinda the point, it can work the other way: ugly solution like TDNR
 can prevent improved records from ever appearing.

I tend to be mistrustful of this kind of
perfect-is-the-enemy-of-the-good thinking, it rarely ends up working
out well. Usually the result is that you end up with nothing. And
while you can't prove a counterfactual, I'm really not sure if getting
the 'good' ever actually acts to hold back the 'perfect' later. The
mechanism is intuitive enough: people decide the 'good' solution is
good enough, resulting in less demand for the better one. But to take
the present situation at least, there is plenty of demand for an
improved records system and it doesn't seem to be getting us any
closer to gaining one. Maybe implementing TDNR will make people
complacent and delay it further, maybe it'll actually make people
hungrier for further improvement, maybe it'll have no effect, who
knows? The point is that refusing something you can have now (though
of course it's an open question whether TDNR is something we can have
now) out of fear that it'll prevent you getting something better
later is speculative and often backfires.


 Incidentally there is now a member of the ML family with a
 sophisticated record system - MLPolyR:
 http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php
 ___
 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




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Ozgur Akgun
On 11 November 2010 01:19, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 I'm not sure that it is desirable to have many records in the
 same module in the first place.


Amongst other reasons,
http://www.haskell.org/haskellwiki/Mutually_recursive_modules

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


[Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Ozgur Akgun
Café,

Is there a way to make GHC dump the code for auto-derived type class
instances, say for Show, Eq and such?

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Dan Doel
On Thursday 11 November 2010 6:22:06 am Sjoerd Visscher wrote:
 What I'm wondering is if it would actually break things if serialize would
 not produce the same String for these functions.

Yes. It would break the (usual) mathematical underpinnings of Haskell.

 The reasoning above is used regularly to shoot down some really useful
 functionality. So what would go wrong if we chose to take the practical
 path, and leave aside the theoretical issues?

You would lose many uses of equational reasoning in your programs. Have you 
every substituted 'x * 2' for the expression 'x + x' in one of your programs, 
or vice versa? You can no longer do that, because someone may be serializing 
the function you're writing, checking how it's implemented, and relying it.

You'd lose the whole notion of 'the category of haskell types and functions' 
goodbye, too. Does f . id = f? Not if the former serializes as f . id. We 
already have a weak case of this, since (\x - undefined x) can be 
distinguished from undefined using seq, but that can be hand-waved away by not 
worrying about bottoms so much. That isn't going to work for serialize. There 
does exist practical Haskell stuff from category theory inspired people.

As a digression... When you get into things like dependent type theory, 
equality is actually incorporated into the language in a much more direct way. 
And there are various sorts of equality you can add to your type theory. Two 
common choices are:

  intensional equality: two values are provably equal if they evaluate to the
  same normal form

  extensional equality: this incorporates non-computational rules, like the
  point-wise equality of functions.

Now, in a type theory where equality is intensional, I cannot prove:

  (forall x. f x = g x) - f = g

However, both these equalities (and others in between and on either side) are 
*compatible*, in that I cannot disprove the above theorem in an intensional 
theory.

What seq and serialize do is break from extensional equality, and allow us to 
disprove the above (perhaps not for seq within a hypothetical theory, since 
the invalidating case involves non-termination, but certainly for serialize). 
And that's a big deal, because extensional equality is handy for the above 
reasoning about programs.

 Also, the above two functions might not be exactly denotationally equal if
 the type is (Float - Float), or the speed or memory use might be
 different. Could it not be that requiring them to be equal could just as
 well break things?

I would not be at all surprised if they are unequal for Float - Float, 
considering how ugly floating point types are. That doesn't justify breaking 
equality for every other type.

Speed and memory use are typically disregarded for equality of (expressions 
denoting) functions. Merge sort and bubble sort are two algorithms for 
computing the same function, even though they vary wildly in these two 
characteristics. If you want a calculus for precisely reasoning about resource 
usage, then you would not necessarily be able to consider these equal.

But, Haskell is simply not such a calculus, and I don't think, what if it 
were, is a good argument for actively breaking extensional equality in such a 
dramatic way (since the breakage would have nothing to do with precise 
reasoning about resource usage).

Gábor Lehel wrote:
 It is true that (a) per Luke Palmer, if we could serialize equal
 functions to equal representations then we could we could decide
 whether two pure functions were equal, which (if not done in the IO
 monad) would(?) break purity; and (b) per Dan Doel, if we wanted to
 implement our serialization in a way so that equal functions get equal
 representations, we couldn't do it, because it's an impossible
 problem.

 But these sort of cancel each other out, because (a) it's an
 impossible problem, and (b) we don't want to do it.

They do not cancel each other out. Rather, it goes like this:

a) Serializing functions gives you a decision procedure for function equality.
b) It is impossible to decide extensional equality of functions.

Together, these mean that any serialization procedure you define is *wrong*, 
in that it violates the semantics of pure Haskell expressions (the resulting 
decision procedure will answer 'False' for some pair of extensionally equal 
expressions f and g).

The way IO can get around this is that when you have:

  serialize (\x - x + x :: Integer) :: IO String
  serialize (\x - 2 * x :: Integer) :: IO String

you can say that the two IO actions are equal in the following sense:

  1) There is an equivalence class of expressions denoting the function in
 question. This equivalence class contains (\x - x + x) and
 (\x - 2 * x)
  2) The IO action produced by serialize selects a string representation
 for one of these expressions at random*.
*) You probably won't ever observe \x - x + x being the output of
   (serialize (\x - 2 * x)), but that's just a coincidence.

This 

[Haskell-cafe] Re: ANN: network-2.2.3, merger with network-bytestring

2010-11-11 Thread Johan Tibell
On Sun, Oct 31, 2010 at 4:14 PM, Johan Tibell johan.tib...@gmail.com wrote:
 Hi all,

 I like to announce a new version of the network package,
 network-2.2.3. You can install the latest version by running:

    cabal update  cabal install network

 This version marks the end of the network-bytestring package, which
 has now been merged into the network package. This means that
 efficient and correct networking using ByteStrings is available as
 part of the standard network package.

 As part of the merger, two new modules have been added:
 Network.Socket.ByteString and Network.Socket.ByteString.lAzy

 This release is backwards compatible with the previous release.

After merging the packages, I only bumped the minor version of
network. That wasn't a great idea, as anyone with a dependency on
network == 2.2.* (or equivalent) and network-bytestring got build
problems due to module name clashes.

I've released network-2.3 and added a preferred version constraint to
Hackage to avoid having people end up using network-2.2.3.*. If you
want the new ByteString-based modules please depend on network-2.3.*,
if you use qualified imports, and network-2.3.0.*, if you don't.

If you previously depended on both network and network-bytestring and
still want to support older versions of network you can use Cabal's
flag feature. Example:

flag network-bytestring

Library
  if flag(network-bytestring)
build-depends:
  network  2.2.3,
  network-bytestring  0.1.4
  else
build-depends:
  network = 2.3   2.3.1

Sorry for the mess.

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


[Haskell-cafe] Stack Overflow?

2010-11-11 Thread Ben Christy
I have implemented a scene graph in Haskell and I have a problem. I walk
down the scenegraph and at each node I recalculate translation matrix and
pass it to each child. Well it seems to be causing a stack overflow and I am
lost as to how to resolve the issue without issue a state variable of some
kind to hold a matrix stack as is common in imperative implementations of
scene graphs. When I run the program fromghci I get
drawingcamera
drawingground
drawinggroundModel
Matrix4x4 {i1j1 = -4.371139e-8, i1j2 = 0.0, i1j3 = 1.0, i1j4 = -3.998,
i2j1
= 0.0, i2j2 = 1.0, i2j3 = 0.0, i2j4 = -1.5, i3j1 = -1.0, i3j2 = 0.0, i3j3 =
-4.3
71139e-8, i3j4 = 3.0, i4j1 = 0.0, i4j2 = 0.0, i4j3 = 0.0, i4j4 = 1.0}
a model
classic matrix operation
drawingcarousel
drawingcarouselbase
drawingcarouselbaseModel
Matrix4x4 {i1j1 = -4.371139e-8, i1j2 = 1.0, i1j3 = -4.371139e-8, i1j4 = 0.0,
i2j
1 = 0.0, i2j2 = -4.371139e-8, i2j3 = -1.0, i2j4 = 0.0, i3j1 = -1.0, i3j2 =
-4.37
1139e-8, i3j3 = 1.9106855e-15, i3j4 = -1.0, i4j1 = 0.0, i4j2 = 0.0, i4j3 =
0.0,
i4j4 = 1.0}
classic matrix operation
drawingcarouselRoof
drawingcarouselRoofModel
Matrix4x4 {i1j1 = -4.371139e-8, i1j2 = 1.0, i1j3 = -4.371139e-8, i1j4 = 0.0,
i2j
1 = 0.0, i2j2 = -4.371139e-8, i2j3 = -1.0, i2j4 = 0.3, i3j1 = -1.0, i3j2 =
-4.37
1139e-8, i3j3 = 1.9106855e-15, i3j4 = -1.0, i4j1 = 0.0, i4j2 = 0.0, i4j3 =
0.0,
i4j4 = 1.0}
classic matrix operation
drawingcarouselFloor
drawingcarouselFloorModel
Matrix4x4 {i1j1 = -4.371139e-8, i1j2 = 1.0, i1j3 = -4.371139e-8, i1j4 = 0.0,
i2j
1 = 0.0, i2j2 = -4.371139e-8, i2j3 = -1.0, i2j4 = 0.0, i3j1 = -1.0, i3j2 =
-4.37
1139e-8, i3j3 = 1.9106855e-15, i3j4 = -1.0, i4j1 = 0.0, i4j2 = 0.0, i4j3 =
0.0,
i4j4 = 1.0}
classic matrix operation
drawingpolls
drawingpoll1
drawingpoll1Model
Matrix4x4 {i1j1 = interactive: loop
interactive: interrupted

As you can see there are only a handful of nodes at this point so I am
confused as to why it is happening here, any thoughts?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Daniel Fischer
On Thursday 11 November 2010 15:27:09, Ozgur Akgun wrote:
 Café,

 Is there a way to make GHC dump the code for auto-derived type class
 instances, say for Show, Eq and such?

-ddump-deriv


 Thanks,
 Ozgur

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


Re: [Haskell-cafe] Stack Overflow?

2010-11-11 Thread Dmitry Astapov
On Thu, Nov 11, 2010 at 4:58 PM, Ben Christy ben.chri...@gmail.com wrote:
 I have implemented a scene graph in Haskell and I have a problem. I walk
 down the scenegraph and at each node I recalculate translation matrix and
 pass it to each child. Well it seems to be causing a stack overflow and I am
 lost as to how to resolve the issue without issue a state variable of some
 kind to hold a matrix stack as is common in imperative implementations of
 scene graphs. When I run the program fromghci I get
[snip]
 Matrix4x4 {i1j1 = interactive: loop
 interactive: interrupted

Check the expression for i1j1 - seems like it boils down to let x = x in x

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


Re: [Haskell-cafe] Opportunity for Haskell porting to java at RD labs in Bay Area, CA

2010-11-11 Thread namekuseijin
given all Oracle woes in the last few months, I'd say this is a
terrible timing and terrible decision.  How about instead an
experienced Haskell programmer to best leverage it rather than a
junior who's learned java at university and has just read Learn
Haskell in 2 weeks?

On Wed, Nov 10, 2010 at 6:42 PM, Padma pa...@sraoss.com wrote:
 We are looking for a entry level Haskell programmer who has experience in
 porting from Haskell to java. Please contact me by Email or you can call me
 at 408-207-9367.



 LOCATION: SUNNYVALE, CA

 DURATION: 6 MONTHS



 Degree: Bs or Ms or Ph.D

 Start immediately

 Good experience in porting particularly from Haskell to java environment.

 Check and validate smooth functioning of the system.(After porting is done)

 This is a RD project. (prior experience is desired)

 Good experience in testing and compiling.







 Regards,

 Padma

 SRAOSS INC.

 5300 Stevens Creek Blvd  Suite 460

 San Jose,CA 95129

 Direct:(408) 207-9367
 Tel: (408) 855-8200 x 321
 Fax: (408) 855-8206
 pa...@sraoss.com
 www.sraoss.com
 www.sra.co.jp



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


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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Malcolm Wallace

The point is that refusing something you can have now (though
of course it's an open question whether TDNR is something we can have
now) out of fear that it'll prevent you getting something better
later is speculative and often backfires.


I think we are very far from having TDNR now.  It is really quite  
complicated to interleave name resolution with type checking in any  
compiler.  So far, we have a design, that's all, no implementation.   
We also have (several) designs for proper record systems.


If the outcome of this discussion is a clamour for better records  
instead of TDNR, then that would certainly make me happy.


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Ketil Malde
Dan Doel dan.d...@gmail.com writes:

 You'd lose the whole notion of 'the category of haskell types and functions' 
 goodbye, too. Does f . id = f? Not if the former serializes as f . id.

..and you are able to tell the difference.  Am I wrong in thinking that
this could be made to work if serialization was to/from an opaque type
instead of (Byte)String, so that the *only* operations would be
serialization and deserialization (and possibly storing to/from file)?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Ozgur Akgun
Thanks!

On 11 November 2010 14:52, Daniel Fischer daniel.is.fisc...@web.de wrote:

 On Thursday 11 November 2010 15:27:09, Ozgur Akgun wrote:
  Café,
 
  Is there a way to make GHC dump the code for auto-derived type class
  instances, say for Show, Eq and such?

 -ddump-deriv

 
  Thanks,
  Ozgur




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


Re: [Haskell-cafe] Gödel's System T

2010-11-11 Thread Aaron Gray
On 11 November 2010 11:43, Petr Pudlak d...@pudlak.name wrote:

 Thanks Dan, the book is really interesting, all parts of it. It looks like
 I'll read the whole book.


Watch out for the decidability issue though :-

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.6.6483

Aaron



  Best regards,
  Petr


 On Wed, Nov 10, 2010 at 05:21:16PM -0500, Dan Doel wrote:

 On Wednesday 10 November 2010 1:42:00 pm Petr Pudlak wrote:

 I was reading the paper Total Functional Programming [1]. I
 encountered an interesting note on p. 759 that primitive recursion in a
 higher-order language allows defining much larger set of function than
 classical primitive recursion (which, for example, cannot define
 Ackermann's function). And that this is studied in in Gödel's System T.
 It also states that this larger set of primitive functions includes all
 functions whose totality can be proved in first order logic.

 I was searching the Internet but I couldn't find a resource (a paper, a
 book) that would explain this in detail, give proofs etc. I'd be happy
 if someone could give me some directions.


 Girard's book, Proofs and Types, has some stuff on System T. A translation
 is
 freely available:

  http://www.paultaylor.eu/stable/Proofs+Types.html

 Skimming, it looks like he gives an argument that T can represent all
 functions that are provably total in Peano arithmetic.

 The rest of the book is also excellent.

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


 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.10 (GNU/Linux)

 iQEcBAEBAgAGBQJM29b+AAoJEC5dcKNjBzhn7CAH/1DYIpZcWenZs4D+cPW2V9+F
 oET+abW2MgdRPPRquDT4qd/nLnI4XhTiiJEZq8mwfAY4OXBUjHnXLKTlKWyHkgCH
 zIRPIXWj0PSHNX+2yAB7muhWmOJv/BfrS9DOKsUDF3Qirtl9kc9x9SkWkVuRe2Yf
 JSAp+biYQkTSQg2MntHuprqTn783lfsLyKOvtNkybk3Kt+Ft7dzPmQgtgXCd5fPm
 eKI1D3b5H5NOH4cwYYUKejpc+8mptTdJVy6Hw8USI4e+hnoe62CZ/2bBf/lOyoCB
 UwNJ09sT5yepyA2DimvI3yZX33OB/K24xfPhsnvHaWAHyz3AkdeMG21eertnmtM=
 =zOw9
 -END PGP SIGNATURE-

 ___
 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: Haskell is a scripting language inspired by Python.

2010-11-11 Thread Simon Marlow

On 04/11/2010 22:38, Lennart Augustsson wrote:

It happened at various universities around the world.  Look at the
original Haskell committee and you'll get a good idea where.

The smallest Haskell I know of is Gofer/Hugs; it originally ran on a 640k PCs.
Before that languages like SASL and KRC ran on PDP-11 with 64k memory.
None of these had a compiler that was bootstrapped, but I had a simple
functional language that compiled itself and ran in 64K.
The smallest bootstrapped Haskell compiler is NHC which (I think) runs
in a few MB.


I bootstrapped GHC from the intermediate C files on a 640K PC around 
1993 or so.  I don't remember exactly, but I think it might have worked, 
for some small value of work.


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


Re: [Haskell-cafe] Re: Haskell is a scripting language inspired by Python.

2010-11-11 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 11/11/10 11:12 , Simon Marlow wrote:
 I bootstrapped GHC from the intermediate C files on a 640K PC around 1993 or
 so.  I don't remember exactly, but I think it might have worked, for some
 small value of work.

If you used the right build environment, the compiler would have arranged
for overlays; the better ones even supported data overlays, but I imagine
that would have wreaked utter havoc with the runtime (its thunks would have
been wrapped in compiler-generated thunks that swapped the overlay space as
needed).

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkzcF7wACgkQIn7hlCsL25UdJACeNi0aPwQRAatUiBH1MDFQrttR
jOcAnjrUA29p/lxqwv3N0WXDRvEO+DYW
=+BuC
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 10:53 AM, Ketil Malde ke...@malde.org wrote:
 ..and you are able to tell the difference.  Am I wrong in thinking that
 this could be made to work if serialization was to/from an opaque type
 instead of (Byte)String, so that the *only* operations would be
 serialization and deserialization (and possibly storing to/from file)?

This was my first thought as well! However, reading to/from a file
would of course be in IO, at which point you'd be free to read the
file back in through normal means to get at the representation. So in
that respect, this is equivalent to (a - b) - IO String.

Outside of IO, it would pretty much have to be limited to serializing
and deserializing. You'd be able to create opaque tokens representing
functions, pass them around, and/or extract the function in order to
apply it. Conveniently, it turns out that Haskell already has support
for this, you can implement it as follows:

 module Serialize.Pure (OpaqueFunction, serialize, deserialize) where

 newtype OpaqueFunction a b = Opaque { deserialize :: a - b }

 serialize = Opaque

Toss in some existential types as desired, if you want to hide the
function's actual type.

I suppose one could object that this isn't actually serializing
anything at all; to which I would respond that, in pure code, how do
you expect to tell the difference?

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


Re: [Haskell-cafe] Gödel' s System T

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 04:04:07PM +, Aaron Gray wrote:
 On 11 November 2010 11:43, Petr Pudlak d...@pudlak.name wrote:
  Thanks Dan, the book is really interesting, all parts of it. It looks like
  I'll read the whole book.

 Watch out for the decidability issue though :-
 
 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.6.6483

Just to clarify, the issue is that you cannot convert System F to
implicitly typed Curry-style: the explicit type abstractions and type
applications are there for a reason. For the same reason, rank-N
polymorphism in Haskell requires explicit type annotations.

There's still nothing wrong with System F as it stands, though.


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


Re: [Haskell-cafe] Re: Haskell is a scripting language inspired by Python.

2010-11-11 Thread Pierpaolo Bernardi
On Thu, Nov 4, 2010 at 20:54, Andrew Coppin andrewcop...@btinternet.com wrote:
 On 04/11/2010 02:16 PM, Jonathan Geddes wrote:

 I mean, comparing BASIC to FP is like comparing a water
 pistol to a tactical thermonuclear device.

You have the similitude backward. It's Haskel that is fun
and BASIC which caused disasters.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Sjoerd Visscher
On Nov 11, 2010, at 3:36 PM, Dan Doel wrote:

 On Thursday 11 November 2010 6:22:06 am Sjoerd Visscher wrote:
 
 The reasoning above is used regularly to shoot down some really useful
 functionality. So what would go wrong if we chose to take the practical
 path, and leave aside the theoretical issues?
 
 You would lose many uses of equational reasoning in your programs. Have you 
 every substituted 'x * 2' for the expression 'x + x' in one of your programs, 
 or vice versa? You can no longer do that, because someone may be serializing 
 the function you're writing, checking how it's implemented, and relying it.


Yes, but it would not break any existing code. It would only break code that 
knowingly did the wrong thing.

 We already have a weak case of this, since (\x - undefined x) can be 
 distinguished from undefined using seq, but that can be hand-waved away by 
 not 
 worrying about bottoms so much. That isn't going to work for serialize.

Why not?

--
Sjoerd Visscher
http://w3future.com




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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread John Lato

 From: Sjoerd Visscher sjo...@w3future.com

 On Nov 11, 2010, at 3:36 PM, Dan Doel wrote:

  On Thursday 11 November 2010 6:22:06 am Sjoerd Visscher wrote:
 
  The reasoning above is used regularly to shoot down some really useful
  functionality. So what would go wrong if we chose to take the practical
  path, and leave aside the theoretical issues?
 
  You would lose many uses of equational reasoning in your programs. Have
 you
  every substituted 'x * 2' for the expression 'x + x' in one of your
 programs,
  or vice versa? You can no longer do that, because someone may be
 serializing
  the function you're writing, checking how it's implemented, and relying
 it.


 Yes, but it would not break any existing code. It would only break code
 that knowingly did the wrong thing.

  We already have a weak case of this, since (\x - undefined x) can be
  distinguished from undefined using seq, but that can be hand-waved away
 by not
  worrying about bottoms so much. That isn't going to work for serialize.

 Why not?


I don't know to what extent it would apply in this hypothetical situation,
but ghc (and probably other compilers) rely upon Haskell's semantics in
performing various code transformations.  If you break the semantics some
transformations become invalid, resulting in incorrect code.

I've experienced this with code that violated ref. transparency.  The
program behavior changed depending on the compiler's optimization settings.
 I'm not keen to go back to that.

I think the only way this would work would be if you consider functions to
be equal only to themselves, i.e. x+x and 2*x are not equal.  That's not
a trade-off I would be willing to make.

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


RE: [Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Simon Peyton-Jones
-ddump-deriv

From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Ozgur Akgun
Sent: 11 November 2010 14:27
To: Haskell cafe
Subject: [Haskell-cafe] ghc dump the code for derived instances

Café,

Is there a way to make GHC dump the code for auto-derived type class instances, 
say for Show, Eq and such?
Thanks,
Ozgur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Sjoerd Visscher

On Nov 11, 2010, at 6:34 PM, John Lato wrote:

 I don't know to what extent it would apply in this hypothetical situation, 
 but ghc (and probably other compilers) rely upon Haskell's semantics in 
 performing various code transformations.  If you break the semantics some 
 transformations become invalid, resulting in incorrect code.
 
 I've experienced this with code that violated ref. transparency.  The program 
 behavior changed depending on the compiler's optimization settings.  I'm not 
 keen to go back to that.

Then don't do that. Being able to serialize functions is just as dangerous as 
having unsafePerformIO. If you don't use it, you don't have problems.

--
Sjoerd Visscher
http://w3future.com




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


[Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
Oops, forgot to send this to the list... sorry, Sjoerd.

On Thu, Nov 11, 2010 at 11:54 AM, Sjoerd Visscher sjo...@w3future.com wrote:
 You would lose many uses of equational reasoning in your programs. Have you
 every substituted 'x * 2' for the expression 'x + x' in one of your programs,
 or vice versa? You can no longer do that, because someone may be serializing
 the function you're writing, checking how it's implemented, and relying it.

 Yes, but it would not break any existing code. It would only break code that 
 knowingly did the wrong thing.

Or code that unknowingly depends transitively on code that does the
wrong thing. In that regard it would be much like unsafePerformIO, and
about as trustworthy. Better off just having any such serialize be
safely in IO, and let people who want to live dangerously just use
unsafePerformIO to get around it.

 We already have a weak case of this, since (\x - undefined x) can be
 distinguished from undefined using seq, but that can be hand-waved away by 
 not
 worrying about bottoms so much. That isn't going to work for serialize.

 Why not?

I'd venture that perhaps because seq only behaves differently when one
possible outcome is _|_. An unsafe serialize could distinguish between
two non-bottom values, which means the sketchy behavior could be free
to wreak havoc in code that's not crashing.

For instance, assuming serialize can be applied to functions of any
type, it would probably be trivial to write a function (isExpr :: a -
Bool) that reports whether an arbitrary term is a primitive value or
the result of some expression, which then lets you write a function
with type (forall a. a - a) that is NOT equivalent to id, which could
then be passed freely into any other piece of code you like. That
sounds like buckets of fun, doesn't it?

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


Re: [Haskell-cafe] Opportunity for Haskell porting to java at RD labs in Bay Area, CA

2010-11-11 Thread David Fox
I would hesitate to call it a terrible decision unless I had a good
idea of what the ratio of Java programmers to Haskell programmers was
out in the world.  Just sayin...

On Thu, Nov 11, 2010 at 7:14 AM, namekuseijin namekusei...@gmail.com wrote:
 given all Oracle woes in the last few months, I'd say this is a
 terrible timing and terrible decision.  How about instead an
 experienced Haskell programmer to best leverage it rather than a
 junior who's learned java at university and has just read Learn
 Haskell in 2 weeks?

 On Wed, Nov 10, 2010 at 6:42 PM, Padma pa...@sraoss.com wrote:
 We are looking for a entry level Haskell programmer who has experience in
 porting from Haskell to java. Please contact me by Email or you can call me
 at 408-207-9367.



 LOCATION: SUNNYVALE, CA

 DURATION: 6 MONTHS



 Degree: Bs or Ms or Ph.D

 Start immediately

 Good experience in porting particularly from Haskell to java environment.

 Check and validate smooth functioning of the system.(After porting is done)

 This is a RD project. (prior experience is desired)

 Good experience in testing and compiling.







 Regards,

 Padma

 SRAOSS INC.

 5300 Stevens Creek Blvd  Suite 460

 San Jose,CA 95129

 Direct:(408) 207-9367
 Tel: (408) 855-8200 x 321
 Fax: (408) 855-8206
 pa...@sraoss.com
 www.sraoss.com
 www.sra.co.jp



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


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

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Claus Reinke

but if improved records are never going to happen


Just to inject the usual comment: improved records have
been here for quite some time now. In Hugs, there is TREX;
in GHC, you can define your own. No need to wait for them.

Using one particular random variation of extensible records 
and labels:


{-# LANGUAGE CPP,TypeOperators,QuasiQuotes #-}

import Data.Label
import Data.Record

data PetOwner = PetOwner deriving Show
data FurnitureOwner = FurnitureOwner deriving Show

-- abstract out labels so that we can bridge backwards-incompatibility
-- http://haskell.org/haskellwiki/Upgrading_packages/Updating_to_GHC_7
#if __GLASGOW_HASKELL__=700
catOwner   = [l|catOwner|]
chairOwner = [l|chairOwner|]
owner  = [l|owner|]
#else
catOwner   = [$l|catOwner|]
chairOwner = [$l|chairOwner|]
owner  = [$l|owner|]
#endif

-- we can still give unique labels, if we want
oldcat   = catOwner := PetOwner
   :# ()

oldchair = chairOwner := FurnitureOwner
   :# ()

-- but we don't have to, even if the field types differ
newcat   = owner := PetOwner
:# ()

newchair = owner := FurnitureOwner
:# ()

main = do
 print $ oldcat #? catOwner
 print $ oldchair #? chairOwner
 print $ newcat #? owner
 print $ newchair #? owner

This variation collected some of the techniques in a sort-of
library, which you can find at 


   http://community.haskell.org/~claus/
   
   in files (near bottom of page)


   Data.Record
   Data.Label
   Data.Label.TH
   
   (there are examples in Data.Record and labels.hs)


That library code was for discussion purposes only, there
is no cabal package, I don't maintain it (I just had to update
the code for current GHC versions because of the usual 
non-backward-compatibility issues, and the operator 
precedences don't look quite right). There are maintained

alternatives on hackage (eg, HList), but most of the time
people define their own variant when needed (the basics
take less than a page, see labels.hs for an example).

I'm not aware of any systematic performance studies
of such library-defined extensible records (heavy use
of type-class machinery that could be compile-time,
but probably is partly runtime with current compilers;
the difference could affect whether field access is
constant or not).

It is also worrying that these libraries tend to be defined
in the gap between Hugs' strict (only allow what is known
to be sound) and GHC's lenient (allow what doesn't bite
now) view of type system feature interactions. 


The practical success weighs heavily in favour of GHC's
approach, but I'm looking forward to when the current
give-it-a-solid-basis-and-reimplement-everything
effort in GHC reaches the same level of expressiveness
as the old-style lenient implementation!-)

Claus

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Stephen Tetley
On 11 November 2010 18:01, C. McCann c...@uptoisomorphism.net wrote:

 For instance, assuming serialize can be applied to functions of any
 type, it would probably be trivial to write a function (isExpr :: a -
 Bool) that reports whether an arbitrary term is a primitive value or
 the result of some expression [SNIP]

Persistent functional languages usually give serialized values
including closures a dynamic type. So can you write isExpr :: Dynamic
- Bool ?

As Persistent Haskell and Clean (both pure functional languages) have
already supported serializing closures / HOFs I'm not sure its really
a such semantical can of worms as this thread suggests.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stack Overflow?

2010-11-11 Thread Ben Christy
It was basically that. I was doing TransformedMatrix = TransformedMatrix *
TransformMatrrix
and should have been doing Transformed Matrix = RotatedMatrix *
TransforrmMatrix

On Thu, Nov 11, 2010 at 10:03 AM, Dmitry Astapov dasta...@gmail.com wrote:

 On Thu, Nov 11, 2010 at 4:58 PM, Ben Christy ben.chri...@gmail.com
 wrote:
  I have implemented a scene graph in Haskell and I have a problem. I walk
  down the scenegraph and at each node I recalculate translation matrix and
  pass it to each child. Well it seems to be causing a stack overflow and I
 am
  lost as to how to resolve the issue without issue a state variable of
 some
  kind to hold a matrix stack as is common in imperative implementations
 of
  scene graphs. When I run the program fromghci I get
 [snip]
  Matrix4x4 {i1j1 = interactive: loop
  interactive: interrupted

 Check the expression for i1j1 - seems like it boils down to let x = x in
 x

 --
 Dmitry Astapov

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


Re: [Haskell-cafe] [ANNOUNCE] csound-expression - csound combinator library

2010-11-11 Thread Anton Kholomiov
Maybe haskellWiki is proper place for this, but I like what haddock is doing
with styles and how it links to functions and modules.


2010/11/10 Erik de Castro Lopo mle...@mega-nerd.commle%2...@mega-nerd.com


 Anton Kholomiov wrote:

  no, it's not here any more, but i've added tutorial. look for update
 
  http://hackage.haskell.org/package/csound-expression

 Thanks for that, but wouldn't it be nicer to move the
 tutorial out of the library sources directoru src/ ?

 Cheers,
 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Am 11.11.2010 14:25, schrieb Stephen Tetley:

I'm not sure about an environment variable. Adding the MinGW\ prefix
looks wrong, you may have to experiment with paths and forward or back
slash separators a bit. I can't remember which convention (Windows)
cabal uses.


I tried every possible combination. Apparently, the configure script is 
completly ignoring those --extra-..-dirs flags.

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


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Stephen Tetley
Have you tried with double backslash \\ and starting from the root? I
think runhaskell under MinGW uses this form:

 runhaskell Setup.hs configure 
 --extra-include-dirs=C:\\msys\\1.0\\local\\include 
 --extra-lib-dirs=C:\\msys\\1.0\\local\\lib

I haven't built a binding for a while so I've forgotten some quirks,
but I found an old message to -Cafe highlighting that paths appear to
need double back slash and should not be in double quotes:

http://www.haskell.org/pipermail/haskell-cafe/2010-March/075387.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 1:57 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 On 11 November 2010 18:01, C. McCann c...@uptoisomorphism.net wrote:

 For instance, assuming serialize can be applied to functions of any
 type, it would probably be trivial to write a function (isExpr :: a -
 Bool) that reports whether an arbitrary term is a primitive value or
 the result of some expression [SNIP]

 Persistent functional languages usually give serialized values
 including closures a dynamic type. So can you write isExpr :: Dynamic
 - Bool ?

But it's not the type of the serialized value that's at issue, it's
the type of the serializable values. Anything that lets you convert an
arbitrary closure into something with internals open to inspection
will likely have dire consequences for parametricity and referential
transparency. Remember, the problem isn't what you do with the
serialized form itself, it's what you can learn via it about the
original value it was serialized from. To retain sanity, either types
that can be serialized must be marked explicitly (perhaps in the
context, similar to having a Data.Typeable constraint) to indicate
potential non-parametric shenanigans, or the result of serializing and
inspecting a value must be quarantined off, such as with IO. Or some
other mechanism, but those seem like the obvious choices.

Having a full serialization function without some restriction along
those lines would be like renaming unsafePerformIO to runIO, moving it
to Control.Monad.IO, and telling people hey, just don't misuse this
and everything will be okay.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Gregory Crosswhite

On 11/11/10 12:07 PM, C. McCann wrote:

To retain sanity, either types
that can be serialized must be marked explicitly (perhaps in the
context, similar to having a Data.Typeable constraint) to indicate
potential non-parametric shenanigans


You mean, like Data.Binary?

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Stephen Tetley
But I don't see that you don't need introspection at user level for
persistence, a dynamic type will do, thus the internals aren't open to
inspection. Whatever introspection is necessary can be handled by the
runtime system as in Clean and Persistent Haskell. You could look at
the internals of a pickle with a binary editor but that's perhaps
cheating.

From my reading of the paper, Persistent Haskell was suitably
referentially transparent:

This paper describes the first-ever implementation of orthogonal
persistence for a compiled purely functional language, based on an
existing St Andrews persistent object store.

The conclusion notes in passing that OCaml's persistence isn't
referentially transparent. If the Haskell version wasn't, I'd expect a
mea culpa from the authors at this point.

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.36.421
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Stephen Tetley
Apologies - an unfortunate typo in my first sentence (extra don't) ,
it should have read: :

 But I don't see that you need introspection at user level for
 persistence, a dynamic type will do, thus the internals aren't open to
 inspection. Whatever introspection is necessary can be handled by the
 runtime system as in Clean and Persistent Haskell. You could look at
 the internals of a pickle with a binary editor but that's perhaps
 cheating.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 11/11/2010, at 4:02 PM, Sebastian Fischer wrote:

  Why blame languages instead of writers?

We _find fault_ with programming languages
and we _blame_ their designers.
A programming language is a tool.
A saucepan whose handle keeps falling off is defective,
and if someone who didn't realise the dangers gets a
pan of boiling water over their feet, we find fault
with the saucepan and blame its designer.

A programming language can help in the production of
working software in several ways:
 - making it easier to do the right thing
 - making it easier to find mistakes
 - making it harder to make mistakes
 - making it easier to read the result.

For some tasks, C makes it very easy to do the right thing.
It also makes it horribly easy to make mistakes and hard to
find them.

The amount of time spent maintaining a program is much higher
than the amount of time spent creating it initially.  That
means that if you have a tradeoff between ease of writing and
the other virtues of a language, ease of writing *matters* less.

Consider the vexed question of repeating all or part of the
record name in the field name.  Yes, this *is* a burden on
the person writing it.  But it is a **help** to the person
reading it.  The same applies to using module prefixes
(possibly abbreviated ones).  If I see 'length' in a
Haskell program, I am for sure going to think it is the one
from the prelude.  If I see 'B.length', I know that I need
to remember what B is (probably some kind of ByteString, these
days).

When people enthuse about how the compiler can figure it all
out, I shudder.  How am *I* going to figure it all out without
heavy machine assistance?

If length, map, and so on had always been part of a Sequence
typeclass, people would not now be talking about
 a lot of value in locally saying 'this particular invocation
 should be ad-hoc overloaded' for common functions like 'length',
 'map', 'lookup', etc.

I expected more use of type classes in the Prelude for Haskell'.


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


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Duncan Coutts
On 11 November 2010 11:23, Nils Schweinsberg m...@n-sch.de wrote:
Configuring pcre-light-0.4...
cabal: Missing dependency on a foreign library:
* Missing C library: pcre

On 11 November 2010 12:41, Stephen Tetley stephen.tet...@gmail.com wrote:
 Do you have the headers installed as well as the dlls?

With this error message, it really is the C libs. If cabal cannot find
the headers then it says so explicitly.

Cabal does the check by making a trivial .c program and linking it
with (approximately):

gcc main.o -lpcre

If that fails then cabal declares that it cannot find the C lib. It's
possible that the lib is present but that there is some other linking
error, it's a bit tricky to distinguish without looking at the error
messages from ld.exe.

So the first thing to try is the above test, or run cabal configure
-v3 and see what error message ld reports.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 3:30 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 The conclusion notes in passing that OCaml's persistence isn't
 referentially transparent. If the Haskell version wasn't, I'd expect a
 mea culpa from the authors at this point.

From a quick glance at the paper, the Haskell version is referentially
transparent in the standard, trivial sense: the persistence operations
all return IO actions. This is of course perfectly fine. What started
this thread, however, was the idea of a serialization function
producing something like a pure ByteString, and why that, as opposed
to (IO ByteString), would be extremely problematic.

What it boils down to is just that any pure serialization function
would necessarily do nothing useful. Serializing closures from IO
actions, on the other hand, I think is a great idea, though probably
difficult to implement!

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


Re: [Haskell-cafe] Splittable random numbers

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 3:13 AM, Richard Senington sc06...@leeds.ac.uk wrote:
 I got hold of, and looked through the paper suggested in the root of this
 thread “Pseudo random trees in Monte-Carlo, and based upon this
 I have thrown together a version of the binary tree based random number
 generator suggested.

 I would like to point out that I do not know very much about random number
 generators, the underlying mathematics or any subsequent papers on this
 subject, this is just a very naive implementation based upon this one paper.

 As a question, the following code actually generates a stream of numbers
 that is more random than I was expecting, if anyone can explain why I would
 be very interested.

What do you mean more random than you were expecting?  Shouldn't they
be maximally random?

BTW, nice module.  Do you want to hackage it up?  If not, I will.

 import System.Random

 data LehmerTree = LehmerTree {nextInt :: Int,
   leftBranch :: LehmerTree,
   rightBranch :: LehmerTree}

 instance Show LehmerTree where
   show g = LehmerTree, current root = ++(show $ nextInt g)

 mkLehmerTree :: Int-Int-Int-Int-Int-Int-LehmerTree
 mkLehmerTree aL aR cL cR m x0 = innerMkTree x0
   where
     mkLeft x = (aL * x + cL) `mod` m
     mkRight x = (aR * x + cR) `mod` m
     innerMkTree x = let l = innerMkTree (mkLeft x)
     r = innerMkTree (mkRight x)
     in LehmerTree x l r

 mkLehmerTreeFromRandom :: IO LehmerTree
 mkLehmerTreeFromRandom = do gen-getStdGen
     let a:b:c:d:e:f:_ = randoms gen
     return $ mkLehmerTree a b c d e f

This can be pure:

mkLehmerTreeFromRandom :: (RandomGen g) = g - LehmerTree

 instance RandomGen LehmerTree where
   next g = (fromIntegral.nextInt $ g, leftBranch g)
   split g = (leftBranch g, rightBranch g)
   genRange _ = (0, 2147483562) -- duplicate of stdRange



 test :: IO()
 test = do gen-mkLehmerTreeFromRandom
   print gen
   let (g1,g2) = split gen
   let p = take 10 $ randoms gen :: [Int]
   let p' = take 10 $ randoms g1 :: [Int]
   -- let p'' = take 10 $ randoms g2 :: [Float]
   print p
   print p'
   -- print p''



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


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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Stephen Tetley
On 11 November 2010 21:23, C. McCann c...@uptoisomorphism.net wrote:

 [Snip]  What started
 this thread, however, was the idea of a serialization function
 producing something like a pure ByteString, and why that, as opposed
 to (IO ByteString), would be extremely problematic.

I think the original poster was intrigued by the possibilities
serializing functions and their first guess a type signature was a
MacGuffin[*].

Its a lot of work to implement persistence. As far as I know its only
implemented for the Windows version of Clean. Napier 88's persistent
store was a very substantial development effort for a programing
language research project - multi-person, multi-year, EU funded
through the ESPRIT Basic Research programme.

[*] In case anyone looks up MacGuffin on Wikipedia, I don't think the
description there is strictly accurate. A MacGuffin doesn't drive the
plot so much as throw the viewer of the scent.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 11/11/2010, at 10:33 PM, Gábor Lehel wrote:

 I would have TDNR apply only in cases where:
...
 - The ambiguity can be resolved by looking at the type of the first
 (taking currying into account, only) parameter of each function and,
 looking at the type constructors from the outside in, comparing only
 type constructors which are concrete types, rather than type variables
 (with or without constraints).

This just feels so wrong.  One of the joys of types in Haskell and of
overloading in Ada is that it depends on *all* the arguments of a
function *and* the result.

I note that record field overloading can be put in a language without
providing ad hoc polymorphism for any other functions.  A little ML:
Given 

  type t1 = {a: int, b: string};
  type t2 = {a: string, b: int};
  val x1 : t1 = {a = 1,  b = 2};
  val x2 : t2 = {b = 2, a = 1};

this interaction followed:

- (#a x1, #a x2, #b x1, #b x2);
val it = (1,1,2,2) : int * string * string * int

Here we had
#a : t1 - int  #b : t1 - string
#a : t2 - string   #b : t2 - int

The consequence is that when I see 
val N = #capacity derived ()
I don't know what capacity means for sure, but I *do* know that it is
a record field, so I have some idea what to look for.
It turns out that there are four possibilities but for two of them
() would not be a legal argument, so there are only two possibilities.

I note that there is a reason for having quite a few records in a
module with many shared field names at different types, which I had
not thought of.  That is the practice of passing a record as a
function's sole argument in order to get the effect of keyword
arguments, fairly popular in SML:

  val max_flow : {
 graph: ('n,'e,'g) Graph.graph,
 s: Graph.node_id,
 t: Graph.node_id,
 capacity : 'e Graph.edge - Num.elem,
 flows: 'e Graph.edge * Num.elem - unit
  } - Num.elem
  
  val min_cost_max_flow : {
 graph: ('n,'e,'g) Graph.graph,
 s: Graph.node_id,
 t: Graph.node_id,
 capacity : 'e Graph.edge - Num.elem,
 cost : 'e Graph.edge - Num.elem,
 flows: 'e Graph.edge * Num.elem - unit
  } - Num.elem

There is no intention here to have lots of values of these record types.
They are anonymous, after all.  This case needs to be considered
separately from other cases.

 
 And, in any case, as a language extension nobody would be forced to
 use it if they don't like it.

Wrong.

They would not be forced to use it in their own code,
but they *WOULD* be forced to read it in other people's code.
(Why so much focus on the writers and so little on the readers?)

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


[Haskell-cafe] Quasiquoter invocation no longer requires/allows a leading dollar sign.

2010-11-11 Thread Michael Snoyman
Sorry, maybe I missed the memo on this one, but I just noticed this
change to quasi-quotation syntax on the GHC 7 upgrade page[1]. So if
GHC 6.12 *requires* the dollar sign, and GHC 7 *rejects* the dollar
sign, is there any way to write code that will run on both? Is there a
reason we can't keep the dollar sign as supported syntax for a release
or two to make for a cleaner migration?

Michael

[1] 
http://haskell.org/haskellwiki/Upgrading_packages/Updating_to_GHC_7#Quasiquotation:_.5B.24foo.7C7C.5D_-.3E_.5Bfoo.7C7C.5D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Dan Doel
On Thursday 11 November 2010 12:34:21 pm John Lato wrote:
 I think the only way this would work would be if you consider functions to
 be equal only to themselves, i.e. x+x and 2*x are not equal.  That's
 not a trade-off I would be willing to make.

In general, it doesn't even have to be based on a mathematical identity. As 
has been stated, this would in general simply break referential transparency. 
Are these two functions equal:

  f x = k (h x) (h x)
  g x = let y = h x in k y y

Presumably, no, if serialize exists (and they may have different performance 
characteristics).

You cannot factor out or inline subexpressions or without the difference being 
observable (presumably) by serialize.

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 12/11/2010, at 2:17 AM, Michael Snoyman wrote:
 So why would you ever need to reuse the same field name in the same
 module?
 
 data PetOwner
 data FurnitureOwner
 
 data Cat = Cat { owner :: PetOwner }
 data Chair = Chair { owner :: FurnitureOwner }
 
 Just the first thing that came to mind, this kind of thing comes up
 often enough to be an irritant. I'm not sure whether or not TDNR is a
 good solution to the problem, just pointing out a use case.

I'm afraid it's not a *convincing* use case.
It's not convincing because here owner *means different things*.

The genius of typeclasses was that it gave us a way to implement
functions differently for different types while still referring
all the implementations to a single interface, so that they should
all in _some_ sense mean the same thing.

If x owns a pet, then x is responsible for providing it with
food, water, shelter, and medical treatment, and can be gaoled
for failing to do so.

If y owns a chair, then y can sit on it, spray it with
mayonnaise, smash it to pieces, burn it to ashes, or do pretty
much anything y pleases.  There is no duty to provide a pet
chair with food, water, c.

There was a German case a couple of years ago where a man
described a fantasy of his on the internet and asked for
a volunteer to help him carry it out in reality.  He got
one.  The other man came to his flat, they had sex, and
then the first man killed the other and ate him.

My take on this was that there were things you *can't*
consent to.  The colleague I discussed it with a couple
of days ago said If I don't own my body, I own nothing
and said that owning your own body had to mean having the
right to volunteer to killed and eaten.  He's such a nice
man, my colleague, and deeply skilled in logic.

Thinking about this, I came to the conclusion that when
he and I say my body we mean different things.
I mean INalienable possession, he means alienable possession.
It's like the difference between a dog's meat (food for the
dog from another animal, take it away and the dog is
hungry) and a dog's flesh (the dog's own matter, take it
away and there is no dog).

There's that rather silly piece in Plato's Republic where
he says Both the community of property and the community
of families ... tend to make them more truly guardians;
they will not tear the city in pieces by differing about
mine and not mine; ... but all will be affected as far
as may be by the same pleasures and pains ...
Since when can my hunger be the same as your hunger?
Since when can my bladder discomfort (I've been sitting at
this keyboard too long) be the same as yours?
Since when can your pleasure in eating onions be the same
as mine (I _hate_ onions, and even if I didn't, I wouldn't
want to eat the _same_ bits of onion you're eating).

Greek didn't distinguish between alienable and inalienable
possession.  If that kind of ambiguity can lead the most
famous philospher in history to write twaddle, what is
confusion in our function names going to do to Haskell
programmers?

TDNR has the same attractiveness as a sugar coated laxative
tablet, and I expect the end product of both to be the same.

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 12/11/2010, at 2:53 AM, Stephen Tetley wrote:
 
 This is fairly onerous for people who are programming to an outside
 schema (i.e. a relational database) as it leads to boiler plate along
 two axes - data type definitions plus class definitions for accessors.

Boiler plate is GOOD news, because the generation of
boiler plate can be automated.
 
 Incidentally there is now a member of the ML family with a
 sophisticated record system - MLPolyR:
 http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php

There is or was also SML# (not related to .Net).

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Alexander Solla


On Nov 11, 2010, at 1:42 PM, Stephen Tetley wrote:


[*] In case anyone looks up MacGuffin on Wikipedia, I don't think the
description there is strictly accurate. A MacGuffin doesn't drive the
plot so much as throw the viewer of the scent.


I think Hitchcock might disagree with you.

In any case, serializing functions is as easy as you want it to be.   
But, there is a big caveat:  You are basically embedding a compiler  
into your run-time.  It can be pretty minimal, relying only on facts  
known about recursively enumerable functions:


class Serialize a where
  serialize :: a - ByteString
  unSerialize :: ByteString - Maybe a  -- Parsers can fail

instance (Serialize a) = Serialize [a] where ...
instance (Serialize a, Serialize b) = Serialize (a, b) where ...

-- We can conclude that a and b must be enumerable from the  
requirement that

-- f is recursively enumerable:
instance (Serialize a, Enum a, Serialize b, Enum b) = Serialize (a -  
b) where

serialize f = serialize $ ( zip [minBound..maxBound]
(fmap f [minBound..maxBound]) )
-- A map instance could be better:  we trade some serialization time  
for more
-- deserialization time.  
instance (Serialize a, Serialize b) = Serialize (Map a b) where ...


instance (Serialize a, Serialize b) = Serialize (a - b) where
serialize f = serialize . fromList $ ( zip [minBound..maxBound]
   (fmap f 
[minBound..maxBound]) )
deserialize map = \x - lookup x (bytestring_decode_map map)
where bytestring_decode_map = ...

There are potentially big problems with this approach:
(i)   Many data types are not instances of Enum (though the really  
should be.  Deriving enumerations is not that hard.  I am willing to  
take one for the team to get GHC to figure out how to derive Enum on  
arbitrary types, but I'm not sure where to start.  Little help?)
(ii)  Time and memory.  We're not encoding a series of instructions  
for computing pure functions, but we're precomputing the results and  
saving them all for later.  This is at least O(size of the domain) *  
O(of the function on each element).  Not big in theoretical terms, but  
something like that could easily cause a factor of [1, \infty)   
slowdown in real code.
(iii)  Serialized objects must be pure.  In particular, you can't  
serialize general IO actions.  I see this as a plus.  It is still easy  
to write an algebra of serializable tokens and a non-serializable  
interpreter to generate IO actions from the tokens.  We do this kind  
of thing all the time -- we just don't serialize the tokens usually.


I think (ii) is the biggest problem.  And it is a big one.  We  
basically need something like template haskell for runtime systems in  
order to do quasi-quoting and compilation at run-time so we can avoid  
reifying the domain and its image under f.


The only thing that can serialize an (IO a) is the Haskell runtime,  
and it does it by running the action (and so putting its sub-steps in  
a series). ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 12/11/2010, at 3:22 AM, Ozgur Akgun wrote:

 On 11 November 2010 01:19, Richard O'Keefe o...@cs.otago.ac.nz wrote:
 I'm not sure that it is desirable to have many records in the
 same module in the first place.
 
 Amongst other reasons, 
 http://www.haskell.org/haskellwiki/Mutually_recursive_modules

The Programatica project showed that recursive modules *could* be
implemented; if I remember correctly, their module resolution code
was in pure Haskell 98.

However, I'll grant you the incomplete implementation status of Haskell98
as an argument for fusing what would have been mutually recursive modules
(although I suspect that two-level types may be better).  That still isn't
an argument for MANY records in the same module.


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


Re: [Haskell-cafe] [ANNOUNCE] csound-expression - csound combinator library

2010-11-11 Thread Erik de Castro Lopo
Anton Kholomiov wrote:

 but I like what haddock is doing
 with styles and how it links to functions and modules.

Well maybe move it to src/Tutorial, then you get the bext of both
worlds, the tutorial is easy to find and it gets haddock docs.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask



 If the outcome of this discussion is a clamour for better records
 instead of TDNR, then that would certainly make me happy.

 Regards,
 Malcolm

well I certainly am clamouring for better records.


This motivated my original reply this post. The trouble is, what
constitutes better records? There are as many views as users of Haskell, 
I bet.


My main motivation is:

As mentioned in my original post: better name space management.

Surprisingly enough, I find the current record system is quite usable, 
bar one feature. My particular use case: commercial applications make 
heavy use of records (in connection with relational databases) and name 
clashes are inevitable.


As I tried to point out in my original post, issues of name space 
management are orthogonal to the type system, but obviously related as 
the type system in Haskell is used to distinguish names.


The thrust of discussion and work on the record system, in so far as 
Haskell has been concerned, has been at the type system level, an 
necessarily so: work on representing the has a relation, extensibility 
etc at the type level. Some relatively usable libraries have been 
developed that provide this support (eg HList).


none of this can address my particular issue: name space management, 
that is, managing the scope of record labels. The type system is not the 
solution to all problems. Hence my proposal.


I don't envisage that my issue will be addressed anytime soon, if at 
all. But by raising it I hope to broaden the focus of the discussion.


The trouble with any rework of the current record system: which way to 
take it ... the design space is large


what would users want ...

- light weight records (c.f. ML)
- first class labels (accessors and setters)
- extensible records
- sub-typing

or in my case

- better name space management

perhaps given the many avenues for exploration of type system support 
for record systems, we could make use of existing libraries with 
rebind-able syntax??


again quoting

http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

Haskell lacks a serious record system. (The existing mechanism for 
named fields in data types was always seen as a stop-gap measure.)


isn't it about time this changed?




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




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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Dan Doel
On Thursday 11 November 2010 11:54:56 am Sjoerd Visscher wrote:
 Yes, but it would not break any existing code. It would only break code
 that knowingly did the wrong thing.

Well, if we added a function that randomly scrambled GHC's heap memory, it 
wouldn't break any existing code, because none would use it. :)

  We already have a weak case of this, since (\x - undefined x) can be
  distinguished from undefined using seq, but that can be hand-waved away
  by not worrying about bottoms so much. That isn't going to work for
  serialize.
 
 Why not?

Because, there is an argument to be made in the seq case that no one really 
cares about the differences it introduces. I don't usually care how my code 
works on bottoms, except inasmuch as it determines various performance 
characteristics of the code*, or whether it works on infinite values. I try, 
generally speaking, to write total functions, and run them on well-defined 
inputs. So when I reason about the programs, it is this aspect that I care 
most about, not about what happens when I feed in undefineds.

There are even folks that have worked on making this perspective rigorous. 
See, Fast and Loose Reasoning is Morally Correct.

serialize is not at all the same in this regard. There is no class of 
functions that is immune to its inspection powers, presumably, because that's 
its whole point. But that also means that there is no class of functions for 
which we are justified in reasoning equationally using the standard 
extensional equality. The only way that would be justified is saying, 
serialize doesn't exist.

 Then don't do that. Being able to serialize functions is just as dangerous
 as having unsafePerformIO. If you don't use it, you don't have problems.

And unsafePerformIO's very name suggests that you're breaking things when you 
use it. It comes with lots of caveats, and the Haskell community will 
generally heap scorn on you if you use it for trivialities (or even non-
trivialities). I don't understand why it would be desirable for a serialize 
function to be branded, don't ever use this unless you're an expert who knows 
what he's doing.

unsafePerformIO is, for many uses, a concession to low-level compiler 
extensibility. You can implement a fair amount of stuff in a library using 
unsafePerformIO that would otherwise require some kind of compiler support. 
What is the analogous motivation for functions to be turned into pure strings 
containing their code?

Of course, if you want, everything is unsafe, be careful, there are many, 
many languages out there that already do that. For instance, ML**, Lisp, C, 
Java, Python,  But this is Haskell, and we try to do a little better than 
that.

-- Dan

[*] Which is irrelevant to the reasoning in question. In fact, if you follow 
Bird's methodology, you first write a naive, obviously correct program, and 
then you transform it into a more efficient version via transformations you've 
shown to preserve semantics. This approach doesn't work if there are no 
correctness-preserving transformations, though.

[**] In fact, Alice ML (I think that's the right one) already has very fancy 
serialization stuff. You can store and load and send entire modules over an 
internet connection, I believe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask

On 12/11/2010 9:22 AM, Richard O'Keefe wrote:


On 12/11/2010, at 2:17 AM, Michael Snoyman wrote:

So why would you ever need to reuse the same field name in the same
module?


data PetOwner
data FurnitureOwner

data Cat = Cat { owner :: PetOwner }
data Chair = Chair { owner :: FurnitureOwner }

Just the first thing that came to mind, this kind of thing comes up
often enough to be an irritant. I'm not sure whether or not TDNR is a
good solution to the problem, just pointing out a use case.


I'm afraid it's not a *convincing* use case.
It's not convincing because here owner *means different things*.



consider length ...

I have records with the attribute length, length can be given as an Int, 
Double, Float or maybe as a constructed type Length, length's use as a 
record selector would also clash with List.length. All these have the 
same denotation.


should I then seporate into int_length, float_length, or use 
rec1_length, rec2_length etc etc...


for proper name space management why should I have to define each record
that defines a length field with different representation in distinct 
modules, or with different names for the field label when they denote 
the same thing?


This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?


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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 8:16 PM, John Lask jvl...@hotmail.com wrote:
 consider length ...

 I have records with the attribute length, length can be given as an Int,
 Double, Float or maybe as a constructed type Length, length's use as a
 record selector would also clash with List.length. All these have the same
 denotation.

 should I then seporate into int_length, float_length, or use rec1_length,
 rec2_length etc etc...

class Lengthy a where
  type LengthType a
  length :: a - LengthType a

This extends easily to lenses if you want setters.

 This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?

By this argument, Haskell should provide global mutable state and
allow side-effects universally.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe

On 12/11/2010, at 2:16 PM, John Lask wrote:

 On 12/11/2010 9:22 AM, Richard O'Keefe wrote:
 
 I'm afraid it's not a *convincing* use case.
 It's not convincing because here owner *means different things*.
 
 
 consider length ...
 
 I have records with the attribute length, length can be given as an Int, 
 Double, Float or maybe as a constructed type Length, length's use as a 
 record selector would also clash with List.length. All these have the same 
 denotation.

All these have the same denotation?  I am extremely confused here.
AH!  You mean you call them all by the same name.  Well yes, that's
the problem, right there.

I remind readers once again that in SML record selectors *don't* clash with
names of functions.  I am not concerned here to argue either for or against
SML-style records and their selectors, only to point out that wanting
*record fields* whose significance depends on the record they select from
is *NOT* the same thing as TDNR in principle, so that arguments for that
don't even come close to being arguments for TDNR as such.

 
 should I then seporate into int_length, float_length, or use rec1_length, 
 rec2_length etc etc...

No, the differing result types are an epiphenomenon of their differing
semantics.

The length of a piece of string is a physical length.
The length of a lecture is a time.
The length of a queue is a natural number (counting people).
The length of a book is a positive integer (counting say pages, or words)
The length of a vowel is a relative time.

These quantities are measured differently, combined differently, and assessed
differently.  Calling them all length is a METAPHOR.  (There are at least
three metaphors in the list above: time-is-space, codex-is-scroll, and
a form of metonomy.)

 for proper name space management why should I have to define each record
 that defines a length field with different representation in distinct 
 modules, or with different names for the field label when they denote the 
 same thing?

But you just explained that while they may have the same denotation (the
identifier), what it DENOTES is NOT the same (otherwise they could not
be different types).

As SML proves, having record-sensitive field names is a *different*
question from Type Directed Name Resolution applied to plain function names.
 
 This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?

But it *isn't* handled *AT ALL* in any of those languages, let alone
handled easily.

In C, Pascal, PL/I, and COBOL field names are *not* values.
C, Pascal, and PL/I let you pass functions as parameters to functions.
But you cannot pass field names that way.  The only thing you can do
with a field name is apply it *immediately* to a record.  And those
languages don't have type variables, so when you apply a selector to
a record, you know then and there what the type is.

If what you want is some sort of record facility at least as good as
SML's, fine.  What I am arguing against is anything resembling Type
Directed Name Resolution (alias ad hoc overloading) being applied to
plain ordinary functions.

(By the way, if the field names of a record type are visible outside its
module, I start wondering why.)


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

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 6:16 PM, Dan Doel dan.d...@gmail.com wrote:
 serialize is not at all the same in this regard. There is no class of
 functions that is immune to its inspection powers, presumably, because that's
 its whole point. But that also means that there is no class of functions for
 which we are justified in reasoning equationally using the standard
 extensional equality. The only way that would be justified is saying,
 serialize doesn't exist.

Admittedly, the class of reasoning I usually use in my Haskell
programs, and the one that you talked about using earlier this
message, is essentially seq doesn't exist.  However, I prefer to use
this class of reasoning because I would prefer if seq actually didn't
exist (er, I think the implication goes the other way).  Not so for
serialize: I would like a serialize function, but I don't want the
semantic burden it brings.  If only there were a way to...

oh yeah.

serialize :: (a - b) - IO String

I still don't really get what we're arguing about.

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


Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask




On 12/11/2010, at 2:16 PM, John Lask wrote:


On 12/11/2010 9:22 AM, Richard O'Keefe wrote:


I'm afraid it's not a *convincing* use case.
It's not convincing because here owner *means different things*.



consider length ...

I have records with the attribute length, length can be given as an Int, Double, Float or 
maybe as a constructed type Length, length's use as a record selector would 
also clash with List.length. All these have the same denotation.


All these have the same denotation?  I am extremely confused here.
AH!  You mean you call them all by the same name.  Well yes, that's
the problem, right there.

I remind readers once again that in SML record selectors *don't* clash with
names of functions.  I am not concerned here to argue either for or against
SML-style records and their selectors, only to point out that wanting
*record fields* whose significance depends on the record they select from
is *NOT* the same thing as TDNR in principle, so that arguments for that
don't even come close to being arguments for TDNR as such.



should I then seporate into int_length, float_length, or use rec1_length, 
rec2_length etc etc...


No, the differing result types are an epiphenomenon of their differing
semantics.

 The length of a piece of string is a physical length.


length of string measured in CM's, in MM, in Inches, as an Int, float
... they all denote the same thing modulo some theory.

You could argue that a length in CM's measured as a float is
semantically different to that of CM's as an Int, which it is, but
somewhere along the line those semantic differences become irrelevant to
the abstract domain of application, your model, and it is that model
that you wish to represent as a program, although you need to deal with
the concrete differences as an implementation detail.


 The length of a lecture is a time.
 The length of a queue is a natural number (counting people).
 The length of a book is a positive integer (counting say pages, or words)
 The length of a vowel is a relative time.

These quantities are measured differently, combined differently, and assessed
differently.  Calling them all length is a METAPHOR.  (There are at least
three metaphors in the list above: time-is-space, codex-is-scroll, and
a form of metonomy.)


for proper name space management why should I have to define each record
that defines a length field with different representation in distinct modules, 
or with different names for the field label when they denote the same thing?


But you just explained that while they may have the same denotation (the
identifier), what it DENOTES is NOT the same (otherwise they could not
be different types).



you are right


As SML proves, having record-sensitive field names is a *different*
question from Type Directed Name Resolution applied to plain function names.




agreed


This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?


But it *isn't* handled *AT ALL* in any of those languages, let alone
handled easily.

In C, Pascal, PL/I, and COBOL field names are *not* values.
C, Pascal, and PL/I let you pass functions as parameters to functions.
But you cannot pass field names that way.  The only thing you can do
with a field name is apply it *immediately* to a record.  And those
languages don't have type variables, so when you apply a selector to
a record, you know then and there what the type is.

If what you want is some sort of record facility at least as good as
SML's, fine.  What I am arguing against is anything resembling Type
Directed Name Resolution (alias ad hoc overloading) being applied to
plain ordinary functions.


that's something like what I want. I am not argiung in favor of TDNR,
only that haskell record system needs improvement, particularly the
scoping of field labels.




(By the way, if the field names of a record type are visible outside its
module, I start wondering why.)




depends on what your using them for ..




___
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] Rebindable record syntax

2010-11-11 Thread Philippa Cowderoy
I stood up and suggested rebindable record syntax at Anglohaskell 
earlier this year, but never got round to posting a proposal. Given the 
TDNR discussion, it seems timely to link everyone to what I'd got round 
to writing:


http://flippac.org/RebindableRecordSyntax.html

Apologies for the lack of concrete examples: if anyone's interested I'll 
try to crank some out soon, specific requests would help. I probably 
don't have the energy to champion this properly on my own, so speak up 
if you think it's a good idea! Incidentally, I believe something similar 
has been proposed elsewhere - it's also possible I'd seen it before and 
forgotten before rediscovering the idea.


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


Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask

On Thu, Nov 11, 2010 at 8:16 PM, John Laskjvl...@hotmail.com  wrote:

consider length ...

I have records with the attribute length, length can be given as an Int,
Double, Float or maybe as a constructed type Length, length's use as a
record selector would also clash with List.length. All these have the same
denotation.

should I then seporate into int_length, float_length, or use rec1_length,
rec2_length etc etc...


class Lengthy a where
   type LengthType a
   length :: a -  LengthType a

This extends easily to lenses if you want setters.




to make use of the class Lengthy I still need to define record selectors
with different names, which is exactly the point I am making...

ie

data Record = RecLen { rec_length :: ... }

instance Lengthy Record where
  length = rec_length


This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?


By this argument, Haskell should provide global mutable state and
allow side-effects universally.



no, but these languages have their strengths as well, for example Cobol
PIC strings format currency values very nicely and it would be great if
there were a Haskell library that could do the same. Not to mention
currency values!

The point is that languages are often constructed with a purpose in
mind, at which they tend to be particularly good. Haskell has
traditionally been a test bed for type system innovation, which is why
we all like it so much.

As and if, the usage of Haskell broadens, then domains of application
stray into areas of application for which it is not ideally suited, in
those circumstances why not consider features of other languages which
handle those use cases well. (for some definition of well)

By the way I am not arguing for TDNR, merely that all is not well with
haskell records.


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


Re: Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Donn Cave
Quoth John Lask jvl...@hotmail.com,
...
 By the way I am not arguing for TDNR, merely that all is not well with
 haskell records.

And you have a lot of company there, but the discussion is taking
place in a thread named Type Directed Name Resolution.  When that
has been put to rest, let's talk about Haskell records!

Donn

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


Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Evan Laforge
 This motivated my original reply this post. The trouble is, what
 constitutes better records? There are as many views as users of Haskell, I
 bet.

 My main motivation is:

 As mentioned in my original post: better name space management.

 Surprisingly enough, I find the current record system is quite usable, bar
 one feature. My particular use case: commercial applications make heavy use
 of records (in connection with relational databases) and name clashes are
 inevitable.

I too would like better records, and I too find them usable if not
ideal in their current form.  They wind up being doubly qualified,
e.g. 'State.state_blocks st' and can be quite verbose.  Consider an
extreme case:

set_track_width view_id width = do
track_views - modify_at set_track_width
(Block.view_tracks view) tracknum $ \tview -
tview { Block.track_view_width = width }
update_view view_id (view { Block.view_tracks = track_views })

update_view view_id view = modify $ \st - st
{ state_views = Map.adjust (const view) view_id (state_views st) }

What I am actually *doing* here, is:

state.get_view(view_id).tracks[tracknum].width := width

Part of the difference is that updating data is fundamentally more
idiomatic in an imperative language, and it's true this is a rare
example (modify_at updates a list at an index, ignore that :P).  But
the fact is that the difference between what I write and what I mean
is reaching almost comical java-like levels.

'modify $ \st - st { State.state_x = f (State.state_x st) }' is quite
common, and modifying two levels deep also happens (which requires an
auxiliary function to be readable).  And the 'f' is buried in the
middle of a bunch of boilerplate.

 - light weight records (c.f. ML)

I actually don't feel a lot of need for this... if I want a
short-lived data structure I just use a tuple.  I use records when
they are being passed through multiple functions, and at that point
I'm probably going to at least a type synonym, and then we're back to
heavy-weight, right?

The only place I can think of where light-weight records would be
handy is simulating keyword args... but even then it seems hardly a
burden to declare a datatype for it, and it gives you a place to put
documentation.  Any other uses out there?

 - first class labels (accessors and setters)

I would love this.  I don't even think accessors is really the
problem, they compose nicely as just functions even if they are a
little wordy.  It's update that's the killer.  The reason I say it's
bearable even though it can be quite verbose is that update (at least
in my programs) is uncommon enough that I can factor all common
updates into functions and then just call those.

 - extensible records
 - sub-typing

Unlike the above things which make it more convenient to write the
same code, it sounds like these things would actually let you write
new kinds of code.  However, I don't really feel like I'm missing
that.  Maybe it's a blub problem?  Are there some examples of cool
things you could do with either of the above that you can't do
(conveniently) without?

In fact, given that updates seem to be the only thing I care about,
maybe I'd be made almost as happy by a functional refs library.  There
are several competing implementations on hackage but AFAIK none are
considered universal and standard (none are in HP, for instance).

 http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

 Haskell lacks a serious record system. (The existing mechanism for named
 fields in data types was always seen as a stop-gap measure.)

 isn't it about time this changed?

I sure think so :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Manatee - The Haskell/Gtk+ Integrated Live Environment first version release!

2010-11-11 Thread Andy Stewart
Hi all,

I have write Simple Manual at http://haskell.org/haskellwiki/Manatee

Enjoy! :)

  -- Andy

Andy Stewart lazycat.mana...@gmail.com writes:

 Hi all,

 I am proud to announce the release my gtk2hs project : Manatee - The 
 Haskell/Gtk+ Integrated Live
 Environment

 http://hackage.haskell.org/package/manatee

 Screenshots at : http:goo.gl/MkVw
 Code at https://patch-tag.com/r/AndyStewart/ beginning with manatee-*

 Manatee is Haskell integrated environment written in Haskell.

 The goal of the Manatee project is to provide a fast, safe and flexible
 integrated environment for haskell hacking.

 You can consider it is new environment mix Gnome and Emacs. 
 Like Gnome to provide friendly graphics interface and work efficient like 
 Emacs.

 Manatee use multi-processes framework, any sub-module running in separate 
 process to protected core
 won't crash. So it
 minimize your losses when some unexpected exception throw in extension.

 Now i have implement below sub-modules in Manatee:

 Editor
 Webkit Browser
 File Manager
 Image Viewer
 IRC Client
 Multimedia Player
 PDF Viewer
 Process Manager
 RSS/Atom reader  
 
From some friends feedback, manatee can't work in XMonad, i will fix it soon. 
 You can play it in Gnome. Enjoy! :)

 Below are steps to build Manatee:

 1) Install C library: In Debian use below command:

  sudo aptitude install libgtksourceview2.0-dev libgconf2-dev libwebkit-dev 
 libcurl4-openssl-dev
 libgtkimageview-dev libpoppler-glib-dev poppler-data libtagc0-dev -y

 2) Install Gtk2hs:

  cabal install gtk2hs-buildtools gtk

 And make sure HOME.cabalbin/ in your PATH.

 3) Install Manatee:

  cabal install manatee-core manatee-anything manatee-browser manatee-editor 
 manatee-filemanager
 manatee-imageviewer manatee-ircclient manatee-mplayer manatee-pdfviewer 
 manatee-processmanager
 manatee-reader manatee
  
 That's all, then type command manatee to play it! :)

 manatee-core manatee-anything manatee are core packages, must be
 install, other extension package you can choose you want.

 Example, if you not install manatee-imageviewer, when you open Image
 file, manatee will call default image-viewer in your system instead.

 Manatee will show you search interface when you startup it.
 You can type some filepath or url to open it, 
 example, you can type Haskell file to open in editor, 
 and type url to open in browser.

 Below are quick play keys:

 F2 == startProcessManager
 F3 == startFeedReader
 F4 == startFileManager
 F5 == startBrowser
 F6 == loginIrcDefaultChannel
 F7 == startIrc

 Manatee project still in early develop stage, just core framework
 finish, many details still not perfect.

 But i think it's good start to build Real-World application in Haskell.

 Below are high task in my TODO list:

 Perfect current sub-module: 
   IDE features, code completion
   browser JavaScript framework
   graphics custom system
   etc.
   
 Terminal emulator: 
   support MVC design, not like VTE widget
   
 Mail-client
 
 BT-Client
 
 Proxy bridge: 
   to build uniform proxy interface to fighting GFW!!!
   
 Jabbar client:
   video support etc.
 
 Spell checker
 
 CHM viewer
 
 DVI viewer
 
 LaTex editor
 
 PS viewer
 
 Multi-thread download manager
 
 Org-Mode : http://orgmode.org/
 
 Twitter client
 
 Network toolkit:
   sniffer etc.
   
 Multi-Language translater 
   offline support
   
 Too many ideas lying in my TODO list
 
 Any suggestion and contribution are welcome! :)

   -- Andy

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


[Haskell-cafe] Re: Manatee - The Haskell/Gtk+ Integrated Live Environment first version release!

2010-11-11 Thread Andy Stewart
My project want to provide a fact:

Haskell not just can do GUI environment, and can do better!

Gtk2hs + Haskell Threads is awesome!

Below is source code lines of Manatee:
  
   All  : 21651
   
   Core and toolkit : 7047
   Daemon and Window Manager: 3656
   Multi-Threads input framework: 2537
   Browser  : 488
   Editor   : 813
   File manager : 774
   Image viewer : 565
   IRC client   : 2212
   Multimedia player: 1358
   PDF viewer   : 457
   Process Manager  : 761
   RSS/Atom reader  : 893

  -- Andy

Andy Stewart lazycat.mana...@gmail.com writes:

 Hi all,

 I am proud to announce the release my gtk2hs project : Manatee - The 
 Haskell/Gtk+ Integrated Live
 Environment

 http://hackage.haskell.org/package/manatee

 Screenshots at : http:goo.gl/MkVw
 Code at https://patch-tag.com/r/AndyStewart/ beginning with manatee-*

 Manatee is Haskell integrated environment written in Haskell.

 The goal of the Manatee project is to provide a fast, safe and flexible
 integrated environment for haskell hacking.

 You can consider it is new environment mix Gnome and Emacs. 
 Like Gnome to provide friendly graphics interface and work efficient like 
 Emacs.

 Manatee use multi-processes framework, any sub-module running in separate 
 process to protected core
 won't crash. So it
 minimize your losses when some unexpected exception throw in extension.

 Now i have implement below sub-modules in Manatee:

 Editor
 Webkit Browser
 File Manager
 Image Viewer
 IRC Client
 Multimedia Player
 PDF Viewer
 Process Manager
 RSS/Atom reader  
 
From some friends feedback, manatee can't work in XMonad, i will fix it soon. 
 You can play it in Gnome. Enjoy! :)

 Below are steps to build Manatee:

 1) Install C library: In Debian use below command:

  sudo aptitude install libgtksourceview2.0-dev libgconf2-dev libwebkit-dev 
 libcurl4-openssl-dev
 libgtkimageview-dev libpoppler-glib-dev poppler-data libtagc0-dev -y

 2) Install Gtk2hs:

  cabal install gtk2hs-buildtools gtk

 And make sure HOME.cabalbin/ in your PATH.

 3) Install Manatee:

  cabal install manatee-core manatee-anything manatee-browser manatee-editor 
 manatee-filemanager
 manatee-imageviewer manatee-ircclient manatee-mplayer manatee-pdfviewer 
 manatee-processmanager
 manatee-reader manatee
  
 That's all, then type command manatee to play it! :)

 manatee-core manatee-anything manatee are core packages, must be
 install, other extension package you can choose you want.

 Example, if you not install manatee-imageviewer, when you open Image
 file, manatee will call default image-viewer in your system instead.

 Manatee will show you search interface when you startup it.
 You can type some filepath or url to open it, 
 example, you can type Haskell file to open in editor, 
 and type url to open in browser.

 Below are quick play keys:

 F2 == startProcessManager
 F3 == startFeedReader
 F4 == startFileManager
 F5 == startBrowser
 F6 == loginIrcDefaultChannel
 F7 == startIrc

 Manatee project still in early develop stage, just core framework
 finish, many details still not perfect.

 But i think it's good start to build Real-World application in Haskell.

 Below are high task in my TODO list:

 Perfect current sub-module: 
   IDE features, code completion
   browser JavaScript framework
   graphics custom system
   etc.
   
 Terminal emulator: 
   support MVC design, not like VTE widget
   
 Mail-client
 
 BT-Client
 
 Proxy bridge: 
   to build uniform proxy interface to fighting GFW!!!
   
 Jabbar client:
   video support etc.
 
 Spell checker
 
 CHM viewer
 
 DVI viewer
 
 LaTex editor
 
 PS viewer
 
 Multi-thread download manager
 
 Org-Mode : http://orgmode.org/
 
 Twitter client
 
 Network toolkit:
   sniffer etc.
   
 Multi-Language translater 
   offline support
   
 Too many ideas lying in my TODO list
 
 Any suggestion and contribution are welcome! :)

   -- Andy

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


Re: [Haskell-cafe] Re: Manatee - The Haskell/Gtk+ Integrated Live Environment first version release!

2010-11-11 Thread David Leimbach
Wow!

Is this just for Linux or is anyone able to run it on Mac OS X?

Dave

On Thu, Nov 11, 2010 at 7:51 PM, Andy Stewart lazycat.mana...@gmail.comwrote:

 My project want to provide a fact:

 Haskell not just can do GUI environment, and can do better!

 Gtk2hs + Haskell Threads is awesome!

 Below is source code lines of Manatee:

   All  : 21651

   Core and toolkit : 7047
   Daemon and Window Manager: 3656
   Multi-Threads input framework: 2537
   Browser  : 488
   Editor   : 813
   File manager : 774
   Image viewer : 565
   IRC client   : 2212
   Multimedia player: 1358
   PDF viewer   : 457
   Process Manager  : 761
   RSS/Atom reader  : 893

  -- Andy

 Andy Stewart lazycat.mana...@gmail.com writes:

  Hi all,
 
  I am proud to announce the release my gtk2hs project : Manatee - The
 Haskell/Gtk+ Integrated Live
  Environment
 
  http://hackage.haskell.org/package/manatee
 
  Screenshots at : http:goo.gl/MkVw
  Code at https://patch-tag.com/r/AndyStewart/ beginning with manatee-*
 
  Manatee is Haskell integrated environment written in Haskell.
 
  The goal of the Manatee project is to provide a fast, safe and flexible
  integrated environment for haskell hacking.
 
  You can consider it is new environment mix Gnome and Emacs.
  Like Gnome to provide friendly graphics interface and work efficient like
 Emacs.
 
  Manatee use multi-processes framework, any sub-module running in separate
 process to protected core
  won't crash. So it
  minimize your losses when some unexpected exception throw in extension.
 
  Now i have implement below sub-modules in Manatee:
 
  Editor
  Webkit Browser
  File Manager
  Image Viewer
  IRC Client
  Multimedia Player
  PDF Viewer
  Process Manager
  RSS/Atom reader
 
 From some friends feedback, manatee can't work in XMonad, i will fix it
 soon.
  You can play it in Gnome. Enjoy! :)
 
  Below are steps to build Manatee:
 
  1) Install C library: In Debian use below command:
 
   sudo aptitude install libgtksourceview2.0-dev libgconf2-dev
 libwebkit-dev libcurl4-openssl-dev
  libgtkimageview-dev libpoppler-glib-dev poppler-data libtagc0-dev -y
 
  2) Install Gtk2hs:
 
   cabal install gtk2hs-buildtools gtk
 
  And make sure HOME.cabalbin/ in your PATH.
 
  3) Install Manatee:
 
   cabal install manatee-core manatee-anything manatee-browser
 manatee-editor manatee-filemanager
  manatee-imageviewer manatee-ircclient manatee-mplayer manatee-pdfviewer
 manatee-processmanager
  manatee-reader manatee
 
  That's all, then type command manatee to play it! :)
 
  manatee-core manatee-anything manatee are core packages, must be
  install, other extension package you can choose you want.
 
  Example, if you not install manatee-imageviewer, when you open Image
  file, manatee will call default image-viewer in your system instead.
 
  Manatee will show you search interface when you startup it.
  You can type some filepath or url to open it,
  example, you can type Haskell file to open in editor,
  and type url to open in browser.
 
  Below are quick play keys:
 
  F2 == startProcessManager
  F3 == startFeedReader
  F4 == startFileManager
  F5 == startBrowser
  F6 == loginIrcDefaultChannel
  F7 == startIrc
 
  Manatee project still in early develop stage, just core framework
  finish, many details still not perfect.
 
  But i think it's good start to build Real-World application in Haskell.
 
  Below are high task in my TODO list:
 
  Perfect current sub-module:
IDE features, code completion
browser JavaScript framework
graphics custom system
etc.
 
  Terminal emulator:
support MVC design, not like VTE widget
 
  Mail-client
 
  BT-Client
 
  Proxy bridge:
to build uniform proxy interface to fighting GFW!!!
 
  Jabbar client:
video support etc.
 
  Spell checker
 
  CHM viewer
 
  DVI viewer
 
  LaTex editor
 
  PS viewer
 
  Multi-thread download manager
 
  Org-Mode : http://orgmode.org/
 
  Twitter client
 
  Network toolkit:
sniffer etc.
 
  Multi-Language translater
offline support
 
  Too many ideas lying in my TODO list
 
  Any suggestion and contribution are welcome! :)
 
-- Andy

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

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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread wren ng thornton

On 11/11/10 8:54 PM, Richard O'Keefe wrote:

I remind readers once again that in SML record selectors *don't* clash with
names of functions.  I am not concerned here to argue either for or against
SML-style records and their selectors, only to point out that wanting
*record fields* whose significance depends on the record they select from
is *NOT* the same thing as TDNR in principle, so that arguments for that
don't even come close to being arguments for TDNR as such.


My sentiments exactly. If people were to argue for SML-esque record 
selectors and the row-polymorphism that goes with them, I might be 
willing to throw in with that cause (or I might not, depending on the 
alternatives). However, that proposal is *very* different than the TDNR 
proposal. With row-polymorphism there's a decent chance of not shooting 
yourself in the face; there's a well-understood type theory that goes 
along with it, and it's been used in practice in other languages with a 
type system fairly similar to Haskell's. With TDNR, however, the 
situation is quite different.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Sebastian Fischer

On Nov 12, 2010, at 5:43 AM, Richard O'Keefe wrote:


A saucepan whose handle keeps falling off is defective,


I do not see TDNR as unambiguously defective as a loose saucepan handle.


The amount of time spent maintaining a program is much higher
than the amount of time spent creating it initially.  That
means that if you have a tradeoff between ease of writing and
the other virtues of a language, ease of writing *matters* less.


Like you, I think that a tradeoff between readability and writability  
should be made in favour of readability. Unlike you, I am not  
convinced that TDNR trades readability for writability.



Consider the vexed question of repeating all or part of the
record name in the field name.  Yes, this *is* a burden on
the person writing it.  But it is a **help** to the person
reading it.  The same applies to using module prefixes
(possibly abbreviated ones).


Not if the extra information is redundant. Then qualification may even  
impair readability by introducing unnecessary clutter.


I don't think that TDNR threatens readability more than type classes  
already do. Not only is Buffalo buffalo Baffalo buffalo buffalo  
buffalo Buffalo buffalo a grammatically valid sentence in the English  
language, also `fmap fmap fmap fmap fmap fmap fmap fmap` is a type  
correct expression in the Haskell programming language. It can already  
be hard today to distinguish occurrences of overloaded functions. TDNR  
does not add much to this, I think.


One difference is that there is a unifying type with a type class  
constraint for all implementations of functions with the same name  
when using type classes but not when using TDNR. Does this make code  
that is using TDNR less readable than code that is using type classes?


As others have pointed out, type classes are insufficient for  
overloading record labels because they do not cover record updates.


How can we add a special kind of overloading for record labels that  
also works for updates? Maybe like this:


rename :: ((name :: String) @ a) = a - a
rename newName someRecord = someRecord { name = newName }

This probably falls under the category of improved record systems. How  
difficult would it be to implement this? Can it be implemented by  
desugaring without substantial extensions to the type system?


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


Re: [Haskell-cafe] Re: Manatee - The Haskell/Gtk+ Integrated Live Environment first version release!

2010-11-11 Thread Andy Stewart
David Leimbach leim...@gmail.com writes:

 Wow!

 Is this just for Linux or is anyone able to run it on Mac OS X?
I don't know whether can work on Mac.

I design it for Linux.

  -- Andy


 Dave

 On Thu, Nov 11, 2010 at 7:51 PM, Andy Stewart lazycat.mana...@gmail.com 
 wrote:

 My project want to provide a fact:

 Haskell not just can do GUI environment, and can do better!

 Gtk2hs + Haskell Threads is awesome!

 Below is source code lines of Manatee:

   All                          : 21651

   Core and toolkit             : 7047
   Daemon and Window Manager    : 3656
   Multi-Threads input framework: 2537
   Browser                      : 488
   Editor                       : 813
   File manager                 : 774
   Image viewer                 : 565
   IRC client                   : 2212
   Multimedia player            : 1358
   PDF viewer                   : 457
   Process Manager              : 761
   RSS/Atom reader              : 893

  -- Andy

 Andy Stewart lazycat.mana...@gmail.com writes:

  Hi all,
 
  I am proud to announce the release my gtk2hs project : Manatee - The 
 Haskell/Gtk+ Integrated
 Live
  Environment
 
  http://hackage.haskell.org/package/manatee
 
  Screenshots at : http:goo.gl/MkVw
  Code at https://patch-tag.com/r/AndyStewart/ beginning with manatee-*
 
  Manatee is Haskell integrated environment written in Haskell.
 
  The goal of the Manatee project is to provide a fast, safe and flexible
  integrated environment for haskell hacking.
 
  You can consider it is new environment mix Gnome and Emacs.
  Like Gnome to provide friendly graphics interface and work efficient 
 like Emacs.
 
  Manatee use multi-processes framework, any sub-module running in 
 separate process to protected
 core
  won't crash. So it
  minimize your losses when some unexpected exception throw in extension.
 
  Now i have implement below sub-modules in Manatee:
 
      Editor
      Webkit Browser
      File Manager
      Image Viewer
      IRC Client
      Multimedia Player
      PDF Viewer
      Process Manager
      RSS/Atom reader
 
 From some friends feedback, manatee can't work in XMonad, i will fix it 
 soon.
  You can play it in Gnome. Enjoy! :)
 
  Below are steps to build Manatee:
 
  1) Install C library: In Debian use below command:
 
   sudo aptitude install libgtksourceview2.0-dev libgconf2-dev 
 libwebkit-dev
 libcurl4-openssl-dev
  libgtkimageview-dev libpoppler-glib-dev poppler-data libtagc0-dev -y
 
  2) Install Gtk2hs:
 
   cabal install gtk2hs-buildtools gtk
 
  And make sure HOME.cabalbin/ in your PATH.
 
  3) Install Manatee:
 
   cabal install manatee-core manatee-anything manatee-browser 
 manatee-editor
 manatee-filemanager
  manatee-imageviewer manatee-ircclient manatee-mplayer manatee-pdfviewer 
 manatee-processmanager
  manatee-reader manatee
 
  That's all, then type command manatee to play it! :)
 
  manatee-core manatee-anything manatee are core packages, must be
  install, other extension package you can choose you want.
 
  Example, if you not install manatee-imageviewer, when you open Image
  file, manatee will call default image-viewer in your system instead.
 
  Manatee will show you search interface when you startup it.
  You can type some filepath or url to open it,
  example, you can type Haskell file to open in editor,
  and type url to open in browser.
 
  Below are quick play keys:
 
      F2     == startProcessManager
      F3     == startFeedReader
      F4     == startFileManager
      F5     == startBrowser
      F6     == loginIrcDefaultChannel
      F7     == startIrc
 
  Manatee project still in early develop stage, just core framework
  finish, many details still not perfect.
 
  But i think it's good start to build Real-World application in Haskell.
 
  Below are high task in my TODO list:
 
      Perfect current sub-module:
        IDE features, code completion
        browser JavaScript framework
        graphics custom system
        etc.
 
      Terminal emulator:
        support MVC design, not like VTE widget
 
      Mail-client
 
      BT-Client
 
      Proxy bridge:
        to build uniform proxy interface to fighting GFW!!!
 
      Jabbar client:
        video support etc.
 
      Spell checker
 
      CHM viewer
 
      DVI viewer
 
      LaTex editor
 
      PS viewer
 
      Multi-thread download manager
 
      Org-Mode : http://orgmode.org/
 
      Twitter client

Re: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 10:00 PM, John Lask jvl...@hotmail.com wrote:
 On Thu, Nov 11, 2010 at 8:16 PM, John Laskjvl...@hotmail.com  wrote:

 consider length ...

 I have records with the attribute length, length can be given as an Int,
 Double, Float or maybe as a constructed type Length, length's use as a
 record selector would also clash with List.length. All these have the
 same
 denotation.

 should I then seporate into int_length, float_length, or use rec1_length,
 rec2_length etc etc...

 class Lengthy a where
   type LengthType a
   length :: a -  LengthType a

 This extends easily to lenses if you want setters.



 to make use of the class Lengthy I still need to define record selectors
 with different names, which is exactly the point I am making...

 ie

 data Record = RecLen { rec_length :: ... }

 instance Lengthy Record where
  length = rec_length

Or,

data Record = RecLen Int ...

instance Lengthy Record where
  type LengthType Record = Int
  length (Record l _ _ ...) = l

But yes, this is irritating boilerplate. A more-powerful record system
is clearly preferable.

 The point is that languages are often constructed with a purpose in
 mind, at which they tend to be particularly good. Haskell has
 traditionally been a test bed for type system innovation, which is why
 we all like it so much.

Which is why I'm opposed to TDNR.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Mark Lentczner
My tuppence:

I feel like the main impetus for TDNR is the awkwardness of records, especially 
when there are multiple record types within a module (as there often are). Now, 
if one proceeds as one has to today, then one may find:

data Foo = Foo { fooName :: String, fooValue :: Double }
data Bar = Bar { barName :: String, barValue :: [String], barSubbars :: [Bar] }

Let us, for sake of argument, ignore that perhaps fooName and barName represent 
the same semantic concept and these should all somehow be refactored. 

I suspect that the prime annoyance, the thing that makes us yearn for our old 
C/C++/Java/Python ways, is the tediousness of having to prefix all the field 
names with foo or bar. Especially when the data type name is large, one 
ends up having to invent coding conventions one doesn't want to:

data ExecutionTraceSummary = ExecutionTraceSummary { etsStart :: Time; ... }

So imagine that we take the tedium out of typing all those prefixes by 
anointing some initial character, say the apostrophe, as a sort of name mangler:

data Foo = Foo { 'name :: String, 'value :: Double }
data Bar = Bar { 'name :: String, 'value :: [String], 'subbars :: [bar] }
data ExecutionTraceSummary = ExecutionTraceSummary { 'start :: Time, ... }

Now, to use them, perhaps we have to explicitly write the full form:

showFoo :: Foo - String
showFoo f = Foo'name f ++ ( ++ show (Foo'value f) ++ )

We could allow a form of shortened local reference by allowing the full form to 
flow through type declarations:

type ETS = ExecutionTraceSummary

logExecutionTraceSummary :: ExecutionTraceSummary - IO ()
logExecutionTraceSummary s = do
putStr $ ETS'start s

Mind you, I realize that apostrophe may not work here, and details haven't been 
worked out.

[...that was the first pence, here comes the second...]

If you buy any of that, then one could allow, in the manner pointed out by some 
(though in particular I'm thinking of David Menendez's example), that this 
construction could imply a type class and associated type. That is, the first 
appearance of 'name in a record implies this:

class C'name a where
  type R'name a :: *
  'name :: a - R'name a

and for each appearance of 'name :: X as a field of Foo:

instance C'name Foo where
  type R'name Foo = X
  'name = Foo'name

(Here, C and R are some unwritable prefixes used by the compiler. It 
remains to be seen if these should be module scoped or program global.)

So, in the case (repeated from above):

data Foo = Foo { 'name :: String, 'value :: Double }
data Bar = Bar { 'name :: String, 'value :: [String], 'subbars :: [Bar] }

We get auto generated:

class C'name a where
  type R'name a :: *
  'name :: a - R'name a

class C'value a where
  type R'value a :: *
  'value :: a - R'value a

class C'subbars a where
  type R'subbars a :: *
  'subbars :: a - R'subbars a

instance C'name Foo where
  type R'name Foo = String
  'name = Foo'name

instance C'name Bar where
  type R'name Bar = String
  'name = Bar'name

instance C'value Foo where
  type R'value Foo = Double
  'value = Foo'value

instance C'value Bar where
  type R'value Bar = [String]
  'value = Bar'value

instance C'subbars Bar where
  type R'subbars Bar = [Bar]
  'subbars = Bar'subbars

*Now* one can write:

showFoo :: Foo - String
showFoo f = 'name f ++ ( ++ show ('value f) ++ )

nameBoth :: Foo - Bar - String
nameBoth f b = 'name f ++   ++ 'name b

None of this requires any more type machinery than already exists with 
TypeFamilies. It perhaps suffer some of the prior objections to implying 
semantic equivalence (in say the 'value fields) where none exists. But, it is 
limited in scope to fields, and only when one uses the special naming sigil 
(apostrophe here).

Of course, this approach would meld nicely with any better record/label system. 
 For starters:

class C'name a where
  type R'name a :: *
  'name :: a - R'name a
  ''name :: R'name a - a - a

instance C'name Foo where
  type R'name Foo = String
  'name = Foo'name
  ''name = \v x - x { Foo'name = v }


There now -- I feel like TNDR is placating the muscle memory in our fingers 
that wants to type f.name ... and I hope we find a solution to replacing the 
tedium of so many fooName fields, and perhaps solve the record update 
ugliness as well!

- Mark


Mark Lentczner
http://www.ozonehouse.com/mark/
IRC: mtnviewmark



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


Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Ben Lippmeier

On 12/11/2010, at 2:26 AM, Malcolm Wallace wrote:

 The point is that refusing something you can have now (though
 of course it's an open question whether TDNR is something we can have
 now) out of fear that it'll prevent you getting something better
 later is speculative and often backfires.
 
 I think we are very far from having TDNR now.  It is really quite 
 complicated to interleave name resolution with type checking in any compiler. 
  So far, we have a design, that's all, no implementation.  We also have 
 (several) designs for proper record systems.

Disciple has TDNR, and there is an implementation in DDC. It is a bit 
complicated, mainly because you can't determine the call graph of the program 
before starting inference. In ML style inference you're supposed to 
let-generalise groups of recursive bindings together, but for TDNR you can only 
determine what is recursive once you've resolved the names (which depends on 
the types, which you need to infer).

The algorithm is described starting at page 168 in my thesis here: 
http://www.cse.unsw.edu.au/~benl/papers/thesis/lippmeier-impure-world.pdf

Disciple doesn't have type functions or associated types though. I think it'd 
be nicer for GHC if we could leverage some of the other extensions, as 
suggested in Mark Lentczner's post.

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


  1   2   >