Re: [Haskell] IO == ST RealWorld

2006-01-30 Thread Marcin 'Qrczak' Kowalczyk
Axel Simon <[EMAIL PROTECTED]> writes: > One function that particularly annoyed me is in Control.Exception > > handle :: (Exception -> IO a) -> IO a -> IO a > > should be > > handle :: MonadIO m => (Exception -> m a) -> m a -> m a I think it would be unimplementable. -- __("< Marcin

Re: [Haskell] Strictness question

2005-06-07 Thread Marcin &#x27;Qrczak' Kowalczyk
Ben Lippmeier <[EMAIL PROTECTED]> writes: > To gloss over details: it'll reduce x far enough so it knows that it's > an Integer, but it won't nessesarally compute that integers value. No, Integers don't contain any lazy components. It statically knows that it's an integer. -- __("< M

Re: [Haskell] Beyond ASCII only editors for Haskell

2005-05-24 Thread Marcin &#x27;Qrczak' Kowalczyk
Benjamin Franksen <[EMAIL PROTECTED]> writes: > Please forgive me for taking this as an opportunity to rant about the > single misfeature of Haskell's layout syntax, which is how if/then/else > must be layed out. For me it's worse that I can't write like this: foo x = do y <- foo x let z

Re: [Haskell] Re: Existing Haskell IPv6 Code

2005-05-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Tony Finch <[EMAIL PROTECTED]> writes: >> But they don't differ in addressing. In BSD sockets the difference >> between streams and packets lies in "socket type", while addresses >> are split into "address families" which bijectively correspond to >> "protocol families". > > I believe there are so

Re: [Haskell] Re: Existing Haskell IPv6 Code

2005-05-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Peter Simons <[EMAIL PROTECTED]> writes: > >> [URIs might be the answer] > > > But what URI should represent e.g. unix datagram sockets? > > I don't think it's worth even trying to hide both stream- > and packet-oriented services behind the same API. These are > completely different things, trea

Re: [Haskell] Re: Should inet_ntoa Be Pure?

2005-05-09 Thread Marcin &#x27;Qrczak' Kowalczyk
Peter Simons <[EMAIL PROTECTED]> writes: > I would be curious to know how other programming languages > have solved this problem. C's solution is the one we all > know and love, and C++ added pretty much nothing to that in > the last 10 years or so. How about others? I once looked at .NET and was

Re: [Haskell] Eternal Compatibility In Theory

2005-05-02 Thread Marcin &#x27;Qrczak' Kowalczyk
robert dockins <[EMAIL PROTECTED]> writes: > Is there a way to reliably and automatically check if two versions of > a haskell module are interface compatible? No, because it would have to check whether the semantics of functions is the same, even if they are written differently. -- __("<

Re: [Haskell] URLs in haskell module namespace

2005-03-23 Thread Marcin &#x27;Qrczak' Kowalczyk
Here is what I designed and implemented for my language Kogut: There is a file format of compilation parameters (compiler options, source file encoding, directories to look for interface files for imported modules, directories to look for libraries, C libraries to link, directories to look for pac

Re: [Haskell] Unicode Source / Keyboard Layout

2005-03-21 Thread Marcin &#x27;Qrczak' Kowalczyk
Sven Moritz Hallberg <[EMAIL PROTECTED]> writes: > 1. In addition to the backslash, accept "mathematical * small > lamda" (U+1D6CC, U+1D706, U+1D740, U+1D77A, and U+1D7B4) for lambda > abstractions. Leave "greek small letter lamda" as a regular letter, > so the Greeks can write their native

Re: [Haskell] Force evaluation

2004-12-06 Thread Marcin &#x27;Qrczak' Kowalczyk
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: > And here's a slight variation in which force has the type a -> a, > eliminating the need for the helper function eval. I'm not sure which > version is better. The version with () does less redundant forcing, although the compiler could perhaps optimi

Re: [Haskell] Real life examples

2004-11-25 Thread Marcin &#x27;Qrczak' Kowalczyk
Lennart Augustsson <[EMAIL PROTECTED]> writes: > An "easy" way to prove it is to provide an equivalent implementation > that uses only pure functions. As far as I remember Control.Monad.ST > can be written purely. And I think the same is true for Data.Dynamic. I think neither of them can. --

Re: [Haskell] Better Exception Handling

2004-11-23 Thread Marcin &#x27;Qrczak' Kowalczyk
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: > The intended semantics is > > / Nothing if x is a set of exceptions > exceptionToMaybe x = | _|_ if x is _|_ > \ Just xotherwise What is exceptionToMaybe (f 0 + error "x") where

Re: [Haskell] How to close a type class

2004-11-12 Thread Marcin &#x27;Qrczak' Kowalczyk
[EMAIL PROTECTED] writes: > Thus we have reduced the problem of excluding certain types from a > typeclass to the problem of excluding all types from one particular > typeclass: Fail. How can we prevent the user from adding instances to > Fail? By not exporting its name? -- __("< Mar

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Marcin &#x27;Qrczak' Kowalczyk
Krasimir Angelov <[EMAIL PROTECTED]> writes: > I guess that this is an overkill since we can just > define IO as > > type IO a = ST RealWorld a 'instance MonadIO IO' would start to need some type system extensions. -- __("< Marcin Kowalczyk \__/ [EMAIL PROTECTED] ^^

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-05 Thread Marcin &#x27;Qrczak' Kowalczyk
Keean Schupke <[EMAIL PROTECTED]> writes: > Why do want global variables? Because they are more convenient than passing a state by hand. They increase modularity by avoiding putting the fact that a computation uses some global state in its type. You don't want stdin/stdout/stderr? Yes, *usually

Re: [Haskell] is $ a no-op?

2004-10-13 Thread Marcin &#x27;Qrczak' Kowalczyk
Johannes Waldmann <[EMAIL PROTECTED]> writes: > I liked to think of it as just a syntactical convention (for years ...) > but is it really at no cost? It does introduce extra function calls, > that is, extra closures etc.? Can these be removed by ghc's optimizer? It is inlined by GHC when optimiz

Re: [Haskell] threading mutable state through callbacks

2004-10-13 Thread Marcin &#x27;Qrczak' Kowalczyk
Jules Bean <[EMAIL PROTECTED]> writes: > Unless its possible to arrange haskell FFI bindings to have types in > MonadIO rather than IO... MonadIO is a class, not a type. Anyway, it's conceptually impossible to wrap a computation of an arbitrary monad in the MonadIO class into IO. It's not a techn

Re: [Haskell] threading mutable state through callbacks

2004-10-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Adrian Hey <[EMAIL PROTECTED]> writes: > The only real insanity with the current situation is the loss of > referential transparency implied by the use of unsafePerformIO, > which is why various pragma hacks and compiler switches need to be > used (in order to prevent inappropriate substitutions).

Re: [Haskell] threading mutable state through callbacks

2004-10-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Jules Bean <[EMAIL PROTECTED]> writes: > I think what people are trying to suggest is an 'initialization > phase' in the IO monad, which takes place "before" the pure > functions are defined. If it was done before, what could you use to specify initial value of such a variable? Only literals? Con

Re: [Haskell] threading mutable state through callbacks

2004-10-12 Thread Marcin &#x27;Qrczak' Kowalczyk
"Simon Marlow" <[EMAIL PROTECTED]> writes: > I'd like to add that while the implementation might be a little unsafe, > there's no problem in principle with the semantics of top-level IORefs. > We could add such a thing as a GHC extension, but it would be nice if it > were an instance of a more gen

Re: ANNOUNCE: Release of Vital, an interactive visual programming environment for Haskell

2003-11-12 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z śro, 12-11-2003, godz. 11:06, Graham Klyne pisze: > I've sometimes thought that a functional language would be the ideal > platform to usher in a purely graphical style of programming; I don't understand why so many people talk about graphical programming, i.e. putting together functi

Re: Number conversions, like floats to doubles

2003-11-08 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z sob, 08-11-2003, godz. 22:59, Hal Daume III pisze: > In NumExts, there's floatToDouble and doubleToFloat. It's a GHC extension, while realToFrac is Haskell 98. -- __("< Marcin Kowalczyk \__/ [EMAIL PROTECTED] ^^ http://qrnik.knm.org.pl/~qrczak/ __

Re: Number conversions, like floats to doubles

2003-11-08 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z sob, 08-11-2003, godz. 22:41, Ben Escoto pisze: > If I want to convert a Float to a Double, should I use > > fromRational . toRational realToFrac :: (Fractional b, Real a) => a -> b It is actually defined as fromRational . toRational but GHC knows to generate specialized code for par

Re: ghc6 behavior with circular instance declaration

2003-10-23 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z śro, 22-10-2003, godz. 06:15, Kenny pisze: > instance (Myeq a,Myeq [a]) => Myeq [a] where > myeq (x:xs) (y:ys) = (myeq x y)&&(myeq xs ys) > > I want to make the 2nd call of myeq to be of an instance function > from the context instead of a recursive call. Why? Since there can be at

Re: lexer puzzle

2003-09-23 Thread Marcin &#x27;Qrczak' Kowalczyk
> > Thus, the only possible lexical interpretation is the one you first > > suggested, namely a constructor "A" followed by a three-dot operator > > "...". > A... should be split into "A.." and "." I found a compromise: let's make it a lexing error! :-) -- __("< Marcin Kowalczyk \

Re: lexer puzzle

2003-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia nie 14. września 2003 01:04, Derek Elkins napisał: > > >A... > > > > A (constructor), then ... (operator). > > This is how I understand Haskell 98 lexing rules. > > My first thought was that it should produce, A.. ., as in (.) (A..), but > obviously that would be wrong as A.. must be a fu

Re: lexer puzzle

2003-09-13 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia pią 12. września 2003 20:31, Iavor Diatchki napisał: > what do people think should be the tokens produced by a haskell lexer > when applied to the following input: > >A... A (constructor), then ... (operator). This is how I understand Haskell 98 lexing rules. -- __("< Marcin

Re: Last call generalised

2003-08-29 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia czw 28. sierpnia 2003 23:04, [EMAIL PROTECTED] napisał: > > copyList (x:xs) = x : copyList xs > > > > is surely not tail-recursive in the traditional sense, but I think > > that most Haskell programmers take it for granted that it runs in > > constant stack space. The problem lies in the fa

Re: Exhaustive Pattern-Matching

2003-08-29 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia czw 28. sierpnia 2003 16:37, Frank Atanassow napisał: > SML has the same limitations w.r.t. guards as Haskell; Haskell > compilers can and do check exhaustiveness, but not redundancy because > matches are tried sequentially. I believe SML matching is also > sequential. If there is a differenc

Re: problems with working with Handles

2003-06-15 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia pią 13. czerwca 2003 16:34, Dean Herington napisał: > `seq` guarantees only enough evaluation to determine whether its first > argument is bottom. That's why your commented code reads only the first > character. You need to evaluate the entire string. As someone else > suggested, `deepSeq`

Re: Yet more text pedantry

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 09 Aug 2002 15:24:55 +0200, George Russell <[EMAIL PROTECTED]> pisze: > but the fact is that the standard access functions return > characters*, and on Solaris the default representation of > a characters is as a signed quantity. Only because of a messy history. No need to transfer the sill

Re: Text in Haskell: a second proposal

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 8 Aug 2002 23:40:42 -0700, Ashley Yakeley <[EMAIL PROTECTED]> pisze: >> 1. Octets. >> 2. C "char". >> 3. Unicode code points. >> 4. Unicode code values, useful only for UTF-16, which is seldom used. >> 5. "What handles handle". > I disagree, they should be: > > 1. Word8 > 2. CChar > 3. Cha

Re: Text in Haskell: A PROPOSAL

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 8 Aug 2002 03:16:09 -0700, Ashley Yakeley <[EMAIL PROTECTED]> pisze: >> With, perhaps, UTF-8 as a reasonable default? > > Perhaps it should _always_ be UTF-8? My files are not in UTF-8, so reading them as UTF-8 is wrong. Files are in the locale encoding unless the programmer explicitly sp

Re: UTF-8 library

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Sat, 10 Aug 2002 01:31:51 -0700, Ashley Yakeley <[EMAIL PROTECTED]> pisze: >>that different pointer >>types have the same representation - we already rely on that, don't we? > > No, we have separate Ptrs and FunctionPtrs IIRC... Yes, but I mean the possibility that Ptr Word8 looks differently t

Re: UTF-8 library

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
09 Aug 2002 10:17:21 +0200, Sven Moritz Hallberg <[EMAIL PROTECTED]> pisze: > I argue _strongly_ against associating some sort of locale state with > handles. > > 1) In agreement with Ashley's statements, file IO should use octets, > because that's what's in a file. So it would imply two types

Re: UTF-8 library

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 8 Aug 2002 09:59:12 -0700 (PDT), anatoli <[EMAIL PROTECTED]> pisze: > I'd still rather associate locale with a handle. I agree. http://www.sf.net/projects/qforeign/ contains an experimental character recoding library with a IO module wrapper which associates encodings with Handles. But I do

Re: UTF-8 library

2002-08-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 08 Aug 2002 19:28:18 +1000 (EST), Manuel M T Chakravarty <[EMAIL PROTECTED]> pisze: > ANSI C guarantees that char is 1 byte (more precisely that > "sizeof (char)" == 1). It says that sizeof (char) == 1 but doesn't say that it means 8 bits. sizeof is measured in chars, whatever it is. But l

Re: newtype pattern matching

2002-01-25 Thread Marcin &#x27;Qrczak' Kowalczyk
25 Jan 2002 08:00:24 +0100, Martin Norbäck <[EMAIL PROTECTED]> pisze: > newtype T1 = C1 Bool > dataT2 = C2 !Bool > > the difference is that the constructor C1 does not exist, so only the > following values exist for T1: > > C1 True (which is the represented as True) > C1 False (which is th

Re: instances and modules

2002-01-01 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 31 Dec 2001 22:52:44 -0800, Feuer <[EMAIL PROTECTED]> pisze: > I don't understand how a type can be considered an instance of a > class if it doesn't provide all the methods of that class. 1. A method can have a default definition. 2. A missing method definition is assumed to be bottom.

Re: Typesetting literate scripts in TeX

2001-12-14 Thread Marcin &#x27;Qrczak' Kowalczyk
> Recently I've hacked up a (yet another) TeX package for typesetting > literate scripts in TeX Cool! I will use it in my thesis. One bug: a line can be broken between an inline code and a comma which immediately follows it. -- __("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net

Re: Scope of imported names

2001-11-02 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 2 Nov 2001 09:30:37 -0800, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > | They are also different in spirit from the rules for > | instance declarations in section 4.3.2 where the binding > | occurrences for the names of the methods must be qualified if > | the unqualified method name

Re: Incoherence

2001-10-25 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 25 Oct 2001 09:47:31 +, Levent Erkok <[EMAIL PROTECTED]> pisze: > Another place where `:=' bindings are badly needed is the recursive > do-notation (mdo, as supported in hugs.) In an mdo, let bindings > have to be monomorphic, because they are passed back to the mfix > loop in a lambda b

Re: Monomorphism, monomorphism...

2001-10-24 Thread Marcin &#x27;Qrczak' Kowalczyk
Wed, 24 Oct 2001 10:36:22 +0200, Hannah Schroeter <[EMAIL PROTECTED]> pisze: > Why not create a dictionary record while compiling the associated > instance (which may, by the H'98 definition, occur only once in > the program)? Instances with contexts are commonly represented as functions which m

Re: Incoherence

2001-10-23 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 23 Oct 2001 08:00:34 -0700, Jeffrey R Lewis <[EMAIL PROTECTED]> pisze: > The best solution is to find a good way to eliminate the DMR. Separating syntaxes of function definition and pattern binding would have the right effect IMHO, but it's a radical change which breaks compatibility and cu

Re: More Unicode nit-picking

2001-10-19 Thread Marcin &#x27;Qrczak' Kowalczyk
19 Oct 2001 06:09:09 +0100, Colin Paul Adams <[EMAIL PROTECTED]> pisze: > But this seems to assume there is a one-to-one mapping of upper-case > to lower-case equivalent, and vice-versa. Apparently this is not so. Indeed, but there exists a default locale-independent case mapping. Language-speci

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-18 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 18 Oct 2001 13:49:11 +0200, Karl-Filip Faxen <[EMAIL PROTECTED]> pisze: > There are two solutions that I can see: Annotate classes in class > constraints with exactly which methods were used. Thus for the > expression "x+y" the inference algorithm would record the constraint > "Num{+} a" if

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-16 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 16 Oct 2001 15:29:36 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > Not giving a default definition is *not* the same as giving a default > definition that calls "error". It's significantly safer. The difference > is that the former makes it much easier for compilers to issue warning

Re: bracket_

2001-10-15 Thread Marcin &#x27;Qrczak' Kowalczyk
Sun, 14 Oct 2001 23:25:40 -0400, Ken Shan <[EMAIL PROTECTED]> pisze: > In Haskell's standard IO module, bracket_ is defined to have type > > IO a -> (a -> IO b) -> IO c -> IO c > > However, in the Exception module in hslibs, bracket_ has type > > IO a -> IO b -> IO c -> IO c > > which

Re: macros. Was: Arrow notation, etc.

2001-10-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 12 Oct 2001 15:38:21 +0200, Jerzy Karczmarczuk <[EMAIL PROTECTED]> pisze: > They are heavily used in Clean, so, there *are* people who see a > need for them in a lazy language. The Clean implementation doesn't inline functions across modules, right? -- __("< Marcin Kowalczyk * [EMAIL PR

Re: Unicode support

2001-10-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 9 Oct 2001 14:59:09 -0700, John Meacham <[EMAIL PROTECTED]> pisze: > I think a cannonical way to get at iconvs ('man 3 iconv' for info.) > functionality in one of the standard librarys would be great. perhaps > I will have a go at it. even if the underlying platform does not have > iconv the

Re: Monomorphism, monomorphism...

2001-10-10 Thread Marcin &#x27;Qrczak' Kowalczyk
09 Oct 2001 13:55:04 -0700, Carl R. Witty <[EMAIL PROTECTED]> pisze: > The TREX paper from Mark Jones and Benedict Gaster (I hope I > have the names right) had both extensible records and extensible > variants (extensible variants being what you would need to implement > downcasts), I don't thin

Re: Extensible downcasts impossible in Haskell? (was Re: Monomorphism, monomorphism...)

2001-10-09 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 9 Oct 2001 10:50:19 +1300, Tom Pledger <[EMAIL PROTECTED]> pisze: > I'm curious about this impossibility. > > - Is it well known? If so, would someone please refer me to a paper > or posting which explains it? I don't know. I'm not even sure if some clever encoding couldn't express

Re: Unicode support

2001-10-09 Thread Marcin &#x27;Qrczak' Kowalczyk
-Unicode and 16-bit-Unicode camps :-) -- Marcin 'Qrczak' Kowalczyk ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Monomorphism, monomorphism...

2001-10-08 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 8 Oct 2001 11:35:48 +0200, Hannah Schroeter <[EMAIL PROTECTED]> pisze: > Now, with the typical dictionary implementation of type classes, > this wouldn't really be too difficult. Dictionaries would have to be make hashable and comparable. For a sane semantics you can't compare their identit

Re: Monomorphism, monomorphism...

2001-10-07 Thread Marcin &#x27;Qrczak' Kowalczyk
Sat, 6 Oct 2001 22:22:24 -0700, Juan Carlos Arévalo Baeza <[EMAIL PROTECTED]> pisze: >>A pattern which is something other than an identifier. > >Like defining a function, as opposed to defining a constant? No: a pattern, e.g. (x,y), Just y, (x:_) etc. A function definition looks like an ide

Re: Monomorphism, monomorphism...

2001-10-06 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 5 Oct 2001 19:02:50 -0700, Juan Carlos Arévalo Baeza <[EMAIL PROTECTED]> pisze: >>"If a declaration group" > >Meaning something like "let g = isNil" up there? Yes, a group of mutually recursive bindings or a single non-recursive binding (equations inside let or where or at module tople

Re: Strange error in show for datatype

2001-10-04 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 4 Oct 2001 06:05:16 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > data T a = T1 Int | T2 a > > It's clear that (T1 Int) has no a's in it, not even bottom. instance Show a => Show (T a) where show x = show (tail [case x of T2 y -> y]) We have show (T1 0 :: T Int) == "[]"

Re: Strange error in show for datatype

2001-10-04 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 4 Oct 2001 14:29:43 +0100, Ross Paterson <[EMAIL PROTECTED]> pisze: > So this extension adds something we already have in Haskell 98, with either > > newtype Void = Void Void > ordata Void = Void !Void Theoretically yes, but this introduces a warning that the data constructor Voi

Re: Strange error in show for datatype

2001-10-04 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 4 Oct 2001 00:36:55 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > Void was a type with one element. What we really want here is > a type with no elements. It's also useful to be able to introduce > such empty types for phantom-type purposes, so GHC now lets you say > > data

Re: Unicode support

2001-09-30 Thread Marcin &#x27;Qrczak' Kowalczyk
30 Sep 2001 14:43:21 +0100, Colin Paul Adams <[EMAIL PROTECTED]> pisze: > I think it should either be amended to mention the BMP subset of > Unicode, or, better, change the reference from 16-bit to 24-bit. 24-bit is not accurate. The range from 0 to 0x10 has 20.087462841250343 bits. There is

Re: Unicode support

2001-09-30 Thread Marcin &#x27;Qrczak' Kowalczyk
30 Sep 2001 22:28:52 +0900, Jens Petersen <[EMAIL PROTECTED]> pisze: > 16 bits is enough to describe the Basic Multilingual Plane > and I think 24 bits all the currently defined extended > planes. So I guess the report just refers to the BMP. In early days the Unicode Consortium was doing every

Re: Prelude and (:) and []((:), []) bugs?

2001-09-21 Thread Marcin &#x27;Qrczak' Kowalczyk
20 Sep 2001 12:37:36 -0600, Alastair David Reid <[EMAIL PROTECTED]> pisze: >> Ah, I forgot that you can't export a constructor on its own. > > You can't? > > I probably knew this once but looking at it now, it seems kinda > surprising. Haskell's module system is supposed to be just namespace

Re: Prelude and (:) and []((:), []) bugs?

2001-09-21 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 20 Sep 2001 13:32:54 +0100, Simon Marlow <[EMAIL PROTECTED]> pisze: > (:) is allowed in an export list; it is just a normal operator. Not quite, it's a reservedop. "Notice that a colon by itself, ":", is reserved solely for use as the Haskell list constructor; this makes its treatment unifo

Re: Type Problem

2001-09-16 Thread Marcin &#x27;Qrczak' Kowalczyk
Sun, 16 Sep 2001 16:28:01 +0800 (GMT-8), Saswat Anand <[EMAIL PROTECTED]> pisze: > trickyFun fun = let x = fun (2::Int) ---(1) > y = fun 'c'---(2) > in "tricky" It can't be done this way in standard Haskell. In GHC and Hugs you

Re: Application letters at the Haskell workshop: suggestion

2001-09-16 Thread Marcin &#x27;Qrczak' Kowalczyk
Sat, 15 Sep 2001 15:44:52 -0500, Duncan Coutts <[EMAIL PROTECTED]> pisze: > I've been using a few variants: single error, multiple error and multiple > error/warning types. I'm also particularly pleased with one that has an > extra combinator which allows seperate 'branches' of an expression to >

Re: The future of Haskell discussion

2001-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 14 Sep 2001 11:51:14 +0100 (BST), D. Tweed <[EMAIL PROTECTED]> pisze: > As a general question (and forgive my ignorance): are the various ffi's > implemented using something like `dlopen' or are they done by actually > putting suitable stubs into the Haskell generated C-code which then gets

Re: Application letters at the Haskell workshop: suggestion

2001-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 14 Sep 2001 12:10:27 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze: > Maybe it should be clarified that there are exceptions in > H98, but *only* in the IO monad. What the extension is > about are exceptions in pure functions. BTW, Exceptions are useful for something other than

Re: The future of Haskell discussion

2001-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 14 Sep 2001 18:04:24 +0300, Eray Ozkural <[EMAIL PROTECTED]> pisze: > I understand that you ought to deal with name mangling at some stage, > but how would the interfaces ultimately look like? It depends how sophisticated tools we create. The easy step is to wrap everything in functions. Th

Re: The future of Haskell discussion

2001-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 14 Sep 2001 02:09:21 -0700, Julian Seward (Intl Vendor) <[EMAIL PROTECTED]> pisze: > The lack of any way to interface to C++ is a problem, IMO. > I would love to be able to write Haskell programs using Qt > and ultimately the KDE libraries, both of which are C++, but > I can't, at the mo.

Re: Application letters at the Haskell workshop: suggestion

2001-09-14 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 14 Sep 2001 01:00:06 +0200, Lennart Augustsson <[EMAIL PROTECTED]> pisze: > I have been writing substantial Haskell programs and I use *NO* > experimental features. In a 2000-line interpreter I used: - FiniteMap (for environments), - Dynamic & Exception (for exceptions in the language being

Re: The future of Haskell discussion

2001-09-12 Thread Marcin &#x27;Qrczak' Kowalczyk
12 Sep 2001 12:37:25 -, [EMAIL PROTECTED] <[EMAIL PROTECTED]> pisze: > * Currently HOPS implements only one evaluation strategy, > namely leftmost outermost graph rewriting with sharing preservation > (without automatic sharing maximisation). > With the standard rules in place, this co

Re: Haskell report (August release)

2001-09-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 23 Aug 2001 10:00:35 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > Please check it out. My plan is that if I hear nothing for a month, > I'll freeze it. Otherwise I'll iterate. I'll send some minor issues in September (much less than before it seems). Please wait... -- __("<

Re: The future of Haskell discussion

2001-09-12 Thread Marcin &#x27;Qrczak' Kowalczyk
Wed, 12 Sep 2001 11:00:38 +0100, Olaf Chitil <[EMAIL PROTECTED]> pisze: > Mark Shields: Lightweight Modules for Haskell > Shortly stated that he is working on a new module system and would like > every interested person to join. I'm interested. How to join? -- __("< Marcin Kowalczyk * [EMAIL

Re: H98: Ix class

2001-09-11 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 11 Sep 2001 09:16:11 -0400, Jan-Willem Maessen <[EMAIL PROTECTED]> pisze: > Just to clarify, do we still require identities (1) and (3) below > (pasted from the Library report and numbered)? That is, is range > obliged to yield its results in strict index order? [This rules out > Ix instan

Re: micro-rant

2001-08-09 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 9 Aug 2001 09:27:40 +0200, Florian Hars <[EMAIL PROTECTED]> pisze: > Yes, getting a sytax error if I write (x-1)*(-x-1) is a real stumbling block. It's not a syntax error. -- __("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA Z

Re: micro-rant

2001-08-09 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 7 Aug 2001 20:20:49 -0700, Memovich, Gary <[EMAIL PROTECTED]> pisze: > As long as were trying to clean up a final version of the Haskell > 98 report, lets simplify it a little by getting rid of unary minus. I'm against removing it, even if compatibility was not an issue. Yes, it's an irreg

Re: FW: Haskell 98 report problem re lexical structure.

2001-07-25 Thread Marcin &#x27;Qrczak' Kowalczyk
Wed, 25 Jul 2001 17:57:59 +0200 (MET DST), Christian Sievers <[EMAIL PROTECTED]> pisze: > The sequence of dashes must not be followed by another symbol, > for example --> or --| do not begin a comment, they are just > ordinary lexemes. Nor preceded. This is symmetrical, it's not dashes that sta

Re: beginner's questions - fix f

2001-07-24 Thread Marcin &#x27;Qrczak' Kowalczyk
24 Jul 2001 12:04:33 -, Lars Henrik Mathiesen <[EMAIL PROTECTED]> pisze: > Now, anything that's defined as "x = f x" is called a fixpoint of f. > It's possible to prove that there's only one (when f is a Haskell > function, at least) so we can talk of 'the' fixpoint. Not necessarily only one

Re: Picky details about Unicode (was RE: Haskell 98 Report possible errors, part one)

2001-07-24 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 23 Jul 2001 11:23:30 -0700, Mark P Jones <[EMAIL PROTECTED]> pisze: > I guess the intention here is that: > > symbol -> ascSymbol | uniSymbol_ Right. > In fact, since all the characters in ascSymbol are either > punctuation or symbols in Unicode, the inclusion of ascSymbol > is redunda

Re: Haskell 98 Report possible errors, part one

2001-07-23 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 23 Jul 2001 15:11:32 +0100, Olaf Chitil <[EMAIL PROTECTED]> pisze: > Both don't allow a simple translation of Haskell into the Haskell > kernel, > e.g. you cannot translate [1..] into Prelude.enumFrom 1, because the > latter may be ambiguous. That's why I was proposing that importing anothe

Haskell 98 Report possible errors, part one

2001-07-22 Thread Marcin &#x27;Qrczak' Kowalczyk
0.4.1. "http:://haskell.org" - typo. Same in the Library Report. 2.2. "any UNIcode character" - spelling inconsistent with "Unicode" elsewhere. Same in appendix B. 2.2. Identifiers can use small and large Unicode letters. What about caseless scripts where letters are neither small nor large? The

Re: Counting Constructors

2001-07-17 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 17 Jul 2001 12:08:51 +0200 (MEST), Tobias Haeberlein <[EMAIL PROTECTED]> pisze: > show (Succ ( ... (Succ Zero)..)) = n > (where n is the number of Succ's) > and > > show (Succ ( ... (Succ x)..)) = show x > (when x != Zero) This is not possible i

Re: library Directory.hs

2001-06-19 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 19 Jun 2001 10:23:30 +0200, Nicole Gabler <[EMAIL PROTECTED]> pisze: > I have a problem: I need the library Directory.hs. But > there is no directory.hs in {Hugs}/lib/ !! All standard > libraries are there expect of this one. Not exactly: Time and CPUTime are also missing. > Is there any a

Re: A problem with the typing system.

2001-06-03 Thread Marcin &#x27;Qrczak' Kowalczyk
Sat, 02 Jun 2001 23:03:29 +1000, Sean Seefried <[EMAIL PROTECTED]> pisze: > zero = \s z ->z > succ x = \s z -> s x (x s z). > > I don't think it's important that I explain why I want the extra > occurrence of x there. I don't understand what the extra x means, so I can only explain what errors

Re: fromInteger

2001-06-01 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 1 Jun 2001 15:25:24 -0700, Saswat Anand <[EMAIL PROTECTED]> pisze: > I can't understand how the arithmatic operators like (+),(-) are = > defined and fromInteger works in that context. They are all in class Num. fromInteger is automatically inserted before all integer literals, e.g. '42' is

Re: Haskell 98 Report

2001-06-01 Thread Marcin &#x27;Qrczak' Kowalczyk
31 May 2001 16:10:43 -0600, Alastair David Reid <[EMAIL PROTECTED]> pisze: > and > > if foo has type > > foo :: (Ord a) => ty > > then fooBy has type > > fooBy :: (a -> a -> Bool) -> ty It's (a -> a -> Ordering) -> ty, with the default value being compare. -- __("< Marcin K

Re: Unicode

2001-05-25 Thread Marcin &#x27;Qrczak' Kowalczyk
Sat, 26 May 2001 03:17:40 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > Is there a way to convert a Haskell String into a UTF-16 > encoded byte stream without writing to a file and then > reading the file back in? Sure: all conversions are available as memory to memory conversions for dir

Re: Unicode

2001-05-24 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 24 May 2001 14:41:21 -0700, Ashley Yakeley <[EMAIL PROTECTED]> pisze: >> - Initial Unicode support - the Char type is now 31 bits. > > It might be appropriate to have two types for Unicode, a UCS2 type > (16 bits) and a UCS4 type (31 bits). Actually it's 20.087462841250343 bits. Unicode

Re: Problem to load the file Stack.hs with Hugs98

2001-05-21 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 21 May 2001 20:51:37 +0200, Mickaël GAUTIER <[EMAIL PROTECTED]> pisze: > I would like to use the file stack.hs wich is provided with Hugs 98 but > the following message errors display: > "Haskell98 does not support restricted type synonyms" > Can you explain me why and how I can load stack.h

Re: Monomorphize, was: Re: Proposal for generalized function partition in List-library

2001-05-18 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 18 May 2001 12:32:11 -0700, John Meacham <[EMAIL PROTECTED]> pisze: > this is interesting, could someone give an example of how polymorphic > recursion would disallow specialization of a function? test:: Show a => a -> [String] test x = show x : test [x] -- __("< Marcin Kowalczyk * [EMA

Re: Templates in FPL?

2001-05-18 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 18 May 2001 11:25:14 +0200, Jerzy Karczmarczuk <[EMAIL PROTECTED]> pisze: > Always when somebody mentions templates in presence of a True > Functionalist Sectarian, the reaction is "What!? Abomination!!". They aren't that wrong, but they have some problems: * It's not specified what interf

Re: Proposal for generalized function partition in List-library

2001-05-17 Thread Marcin &#x27;Qrczak' Kowalczyk
17 May 2001 19:36:44 GMT, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> pisze: > PS. What I would perhaps put into standard library: And also: split :: (a -> Bool) -> [a] -> [[a]] split p c = let (xs, ys) = break p

Re: Proposal for generalized function partition in List-library

2001-05-17 Thread Marcin &#x27;Qrczak' Kowalczyk
Thu, 17 May 2001 10:06:55 +0200, Bernd Holzmüller <[EMAIL PROTECTED]> pisze: > I would like to propose a new function for module List that generalizes > the current function partition :: (a -> Bool) -> [a] -> [[a]] No, current partition has type (a -> Bool) -> [a] -> ([a], [a]) so your function

Re: BAL paper available

2001-05-15 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 15 May 2001 21:14:02 +0300, Dylan Thurston <[EMAIL PROTECTED]> pisze: >> Nor hard numeric work (efficient, easy to manipulate arrays). > > If I understand correctly, Marcin Kowalczyk is working on exactly > this last point... Well, I improved efficiency of ghc's arrays by removing various

Re: BAL paper available

2001-05-15 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 15 May 2001 16:10:20 +0400, S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > The matter was always in parametric domains ... The solution is simple: don't model domains as types. Model them as values (records with operations). Some simple domains can be also modelled as types for convenience.

Fundeps and class contexts

2001-05-10 Thread Marcin &#x27;Qrczak' Kowalczyk
Would allowing this make sense? class C a b | a -> b class C a b => S a I want to simulate a particular "class synonym" (with four superclasses instead of one C here) where the type 'b' is uninteresting for its users. Currently I have to write class C a b | a -> b class C a b =>

Re: Scoped type variables

2001-05-08 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 8 May 2001 08:25:39 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > I was meaning in the translation into System F of the program. [...] Ah, OK, sorry. More strange behavior of Hugs (none of this is allowed by ghc): \(x :: a) (y :: b) -> x+y -- not allowed \(x :: a) -> \(y

Re: Scoped type variables

2001-05-08 Thread Marcin &#x27;Qrczak' Kowalczyk
Tue, 8 May 2001 00:47:58 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > g = \x::(Int,Bool) -> let-type (a,b) = (Int,Bool) in e > > But notice that the RHS of a pattern-matching let-type is statically > guaranteed to have the right shape. So I don't allow > > let-type (a,b)

Re: User defined Ix instances potentially unsafe

2001-05-07 Thread Marcin &#x27;Qrczak' Kowalczyk
Mon, 7 May 2001 03:15:16 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > The constraint (*) also specifies that 'range' returns subscripts > in increasing order of index. That seems reasonable, but perhaps > less important. It is important if elems should return elements in the same orde

Re: Help wanted with hugs error message

2001-05-04 Thread Marcin &#x27;Qrczak' Kowalczyk
Fri, 04 May 2001 20:06:23 +0100, Robert Ennals <[EMAIL PROTECTED]> pisze: > "exp" is defined as exponentiation, as part of the "Floating" > type class in the standard Prelude - which is imported by default. And to fix the problem you may do either of these: * import Prelude hiding (exp) * Use Fa

  1   2   3   4   5   >