Re: Wanted: local data, class, instance declarations

2006-01-30 Thread Bulat Ziganshin
Hello Johannes, Friday, January 27, 2006, 1:00:42 PM, you wrote: JW let instance Ord Item where ... JW xs :: [ Item ] ; xs = ... JW in sort xs are you familiar with generic haskell? one of its features is the local definitions of the special cases for generic functions, what is close to

strict Haskell dialect

2006-02-01 Thread Bulat Ziganshin
Hello John, Wednesday, February 01, 2006, 6:48:48 AM, you wrote: On the other hand, if pattern bindings were strict by default, I bet there would be a lot fewer accidental space leaks. JM I don't think this is true. I think there would just be a whole lot of a JM different type of space leak.

Re[2]: ~ patterns

2006-02-01 Thread Bulat Ziganshin
Hello Simon, Tuesday, January 31, 2006, 1:31:26 PM, you wrote: SM We must find *something* to throw away though! :-) newspeak is the only language whose dictionary is decreasing (c) 1984 :) at least from library we should throw many things, including old exceptions, data.array and of course

Re[2]: Comment Syntax

2006-02-02 Thread Bulat Ziganshin
Hello Manuel, Thursday, February 02, 2006, 3:40:26 AM, you wrote: MMTC I am against such a change. The change would break existing software MMTC (eg, Yampa) and secondly I don't buy the main sources of MMTC confusion for beginners argument. The confusion arises only when a MMTC single line

Re[2]: strict Haskell dialect

2006-02-02 Thread Bulat Ziganshin
Hello John, Thursday, February 02, 2006, 4:24:06 AM, you wrote: It can, but so far it's really ugly to apply transformations to entire modules. A little syntactic sugar could be good there. JM module $hat.Foo(..) where JM ... JM could mean pass the entire module through the 'hat' function of

Re[2]: Wanted: local data, class, instance declarations

2006-02-02 Thread Bulat Ziganshin
Hello John, Thursday, February 02, 2006, 6:03:06 AM, you wrote: Unfortunately, local instance declarations threaten the coherence property of type classes and principle types. See for example, ``Functional pearl: implicit configurations—or, type classes reflect the values of types'', Sect

Re[2]: Test performance impact (was: The dreaded M-R)

2006-02-02 Thread Bulat Ziganshin
Hello John, Thursday, February 02, 2006, 12:51:58 PM, you wrote: JH Let me make clear that what concerns me is not the impact of the M-R on JH space and time JH performance on average. What concerns me is the difficulty of debugging JH performance JH problems. may be it's better in such case

Re: fundeps syntax is ugly

2006-02-02 Thread Bulat Ziganshin
Hello Johannes, Thursday, February 02, 2006, 2:17:42 PM, you wrote: JW When I first learned functional dependencies JW I remember I was really confused by their syntax. JW First, it is hard to find it defined: i should wrote this earlier, but nevertheless: Hugs documentation contains

Re[2]: fundeps syntax is ugly

2006-02-02 Thread Bulat Ziganshin
Hello Bulat, Thursday, February 02, 2006, 3:48:45 PM, you wrote: JW When I first learned functional dependencies JW I remember I was really confused by their syntax. JW First, it is hard to find it defined: BZ Hugs documentation contains excellent introduction into the fundeps. namely chapter

Re[2]: give equal rights to types and classes! :)

2006-02-03 Thread Bulat Ziganshin
Hello Wolfgang, Friday, February 03, 2006, 2:22:17 AM, you wrote: 1) significantly simplifies declarations using typeclasses. i was seriously bitten by those huge declarations, and think that simplification in this area will lead to much wider use of type classes by the ordibary users (like

Re: Unary operators [was: Re: ~ patterns]

2006-02-03 Thread Bulat Ziganshin
Hello Benjamin, Friday, February 03, 2006, 2:29:47 AM, you wrote: (+ x) --- (? + x) i like this idea! but i tink that it's too late for such incompatible change :( really, unary operators can be added to language without any troubles. we need only to prohibit using of the same symbol for unary

Re[2]: Priorities

2006-02-03 Thread Bulat Ziganshin
Hello Tomasz, Friday, February 03, 2006, 10:52:22 AM, you wrote: Personally, I'm not sure about caseless underscore, concurrency, natural numbers and parallel list comprehensions. TZ The design of Haskell was so great, that we could add concurrency as TZ a library without introducing

Re[2]: Comment Syntax

2006-02-03 Thread Bulat Ziganshin
Hello John, Friday, February 03, 2006, 3:39:38 AM, you wrote: Got a unicode-compliant compiler? JM sure do :) JM but it currently doesn't recognize any unicode characters as possible JM operators. are you read this? :) Log: Add support for UTF-8 source files GHC finally has

