Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-19 Thread Lennart Augustsson

Greg Woodhouse wrote:

Well...think about this way. The function

f i = [1, 1 ..]!!i

is just a constant function expressed in a complicated way. Can I
algoritmically determine that f is a constant function?


In general, no.  Even in this case I'm pretty sure you'll need induction
somewhere.



I suppose the big picture is whether I can embed the theory of finite
lists in the theory of infinite lists, preferably in such a way that
the isomorphism of the theory finite lists with the embedded
subtheory is immediately obvious.


I don't think you'll find such an embedding that is satisfying, i.e.,
that gives you much insight.  Reasoning about total functions on
finite lists can be done with sets (and set theory), reasoning about
partial functions and/or lazy lists needs domains.
An example
reverse . reverse = id
is true for all finite lists, but not true for any infinite lists
(nor any partial lists).
(What remains true for all lists is that
reverse . reverse = id
where = is the usual domain ordering.)

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


Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-19 Thread Gracjan Polak
2005/11/19, Benjamin Franksen

 [You should read some of his papers, for instance the most unreliable
 techique in the world to compute pi. I was ROTFL when I saw the title
 and reading it was an eye-opener and fun too.]


Care to post a link? Seems interesting, but unknown to google :)

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


Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-19 Thread Jacob Nelson


http://users.info.unicaen.fr/~karczma/arpap/

On Sat, 19 Nov 2005, Gracjan Polak wrote:


2005/11/19, Benjamin Franksen


[You should read some of his papers, for instance the most unreliable
techique in the world to compute pi. I was ROTFL when I saw the title
and reading it was an eye-opener and fun too.]



Care to post a link? Seems interesting, but unknown to google :)

--
Gracjan
___
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[2]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-19 Thread Bulat Ziganshin
Hello John,

Saturday, November 19, 2005, 2:25:47 AM, you wrote:

JM  grep -o ' [-+.*/[EMAIL PROTECTED] ' GenUtil.hs | sort | uniq -c | sort -n
JM  30  .

JM one of the most common operators.

especially in comments ;)  add the following filter to strip them:

import System.Environment

main = interact (noStream.(unlines.map noEnd.lines))

noStream ('{':'-':xs) = noInStream xs
noStream (c:xs)   = c:noStream xs
noStream= 

noInStream ('-':'}':xs) = noStream xs
noInStream (_:xs)   = noInStream xs
noInStream= 

noEnd ('-':'-':xs) = 
noEnd (c:xs)   = c:noEnd xs
noEnd= 


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[4]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-19 Thread Bulat Ziganshin
Hello Sebastian,

Friday, November 18, 2005, 6:35:13 PM, you wrote:

 groupLen mapper combinator tester  =  length . takeWhile tester . scanl1 
 combinator . map mapper

SS This is a border line example of what I would consider being abuse of
SS the (.) operator.
SS First of all, that line is 96 characters long. A bit much if you ask
SS me.

my 15 CRT holds entire 100, even 102 chars in line and i don't want
to lose even one of them! :)  especially when comment to this function
occupies another 7 lines :)

SS groupLen' mapper combinator tester xs
SS= length $ takeWhile tester $ scanl1 combinator $ map mapper xs

SS The difference is minimal, if anything I think that writing out the
SS list argument is actually clearer in this case (although there are
SS cases when you want to work on functions, and writing out the
SS parameters makes things less clear).

... including this one. i'm work with functions, when possible: build
them from values and other functions, hold them in datastructures,
pass and return them to/from functions. if function definition can be
written w/o part of its arguments, i do it in most cases

moreover, in some cases this leads to dramatic changes in speed. see:

-- |Test whether `filepath` meet one of filemasks `filespecs`
match_filespecs filespecs {-filepath-}  =  any_function (map match_FP filespecs)

function `match_FP` thranslates regexps to functions checking that
given filename match this regular expression:

match_FP :: RegExp - (String-Bool)

when definition of `match_filespecs` contained `filepath`, this
testing works very slow for large filelists. imho, for each filename
list of filespecs was retranslated to testing functions, each
function applied to filename and then results was combined by
`any_function`. it's a pity, especially cosidering that most common
case for regexps list was just [*], which must render to
(const True) testing function. so, in this case it was absolutely
necessary to write all this regexp machinery in point-free style, so that
it returns data-independent functions, which then optimized
(reduced) by Haskell evaluator before applying them to filenames

on the Wiki page RunTimeCompilation there is another examples of
building functions from datastructures before applying to input data

it is very possible that this point-free `groupLen` definition,
together with other point-free definitions, makes filelist processing
in my program faster - i just dont't checked it

SS I'm not saying it's impossible to make good use of (.), I'm saying
SS that it's not crucial enough to warrant giving it the dot, which in my
SS opinion is one of the best symbols (and I'd hand it over to record
SS selection any day of the week!).
SS I'm also saying that people tend to abuse the (.) operator when they
SS start out because they think that less verbose == better, whereas
SS most people, in my experience, tend to stop using (.) for all but the
SS simplest cases (such as filte (not . null)) after a while to promote
SS readability. I prefer adding a few lines with named sub-expressions to
SS make things clearer.

readability is not some constant factor for all people. it depends
on your experience. for you it is natural to work with data values.
for me, it's the same natural to work with function values, partially
apply and combine them. and in those definitions the variables
containing actual data is just looks as garbage for me

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread David Roundy
On Fri, Nov 18, 2005 at 05:42:41PM +0300, Bulat Ziganshin wrote:
   can anyone write at least the list of record proposals for Haskell?
 or, even better, comment about pros and contras for each proposal?

I'd benefit from just a list of problems that the record proposals want to
solve.

I can list the issues that seem important to me, but I am sure my list
isn't complete.  Also note that some of these goals may be mutually
contradictory, but agreeing on the problems might help in agreeing on the
solutions.

A getter is a way to get a field out of a record, a setter is a way to
update a field in a record.  These may be either pattern-matching syntaxes,
functions or some other odd syntax.

Here's the quick summary, expanded below:

1. The field namespace issue.
2. Multi-constructor getters, ideally as a function.
3. Safe getters for multi-constructor data types.
4. Getters for multiple data types with a common field.
5. Setters as functions.
6. Anonymous records.
7. Unordered records.

2. Multi-constructor getters.

1. Field namespace issue:

Field names should not need to be globally unique.  In Haskell 98, they
share the function namespace, and must be unique.  We either need to make
them *not* share the function namespace (which means no getters as
functions), or somehow stick the field labels into classes.

2. Multi-constructor getters, ideally as a function:

An accessor ought to be able to access an identically-named field from
multiple constructors of a given data type:

 data FooBar = Foo { name :: String } | Bar { name :: String }

