We are pleased to announce an alpha/preview version of VHS (Visual Haskell),
which integrates the Haskell functional language with the Microsoft Visual
Studio .NET 2003 IDE, and VHS-AM, which allows the use of VHS with the
Microsoft Assignment Manager tools.
This preview version supports:
- Syntax
Ketil Malde <[EMAIL PROTECTED]> writes:
> Did you perhaps mean:
>
> g :: a -> a = \x -> x
>
> which has type () -> () ?
Or maybe the difference between:
g :: Num a => a -> a
g = \x -> 1
(which gives the specified type) and
g' :: forall a . Num a => a -> a
g' = \x -> 1
(which
Paul Govereau <[EMAIL PROTECTED]> writes:
> This is a great example, thanks for posting it. However, I feel like
> the real problem in this example is the lexically-scoped type
> variables declared with your function f. I am always surprised by the
> effects that lexically-scoped type variables ca
Hi,
Andrew's "problem" is not a typing problem. The problem is due
to the way type classes are implemented.
Note that Oleg's "solution" imposes the exact some improvement
conditions as the FD in Andrew's code. However, Oleg manipulates
the instance declaration and the instance body, so that
the d
Andrew Bromage wrote:
> module FD where
>
> class C from to | from -> to where
> g :: from -> to
> h :: to -> from
>
> instance C Char Bool where
> g c = c == 'T'
> h b = if b then 'T' else 'F'
>
> --f :: (C Char a) => Char -> a
> f c = g c
Indeed, functional dependencies are
John Meacham wrote:
>On Wed, Nov 24, 2004 at 10:40:41PM +, Ben Rudiak-Gould wrote:
>
>>If the unsafePerformIO hack doesn't work in your new Haskell
>>compiler, you can replace it with some other magic that does work. It's
>>fine for the Haskell environment to hide impure magic behind a pure
>>i
G'day all.
Quoting Lennart Augustsson <[EMAIL PROTECTED]>:
> Here is a small puzzle.
You can understand this one because the closed world hypothesis doesn't
apply to type context inference. However, this seems as good a time as
any to mention one of my pet peeves again:
module FD where
class
On Thu, Nov 25, 2004 at 12:49:13AM +0100, Benjamin Franksen wrote:
> On Thursday 25 November 2004 00:38, Ben Rudiak-Gould wrote:
> > John Meacham wrote:
> > >With my mdo proposal, and I think all proposals brought forth, the
> > >module system behaves identically to how it normally does for
> >
On Wed, Nov 24, 2004 at 11:38:42PM +, Ben Rudiak-Gould wrote:
> John Meacham wrote:
>
> >With my mdo proposal, and I think all proposals brought forth, the
> >module system behaves identically to how it normally does for
> >namespace control. [...] modules do not change code at all, they
> >ar
Gosh, I shouldn't post to mailing lists after midnight. Please excuse my
needless explanations. I didn't understand your answer at first.
Cheers,
Ben
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
I realize now that your original example did not actually have any
such type variables. While playing around with your puzzle, I managed
to introduce some. However, perhaps the lexically-scoped type
variables are interesting in their own right.
Sorry for the confusion,
--Paul
On Nov 24, Paul G
On Thursday 25 November 2004 00:38, Ben Rudiak-Gould wrote:
> John Meacham wrote:
> >With my mdo proposal, and I think all proposals brought forth, the
> >module system behaves identically to how it normally does for
> >namespace control. [...] modules do not change code at all, they
> >are pur
On Thursday 25 November 2004 00:29, Scott Turner wrote:
> John Goerzen wrote:
> > I note, though, that "making an Either into a Monad" doesn't do
> > anything to deal with asynchronous exceptions.
>
> [ snip]
>
> > I was referring to exceptions generated by things such as signals,
> > interrupts, c
This is a great example, thanks for posting it. However, I feel like
the real problem in this example is the lexically-scoped type
variables declared with your function f. I am always surprised by the
effects that lexically-scoped type variables can have on top-level
declarations.
Consider anothe
John Meacham wrote:
>With my mdo proposal, and I think all proposals brought forth, the
>module system behaves identically to how it normally does for
>namespace control. [...] modules do not change code at all, they
>are pure syntantic sugar for deciding what names you can see.
I'm not sure I unde
John Goerzen wrote:
> I note, though, that "making an Either into a Monad" doesn't do
> anything to deal with asynchronous exceptions.
[ snip]
> I was referring to exceptions generated by things such as signals,
> interrupts, certain network errors, stack problems, etc.
How would you like asynchro
On Wed, Nov 24, 2004 at 10:40:41PM +, Ben Rudiak-Gould wrote:
> John Meacham wrote:
>
> >On Wed, Nov 24, 2004 at 02:40:52PM +, Ben Rudiak-Gould wrote:
> >
> >>But they can all be implemented with George Russell's library plus safe
> >>(pure) uses of unsafePerformIO.
> >
> >George Russell's
Lennart Augustsson wrote:
> What do you mean when you say the interface is pure?
>
> If your module is really pure then there should be an implemenation
> of it (which could have really bad complexity) with the same observable
> behaviour that uses only pure Haskell. Is this possible?
Really? I ag
Ben Rudiak-Gould wrote:
Yes it does. :-) If each Haskell environment ships with a correct
implementation of the library, then its interface is the only part that
matters. If the unsafePerformIO hack doesn't work in your new Haskell
compiler, you can replace it with some other magic that does wor
John Meacham wrote:
>On Wed, Nov 24, 2004 at 02:40:52PM +, Ben Rudiak-Gould wrote:
>
>>But they can all be implemented with George Russell's library plus safe
>>(pure) uses of unsafePerformIO.
>
>George Russell's library is precicly an invalid use of unsafePerformIO.
>[...] hiding it in a modul
Lennart Augustsson wrote:
[snip]
So in what sense is this really ambiguous?
I think it would be quite reasonable to allow the Puzzle module
to compile, resolving `a' to be Bool. I.e., if there is only one
instance that can satisfy a constraint and there is no possibility
of adding instances outsid
On Wed, Nov 24, 2004 at 03:48:56PM +, Keean Schupke wrote:
> Having admited to wavering on the edge of accepting top level TWIs, perhaps
> one of the supporters would like to comment on qualified importing... IE
> what
> happens to the unique property if I import 2 copies like so:
>
>modu
On Wed, Nov 24, 2004 at 02:40:52PM +, Ben Rudiak-Gould wrote:
> John Meacham wrote:
>
> > randomIO [...] Data.Unique [...] Atom.hs [...] caching
>
> These are all great examples of cases where having per-process state
> makes sense.
>
> But they can all be implemented with George Russell's
On Wed, Nov 24, 2004 at 07:14:28PM +, Jules Bean wrote:
>
> On 24 Nov 2004, at 18:28, John Goerzen wrote:
>
> >I note, though, that "making an Either into a Monad" doesn't do
> >anything
> >to deal with asynchronous exceptions.
> >
[ snip]
> If that isn't what you meant by asynchronous exc
Here is a small puzzle.
-- The following generates a type error:
f :: Char -> Char
f c =
let x = g c
in h x
-- But this definition does not:
f :: Char -> Char
f c =
let x :: Bool
x = g c
in h x
Furthermore, replacing Bool by any other type in the
latter definition will alw
On 24 Nov 2004, at 19:16, Scott Turner wrote:
Each error type is an instance of Hierarchical, so that its errors may
be
considered part of a larger category of errors. In the instance
definition,
'parent' specifies how the error appears if it is caught by a handler
expecting then next more gener
On 2004 November 24 Wednesday 13:12, Jules Bean wrote:
> On 24 Nov 2004, at 16:21, Scott Turner wrote:
> > On 2004 November 23 Tuesday 10:51, John Goerzen wrote:
> > The way to deal with those kinds of details is to use Either in a
> > monad.
> Ok, I glanced through your code, and you seem to be
On 24 Nov 2004, at 18:28, John Goerzen wrote:
I note, though, that "making an Either into a Monad" doesn't do
anything
to deal with asynchronous exceptions.
We may be talking at cross purposes here. If, by 'asynchronous
exceptions' you mean that exceptions may lurk arbitrarily deeply within
use
[ We apologize for multiple copies ]
***
1st International Workshop on Automated
Specification and Verification
of Web Sites (WWV'05)
March 14-15 2005, Valencia, SPAIN
http://www.dsic.upv.es/w
On Wed, Nov 24, 2004 at 06:12:27PM +, Jules Bean wrote:
> Ok, I glanced through your code, and you seem to be reimplementing many
> of the ideas in the MonadError class, which also makes Either into a
> Monad.
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/
> Control.Monad
On 24 Nov 2004, at 16:21, Scott Turner wrote:
On 2004 November 23 Tuesday 10:51, John Goerzen wrote:
The way to deal with those kinds of details is to use Either in a
monad. I'm
skeptical of the need for dynamic scope in conventional exception
handling,
so I took a shot at this problem, with s
On 2004 November 23 Tuesday 10:51, John Goerzen wrote:
> > for pure functions, returning Either Error Result is the way to go.
> One example: I've written an FTP client library. For every operation,
> there are several possible outcomes... mainly: success, low-level
> network error, or server err
Having admited to wavering on the edge of accepting top level TWIs, perhaps
one of the supporters would like to comment on qualified importing... IE
what
happens to the unique property if I import 2 copies like so:
module Main where
import Library as L1
import Library as L2
Although each
John Meacham wrote:
> randomIO [...] Data.Unique [...] Atom.hs [...] caching
These are all great examples of cases where having per-process state
makes sense.
But they can all be implemented with George Russell's library plus safe
(pure) uses of unsafePerformIO. I hope his library or something l
On 24 November 2004 11:10, Lennart Augustsson wrote:
> George Russell wrote:
>> I think their disadvantages are overstated. Glasgow Haskell uses
>> them lots,
>
> And I bet the implementors wish they hadn't used them as much. ;)
Bingo. Not to say I universally dissaprove of top-level variables
There is no problem getting multiple copies of the channels... I take it
you are not familiar with the internals of OSs (I have written a small
OS myself, complete with real device drivers)... The OS is started at
boot, it initialises its own state, then it forks the device drivers, then
it forks u
Okay, I have reconsidered, and I think I would be happy with top-level TWI's
providing they can be qualified on import, for example:
module Main where
import Library as L1
import Library as L2
main :: IO ()
main = do
L1.do_something_with_library
L2.do_something_with_libra
Tomasz wrote:
> Without unsafePerformIO Haskell gives me many guarantees for free.
> With unsafePerformIO, they are no longer for free, I have to think, prove,
> etc. When I mistakenly give a pure function interface to an unpure
> "function", it can affect my program in most unexpected places.
I th
George Russell wrote:
I think their disadvantages are overstated. Glasgow Haskell uses them
lots,
And I bet the implementors wish they hadn't used them as much. ;)
Now we have some weird division of flags into static and dynamic,
for instance. Global (top level) variables can be very convenient,
Thanks John for the list of things for which you need global variables,
indeed where Haskell already has global variables.
I think their disadvantages are overstated. Glasgow Haskell uses them lots,
as does the Workbench (I reckon about 80 or 100 times), as I suspect do
most large programs that ha
On Tue, 23 Nov 2004, John Goerzen wrote:
(snip)
> I've been using Haskell for 1-2 months now, and feel fairly comfortable
(snip)
> catchJust :: (Exception -> Maybe b) -> (c -> a) -> c -> (b -> a) -> a
(snip)
Yes, this was one of the first things that bothered me, too, when I
started actually writi
On Wed, Nov 24, 2004 at 01:35:53AM -0500, Judah Jacobson wrote:
> Very nice survey of practical applications! To futher clarify the
> discussion, though, I'd like to note two distinct uses of
> unsafePerformIO:
>
> 1) encapsulating referentially transparent IO actions into pure functions
> 2) cre
Jacques Carette wrote on LtU on Wed, 11/24/2004
] One quick (cryptic) example: the same difficulties in being able to
] express partial evaluation in a typed setting occurs in a CAS
] [computer algebra system]. Of course I mean to have a partial
] evaluator written in a language X for language X,
Adrian Hey wrote:
On Tuesday 23 Nov 2004 9:29 am, Keean Schupke wrote:
myDriver :: (Chan in,Chan out) -> State -> IO State
myDriver (in,out) state = do
-- read commands from in
-- process commands
-- reply on out
myDriver (in,out) new_state
How does this solve the pro
Adrian Hey wrote:
On Tuesday 23 Nov 2004 9:39 am, Lennart Augustsson wrote:
I find it hard to argue these things in the abstract. Could you
post us a (simplified) signature for a module where you are
using top level variables? Maybe that way I can be convinced
that you need them. Or vice versa.
On Tuesday 23 Nov 2004 9:39 am, Lennart Augustsson wrote:
> I find it hard to argue these things in the abstract. Could you
> post us a (simplified) signature for a module where you are
> using top level variables? Maybe that way I can be convinced
> that you need them. Or vice versa. :)
Nope,
On Wed, Nov 24, 2004 at 08:53:47AM +0100, Lennart Augustsson wrote:
> Well, I don't. unsafePerformIO is an extension that is very much
> against the spirit of Haskell. Haskell with it does not have the
> properties I want. So I don't use it. :)
I hope 'it' means unsafePerformIO, not Haskell :)
On Tuesday 23 Nov 2004 9:29 am, Keean Schupke wrote:
> Is this a joke?
No.
> Seriously if you writing the OS in haskell this is trivial,
> you fork a thread using forkIO at system boot to maintain the driver,
> all 'processes' communicate to the thread using channels, the thread
> maintains local
Tomasz Zielonka wrote:
On Tue, Nov 23, 2004 at 08:50:45PM -0800, John Meacham wrote:
Atom.hs from ginsu..
This is perhaps the best example, and an incredibly useful piece of code
for anyone struggling with space problems out there.
it provides
data Atom = ... (abstract)
instance Ord Atom
in
49 matches
Mail list logo