Re[2]: strict Haskell dialect

2006-02-03 Thread Bulat Ziganshin
Hello Wolfgang, Friday, February 03, 2006, 1:46:56 AM, you wrote: i had one idea, what is somewhat corresponding to this discussion: make a strict Haskell dialect. implement it by translating all expressions of form f x into f $! x and then going to the standard (lazy) haskell translator.

Re[2]: Priorities

2006-02-03 Thread Bulat Ziganshin
Hello Tomasz, Friday, February 03, 2006, 2:00:23 PM, you wrote: Personally, I'm not sure about caseless underscore, concurrency, natural numbers and parallel list comprehensions. TZ The design of Haskell was so great, that we could add concurrency as TZ a library without

Re[2]: Priorities

2006-02-04 Thread Bulat Ziganshin
Hello John, Friday, February 03, 2006, 8:11:48 PM, you wrote: Yes. Plus, I'd say, the presence of threading primitives that return certain well-defined exceptions or something along those lines, so that it's not necessary to know whether multithreading is supported at compile time. JM

Re[2]: give equal rights to types and classes! :)

2006-02-04 Thread Bulat Ziganshin
Hello Marcin, Saturday, February 04, 2006, 2:23:50 AM, you wrote: if my idea was incorporated in Haskell, this change don't require even changing signatures of most functions working with arrays - just Array type become Array interface, what a much difference? What would 'Eq - Eq - Ord -

Re[3]: give equal rights to types and classes! :)

2006-02-04 Thread Bulat Ziganshin
Hello Dave, Saturday, February 04, 2006, 3:52:46 AM, you wrote: Now i'm trying to generalize my functions parameters/results to type classes instead of single types. for example, getFileSize function can return any numeric value, be it Integer, Word or Int64. This, naturally, results in those

Re[2]: strict Haskell dialect

2006-02-04 Thread Bulat Ziganshin
Hello Tomasz, Saturday, February 04, 2006, 12:39:38 PM, you wrote: make a strict Haskell dialect. TZ I am with you. If Haskell switches to strictness, as i said, strict _dialect_ is interesting for optimization, moving from other languages and making strict variants of data structures --

extending bang proposal Re: strict Haskell dialect

2006-02-06 Thread Bulat Ziganshin
Hello Ketil, Monday, February 06, 2006, 4:06:35 PM, you wrote: foo :: !Int - !Int KM (Is the second ! actually meaningful?) yes! it means that the function is strict in its result - i.e. can't return undefined value when strict arguments are given. this sort of knowledge should help a

Re[2]: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-06 Thread Bulat Ziganshin
Hello Henning, Monday, February 06, 2006, 4:12:44 PM, you wrote: In my opinion all the special syntactic sugar for lists should go away. I don't think lists are special enough to motivate it. HT Fine, someone shares my attitude towards the list sugar. Nevertheless, do HT you mean with 'no

Re[2]: Restricted Data Types

2006-02-07 Thread Bulat Ziganshin
Hello John, Tuesday, February 07, 2006, 4:23:36 AM, you wrote: data Eq a = Set a = Set (List a) that is a sort of extension i will be glad to see. in my Streams library, it's a typical beast and i forced to move all these contexts to the instances/functions definitions: data

Re[2]: Tuple-like constructors

2006-02-07 Thread Bulat Ziganshin
Hello Robert, Tuesday, February 07, 2006, 6:42:41 PM, you wrote: More disturbing is the complete inability to write general functions over tuples. RD As I understand it, you still have to write down the instance RD declarations when using '-fgenerics'. only one generic instance. it's very

Re[2]: Priorities

2006-02-08 Thread Bulat Ziganshin
Hello John, Friday, February 03, 2006, 12:00:32 PM, you wrote: JM If we had a good standard poll/select interface in System.IO then we JM actually could implement a lot of concurrency as a library with no JM (required) run-time overhead. I'd really like to see such a thing get JM into the

Re[2]: Java-like

2006-02-08 Thread Bulat Ziganshin
Hello Ian, Wednesday, February 08, 2006, 9:28:51 PM, you wrote: nonrecursive let in Haskell so that I could write let x = ...x... in ..., IL I would argue that the language should discourage variable shadowing, so IL that shadow warnings can be used to find bugs. i use such shadowing to change

