Re[2]: Java-like
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 variable meaning in a part of code -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
exported pattern matching
Sometimes I'd like to use a smart constructor but have pattern matching as well. There has been talk elsewhere of allowing export of data constructors for /matching/ but not for /construction/: module One- data Picky a = Nil | One a picky x = if some_complex_thing x then One x else Nil module Two- f x = g $ picky x g Nil y = y g (One x) y = x h Nil = One True - I'd like for the function g to be fine and the function h to get a complaint like "error: no constructor 'One'" or, even better, "error: 'One' only works in pattern matching" Jim ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
LIbraries? Matrices?
Is this the appropriate place to discuss libraries for HPrime? Clearly, we can't really be sure what changes (if any) can be made to existing libraries until the core language is decided upon. On the other hand, we might agree that some libraries should be added, though their interface must wait until the language solidifies. I'm thinking here of a standard matrix library. Please excuse me if this is the wrong forum. Jim ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Priorities
On Wed, Feb 08, 2006 at 12:03:54PM +0300, Bulat Ziganshin 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 standard. Well, mainly it would just be a really useful thing > JM> to have in general. If others think it is a good idea I can try to come > JM> up with a suitable API and submit it to the repo. > > i have delayed answering to this letter until i announced my Streams > library. now i can say that such API already exists - in terms of my > library you need just to write an transformer that intercepts > vGetBuf/vPutBuf calls and pass them to the select/poll machinery. so > you can write such transformer just now and every program that uses > Streams will benefit from its usage. Converting programs that use > Handles to using Streams should be also an easy task. I was actually asking for something much more modest, which was the routine needed to pass them to the select/poll machinery. but yeah, what you say is one of my expected uses of such a routine. Once a standard IO library settles down, then I can start working on the exact API such a routine would have. > of course, Streams library is not some standard just now, and moreover > - it is not compatible with JHC. the greatest problem is what i using > type classes extensions available in GHC/Hugs what is not in H98 > standard. so, i'm interested in pushing Haskell' to accept most > advanced possible extensions in this area and, of course, in actual > implementing these extensions in the Haskell compilers. alternative > way to make Streams available to wider range of Haskell compilers is > to strip support of streams working in monads other that IO. Don't take the absence of a feature in jhc to mean I don't like or want that feature. There are a lot of things I don't have but that I'd definitly want to see in the language simply because I was only shooting for H98 to begin with and was more interested in a lot of the back end stuff. You should figure out the nicest design that uses just the extensions needed for the design you want. it could help us decide what goes into haskell-prime to know what is absolutely needed for good design and what is just nice to have. > if you can make select/poll transformer, at least for testing > purposes, that will be really great. Yeah, I will look into this. the basic select/poll call will have to be pretty low level, but hopefully it will allow interesting higher level constructs based on your streams or an evolution of them. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Scoped type variables
Sorry, but I cannot resist to mention an alternative language construct to scoped type variables which gives you the same power of annotating any subexpression with type information. I did mention it in my ICFP 2001 paper on Compositional Explanations of Types as a side note. The nice property of this language construct is that all type variables scope only over a single type; you never have to look if the same type variable appears somewhere else far away in your program. The idea is that a type may contain part of a type environment (so actually it is no longer a type but a typing). This typ environment constructs the relation to other types. Instead of f :: forall a. [a] -> ... f xs = ... where g :: a -> [a] g x = x:xs you write f :: [a] -> ... f xs = ... where g :: (xs::[b]) => b -> [b] g x = x:xs So (xs::[b]) is this new type environment that is part of the type of g. Whether you want to write it similar to a class context, is a matter of taste. This extended type (typing) is the principal monomorphic typing for the function g. Every subexpression has a principal monomorphic typing and hence you can annotate any expression with a typing. Type variables always scope only over a typing. This system of typings works fine for the Hindley-Milner system and also for Haskell 98 classes. I have to admit that I never looked beyond; so I don't know which problems may crop up for rank-n, existentials etc. Ciao, Olaf ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Tuple-like constructors
Robert Dockins wrote: data Tuple a b = Tuple a !b -- (a,b)=== Tuple a (Tuple b ())-- (a,b,c) === Tuple a (Tuple b (Tuple c ())) -- etc... A problem with this is that there's no way of supporting partially-applied tuple type constructors without some sort of type system extension. But maybe there's no reason to support this. Are there any situations where people use "(,) a" where they couldn't simply define a new product type? I rather like the following solution for traversable tuples: Introduce unboxed pairs (# a,b #) and unboxed unit (# #) into the language. Allow datatypes to be specialized at unboxed types. Define data Tuple a = Tuple a and let (a,b) = Tuple (# a,(# b,(# #)#)#) (a,b,c) = Tuple (# a,(# b,(# c,(# #)#)#)#) ... Then allow class instances to be declared at unboxed types and type parameters to be instantiated at unboxed types by doing compile-time specialization (like C++ templates), and voila. No problem of ordinary tuple access becoming less efficient, though some care would be needed to prevent typeclass-based traversal from taking O(n^2) time. Of course, the compile-time specialization part is a bit tricky. -- Ben ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
On Wed, Feb 08, 2006 at 06:01:15PM +, Ben Rudiak-Gould wrote: > > Well, I took it as a stripped-down example. I've often wished for a > nonrecursive let in Haskell so that I could write let x = ...x... in ..., > and restricting x's interface would be similarly useful. But you could > argue that I should break out my pipeline stages into separate functions > and compose them, and I suppose you'd probably be right. I would argue that the language should discourage variable shadowing, so that shadow warnings can be used to find bugs. Thanks Ian ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Re[2]: Tuple-like constructors
Robert Dockins <[EMAIL PROTECTED]> writes: > instance (Bin a,Bin b,Bin c,Bin d) => Bin (a,b,c,d) > > See the problem? Sooner or later (probably sooner) I'll get tired of > typing. I have to write down an 'instance' declaration for each > value of n. Clearly this can't generalize to all n. There has been a suggestion that the 'deriving' mechanism be de-coupled from the datatype declaration. Together with a generic default definition, that means you could write something like deriving Bin for () and hence not need to write the tedious instance header yourself, since the compiler can easily infer it. Regards, Malcolm ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Tuple-like constructors
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: > In my language Kogut there are only pairs, and larger tuples are > expressed by nested pairs (biased in the same direction as lists, > without an end marker of course). > > I wonder whether the performance difference is really that > significant. Short tuples seem to be much more common. Anyone could > gather statistics about runtime usage of tuples of varying sizes? I agree that most uses of tuples are small, and for these, a nested representation will not be so bad. But Robert was proposing a nested representation precisely for the case where the tuples are large (possibly machine generated), and it is in those cases that performance might start to matter. Regards, Malcolm ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
Marcin 'Qrczak' Kowalczyk wrote: Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: Parametricity, what else? But he is writing the function inline. Well, I took it as a stripped-down example. I've often wished for a nonrecursive let in Haskell so that I could write let x = ...x... in ..., and restricting x's interface would be similarly useful. But you could argue that I should break out my pipeline stages into separate functions and compose them, and I suppose you'd probably be right. -- Ben ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Scoped type variables
| >b) A pattern type signature may bring into scope a skolem bound | > in the same pattern: | > data T where | > MkT :: a -> (a->Int) -> T | > f (MkT (x::a) f) = ... | > | > The skolem bound by MkT can be bound *only* in the patterns that | > are the arguments to MkT (i.e. pretty much right away). | | I see -- my scheme was overly simple. But this too feels unsatisfactory. | What if we want to give signatures for both arguments? Will the a's | be the same? Yes f (MkT (x::a) (f::a->Int)) = ... You can imagine that either (a) both bind 'a' to the skolem, but must do consistently; or (b) that (x::a) binds 'a', and (f::a->Int) is a bound occurrence. It doesn't matter which you choose, I think. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: >>> that i want to say is what the first variant allows to define type of >>> 'x' in such way that the only Show-specific operations are allowed, >> Why? > > Parametricity, what else? I'd much rather pass my precious String to a > function of type [a] -> [a] or Functor a => a Char -> a Char than to a > function of type String -> String. But he is writing the function inline. It doesn't matter whether it's polymorphic when it's ever applied only to a string written in the very same line. -- __("< Marcin Kowalczyk \__/ [EMAIL PROTECTED] ^^ http://qrnik.knm.org.pl/~qrczak/ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Scoped type variables
On Wed, Feb 08, 2006 at 11:19:41AM -, Simon Peyton-Jones wrote: > I agree with the "simplest thing" plan. But if HPrime is to include > existentials, we MUST have a way to name the type variables they bind, > otherwise we can't write signatures that involve them. Stephanie and > Dimitrios and I are working on this scheme: > [...] >b) A pattern type signature may bring into scope a skolem bound > in the same pattern: > data T where > MkT :: a -> (a->Int) -> T > f (MkT (x::a) f) = ... > > The skolem bound by MkT can be bound *only* in the patterns that > are the arguments to MkT (i.e. pretty much right away). I see -- my scheme was overly simple. But this too feels unsatisfactory. What if we want to give signatures for both arguments? Will the a's be the same? ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
Bulat Ziganshin wrote: main = do return "xx" >>= ((\x -> print x) :: Show a => a -> IO ()) main2 = do return "xx" >>= (\(x:: (forall a . (Show a) => a)) -> print x) main3 = do (x :: forall a . Show a => a) <- return "xx" print x the second and third variant should do the same, to my mind. Well, you need to change your mind. :-) Forall is like a function; when you write forall a. Show a => a -> IO () it means something like (a::Type) -> ShowDict a -> a -> IO () In other words, the caller supplies three things: the type a, a dictionary for Show a, and a value of a. But when you write forall a. Show a => a it means something like (a::Type) -> ShowDict a -> a In other words, the caller supplies two things, the type a and a dictionary for Show a, and the callee *returns* a value of a. In this case the callee has to be prepared to produce a value of whatever type the caller requests, and it can't do that if it only has a String. On the other hand exists a. Show a && a means (a::Type, ShowDict a, a) i.e. the callee chooses the type and dictionary as well as the value, which is what you need here. -- Ben ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
Marcin 'Qrczak' Kowalczyk wrote: Bulat Ziganshin <[EMAIL PROTECTED]> writes: that i want to say is what the first variant allows to define type of 'x' in such way that the only Show-specific operations are allowed, Why? Parametricity, what else? I'd much rather pass my precious String to a function of type [a] -> [a] or Functor a => a Char -> a Char than to a function of type String -> String. Restricting an interface is a very good thing from a program verification standpoint. It's much the same in object-oriented languages, except that the existence of dynamic downcasting kind of spoils things. But then, Haskell has undefined and unsafePerformIO. -- Ben ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re[2]: Restricted Data Types: A reformulation
Hello Jan-Willem, Wednesday, February 08, 2006, 4:26:48 PM, you wrote: JWM> Should there be a class which is implemented by every well-formed JWM> type of kind (*)? Should that class have one or more of the following: JWM>* Structural decomposition and reconstruction a la Generics? JWM>* Scrapped-boilerplate traversal a la Typeable? JWM>* Ability to coerce to Dynamic? JWM> It would be a special source of amusement to me if such a class were JWM> called All or Forall... :-) (though a moment's thought will tell you JWM> it's Wrong.) it's called "Object" in OOP languages, so we are clearly should name it "Function" ;) -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Restricted Data Types: A reformulation
On Feb 7, 2006, at 11:45 PM, John Meacham wrote: Ashley Yakeley has convinced me this proposal won't work as is. I knew that dropping of the a type parameter in the dictionary passing scheme would bite me :). though, perhaps it will inspire another proposal? In the meantime, I will see about implementing the 'wft' constraints as mentioned in the paper. though, the example ashley gave gives me pause about how useful these will be in general. hmm... It occurs to me to muse that the "wft" constraints look a whole lot like "Typeable" constraints (ie (Typeable (m (a -> a))) => m Int ). Should there be a class which is implemented by every well-formed type of kind (*)? Should that class have one or more of the following: * Structural decomposition and reconstruction a la Generics? * Scrapped-boilerplate traversal a la Typeable? * Ability to coerce to Dynamic? It would be a special source of amusement to me if such a class were called All or Forall... :-) (though a moment's thought will tell you it's Wrong.) -Jan-Willem Maessen John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Bang patterns, ~ patterns, and lazy let
Simon Peyton-Jones wrote: | What have you got in mind? ANY tupling of bindings may change the SCC | structure, and hence the results of type inference--I'm taking that as | read. But that still leaves the question of whether the dynamic | semantics of the program is changed. Let's assume for the time being | that all bindings carry a type signature--then the SCC structure is | irrelevant, isn't it? Or am I missing something here? I'm under the | impression that the *dynamic* semantics of | | p1 = e1 | p2 = e2 | | *would* be the same as (p1,p2) = (e1,e2) under my strict matching | proposal. I don't see how the SCC structure can affect that. Well I put the example that you sent me on the Wiki, right at the bottom. Did I get it wrong? let { (y:ys) = xs; (z:zs) = ys } in body means case xs of (y:ys) -> case ys of (z:zs) -> body whereas let (y:ys, z:zs) = (xs,ys) in body means case (fix (\~(y:ys, z:zs). (xs,ys))) of (y:ys, z:zs) -> body which isn't the same. Simon Oh yes, you're right of course. In the denotational semantics I wrote last night, multiple bindings are combined using (+), which *is* the same as tupling them. But remember the thing I left unproven, because it was late at night? E[[let defs1 in let defs2 in exp]]env = E[[let defs1; defs2 in exp]]env It's not true, as this example shows. That'll teach me! In let y:ys = xs; z:zs = ys in body then the result is _|_, because matching the entire *group* against (xs, _|_) fails, but once the example is split into two nested lets then everything works. Yuck. John ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Java-like
Bulat Ziganshin <[EMAIL PROTECTED]> writes: > that i want to say is what the first variant allows to define type of > 'x' in such way that the only Show-specific operations are allowed, Why? A class is not a type. Haskell has no non-trivial subtyping. If it's always a string, then it can be treated as a string. Haskell is not Java and can't be coerced to Java without a major redesign of the type system. -- __("< Marcin Kowalczyk \__/ [EMAIL PROTECTED] ^^ http://qrnik.knm.org.pl/~qrczak/ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Scoped type variables
| I think we should "do the simplest thing that could possibly work", | and then see if we really need more. By "work", I mean a compatible | extension of H98 that makes it possible to add type signatures for | local bindings (which isn't always possible in H98). How about: | | * no implicit binding of type variables: to bind, use "forall". | | * pattern type annotations allowed only at the top level of pattern |bindings and lambda arguments (not on sub-patterns or arguments of |function bindings). | | * no result type annotations (except on pattern bindings, where they're |equivalent to top-level pattern type annotations). | I agree with the "simplest thing" plan. But if HPrime is to include existentials, we MUST have a way to name the type variables they bind, otherwise we can't write signatures that involve them. Stephanie and Dimitrios and I are working on this scheme: * Scoped type variables stand for type *variables*, not types. * Type variables are brought into scope only by one of two ways: a) The forall'd variables of a declaration type signature f :: forall a b. f x y = e b) A pattern type signature may bring into scope a skolem bound in the same pattern: data T where MkT :: a -> (a->Int) -> T f (MkT (x::a) f) = ... The skolem bound by MkT can be bound *only* in the patterns that are the arguments to MkT (i.e. pretty much right away). The idea is that scoped type variables can be bound either at, or very close to, the point at which they are actually abstracted. This is a good topic to debate. S+D+I will try to put forth a set of rules shortly. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Scoped type variables
On Tue, Feb 07, 2006 at 08:15:19PM +, Ben Rudiak-Gould wrote: > Simon PJ thinks that Haskell' should include scoped type variables, and I > tend to agree. But I'm unhappy with one aspect of the way they're > implemented in GHC. What I don't like is that given a signature like > > x :: a -> a > > there's no way to tell, looking at it in isolation, whether a is free or > bound in the type. A second problem with GHC's provision of scoped type variables is the confusing variety of ways of doing it. Some of them address the same problem that partial type signatures aim at (e.g. by allowing signatures for parts of arguments and/or the result of functions). Partial type signatures may well not be ready in time for Haskell', but we should still try to avoid overlap. I think we should "do the simplest thing that could possibly work", and then see if we really need more. By "work", I mean a compatible extension of H98 that makes it possible to add type signatures for local bindings (which isn't always possible in H98). How about: * no implicit binding of type variables: to bind, use "forall". * pattern type annotations allowed only at the top level of pattern bindings and lambda arguments (not on sub-patterns or arguments of function bindings). * no result type annotations (except on pattern bindings, where they're equivalent to top-level pattern type annotations). ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Bang patterns, ~ patterns, and lazy let
| What have you got in mind? ANY tupling of bindings may change the SCC | structure, and hence the results of type inference--I'm taking that as | read. But that still leaves the question of whether the dynamic | semantics of the program is changed. Let's assume for the time being | that all bindings carry a type signature--then the SCC structure is | irrelevant, isn't it? Or am I missing something here? I'm under the | impression that the *dynamic* semantics of | | p1 = e1 | p2 = e2 | | *would* be the same as (p1,p2) = (e1,e2) under my strict matching | proposal. I don't see how the SCC structure can affect that. Well I put the example that you sent me on the Wiki, right at the bottom. Did I get it wrong? let { (y:ys) = xs; (z:zs) = ys } in body means case xs of (y:ys) -> case ys of (z:zs) -> body whereas let (y:ys, z:zs) = (xs,ys) in body means case (fix (\~(y:ys, z:zs). (xs,ys))) of (y:ys, z:zs) -> body which isn't the same. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Bang patterns, ~ patterns, and lazy let
Simon Peyton-Jones wrote: I've updated the Wiki to add your strict proposal, but rather briefly. If you want to add stuff, send it to me and I'll add it. Meanwhile: | And as a consequence, it is no longer possible to transform a pair of | bindings into a binding of a pair. In Haskell 98, | | p1 = e1 | p2 = e2 | | is always equivalent to | | (~p1, ~p2) = (e1,e2) In your strict proposal, I'm sure you hope that the above pair would be equivalent to (p1,p2) = (e1,e2) which would be even nicer. But sadly I don't think it is, because that'd change the strongly connected component structure. Somehow that smells wrong. Simon What have you got in mind? ANY tupling of bindings may change the SCC structure, and hence the results of type inference--I'm taking that as read. But that still leaves the question of whether the dynamic semantics of the program is changed. Let's assume for the time being that all bindings carry a type signature--then the SCC structure is irrelevant, isn't it? Or am I missing something here? I'm under the impression that the *dynamic* semantics of p1 = e1 p2 = e2 *would* be the same as (p1,p2) = (e1,e2) under my strict matching proposal. I don't see how the SCC structure can affect that. John ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Bang patterns, ~ patterns, and lazy let
I've updated the Wiki to add your strict proposal, but rather briefly. If you want to add stuff, send it to me and I'll add it. Meanwhile: | And as a consequence, it is no longer possible to transform a pair of | bindings into a binding of a pair. In Haskell 98, | | p1 = e1 | p2 = e2 | | is always equivalent to | | (~p1, ~p2) = (e1,e2) In your strict proposal, I'm sure you hope that the above pair would be equivalent to (p1,p2) = (e1,e2) which would be even nicer. But sadly I don't think it is, because that'd change the strongly connected component structure. Somehow that smells wrong. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re[4]: Restricted Data Types
Hello Simon, Tuesday, February 07, 2006, 7:36:23 PM, you wrote: SPJ> | data Eq a => Set a = Set (List a) SPJ> | SPJ> | that is a sort of extension i will be glad to see. in my Streams SPJ> | library, it's a typical beast and i forced to move all these contexts SPJ> | to the instances/functions definitions: SPJ> Another reasonable alternative is SPJ> data Set a = Eq a => Set (List a) sorry, i don't know much about all these intrinsics. all that i need as an ordinal programmer is just to define constraints to some type's parameters at the place where this type declared, instead of copying these resctrictions to declarations of all the fucntions/instances that uses this type directly or indirectly. how we can say that Haskell supports ADTs if these restrictions should be copied even to modules that uses this type and don't want to know anything about its internal limitations?! example: data BufferedStream h = BufferedStream h (Ptr ()) bufferStream :: (Stream h) => h -> IO (BufferedStream h) instance (Stream h) => Stream (BufferedStream h) import BufferedStream data Database h = Database (BufferedStream h) (Map String FilePos) createDatabase :: (Stream h) => h -> IO (Database h) instance (Stream h) => DatabaseInterface (Database h) and so on, so on. why i should multiply this context declaration without end? all what i really need is just one more syntax sugar - please allow me to write this context just one time and then any use "BufferedStream h" should enforce that 'h' belongs to the "Stream" class. automagically. btw, this is one more method to decrease differences between types and classes. if "Stream" was a type, then requirement that 'h' have type "Stream" can be easily encoded in the definition of "BufferedStream". i want to make Haskell more class-friendly language because i know how to use this power and the proposed desugaring is one more step in this direction. of course, my next proposal will be syntax-desugaring of data BufferedStream = BufferedStream Stream (Ptr ()) to data BufferedStream h = (Stream h) => BufferedStream h (Ptr ()) :) the same applies to the code like this: (x::Show) <- return "xx" print x as i shown in the Java-like example, there is the way to express such restrictions even in current GHC implementation. the question is only in desugaring this neat form to the following: return "xx" >>= ((\x -> print x) :: Show a => a -> IO ()) -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re[2]: Priorities
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 standard. Well, mainly it would just be a really useful thing JM> to have in general. If others think it is a good idea I can try to come JM> up with a suitable API and submit it to the repo. i have delayed answering to this letter until i announced my Streams library. now i can say that such API already exists - in terms of my library you need just to write an transformer that intercepts vGetBuf/vPutBuf calls and pass them to the select/poll machinery. so you can write such transformer just now and every program that uses Streams will benefit from its usage. Converting programs that use Handles to using Streams should be also an easy task. of course, Streams library is not some standard just now, and moreover - it is not compatible with JHC. the greatest problem is what i using type classes extensions available in GHC/Hugs what is not in H98 standard. so, i'm interested in pushing Haskell' to accept most advanced possible extensions in this area and, of course, in actual implementing these extensions in the Haskell compilers. alternative way to make Streams available to wider range of Haskell compilers is to strip support of streams working in monads other that IO. if you can make select/poll transformer, at least for testing purposes, that will be really great. -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Bang patterns, ~ patterns, and lazy let
Simon Peyton-Jones wrote: | The trouble with those parts is that NOWHERE do they discuss how to | translate a let or where containing more than one binding. If they're | not to be translated via tupling, then how are they to be translated? Sorry I wasn't clear. Given let { p1 = e1; ... ; pn = en } in e0 (P1) For each pattern pi that is of form !qi = ei, transform it to [EMAIL PROTECTED] = ei and replace e0 by (xi `seq` e0) (P2) Now no pattern has a ! at the top. Now apply the existing rules in 3.12 of the Haskell report. So step (P1) above adds some seqs, and after that it's all just standard Haskell 98. My summary so far: Good summary. 1) Bang patterns by themselves are quite decent, well-behaved patterns. 2) Rule (P1) is simple to describe. But the ! in a pattern binding is treated as part of the *binding* rather than part of the *pattern* which is wart-y. And as a consequence, it is no longer possible to transform a pair of bindings into a binding of a pair. In Haskell 98, p1 = e1 p2 = e2 is always equivalent to (~p1, ~p2) = (e1,e2) and you can make this change *locally*, without consideration of the body of the let in which the bindings appear. With ! bindings (let's use a different name from ! patterns, because they are not the same thing), there's no way to rewrite !p1 = e1 !p2 = e2 as a single tuple binding, because there's nowhere you can put the ! that will have the same effect. Thus we lose a law from the algebra of bindings, which is part of the reason why this is warty. John ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Bang patterns, ~ patterns, and lazy let
| The trouble with those parts is that NOWHERE do they discuss how to | translate a let or where containing more than one binding. If they're | not to be translated via tupling, then how are they to be translated? Sorry I wasn't clear. Given let { p1 = e1; ... ; pn = en } in e0 (P1) For each pattern pi that is of form !qi = ei, transform it to [EMAIL PROTECTED] = ei and replace e0 by (xi `seq` e0) (P2) Now no pattern has a ! at the top. Now apply the existing rules in 3.12 of the Haskell report. So step (P1) above adds some seqs, and after that it's all just standard Haskell 98. My summary so far: 1) Bang patterns by themselves are quite decent, well-behaved patterns. 2) Rule (P1) is simple to describe. But the ! in a pattern binding is treated as part of the *binding* rather than part of the *pattern* which is wart-y. 3) There is a good argument to be made that pattern bindings should be strict by default. That is let (x,y) = e in b would evaluate e strictly. However that is *not* the same as saying that 'let' is strict. let x = e in b remains a lazy binding of x (because, as usual, a variable pattern matches without evaluation). 4) John argues that it would be bad to adopt bang patterns without also adopting (3). I don't agree. But I'm still attracted by (3). I will add some of this to the Wiki. Please do not treat it as "my" page --- any committee member can edit it. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Restricted Data Types Now
It seems we can emulate the restricted data types in existing Haskell. The emulation is good enough to run the examples recently suggested on this list. So, we can start gaining experience with the feature. The emulation involves a slight generalization of the Monad class -- something that also addresses concerns by Amr Sabry http://www.haskell.org/pipermail/haskell/2005-January/015113.html that is, defining monad-like things with additional value constraints. The generalization of the Monad class seems to be backward compatible: > {-# OPTIONS -fglasgow-exts #-} > {-# OPTIONS -fallow-undecidable-instances #-} > > module RestrictedMonad where > > import List > > class MN2 m a where > ret2 :: a -> m a > fail2 :: String -> m a > > class (MN2 m a, MN2 m b) => MN3 m a b where > bind2 :: m a -> (a -> m b) -> m b That is, we introduce two classes, and we spell out the types of values produced by monadic computations. The standard monad stuff seems to work, at least in the tried cases. For example, we can define Maybe monad in the traditional way > instance MN2 Maybe a where > ret2 = Just > fail2 _ = Nothing > > instance MN3 Maybe a b where > bind2 (Just x) f = f x > bind2 Nothing _ = Nothing and can write the regular code > test3f () = bind2 (ret2 "a") (\x -> ret2 $ "b" ++ x) > test3f' () = bind2 (fail2 "") (\x -> ret2 $ "b" ++ x) whose inferred type is *RestrictedMonad> :t test3f test3f :: (MN3 m [Char] [Char]) => () -> m [Char] which is quite reasonable. We can instantiate that to the Maybe monad: > test3:: Maybe String = test3f () *RestrictedMonad> test3 Just "ba" Let us now run the example suggested by John Meacham > data Eq a => Set a = Set [a] deriving Show > unSet (Set x) = x > > singleton :: Eq a => a -> Set a > singleton x = Set [x] BTW, the Eq constraint in singleton's signature is forced upon us. If we give the signature, we must mention the constraint. OTH, we can omit the signature and it will be inferred. > instance Eq a => MN2 Set a where > ret2 = singleton > > instance (Eq a,Eq b) => MN3 Set a b where > bind2 (Set x) f = Set (nub . concatMap (unSet . f) $ x) Again, we cannot forget the Eq constraints, because the typechecker will complain (and tell us exactly what we have forgotten). Now we can instantiate the previously written test3f function for this Set monad: > test4 :: Set String = test3f () *RestrictedMonad> test4 Set ["ba"] The latter code shows that the Eq constraint (required by nub) is indeed being provided by the `monad', although the test3f function had _no_ Eq constraints. > test5 = case test3f () of Set x -> nub x Here's another similar example. Again, test6 per se has no Eq constraints (and it is polymorphic over the value a) > test6 x = bind2 (ret2 x) (\x -> ret2 x) > test7 = case test6 True of Set x -> nub x > test7' = case test6 True of Just x -> x *RestrictedMonad> :t test6 test6 :: (MN3 m a a) => a -> m a Here's Ashley Yakeley's recent example: > class HasInt a where > getInt :: a -> Int > instance HasInt Int where > getInt = id > instance HasInt Bool where > getInt = const 1 > > data HasInt a => T a = T Int a deriving Show > > -- forced constraint > instance HasInt a => MN2 T a where > ret2 a = T (getInt a) a > > instance (HasInt a, HasInt b) => MN3 T a b where -- forced constraints > bind2 (T i1 i2) f = let (T _ b) = f i2 in T i1 b > > foo () = bind2 (ret2 True) (const (ret2 3)) > > fooT :: T Int > fooT = foo () ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime