
Hello, perhaps i will make a wishlist of topics not dealt in the tutorials. Here is something i miss in each of them: notes at the semantics of data constructors. We read data Pair a b = Pair a b in YetAnotherHaskellTutorial. And that is all ! If we omit "data" here, this would be a silly pleonasm. And no single word about this strange behavior of "data" in every tutorial i read. A similar point: The tutorials teach, that "=" has a similar meaning than "=" in mathematics. But there is a big difference: it is not reflexive. The the right side is the definition of the left. Thus "x=y" has still some kind of temporality, which mathematics doesn't have. Wadler himself describes bunches of lazily computed equations as "dataflows" somewhere. Ok, so much on theory. Here a concrete question: For adapting hws (one of the reasons for me to be here, not many languages have a native web server) to Windows i must work on time. In System.Time i found data ClockTime = TOD Integer Integer 2 questions arise here: Does this define "TOD" (which i do not find elsewhere) together with ClockTime also ? And: Why is this not: data ClockTime Integer Integer = TOD Integer Integer ? Is it just an abbreviation for the first? Or is there a connection to ClockTime as an "abstract data type" (a notion, which would have a subtle different meaning than in OOP - since "instance" is such different thing here). Thanks for your attention, Joost

Hello Joost, Sunday, December 30, 2007, 5:24:59 PM, you wrote:
data ClockTime = TOD Integer Integer
it declares type with name ClockTime (which you may use on type signatures, other type declarations and so on) with one constructor TOD accepting two Integer values. the only way to construct value of this type is to apply TOD to two Integer expressions (believe it or not but this declaration automatically defines TOD as function with the following signature: TOD :: Integer -> Integer -> ClockTime f.e.: seconds2clockTime :: Double -> ClockTime seconds2clockTime s = TOD (floor(s)) (round(s*1e12) the only way to deconstruct values of this type is to use TOD constructor in parser matching, f.e.: clockTime2seconds :: ClockTime -> Double clockTime2seconds (TOD s p) = fromInteger(s) + fromInteger(p)/1e12 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Dec 30, 2007, at 8:24 AM, Joost Behrends wrote:
For adapting hws (one of the reasons for me to be here, not many languages have a native web server) to Windows i must work on time. In System.Time i found
data ClockTime = TOD Integer Integer
2 questions arise here: Does this define "TOD" (which i do not find elsewhere) together with ClockTime also ? And: Why is this not:
data ClockTime Integer Integer = TOD Integer Integer ?
Is it just an abbreviation for the first? Or is there a connection to ClockTime as an "abstract data type" (a notion, which would have a subtle different meaning than in OOP - since "instance" is such different thing here).
You are right that it defines the TOD constructor. As for you second question, I will try to be somewhat formal in my response, so hopefully I don't just throw you off more. The quick answer is that since we already know the parameters on the right side are Integers, we don't need to specify them on the left side. When you define datatypes, you are essentially defining a type-level constructors on the left hand side and (value-level) constructors on the right hand side. Just like normal functions, constructors and type constructors can be parameterized. Let's deviate for a moment from Haskell's notation for data types and approach this from the viewpoint of a dependently typed language (a language in which there is little separating between the type level and the value level). The data type we are defining here is called ClockTime, so its type might be represented as ClockTime :: * , where * represents "Kind," the type of types. For completeness, the sole constructor we define is called TOD and has type TOD :: Integer -> Integer -> ClockTime . Now, let's say we had tried defining ClockTime with parameters as you suggested. ClockTime' :: Integer -> Integer -> * Do you see the problem? In order to use the ClockTime type constructor, we would have to use Integer values. This (1) does not make much sense in a language like Haskell which doesn't have true dependent types, and (2) does not help us in any way with our definition of the TOD constructor. We already know by the definition of TOD that it takes two Integers and returns a ClockTime. If we used this modified definition of ClockTime, we would have to parameterize it to specify TOD, maybe like. TOD' :: Integer -> Integer -> ClockTime' 2 3 (I chose the 2 and 3 arbitrarily, but these exact values have no particular relevance here.) This would not work in Haskell. However, there are cases where you would want to parameterize a type constructor. For example, say we _wanted_ our TOD constructor take two values of arbitrary types. If we want the type level to reflect the types of these parameters, ClockTime must be parameterized. ClockTime'' :: * -> * -> * TOD'' :: a -> b -> ClockTime'' a b In Haskell notation, this would be equivalent to data ClockTime'' a b = TOD'' a b . So, to summarize, the reason that we don't use data ClockTime Integer Integer = TOD Integer Integer is because we don't want to parameterize ClockTime, and even if we did, we could not use Integer values like this to do it because Haskell is not dependently typed. - Jake

Thanks to both fast answers. there remain problems with Jakes mail for me. This:
When you define datatypes, you are essentially defining a type-level constructors on the left hand side and (value-level) constructors on the right hand side.
is very useful for me. "data" defines TWO constructors, ok. And if i want construction on the type level, then the arguments must obviously be type-"valued", means parameters. From this i conclude, that data ClockTime Integer Integer = ... would never make sense, whatever on the right size. The next isn't understandable for me - i have not the slightest conception of dependently typed languages. Then i arrive at
. Now, let's say we had tried defining ClockTime with parameters as you suggested.
ClockTime' :: Integer -> Integer -> *
Do you see the problem? In order to use the ClockTime type constructor, we would have to use Integer values.
Cannot see any problem here - do we NOT want ClockTime to be initialized by two Integers ? Or is this the main reason for introducing "TOD" - to be able to change it without having to make any changes to code using ClockTime ? To repeat myself - am i right understanding, that this needs a differently named data constuctor ? (I cited "abstract type" from the library reference. Not important for me at the moment, what that means in Haskell.) Thanks for your attention, Joost

2007/12/30, Joost Behrends
. Now, let's say we had tried defining ClockTime with parameters as you suggested.
ClockTime' :: Integer -> Integer -> *
Do you see the problem? In order to use the ClockTime type constructor, we would have to use Integer values.
Cannot see any problem here - do we NOT want ClockTime to be initialized by two Integers ? Or is this the main reason for introducing "TOD" - to be able to change it without having to make any changes to code using ClockTime ? To repeat myself - am i right understanding, that this needs a differently named data constuctor ?
We want a value of type ClockTime to be initialized by two Integers, but the type of this value will be ClockTime, not (ClockTime 2 3), its _type_ won't depend on its _content_, ok ? With dependent types, you can have type constructors (not data constructors) with an non-type parameter, but Haskell hasn't dependent typing. To give you an example of the potential usefulness of dependent type, you can have a list type which is parametrized by the length of the list. data List :: * -> Integer -> * where Empty :: List a 0 Cons :: a -> List a n -> List a (n+1) you then can type head() so that you can't apply it on an empty list : head :: List a n -> List a (n-1) | n > 0 head (Cons x xs) = xs and the compiler will enforce this restriction at compile time (as well as it can). Dependent typing is interesting but not really practical yet. You can simulate it more or less with Haskell and GHC extensions, but Haskell isn't dependently typed. -- Jedaï

On Dec 30, 2007, at 12:32 PM, Joost Behrends wrote:
Thanks to both fast answers.
there remain problems with Jakes mail for me. This:
When you define datatypes, you are essentially defining a type-level constructors on the left hand side and (value-level) constructors on the right hand side.
is very useful for me. "data" defines TWO constructors, ok.
To be more accurate, it defines one type constructor and however many value constructors you want to define.
Then i arrive at
. Now, let's say we had tried defining ClockTime with parameters as you suggested.
ClockTime' :: Integer -> Integer -> *
Do you see the problem? In order to use the ClockTime type constructor, we would have to use Integer values.
Cannot see any problem here - do we NOT want ClockTime to be initialized by two Integers ? Or is this the main reason for introducing "TOD" - to be able to change it without having to make any changes to code using ClockTime ? To repeat myself - am i right understanding, that this needs a differently named data constuctor ?
No, we do not want the _type_ to be parameterized with our _values_. That is the difference between ClockTime and TOD; ClockTime is on the type level and TOD is on the value level. ClockTime is the type of the value returned by TOD after applying it to two Integer values. - Jake

On Dec 30, 2007 9:24 AM, Joost Behrends
A similar point: The tutorials teach, that "=" has a similar meaning than "=" in mathematics. But there is a big difference: it is not reflexive. The the right side is the definition of the left. Thus "x=y" has still some kind of temporality, which mathematics doesn't have. Wadler himself describes bunches of lazily computed equations as "dataflows" somewhere.
The "=" in the data declaration syntax is different from the "=" in value
and type declarations.
type A = B
means that "A" can be used wherever "B" can be used.
data A = B
means that "B" constructs a value of type "A". The "=" acts more like the
"::=" in a BNF grammar. It is *not* a claim that A equals B, since A is a
type and B is a data constructor. Furthermore, types and data constructors
have disjoint namespaces, hence the common idiom of using the same name for
the type and the constructor when the type has only one constructor.
There is an alternative syntax for data declarations in recent versions of
GHC. Using it, you would write:
data A where
B :: A
This defines a type A, and a constructor B which has type A.
data ClockTime where TOD :: Integer -> Integer -> ClockTime
This defines a type ClockTime, and a constructor TOD which takes two
Integers and constructs a ClockTime.
data Pair :: * -> * -> * where
Pair :: a -> b -> Pair a b
This defines a type constructor Pair, which takes two types and constructs a
new type, and a constructor, also called Pair, which, for arbitrary types a
and b, takes a value of type a and a value of type b and constructs a value
of type Pair a b.
--
Dave Menendez

G'day all.
Quoting David Menendez
data A = B
means that "B" constructs a value of type "A". The "=" acts more like the "::=" in a BNF grammar.
And, indeed, that was the syntax for it in Miranda.
It is *not* a claim that A equals B, since A is a type and B is a data constructor.
Wrong. It _is_ a claim that A equals B. Or, rather, that the set of values[*] A is defined as the least-fixpoint solution of the equation A = B. Think of this: data IntList = Nil | Cons Int IntList This corresponds to an equation: IntList = { Nil } + { Cons } * Int * IntLIst where plus denotes union (or disjoint union; either works in this case) and star denotes Cartesian product. The least fixpoint of this equation is precisely the set of values[*] in IntList.
Furthermore, types and data constructors have disjoint namespaces, hence the common idiom of using the same name for the type and the constructor when the type has only one constructor.
I think that's the major source of the confusion here, yes. Cheers, Andrew Bromage [*] Theoretical nit: It's not technically a "set". Consider the data type: data Foo = Foo (Foo -> Bool) This declaration states that there's a bijection between the elements of Foo and the elements of 2^Foo, which by Cantor's diagonal theorem cannot be true for any set. That's because we only allow computable functions, and Foo -> Bool is actually an exponential object in the category Hask.

On Dec 31, 2007 7:17 AM,
This declaration states that there's a bijection between the elements of Foo and the elements of 2^Foo, which by Cantor's diagonal theorem cannot be true for any set. That's because we only allow computable functions,
Nit the nit: Or (more commonly, I think) all continuous functions.
and Foo -> Bool is actually an exponential object in the category Hask.
- Benja

Andrew Bromage wrote:
[*] Theoretical nit: It's not technically a "set".
Consider the data type:
data Foo = Foo (Foo -> Bool)
This declaration states that there's a bijection between the elements of Foo and the elements of 2^Foo, which by Cantor's diagonal theorem cannot be true for any set. That's because we only allow computable functions, and Foo -> Bool is actually an exponential object in the category Hask.
Data types consist only of computable elements. Since there are only countably many computable functions, every data type has at most countably many elements. In particular, it is a set. The least fixed point under these restrictions is not a bijection between Foo and 2^Foo. It is only a bijection between Foo and the subset of computable 2^Foo. -Yitz

Andrew Bromage wrote:
[*] Theoretical nit: It's not technically a "set".
Consider the data type:
data Foo = Foo (Foo -> Bool)
This declaration states that there's a bijection between the elements of Foo and the elements of 2^Foo, which by Cantor's diagonal theorem cannot be true for any set. That's because we only allow computable functions, and Foo -> Bool is actually an exponential object in the category Hask.
I wrote:
Data types consist only of computable elements. Since there are only countably many computable functions,
What I meant by that is that there are only countably many lambdas, and we can define a "computable value" as a lambda. The classical definition of "general recursive function" refers to functions in Integer -> Integer to begin with, so there can only be countably many values by construction.
every data type has at most countably many elements. In particular, it is a set.
The least fixed point under these restrictions is not a bijection between Foo and 2^Foo. It is only a bijection between Foo and the subset of computable 2^Foo.
-Yitz

On Jan 1, 2008 3:43 PM, Yitzchak Gale
The classical definition of "general recursive function" refers to functions in Integer -> Integer to begin with, so there can only be countably many values by construction.
Except that there are uncountably many (2^Aleph_0) functions in Integer -> Integer. That doesn't change the fact that there are countably many computable functions, as you guys have been saying. But I think you need to refer to the LC or Turing machine definition to get countability. Luke

I wrote:
The classical definition of "general recursive function" refers to functions in Integer -> Integer to begin with, so there can only be countably many values by construction.
Luke Palmer wrote:
Except that there are uncountably many (2^Aleph_0) functions in Integer -> Integer.
No, only countably many. By the type expression Integer -> Integer we mean all Haskell functions mapping Integers to Integers. There are only countably many of those. Of course, you can sometimes use Haskell-like notation for discussing other mathematical concepts. In that context, you might mean to include uncomputable functions in your types. (Hey, there's a fun idea - how would you write the infinite injury algorithm in Haskell?) But that was not the context in this thread. The category Hask that we often mention in discussions about Haskell the programming language is most certainly a small category. -Yitz

Hi Yitz,
On Jan 2, 2008 10:34 AM, Yitzchak Gale
No, only countably many. By the type expression Integer -> Integer we mean all Haskell functions mapping Integers to Integers. There are only countably many of those. ... But that was not the context in this thread. The category Hask that we often mention in discussions about Haskell the programming language is most certainly a small category.
I don't know. My understanding has been that at least part of the benefit of denotational semantics is that you can define what an expression means without referring back to the syntactic construction or the operational semantics of that expression -- and thus use the denotational semantics to check whether the operational semantics are "right." But if you start with "all Haskell functions," you already have to know what a Haskell function *is*. I think it should be "allowed" to think of the semantics of Haskell as being defined independently of the (relatively operational) notion of "computable function," and then define "computable function" to be that subset of the functions in the model that you can actually write in Haskell. And the only explicit non-syntactic constructions of models for Haskell-like languages that I'm familiar with aren't countable (they contain all continuous functions, which in the case of (Integer -> Integer) comes out to all monotonous functions). So I disagree that the function types of Hask should automatically be taken to be countable. If you want to assume it for some given purpose, sure, fine, but IMO that's an additional assumption, not something inherent in the Haskell language. Best, - Benja

Hi Benja, I wrote:
By the type expression Integer -> Integer we mean all Haskell functions mapping Integers to Integers. There are only countably many of those. ... But that was not the context in this thread. The category Hask that we often mention in discussions about Haskell the programming language is most certainly a small category.
Benja Fallenstein wrote:
I don't know. My understanding has been that at least part of the benefit of denotational semantics is that you can define what an expression means without referring back to the syntactic construction or the operational semantics of that expression -- and thus use the denotational semantics to check whether the operational semantics are "right." But if you start with "all Haskell functions," you already have to know what a Haskell function *is*.
Denotational semantics maps expressions in a language - hence, syntax - into something that represents their semantics. You can choose different such mappings to represent different semantics of the same expressions. The Haskell Report clearly defines what a Haskell function is in terms of syntax. So my semantics are well-defined, and they represent what I understand when I read a Haskell program. In fact, these semantics do not really depend on all aspects of the syntax - only the existence of certain primitive functions, and certain constructions such as function definition, pattern matching, ADTs, etc. The same assumptions are made for any semantics of Haskell. Benja Fallenstein wrote:
I think it should be "allowed" to think of the semantics of Haskell as being defined independently of the (relatively operational) notion of "computable function," and then define "computable function" to be that subset of the functions in the model that you can actually write in Haskell.
"Computable function" is not operational - it just means functions that are lambdas, if you'd like. It just so happens that, so far, those are the only functions we know how to compute operationally. Maybe that quantum stuff... But yes, sure you can do that. That seems to be the approach in some papers. In particular, the one by Reynolds in which he proves that Haskell types cannot be represented by sets. Sounds like strong evidence that those are the wrong semantics to choose when studying Haskell as a programming language. Though it is certainly interesting to do so in a theoretical setting.
And the only explicit non-syntactic constructions of models for Haskell-like languages that I'm familiar with aren't countable (they contain all continuous functions, which in the case of (Integer -> Integer) comes out to all monotonous functions).
It is not any less syntactic than mine. It only differs in the semantics assigned to the symbol Integer -> Integer.
So I disagree that the function types of Hask should automatically be taken to be countable.
No, I agree with you. It's not automatic. It depends on your choice of semantics.
If you want to assume it for some given purpose, sure, fine, but IMO that's an additional assumption, not something inherent in the Haskell language.
Agreed. Thanks, Yitz

G'day all.
Quoting Yitzchak Gale
Data types consist only of computable elements. Since there are only countably many computable functions, every data type has at most countably many elements. In particular, it is a set.
I still say it "isn't a set" in the same way that a group "isn't a set". Haskell data types have structure that is respected by Haskell homomorphisms. Sets don't. Cheers, Andrew Bromage

On Sun, 30 Dec 2007, Joost Behrends wrote:
A similar point: The tutorials teach, that "=" has a similar meaning than "=" in mathematics. But there is a big difference: it is not reflexive. The the right side is the definition of the left. Thus "x=y" has still some kind of temporality, which mathematics doesn't have. Wadler himself describes bunches of lazily computed equations as "dataflows" somewhere.
The distinction between '=' and '==' is much like in C, although mixing them up is not so dangerous like in C. ':=' and '=' like in Wirth languages would be nicer.
For adapting hws (one of the reasons for me to be here, not many languages have a native web server) to Windows i must work on time.
Several people have adapted and further developed HWS: http://www.haskell.org/haskellwiki/Applications_and_libraries/Web_programmin... http://darcs.haskell.org/hws/ http://www.informatik.uni-freiburg.de/~thiemann/WASH/ (WSP) There is also a mailing list dedicated to Haskell and Web development: http://www.haskell.org/mailman/listinfo/web-devel

Thanks for that info:
Several people have adapted and further developed HWS:
http://www.haskell.org/haskellwiki/Applications_and_libraries/Web_programmin...
http://darcs.haskell.org/hws/ http://www.informatik.uni-freiburg.de/~thiemann/WASH/ (WSP)
There is also a mailing list dedicated to Haskell and Web development: http://www.haskell.org/mailman/listinfo/web-devel
I've already browsed through the docomentation of all that. Sorry, but i will not use WASH. I like things to be direct, to write >> p { ... } or similar things instead of <p> ... </p> is worsening things for me. Same with SQL. To work competently with CSS or SQL you must learn that languages anyway. (I still didn't master CSS2.1, but will have mastered it in the near future. Haskell's pattern matching has helped me much to understand the selectors of CSS - but problems with the "natural flow" of elements and positioning are still there). Using WASH (or HaskellDB) for me only means, that i must learn another interface on top of that. For databases i could imagine to do that for 1. Real database abstraction (which would require far more complete drivers, ODBC for example) 2. Mighty ORM abilities. With anything less, i do not want that extra learning. I consider the most approaches as megalomanical, which try to "improve" SQL. SQL is an ingenious achievement with its complete avoidancs of iteration - it's working with sets - in an area, where performance is everything. Still now it's a model for many things in language design - i remember to have read something corresponding on www.haskell.org even (don't remember the context). For CSS (i try to do most things there, not in HTML) i see no use for that extra learning at all. Please do not feel offended. Sometimes i am too rash with hard words. And concerning the web servers: I haven't seen any indication, that someone has ported hws to Windows - as easy as that is. There is not even use of unix domain sockets in hws, nothing unix-specific with IPC (or communication among threads). It's just EpochTime and access permissions and only changes in Utils.hs and Main.hs have to be made it seems (The other modules compile on my system at least). If someone had done that, it would be in the core code of hws. However it is kind of nasty for a Haskell beginner. The Windows API is accessible via FFI, but nearly undocumented (and i am used to portability, do not want to study it earnestly. We have the module os in Python - i am missing that in Haskell). And time looks complicated in the standard lib. It was even an obstacle for compiling HDBC (old-time had to be exposed - that is, what i thought at first, but had to find out then, that cabal ignores exposition and hiding of modules :[[ ). Cheers, Joost

On Dec 30, 2007 6:24 PM, Joost Behrends
I've already browsed through the docomentation of all that. Sorry, but i will not use WASH. I like things to be direct, to write >> p { ... } or similar things instead of <p> ... </p> is worsening things for me.
Haskell is not a good "quick and dirty" templating language. See perl for 500 templating approaches. So, now that we're past that. One of the beautiful things I have noticed about Haskell is that there has been essentially nothing I have not been able to factor out. If I have any common repeated logic anywhere in my program, I have always been able to naturally factor it out so it appears in only one place. So how, prey tell, do you factor out an expression which includes <p>...</p>? It is not Haskell, Haskell has no power there. What the libraries you are looking at do is precisely to encode HTML/SQL into Haskell, so it may be manipulated by Haskell functions without resorting to string mangling. Haskell however does not look anything like HTML or like SQL, so there is a mapping you must learn. But that mapping is a refined version of what you might come up with if you were starting from scratch and diligently refactoring as much as possible. Surely learning that mapping is easier than building your own (which will doubtlessly be worse (no offense, that's the first law of library use)). And since you are a Haskell beginner, learning a library will teach you not only the library, but loads about common idioms and Haskell programming in general. As an example, it was only after using the Parsec library that I finally came to terms with monads; for whatever reason, I was incapable of grokking them studying only the standard built-ins. I dunno, it just seems odd to me to avoid "extra learning" when you're trying to learn the language in the first place. Luke

Hi,
So how, prey tell, do you factor out an expression which includes <p>...</p>? It is not Haskell, Haskell has no power there. Surely learning that mapping is easier than building your own (which will doubtlessly be worse (no offense, that's the first law of library use)).
And since you are a Haskell beginner, learning a library will teach you not only the library, but loads about common idioms and Haskell programming in general. As an example, it was only after using the Parsec library that I finally came to terms with monads; for whatever reason, I was incapable of grokking them studying only the standard built-ins.
I dunno, it just seems odd to me to avoid "extra learning" when you're trying to learn the language in the first place.
Luke
this is very debatable. Yesterday i read "there should be no libraries at all" from anyone here. And i know from Python, that libraries can be bad - i rewrote ftplib for my own use. I differentiate always between the language core and its libraries. Pythons unicode is catastrophic - but the core language is very, very fine. If there were a better STDLIB (and not many of them and Boost on top) and no autoconf, i would stick to C++. Still the fastest language and very powerful with types, respective classes. And i will embed Haskell into websides - thats the next step after having ported the server. The least, what can be done here, and can be done easily, is a kind of preprocessor. Perhaps i'll call it phaskelp (? - or phasp ?). Happy New Year, Joost

I forgot 2 things:
The distinction between '=' and '==' is much like in C, although mixing them up is not so dangerous like in C. ':=' and '=' like in Wirth languages would be nicer.
Strangely nobody reacted on this. That a=a+1 is an infinite recursion here (but _|_ obviously not completely "out of scope") makes "=" totally different in my eyes. And that outside monads variables normally have just one line, where they are on the left side, makes another huge difference in the structure of your code. Then - more on wrapper libraries for SQL or HTML. I consider "interpolation" useful with HTML, that is kind of other way around than WASH. You write a page and embed your high-level in it. Not HTML should bended to your high-level language. The so much mightier language should do the service here. Then sides can possibly be upgraded by extern web designers. With Python i realized an own way of embedding a (greatly reduced) subset of the language into HTML - the project at sourceforge.net is named "thrases". And concerning SQL: I like the parts of the language - all capitalized - as landmarks in my code, even in modified forms like: "SELECT number, customer FROM " ++ currcols ++ .... Here i see from afar, what the code around this line does. Happy New Year, Joost

On Mon, 31 Dec 2007 14:36:02 +0200, Joost Behrends
I forgot 2 things:
The distinction between '=' and '==' is much like in C, although mixing them up is not so dangerous like in C. ':=' and '=' like in Wirth languages would be nicer.
Strangely nobody reacted on this. That a=a+1 is an infinite recursion here
What is more strange is that a = a + 1 and a = 1 + a are somehow distinct. The second give a stack overflow almost instanly, but the first don't. ________ Information from NOD32 ________ This message was checked by NOD32 Antivirus System for Linux Mail Servers. part000.txt - is OK http://www.eset.com

"Cristian Baboi"
What is more strange is that a = a + 1 and a = 1 + a are somehow distinct. The second give a stack overflow almost instanly, but the first don't.
That's because what the runtime does looks in the second case like a = 1 + 1 + 1 + 1 + 1 + ... + a ... and the first like a = a = a = a = a = a = a = ... = 1 + a , which is a much more space efficient endless loop. That's not specified though, the runtime could choose to let + force the two chunks the different way round. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Achim Schneider
That's not specified though, the runtime could choose to let + force the two chunks the different way round.
And that is probably also the reason why [1..] == [1..] is _|_. Is "Something that can be, in any evaluation strategy, be bottom, is bottom" quite right, i.e. the formalism defined such, that no possibly unevaluable thing is defined? -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Am Montag, 31. Dezember 2007 17:43 schrieb Achim Schneider:
Achim Schneider
wrote: That's not specified though, the runtime could choose to let + force the two chunks the different way round.
And that is probably also the reason why [1..] == [1..] is _|_.
Is "Something that can be, in any evaluation strategy, be bottom, is bottom" quite right, i.e. the formalism defined such, that no possibly unevaluable thing is defined?
I think it's the other way round. False && _|_ would be bottom in a right-to-left evaluation strategy, but is defined since False && _ = False. And, IIRC, excepting cases where the order of pattern matches intervenes, any expression which can be evaluated in any strategy (without hitting bottom, that is) can also be evaluated lazily and lazy evaluation yields the same value. Cheers, Daniel

On 31 Dec 2007, at 10:43 AM, Achim Schneider wrote:
Achim Schneider
wrote: That's not specified though, the runtime could choose to let + force the two chunks the different way round.
And that is probably also the reason why [1..] == [1..] is _|_.
Is "Something that can be, in any evaluation strategy, be bottom, is bottom" quite right, i.e. the formalism defined such, that no possibly unevaluable thing is defined?
No. Again, the semantics of Haskell are defined denotationally, not operationally. In fact, Haskell implementations are required to use an evaluation strategy that finds a value whenever one (denotationally) exists, so it's the exact opposite of what you said. Strict languages come much closer to your rule, OTOH. jcc

Jonathan Cast
On 31 Dec 2007, at 10:43 AM, Achim Schneider wrote:
Achim Schneider
wrote: That's not specified though, the runtime could choose to let + force the two chunks the different way round.
And that is probably also the reason why [1..] == [1..] is _|_.
Is "Something that can be, in any evaluation strategy, be bottom, is bottom" quite right, i.e. the formalism defined such, that no possibly unevaluable thing is defined?
No. Again, the semantics of Haskell are defined denotationally, not operationally. In fact, Haskell implementations are required to use an evaluation strategy that finds a value whenever one (denotationally) exists, so it's the exact opposite of what you said.
Strict languages come much closer to your rule, OTOH.
I guess I just have to change unevaluable to not denotationally reducable. Except to _|_, of course. Which makes it completely logical, but also completely meaningless if you don't look at the algebra. It seems like I have to translate the formulae to plain English after all. Not today, though, I'm planning to be drunk in one hour and a half. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On 31 Dec 2007, at 1:33 PM, Achim Schneider wrote:
Jonathan Cast
wrote: On 31 Dec 2007, at 10:43 AM, Achim Schneider wrote:
Achim Schneider
wrote: That's not specified though, the runtime could choose to let + force the two chunks the different way round.
And that is probably also the reason why [1..] == [1..] is _|_.
Is "Something that can be, in any evaluation strategy, be bottom, is bottom" quite right, i.e. the formalism defined such, that no possibly unevaluable thing is defined?
No. Again, the semantics of Haskell are defined denotationally, not operationally. In fact, Haskell implementations are required to use an evaluation strategy that finds a value whenever one (denotationally) exists, so it's the exact opposite of what you said.
Strict languages come much closer to your rule, OTOH.
I guess I just have to change unevaluable to not denotationally reducable.
Well, defined as _|_. Reduction isn't really a very good model for denotational semantics at all (it's an operational concept). Think of a recursively defined value as a limit: let x = f x in x = lim(_|_, f _|_, f (f _|_), ...) and then other functions pass through that limit g (let x = f x in x) = g (lim(_|_, f _|_, f (f _|_), ...) = lim(g _|_, g (f _|_), g (f (f _|_)), ...) In that sense, a value is _|_ iff it cannot be proven not to be --- iff any sequence it is a LUB (limit) of is everywhere _|_. But again, don't think operationally --- think in terms of LUBs of increasing sequences. jcc

Jonathan Cast
[...]
Right click -> Color Label -> Red. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On Dec 31, 2007, at 6:50 AM, Cristian Baboi wrote:
On Mon, 31 Dec 2007 14:36:02 +0200, Joost Behrends
wrote:
I forgot 2 things:
The distinction between '=' and '==' is much like in C, although mixing them up is not so dangerous like in C. ':=' and '=' like in Wirth languages would be nicer.
Strangely nobody reacted on this. That a=a+1 is an infinite recursion here
What is more strange is that a = a + 1 and a = 1 + a are somehow distinct. The second give a stack overflow almost instanly, but the first don't.
To explain this, let's look at the expansions. The first one looks like this: a + 1 a + 1 + 1 a + 1 + 1 + 1 a + 1 + 1 + 1 + 1 ... a + 1 + ... + 1 The second one looks like this: 1 + a 1 + 1 + a 1 + 1 + 1 + a 1 + 1 + 1 + 1 + a ... 1 + ... + 1 + a I suspect that GHC is evaluating the second one strictly, as though it was this instead: a = foldl1' (+) (repeat 1) + a This way, the stack never gets any larger. The first one, however, has runtime behavior comparable to this: a = foldl' (+) a (repeat 1) The first thing this version has to do is evaluate a, which starts infinite recursion. The second one doesn't suffer from this because it has real values to manipulate strictly instead of just substitution rules and thunks. I'm speculating here, so somebody please correct me if I'm wrong. - Jake

On Mon, 2007-12-31 at 12:36 +0000, Joost Behrends wrote:
And concerning SQL: I like the parts of the language - all capitalized - as landmarks in my code, even in modified forms like:
"SELECT number, customer FROM " ++ currcols ++ ....
Here i see from afar, what the code around this line does.
And the backside of treating SQL as strings, like you do here, is that you are able to construct malformed SQL and the errors you get from this can only be handled at runtime. This is the reason HaskellDB (and other similar projects?) exists. I too am not sure that HaskellDB is the perfect solution though. It provides both type safety and an abstraction. Personally i'd be fine with just the type safety. Not sure if it's feasible to embed the whole SQL-syntax in Haskell using just ADT's and combinators though. Mattias

Joost Behrends wrote:
We read
data Pair a b = Pair a b
in YetAnotherHaskellTutorial. And that is all ! If we omit "data" here, this would be a silly pleonasm. And no single word about this strange behavior of "data" in every tutorial i read.
When learning a language, I find it useful to consult grammar to find out the relevant part of the syntax; then I can check the Haskell online report for explanations. For example you presented: ... searching for data in http://www.hck.sk/users/peter/HaskellEx.htm ... gives you http://www.hck.sk/users/peter/HaskellEx.htm#topdecl ... and from there you can quickly find relevant part of Haskel report: http://www.haskell.org/onlinereport/decls.html#sect4.2.1 Haskell has a nice html specification online (thanks for it!). Peter.
participants (16)
-
Achim Schneider
-
ajb@spamcop.net
-
Benja Fallenstein
-
Bulat Ziganshin
-
Chaddaï Fouché
-
Cristian Baboi
-
Daniel Fischer
-
David Menendez
-
Henning Thielemann
-
Jake McArthur
-
Jonathan Cast
-
Joost Behrends
-
Luke Palmer
-
Mattias Bengtsson
-
Peter Hercek
-
Yitzchak Gale