Re: runtime reflection for classes

2006-02-09 Thread Bulat Ziganshin
Hello Johannes, Thursday, February 09, 2006, 1:43:38 PM, you wrote: JW With Data.Generics, we can get an object's type, constructor and fields. really, SYB way to metaprogramming is just to encode information about type in the datastructure. you can do somethiong in this fashion just by

Re[2]: runtime reflection for classes

2006-02-09 Thread Bulat Ziganshin
Hello Johannes, Thursday, February 09, 2006, 2:43:49 PM, you wrote: again TH can be used and you will be limited only by the volume of information, available for TH code. JW Is information such as instance C t1 t2 .. available for such code? JW I guess not since this would require

Re[2]: Pragmas for FFI imports

2006-02-22 Thread bulat . ziganshin
Hello Simon, Wednesday, February 22, 2006, 12:53:09 PM, you wrote: SM simplicity, packages are the unit in several concepts: distribution, SM dependency, versioning, licensing, dynamic linking, include file SM dependencies, external library dependencies, and more. If we start SM confusing the

Re[2]: Array interface refactoring

2006-02-22 Thread Bulat Ziganshin
Hello Ben, Wednesday, February 22, 2006, 9:47:19 PM, you wrote: BRG While we're on the topic, I have a couple of problems with the current array BRG system that cut deeper than the naming: BRG * The function for getting the bounds of an MArray is pure, so the BRGinterface can't

Re[2]: Module System

2006-02-23 Thread Bulat Ziganshin
Hello Simon, Thursday, February 23, 2006, 2:21:22 PM, you wrote: SMghc --make My.Dotted.Module.hs Main.hs SM works fine. Similarly with GHCi. i don't known that. we should add this to faq SM It's only when GHC has to actually *find* a source file for a module SM that the hierarchical

Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus, Friday, February 24, 2006, 2:46:40 PM, you wrote: CR yes, this would add one constraint on where to place definitions. but CR grouping logically related definitions together is not quite what one CR might think anyway: aren't the definitions making up the interface CR most strongly

Re[2]: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus, Friday, February 24, 2006, 6:55:51 PM, you wrote: CR not quite (though I believe that would be close to Simon M's idea). CR in my modification, both map and length would move completely CR into the export section WHY? it's not the interface. implementation of exported functions is

Re[2]: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus, Friday, February 24, 2006, 7:53:09 PM, you wrote: CR public class C a CR where CR public m1 :: a CR private m2 :: a - String please don't stop on this! public map (private f) (public (private x:public xs)) = private (public f (private x)) `public :`

Re[2]: overlapping instances and constraints

2006-02-28 Thread Bulat Ziganshin
Hello John, Tuesday, February 28, 2006, 4:23:24 AM, you wrote: i had plans to propose the same and even more: instance C2 a b | a/=b JM I was thinking it would be all kinds of useful if we had two predefined JM classes JM class Eq a b JM class NEq a b JM where Eq has instances exactly

Re[2]: overlapping instances and constraints

2006-02-28 Thread Bulat Ziganshin
Hello Claus, Tuesday, February 28, 2006, 1:54:25 PM, you wrote: CR class NEq a b CR instance Fail a = NEq a a CR instance NEq a b i think that this definition just use ad-hoc overlapping instances resolution mechanism that we want to avoid :))) -- Best regards, Bulat

Re[2]: Keep the present Haskell record system!

2006-03-06 Thread Bulat Ziganshin
Hello Claus, Monday, March 6, 2006, 4:30:04 PM, you wrote: my own opinion is that this scheme is like classes - they can be resolved at compile time in most real cases but noone do it because code will be too large. if some function can accept any records which has field 'a' then to use this

Re: small extension to `...` notation

2006-03-09 Thread Bulat Ziganshin
Hello Doaitse, Thursday, March 9, 2006, 12:01:37 AM, you wrote: DS xs `zipWith (+)` ys i had the same desire several times Possibly `(expr)` ? it will be non-readable. it is better to just prohibit using of backquotes inside backquotes. and fixity can be fixed at 0, imho. at least, my

Re[2]: darcs patch: add Data.Set.notMember and Data.Map.notMember

2006-03-10 Thread Bulat Ziganshin
Hello Christian, Friday, March 10, 2006, 2:32:02 PM, you wrote: f x | not (x `Set.member` map) foo = ... is hard to read. btw, (x `not.Set.member` map), as proposed by Doaitse Swierstra, will look better in this case -- Best regards, Bulatmailto:[EMAIL

Re[2]: [Haskell-cafe] STUArray

2006-03-12 Thread Bulat Ziganshin
Hello Chris, Sunday, March 12, 2006, 2:05:09 PM, you wrote: CK Is GHC.PArr documented? it's perfectly documented in module sources itself :) you can also look at the ndpFlatten directory in ghc compiler's sources. i've successfully used them in my program, of course this makes program faster

Re[2]: the MPTC Dilemma (please solve)

2006-03-19 Thread Bulat Ziganshin
Hello Lennart, Sunday, March 19, 2006, 4:05:03 AM, you wrote: LA I have to agree with Manuel. I write a lot of Haskell code. LA People even pay me to do it. I usually stay with Haskell-98, when i wrote application code, i also don't used extensions very much, i even don't used Haskell-98 very

Re[4]: Keep the present Haskell record system!

2006-03-19 Thread Bulat Ziganshin
Hello Claus, Monday, March 6, 2006, 2:35:04 PM, you wrote: also, while i like dynamic records for some types of tasks, i think that the spirit of Haskell in whole is to give explicit definitions of all types used and in this respect this type extension in not on main way. CR record

Re[4]: the MPTC Dilemma (please solve)

2006-03-19 Thread Bulat Ziganshin
Hello Manuel, Sunday, March 19, 2006, 7:25:44 PM, you wrote: i had a class which defines default reference type for monads: class Ref m r | m-r where to be exact, class Ref m r | m-r, r-m where newRef :: a - m (r a) readRef :: r a - m a writeRef :: r a - a - m () or even worser:

Re[2]: Strict tuples

2006-03-20 Thread Bulat Ziganshin
Hello Simon, Monday, March 20, 2006, 1:47:52 PM, you wrote: i've proposed to allow adding strict mark to any type constructors and type constructor parameters so that finally we can define any data structure that can be defined in strict languages. in particular: type StrictPair a b = !(,)

Re[2]: Strict tuples

2006-03-22 Thread Bulat Ziganshin
Hello Wolfgang, Wednesday, March 22, 2006, 1:29:24 AM, you wrote: you said WHAT you think but not said WHY? my motivation is to be able to use myriads of already implemented algorithms on new datatypes as i said, shebang patterns allow only to specify that IMPLEMENTATION of some function is

Ticket #15: add a binary IO interface

2006-03-22 Thread Bulat Ziganshin
Hello , about this - i'm almost sure that current widely used libraries (NewBinary) is not as good as my own one (http://freearc.narod.ru/Streams.tar.gz) is not ever used and even still not documented, so it is not easy to make right choice :) -- Best regards, Bulat

Re: Ticket #15: add a binary IO interface

2006-03-24 Thread Bulat Ziganshin
Hello Bulat, Wednesday, March 22, 2006, 4:38:13 PM, you wrote: BZ about this - i'm almost sure that current widely used libraries BZ (NewBinary) is not as good as my own one BZ (http://freearc.narod.ru/Streams.tar.gz) is not ever used and even BZ still not documented, so it is not easy to make

Re[2]: important news: refocusing discussion

2006-03-25 Thread Bulat Ziganshin
Hello Ross, Saturday, March 25, 2006, 4:16:01 AM, you wrote: On Fri, Mar 24, 2006 at 02:47:09PM -, Simon Marlow wrote: I think it would be a mistake to relegate concurrency to an addendum; it is a central feature of the language, and in fact is one area where Haskell (strictly speaking

unicode/internalization issues

2006-03-26 Thread Bulat Ziganshin
Hello haskell-prime, i've planned some time ago to open unicode/internalization wiki page, what reflects current state of the art in this area. here is the information i have, please add/correct me if i don't know something or wrong. 1. Char supports full Unicode range (about million of chars)

the following program can't be compiled with ghc 6.4.1

2006-03-28 Thread Bulat Ziganshin
to be fair, it also don't work with Hugs 03 and Hugs 05 data UnboxedMutableArray i e = UMA !i !i type IOUArray i e = UnboxedMutableArray i e data Dynamic a i e = Dynamic (a i e) type DynamicIOUArray s = Dynamic IOUArray if second line substituted with the following type IOUArray =

Re[2]: FFI, safe vs unsafe

2006-04-01 Thread Bulat Ziganshin
Hello John, Saturday, April 1, 2006, 4:53:00 AM, you wrote: In an implementation which runs more than one Haskell thread inside one OS thread, like ghc without -threaded or hugs, the threads are NOT completely independent, because they share one C stack. So while no, state-threads, a la

Re[4]: thread priorities?

2006-04-01 Thread Bulat Ziganshin
Hello Simon, Friday, March 31, 2006, 4:57:19 PM, you wrote: threadSetPriority :: ThreadID - Int - IO () it was requested by Joel Reymont, and he even give us information how that is implemented in Erlang, together with hint to assign higher priorities to consuming threads. Yes, but the

Re[2]: Concurrency

2006-04-01 Thread Bulat Ziganshin
Hello David, Saturday, April 1, 2006, 4:31:05 PM, you wrote: I'd like to be sure that asynchronous exceptions can get into the standard. They require concurrency, but I'm not sure that they're included in John's page. this an another ticket It would also be nice to address signal behavior,

Re[2]: FFI, safe vs unsafe

2006-04-03 Thread Bulat Ziganshin
Hello John, Monday, April 3, 2006, 12:53:05 PM, you wrote: new stacks can be allocated by alloca() calls. all these alloca-allocated stack segments can be used as pool of stacks assigned to the forked threads. although i don't tried this, my own library also used processor-specific method.

Re[2]: FFI, safe vs unsafe

2006-04-04 Thread Bulat Ziganshin
Hello John, Tuesday, April 4, 2006, 5:55:19 AM, you wrote: In my survey of when 'reentrant concurrent' was needed, I looked at all the standard libraries and didn't find anywhere it was actually needed. Are there some compelling examples of when it is really needed in a setting that doesn't

Deriving for newtypes

2006-04-04 Thread Bulat Ziganshin
Hello , as i see, it was some form of formal specification for subj: http://www.cse.unsw.edu.au/~dons/haskell-1990-2000/msg05468.html -- Best regards, Bulat mailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list

Re[2]: 'deriving Tree (Eq,Ord)'

2006-04-04 Thread Bulat Ziganshin
Hello Ross, Tuesday, April 4, 2006, 4:55:09 PM, you wrote: http://www.cse.unsw.edu.au/~dons/haskell-1990-2000/msg00727.html (Making 'deriving' a separate declaration instead of a clause) Orphan instances are discouraged in the GHC libraries, so there might not be much support for adding a

Re[2]: deeqSeq proposal

2006-04-11 Thread Bulat Ziganshin
Hello John, Tuesday, April 11, 2006, 2:43:49 AM, you wrote: true. in any case, deepseq is not always a win. don't forget that Andy don't plan to apply deepSeq to any expression. in his program, there is a LARGE datastructure with a couple of unevaluated thunks what may be simplified by call to

Re: Class ATs Question

2006-04-28 Thread Bulat Ziganshin
Hello Ashley, Friday, April 28, 2006, 5:09:07 AM, you wrote: You can do two-way fundeps. Can these be done with associated types? For instance: It might not be a great loss if not. may be you want to say it might be a great loss ? i'm using two-way fundeps to implement monad-independent

Re[2]: Class System current status

2006-05-12 Thread Bulat Ziganshin
Hello Stephanie, Thursday, May 11, 2006, 5:45:15 PM, you wrote: - We're already in that state. There *is* a lot of Haskell code that uses FDs, it's just not Haskell 98 code. Whenever ATs take over, we'll still have to deal with this code. are you sure about *lots* ? i seen only 3-4 ones

Re[2]: Class System current status

2006-05-12 Thread Bulat Ziganshin
Hello Johannes, Friday, May 12, 2006, 4:18:29 PM, you wrote: = Partial p i b | p i - b where ... -- (*) (*) A funny visual aspect of FDs is the absurd syntax. On the left of |, the whitespace is (type arg) application, but on the right, it suddenly denotes sequencing (tupling) i

Re[2]: Class System current status

2006-05-12 Thread Bulat Ziganshin
Hello Simon, Friday, May 12, 2006, 8:05:25 PM, you wrote: My suggestion is this: * Specify MPTCs in the main language * Specify FDs in an Appendix (with some reasonably conservative interpretation of FDs). * A Haskell' implementation should implement the Appendix, and

allow to give default implementatoions for methods of base class

2006-08-14 Thread Bulat Ziganshin
Hello Jon, Monday, August 14, 2006, 1:49:58 PM, you wrote: instance Monad [] where fmap = map return x = [x] join = concat i support this idea. [...] I'm not sure it's quite right. Surely it only makes sense if it defines all the (necessary) superclass methods -- in

Re[4]: All Monads are Functors

2006-08-14 Thread Bulat Ziganshin
Hello Taral, Monday, August 14, 2006, 3:34:29 PM, you wrote: On 8/14/06, Jon Fairbairn [EMAIL PROTECTED] wrote: of course, there's no reason to do that, but what I'm proposing is that we allow default instance declarations in class declarations in much the same way as default methods: I

Re[2]: map and fmap

2006-08-15 Thread Bulat Ziganshin
Hello Duncan, Tuesday, August 15, 2006, 2:37:50 AM, you wrote: If it goes in that direction it'd be nice to consider the issue of structures which cannot support a polymorphic map. Of course such specialised containers (eg unboxed arrays or strings) are not functors but they are still useful

Re[2]: Exceptions

2006-09-01 Thread Bulat Ziganshin
Hello Simon, Thursday, August 31, 2006, 12:33:26 PM, you wrote: I don't think we need more extensions to do a reasonable job of extensible exceptions: http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf i'm not yet read but guess that this is paper you will present at ICFP? can you

Re[2]: Exceptions

2006-09-01 Thread Bulat Ziganshin
Hello Andres, Friday, September 1, 2006, 2:27:34 PM, you wrote: Thanks for your interest in open data types. As one of the authors of the open data types paper, I'd like to comment on the current discussion. i'm not yet read about this, but may be open types have something in common with

Re[4]: Exceptions

2006-09-06 Thread Bulat Ziganshin
Hello Manuel, Wednesday, September 6, 2006, 9:17:46 PM, you wrote: So, both features are truly orthogonal and, in fact, they are synergetic! More precisely, an alternative syntax for Löh/Hinze open types are overlapping type families. So, we might define S alternatively as data

Re[2]: Pattern guards

2006-09-28 Thread Bulat Ziganshin
Hello Conor, Thursday, September 28, 2006, 10:30:46 PM, you wrote: gcd x y | compare x y - LT = gcd x (y - x) GT = gcd (x - y) y gcd x _ = x or some such. I wish I could think of a better example without too much context, but such a thing escapes me for the moment. In general,

Two things that i still can't understand in Haskell standard

2006-10-14 Thread Bulat Ziganshin
Hello haskell-prime, first is the monomorphism restriction. why isn't it possible to check _kind_ of parameter-less equation and apply monomorphism restrictions only to values of kind '*'? so, this: sum = foldr1 (*) will become polymorphic because its kind is '*-*' while this exps = 1 : map

three syntax-sugar proposals

2006-10-14 Thread Bulat Ziganshin
Hello haskell-prime, 1. allow to use '_' in number literals. its used in Ruby and i found that this makes long number literals much more readable. for example maxint = 2_147_483_648 2. allow to use string literals in patterns as head of matched list: optionValue (kb++n) = read n * 2^10

Re: Concurrency

2006-10-15 Thread Bulat Ziganshin
Hello William, Sunday, October 15, 2006, 5:07:26 PM, you wrote: http://www.seas.upenn.edu/~lipeng/homepage/unify.html can this be ported to windows? (i don't yet read the paper) -- Best regards, Bulatmailto:[EMAIL PROTECTED]

Re[2]: (Pattern) Guards in lambdas

2006-10-18 Thread Bulat Ziganshin
Hello Claus, Wednesday, October 18, 2006, 2:44:29 PM, you wrote: (\ arms ) x this looks great. smth like: proc $ \[x] - x*2 \[x,y] - x*y \[]- 0 -- Best regards, Bulatmailto:[EMAIL PROTECTED]

Re: Standard syntax for preconditions, postconditions, and invariants

2006-10-19 Thread Bulat Ziganshin
Hello Alan, Thursday, October 19, 2006, 5:54:06 PM, you wrote: I propose that haskell' include a standard syntax for invariants that the programmer wants to express. The intent is not to have standardized checks on the invariants, its just to supply a common way to specify invariants to

Re: Module imports anywhere

2006-10-22 Thread Bulat Ziganshin
Hello Henning, Sunday, October 22, 2006, 5:48:11 PM, you wrote: I don't see the benefit of allowing imports anywhere at top-level. it is useful to move together imports and related code. say: #if HUGS import Hugs.Base addInt = hugsAddInt #elseif GHC import GHC.Base addInt = ghcAddInt #endif

Re[2]: digit groups

2006-10-25 Thread Bulat Ziganshin
Hello Jon, Wednesday, October 25, 2006, 6:37:33 PM, you wrote: 0x_3729 makes perfect sense as hex and the _ does a nice job of separating the digits into readable groups. 0x~~3729 looks similar, but doesn't mean the same thing at all. 0x~~0x3729 is ugly and probably less

Re[2]: digit groups

2006-10-26 Thread Bulat Ziganshin
Hello Iavor, Thursday, October 26, 2006, 4:51:00 AM, you wrote: kb,mg,gb :: Num a = a kb = 1024 mb = 1024 * kb gb = 1024 * mb b :kb :mb :gb :_ = iterate (1024*) 1 :: [Int] b_:kb_:mb_:gb_:tb_:_ = iterate (1024*) 1 :: [Integer] and now we can write (4 * kb) instead for 4096. btw,

Re[4]: digit groups

2006-10-26 Thread Bulat Ziganshin
Hello Taral, Thursday, October 26, 2006, 6:33:44 PM, you wrote: btw, your variant requires re-calculating values on each their use That's what constant folding is for. are c.f. should work for polymorhic values? afaiu, it's just the problem that leads to the famous monomorhism restriction.

Re[2]: Proposal for stand-alone deriving declarations?

2006-11-02 Thread Bulat Ziganshin
Hello Brian, Thursday, November 2, 2006, 12:15:38 AM, you wrote: In particular, I think having features like : import M1 hiding (instance C T) and     module M hiding (instance C T) would eliminate the need for special-case handling of derived instances (if two imported modules happen

Re[2]: Proposal for stand-alone deriving declarations?

2006-11-02 Thread Bulat Ziganshin
Hello Malcolm, Thursday, November 2, 2006, 12:46:43 AM, you wrote: instance Num (Bar z) where and instance Num (Bar z) The former declares that _no_ methods are defined (except for defaults), and the latter, with your proposal, that _all_ methods are defined. The i join to this

Re: [Haskell-cafe] Fractional/negative fixity?

2006-11-04 Thread Bulat Ziganshin
Hello Dan, Saturday, November 4, 2006, 5:07:15 AM, you wrote: Here's an idea that (I think) is useful and backwards compatible: fractional and negative fixity. yes, i think the same. for example, once i've tried to define postfix 'when' operator like those in perl/ruby print msg `on`

Re[2]: [Haskell-cafe] Fractional/negative fixity?

2006-11-06 Thread Bulat Ziganshin
Hello Henning, Monday, November 6, 2006, 1:27:54 PM, you wrote: print msg `on` mode==debug but failed because my code frequently contains '$' and there is no way to define operation with a lower precedence This could be solved by the solutions proposed in this thread:

Re[4]: [Haskell-cafe] Fractional/negative fixity?

2006-11-08 Thread Bulat Ziganshin
Hello Nicolas, Wednesday, November 8, 2006, 1:25:23 AM, you wrote: prec ?? $ over-specification). You want ?? to bind more tightly than does $; that's exactly what this approach would let you specify. and how then compiler will guess that is relational priority of this operator comparing

Re: String literals

2006-11-11 Thread Bulat Ziganshin
Hello Lennart, Saturday, November 11, 2006, 6:49:15 AM, you wrote: class IsString s where fromString :: String - s My guess is that the defaulting mechanism needs to be extended to default to the String type as well, imho, it is MUST BE. this will allow to became ByteString and any

Re[2]: String literals

2006-11-11 Thread Bulat Ziganshin
Hello Donald, Saturday, November 11, 2006, 7:33:48 AM, you wrote: Yes, pattern matching is the issue that occurs to me too. While string literals :: ByteString would be nice (and other magic encoded in string literals, I guess), what is the story for pattern matching on strings based on

Annotation system for Haskell

2006-11-12 Thread Bulat Ziganshin
Both Java and C# provides annotations that can be used to pass some additional information about code to around-language tools and queried at program runtime via Reflection API: [AuthorAttribute (Ben Albahari)] class A { [Localizable(true)] public String Text { get {return text;

Re[2]: String literals

2006-11-13 Thread Bulat Ziganshin
Hello Simon, Monday, November 13, 2006, 8:27:08 PM, you wrote: In my experience I've seen more requests for overloaded *Boolean* literals than strings. In a Fran context, for example. what you mean by this? а few days ago i've published in cafe small lib that allows to write things like (str

Re[2]: base libraries

2006-11-26 Thread Bulat Ziganshin
Hello Malcolm, Friday, November 24, 2006, 8:26:11 PM, you wrote: i think that we should require H' compatibility instead of H98 one, so require to not use fundeps, but allow MPTC. this means that NHC should be ruled out as non-H' compliant compiler instead of these libs Why pick on nhc98?

Standard (core) libraries initiative: rationale

2006-11-27 Thread Bulat Ziganshin
Hello libraries, like computer is a net, nowadays language is a library. there is nothing exceptional in C++ and Java languages except for their huge library codebase that makes them so widely appreciated while it's impossible for Haskell to have the same level of libraries maturity, we can try

Re[2]: Teaching

2006-11-30 Thread Bulat Ziganshin
Hello Iavor, Thursday, November 30, 2006, 8:41:43 PM, you wrote: However, I am not sure that this particular use justifies the addition of defaulting to the _language_. For example, it is possible that defaulting is implemented as a switch to the command-line interpreter. how about using

Re[2]: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello Rene, Wednesday, January 24, 2007, 10:49:06 PM, you wrote: Going by the traffic over the previous months, I think that class aliases or extensible records would be higher on most peoples lists than views. i think that proper views is a must for Haskell - We are keen on abstraction, but

ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello Simon, Monday, January 22, 2007, 5:57:27 PM, you wrote: adding view patterns to Haskell. many of us was attracted to Haskell because it has clear and simple syntax. but many Hugs/GHC extensions done by independent developers differ in the syntax they used, because these developers either

Re[2]: ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello David, Wednesday, January 31, 2007, 7:12:05 PM, you wrote: data Coord = Coord Float Float view of Coord = Polar Float Float where Polar r d= Coord (r*d) (r+d)-- construction Coord x y | x/=0 || y/=0 = Polar (x*y) (x+y)-- matching This is

Re[4]: ADT views Re: [Haskell] Views in Haskell

2007-02-01 Thread Bulat Ziganshin
Hello J., Thursday, February 1, 2007, 1:36:33 AM, you wrote: Yes - you've reiterated Wadler's original design, with an automatic problems with equational reasoning raised by this approach. ok, i can live without it. i mean reasoning :) i guess that anything more complex than Turing machine

Re[2]: List syntax (was: Re: help from the community?)

2007-02-03 Thread Bulat Ziganshin
Hello Brian, Saturday, February 3, 2007, 10:55:52 AM, you wrote: bracket_ (enter a) (exit a) (do b c)-- looks like LISP... this pattern is very typical in my programs and i use '$' before last

Re: General pattern bindings

2007-04-15 Thread Bulat Ziganshin
Hello Twan, Saturday, April 14, 2007, 5:43:03 AM, you wrote: I did not even know these things existed, is there anyone who actually uses general pattern bindings? b:kb:mb:gb:_ = iterate (1024*) 1 unfortunately, they got monotypes, so at last end i finished with simpler definitions

Re[2]: [Haskell-cafe] global variables

2007-05-20 Thread Bulat Ziganshin
Hello Isaac, Sunday, May 20, 2007, 6:41:54 PM, you wrote: Maybe some sort of ISOLATE, DON'T_OPTIMIZE (but CAF), or USED_AS_GLOBAL_VARIABLE pragma instead of just the insufficient NOINLINE would be a good first step... or LOOK_BUT_DON'T_TOUCH :) -- Best regards, Bulat

Re: default fixity for `quotRem`, `divMod` ??

2007-06-19 Thread Bulat Ziganshin
Hello Isaac, Monday, June 18, 2007, 9:20:29 PM, you wrote: I was just bitten in ghci by `divMod` being the default infixl 9 instead of the same as `div` and `mod`. one of my hard-to-find bugs was exactly in this area: i wrote something like x `div` y+1 instead of x `div` (y+1) so, based

Re[2]: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Bulat Ziganshin
Hello Simon, Wednesday, July 11, 2007, 11:38:31 AM, you wrote: So Greg's idea (or at least my understanding thereof) is to write it like this: do { f $(stuff1) $(stuff2) } Simon, it is thing i dreamed for a years! Haskell has serious drawback for imperative programming compared to

Re[2]: Make it possible to evaluate monadic actions when assigning record fields

2007-07-12 Thread Bulat Ziganshin
Hello Neil, Thursday, July 12, 2007, 3:10:10 PM, you wrote: This extension seems like a great idea - my only concern would be about the order of computations. Clearly left-to-right makes sense, but this may break some natural intuition in Haskell: i think that undefined order will be a best

Standard libraries

2007-11-15 Thread Bulat Ziganshin
Hello haskell-prime, one more proposal is about standard libs. it is well known that today libs outweighs all other parts of modern language and work on their standardization will probably stall the whole Haskell-prime process. OTOH, languages like Java was grown due to their rich set of

  1   2   >