However we access name, we should be able to access it from either
constructor easily (as Haskell 98 does, and we'd like to keep this).

3. Safe getters for multi-constructor data types.

Getters ought to be either safe or explicitly unsafe when only certain
constructors of a data type have a given field (this is my pet peeve):

 data FooBar = Foo { foo :: String } | Bar { bar :: String }

This shouldn't automatically generate a function of type

 foo :: FooBar - String

which will fail when given a FooBar of the Bar constructor.  We can always
write this function ourselves if we so desire.

4. Getters for multiple data types with a common field.

This basically comes down to deriving a class for each named field, or
something equivalent to it, as far as I can tell.  This also works with the
namespace issue, since if we are going to define getters and setters as
functions, we either need unique field labels or we need one class per
field label--or something equivalent to a class for each field label.

5. Setters as functions.

It would be nice to have a setter function such as (but with perhaps a
better name)

 set_foo :: String - Foo - Foo

be automatically derived from

 data Foo = Foo { foo :: String }

in the same way that in Haskell 98 foo :: Foo - String is implicitely
derived.

Note that this opens up issues of safety when you've got multiple
constructors, and questions of how to handle setting of a field that isn't
in a particular datum.

6. Anonymous records.

This idea is from Simon PJ's proposal, which is that we could have
anonymous records which are basically tuples on steroids.  Strikes me as a
good idea, but requires that we address the namespace question, that is,
whether field labels share a namespace with functions.  In Simon's
proposal, they don't.

This is almost a proposal rather than an issue, but I think that it's a
worthwhile idea in its own right.

7. Unordered records.

I would like to have support for unordered records, which couldn't be
matched or constructed by field order, so I could (safely) reorder the
fields in a record.  This is really an orthogonal issue to pretty much
everything else.


Argh.  When I think about records too long I get dizzy.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread Wolfgang Jeltsch
Am Samstag, 19. November 2005 14:57 schrieb David Roundy:
 [...]

 2. Multi-constructor getters, ideally as a function:

 An accessor ought to be able to access an identically-named field from

 multiple constructors of a given data type:
  data FooBar = Foo { name :: String } | Bar { name :: String }

 However we access name, we should be able to access it from either
 constructor easily (as Haskell 98 does, and we'd like to keep this).

Let's take a concrete example.  Say, I have a type Address which is declared 
as follows:

data Address = OrdinaryAddr {
name :: String,
street :: String,
number :: Int,
city :: String,
postalCode :: Int
} | POBoxAddr {
name :: String,
poBox :: Int,
city :: String,
postalCode :: Int
}

In this example, it would be really good if there was a getter function for 
extracting the name out of an ordinary address as well as an PO box address.  
But in my opinion, the above declaration is not very nice and one should 
write the following instead:

data Address = Address {
name :: String,
destination :: Destination,
city :: String,
postalCode :: Int
}

data Destination = OrdinaryDest {
street :: String,
number :: Int
} | POBoxDest {
poBox :: Int
}

And with this declaration we wouldn't need getter functions which are able to 
access identically-named fields from different data constructors of the same 
type.  So I wonder if this feature is really sensible.

 [...]

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


Re: [Haskell-cafe] Two questions: lazy evaluation and Church-Rosser

2005-11-19 Thread Ben Rudiak-Gould

Gregory Woodhouse wrote:

I've been trying to do some background reading on lambda calculus, and
have found discussions of strict evaluation strategies (call-by-value and
call-by-name) but have yet to find an appropriate framework for modeling
lazy evaluation


Just wanted to point out that call-by-name is non-strict. Lazy
evaluation is basically just call-by-name with extra sharing; if you only
care about semantics and not time/space behavior, it's the same as call-by-name.


(much less infinite lists and comprehensions).


In a lazy or call-by-name operational semantics, you never get infinite 
lists, just lists with unevaluated tails which get unwrapped as needed.


List comprehensions in Haskell are syntactic sugar. The Haskell 98 report 
explains how to transform them away.


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


Re: [Haskell-cafe] Records

2005-11-19 Thread Antti-Juhani Kaijanaho
Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]
 Syntax that changes depending on spacing is my number
 one gripe with the Haskell syntax

I've generally considered that one of the good ideas in most current
languages (it's not specific to Haskell). ISTR there was a Basic dialect
where
  IFX=0THENX=X+1
and
  IF X = 0 THEN X = X + 1
meant the same thing. If that dialect had allowed multi-character
variable names (which I think it didn't), ANDY would have been parsed as
AND Y instead of the simple variable ANDY.

Hence, spacing being significant is not Haskell-specific and is
generally a good thing.

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


Re: [Haskell-cafe] Records

2005-11-19 Thread Ketil Malde

Antti-Juhani Kaijanaho wrote:


Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]
 


Syntax that changes depending on spacing is my number
one gripe with the Haskell syntax
   



I've generally considered that one of the good ideas in most current
languages (it's not specific to Haskell). ISTR there was a Basic dialect
where
 IFX=0THENX=X+1
and
 IF X = 0 THEN X = X + 1
meant the same thing. 
 

My point is that e.g. currently foo? bar, foo ?bar and foo ? bar 
have (at least two) different meanings.   Hierarchical naming collides 
with function composition (admittedly only rarely in practice).  
Template haskell collides with list comprehensions.


Do you really think that is such a great idea?

-k

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


Re[2]: [Haskell-cafe] records proposals list

2005-11-19 Thread Bulat Ziganshin
Hello David,

Saturday, November 19, 2005, 4:57:09 PM, you wrote:

DR I'd benefit from just a list of problems that the record proposals want to
DR solve.

DR 1. The field namespace issue.
DR 2. Multi-constructor getters, ideally as a function.
DR 3. Safe getters for multi-constructor data types.
DR 4. Getters for multiple data types with a common field.
DR 5. Setters as functions.
DR 6. Anonymous records.
DR 7. Unordered records.

DR Argh.  When I think about records too long I get dizzy.

really you are wrote solutions for all these problems (except 6), and
it's just an additional syntax sugar (like the fields itself). for
beginning, we must split this list to two parts: belonging to static
(like H98) and dynamic (anonymous) records. items in your list (except
6) belongs to static ones. dynamic records is whole different beast
and it's really hard to master, so the first question will be:

are we wanna to have in Haskell only static records, only dynamic
records or both?

as i see, GHC team want to implement such proposal, which will resolve
both issues. and wainting (waiting+wanting:) for such solution, they
are don't implement suggestions which address only static records
problems

but the dynamic records is too complex thing: it may be syntactically
incompatible with H98, it may require changes to GHC internals and so
on, so they are delayed until better times


besides this all, i want to add one more item to your list:

7. OOP-like fields inheritance:

data Coord = { x,y :: Double }
data Point : Coord = { c :: Color }

of course this is just another sort of syntax sugar once we start
using classes to define getter/setter functions


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] re-definition of '.'

2005-11-19 Thread Bulat Ziganshin
Hello haskell-cafe,

if we will define . as:

a.b = b a

then we can use . for

1) field selection

2) sequential functions application in OOP style:

[1..100] .map (2*) .sum

3) qualified identifiers - if we treat module name as the record
containing all its exported functions:

import M (f,g,h) defines record M with fields f, g and h



The only problem is priority of this operation - for field selection
it need to be greater than for application:

infixl 11 .

while for OOP-styled operations with arguments - its priority must be
minimal. one possible solution is rather revolitionary: raise priority
of . if there is no spaces around it, so the following will be
interpreted precisely as we want:

record.field .List.map (2*) .sum


-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] re-definition of '.'

2005-11-19 Thread Cale Gibbard
We don't need another ($) though, and writing things backwards looks funny. :)

 - Cale

On 19/11/05, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 Hello haskell-cafe,

 if we will define . as:

 a.b = b a

 then we can use . for

 1) field selection

 2) sequential functions application in OOP style:

 [1..100] .map (2*) .sum

 3) qualified identifiers - if we treat module name as the record
 containing all its exported functions:

 import M (f,g,h) defines record M with fields f, g and h



 The only problem is priority of this operation - for field selection
 it need to be greater than for application:

 infixl 11 .

 while for OOP-styled operations with arguments - its priority must be
 minimal. one possible solution is rather revolitionary: raise priority
 of . if there is no spaces around it, so the following will be
 interpreted precisely as we want:

 record.field .List.map (2*) .sum


 --
 Best regards,
  Bulat  mailto:[EMAIL PROTECTED]



 ___
 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] How to use notFollowedBy function in Parsec

2005-11-19 Thread Sara Kenedy
Dear all,
Using Parsec, I want to represent a string (of anyToken) not ended
with symbol semi (;). I use the command notFollowedby as follows:

module Parser where

import Parsec

import qualified ParsecToken as P

import ParsecLanguage


langDef::LanguageDef ()

langDef = emptyDef

{reservedOpNames = []}
lexer::P.TokenParser()

lexer = P.makeTokenParser langDef

semi= P.semi lexer

str1 :: Parser String
str1 = do {str - many anyToken; notFollowedBy semi; return str}

However, when I compile, there is an error.

ERROR Test.hs:17 - Type error in application
*** Expression : notFollowedBy semi
*** Term   : semi
*** Type   : GenParser Char () String
*** Does not match : GenParser [Char] () [Char]


I do not know how to fix it. Help me. Thanks for your time.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread Dimitry Golubovsky

David Roundy wrote:



4. Getters for multiple data types with a common field.



[skip]



4. Getters for multiple data types with a common field.

This basically comes down to deriving a class for each named field, or
something equivalent to it, as far as I can tell.  This also works with the
namespace issue, since if we are going to define getters and setters as
functions, we either need unique field labels or we need one class per
field label--or something equivalent to a class for each field label.


This is a problem similar to one I had to solve for HSFFIG to design a 
syntax to access fields of C structures (where different structures may 
have fields of same name but of different types).


I ended up with a multiparameter class parameterized by a C structure 
name, field name, field type, and for each occurrence of these in C 
header file I autogenerated an instance of this class.


See

http://hsffig.sourceforge.net/repos/hsffig-1.0/_darcs/current/HSFFIG/FieldAccess.hs

for the class itself, and a typical instance (autogenerated of course) 
looked like


instance HSFFIG.FieldAccess.FieldAccess S_362 ((CUChar)) V_byteOrder where
  z -- V_byteOrder = ((\hsc_ptr - peekByteOff hsc_ptr 0)) z
{-# LINE 5700 XPROTO_H.hsc #-}
  (z, V_byteOrder) -- v = ((\hsc_ptr - pokeByteOff hsc_ptr 0)) z v
{-# LINE 5701 XPROTO_H.hsc #-}

for a field `byteOrder' of type `unsigned char'.

This might work in general for what is proposed in the item 4 quoted 
above. A class with 3 parameters will be needed, and perhaps some 
syntactic sugar to autogenerate it and its instances. The only downside 
is GHC needs too much memory to compile all this: I had to add a 
splitter utility to HSFFIG otherwise GHC failed short of memory on even 
several tens of C structures.


Dimitry Golubovsky
Middletown, CT

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


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-19 Thread Andrew Pimlott
On Sat, Nov 19, 2005 at 06:43:48PM -0500, Sara Kenedy wrote:
 str1 :: Parser String
 str1 = do {str - many anyToken; notFollowedBy semi; return str}
 
 However, when I compile, there is an error.
 
 ERROR Test.hs:17 - Type error in application
 *** Expression : notFollowedBy semi
 *** Term   : semi
 *** Type   : GenParser Char () String
 *** Does not match : GenParser [Char] () [Char]

The problem is that notFollowedBy has type

notFollowedBy  :: Show tok = GenParser tok st tok - GenParser tok st ()

ie, the result type of the parser you pass to notFollowedBy has to be
the same as the token type, in this case Char.  (The reason for this
type is obscure.)  But semi has result type String.  You could fix the
type error by returning a dummy Char:

str1 = do {str - many anyToken
  ; notFollowedBy (semi  return undefined)
  ; return str}

I think this will even work; however notFollowedBy is a pretty
squirrelly function.  There was a discussion about it:

http://www.haskell.org/pipermail/haskell/2004-February/013621.html

Here is a version (which came out of that thread) with a nicer type,
that probably also works more reliably (though I won't guarantee it):

notFollowedBy' :: Show a = GenParser tok st a - GenParser tok st ()
notFollowedBy' p  = try $ join $  do  a - try p
  return (unexpected (show a))
  |
  return (return ())

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