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 chan
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
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 u
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
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 proper
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
m
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
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.
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
> signifi
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 re
| >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
| > ar
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] -
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
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
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
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>*
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 im
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
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 treat
| 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 bi
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
| 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 bindin
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,
|
|
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
|
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 d
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 sta
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
| 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) Fo
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 a
29 matches
Mail list logo