Re: Help with lists?

1999-10-20 Thread Keith Wansbrough
nly works for functions with one list argument. You probably want lift0SS :: [Int] -> SS lift0SS xs = SS xs lift1SS :: ([Int] -> [Int]) -> SS -> SS lift1SS f (SS xs) = SS (f xs) lift2SS :: ([Int] -> [Int] -> [Int]) -> SS -> SS -> SS lift2SS f (SS xs) (SS ys)

Re: Reduction count as efficiency measure?

1998-11-25 Thread Keith Wansbrough
ithm. The real answer, as others have pointed out, is to use a profiler, which performs timings on the actual code output by the compiler you have chosen to use. In the end, the only benchmark that makes any sense is running your real application under real conditions. H

Re: Haskell 98: randomIO

1998-12-02 Thread Keith Wansbrough
3), setstate(3) springs to mind. -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotland. [><] ) : : Native of Antipodean Auckland, New Zealand

Re: Stream of random comments continues

1998-12-04 Thread Keith Wansbrough
now how many you are going to use from each stream. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotland. [><] ) : : Native

Pseudorandom numbers based on general hash functions

1998-12-15 Thread Keith Wansbrough
Further to the recent discussion of pseudorandom numbers, I have now been able to obtain and make available the thesis _General Hashing_ and paper on hashing. Chapter 5 of the thesis discusses generating aperiodic [sic] pseudorandom numbers. I have almost completed an implementation of this in H

Re: Haskell 98 draft report

1998-12-21 Thread Keith Wansbrough
If you get lots of values on the 0.5 boundary, `round up' gives you an error of +0.5 for each, whereas round-to-even gives you a mean error of zero. I think IEEE floating point does this by default for its basic operations. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) --

No Subject

1999-01-09 Thread Keith Wansbrough
27;s a parser generator for Haskell, and you could write your own infix to RPN program using it. Alternatively, there is a parsing combinator library that's probably a lot easier to work with, but less general. Both are available at http://www.haskell.org/libraries/ HTH. --KW 8-) -- :

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Keith Wansbrough
ends. URL is http://www.cs.indiana.edu/hyplan/tveldhui/papers/ --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotland. [><] )

GHC in Japanese Fifth Generation Project!

1999-03-03 Thread Keith Wansbrough
I was amused to disover recently (thanks to Zhou-san, at POPL) that the name GHC (well, really FGHC or `flat' GHC) has already been used, by the Japanese Fifth Generation Project. FGHC stands for Flat Guided Horn Clause, and it's a language that was used by the project for knowledge representatio

Re: Plea for Change #2: Tools

1999-03-30 Thread Keith Wansbrough
Hugs would be nice in GHC, too. But that's a matter for discussion on the GHC lists. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotla

Re: I/O Question for Haskell

1999-05-13 Thread Keith Wansbrough
ather than treated as end-of-file; this allows interactive applications. I've cc'd this to the hugs-users list in case the developers want to comment. HTH. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laborator

Re: how to write a simple cat

1999-05-28 Thread Keith Wansbrough
putStr s --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotland. [><] ) : : Native of Antipodean Auckland, New Zealand: 1

Re: how to write a simple cat

1999-06-01 Thread Keith Wansbrough
Sven Panne wrote: > > Don't fear! Mr. One-Liner comes to the rescue:;-) > > > >longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| >zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr Friedrich wrote: > Do you want to drive me away from lear

Re: Language Feature Request: String Evaluation

1999-06-08 Thread Keith Wansbrough
> > Alex, you might want to explain to people (such as myself) > > who don't know how Perl etc decide how much white space to insert > > in the string that's broken across a line. One space? None? > > What of the indentation spaces on the new line? What if > > you really want those spaces to a

Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Keith Wansbrough
all the attention given to names in the literature and magic (for to name a thing is to control it), names in programming languages have received curiously little attention. Although today's computer programming languages force a rigid syntax on the programmer, they permi

Re: Layout rules.

1999-07-02 Thread Keith Wansbrough
} If you do this more than once, you find yourself coding hard up against the right-hand edge of the edit window. Obviously allowing the `else' to line up with the `if' would help a little here, but not completely... conceptually, {-stuff-} is in the same path of control as `f <- checkF

Re: Please define __HASKELL_VERSION__=98

1999-07-05 Thread Keith Wansbrough
Patrik writes: > Please define the cpp macro > > __HASKELL_VERSION__=98 > > for all Haskell 98 implementations. Haskell implementors out there might be interested in my proposal for (inter alia) a properly Haskellised preprocessor for Haskell, submitted to the Haskell Workshop. This include

Re: second rank polymorphism

1999-07-07 Thread Keith Wansbrough
te-in-place, but this is quite hard for the compiler to do. Usually you give it a hand by saying `I will use this datum in a single-threaded manner' by putting it inside the ST or IO monads. This makes your code look much more imperative, though. > Jan HTH. --KW 8

Re: second rank polymorphism

1999-07-07 Thread Keith Wansbrough
\/c. (a->b) -> (b->c) -> (a->c) is clearly different from (.') :: \/c \/b. \/a. (a->b) -> (b->c) -> (a->c) although the two are in some sense equivalent. > Doesn't haskell 98 allow in place updating e.g; for records? [see next message] > Thank

In-place update

1999-07-08 Thread Keith Wansbrough
perative language. This doesn't necessarily mean there isn't a better way to write it in the functional language, just that the algorithm in your favourite algorithms book is tuned for C rather than Haskell. HTH. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) -

Deriving Enum

1999-07-07 Thread Keith Wansbrough
Section 6.3.4 of the Haskell 98 report says "Instances of Enum may be derived for any enumeration type (types whose constructors have no fields). There are also Enum instances for floats." A consequence of this is that an Enum dictionary *cannot* be derived for: data MyInt = MyInt Int

Re: Deriving Enum

1999-07-08 Thread Keith Wansbrough
0 0..] will give [MyPair 0 0, MyPair 0 1, MyPair 0 2, MyPair 0 3, ...] and will never reach MyPair 1 0. (A related point is that (toEnum 0) is MyPair 0 0 here; what about negative integers?) --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Comp

Re: deriving Enum. Reply

1999-07-08 Thread Keith Wansbrough
Ah, but the same is true for Ord and yet Ord instances may be derived automatically. Deriving should do something that is clearly sensible; it doesn't have to be the only thing possible. I think the lexicographic ordering is clearly sensible. --KW 8-) -- : Keith W

Re: Looking for TkHaskell

1999-07-20 Thread Keith Wansbrough
en may be working on a > graphics implementation with a similar basis. > http://www.cs.chalmers.se/Cs/Research/Functional/Meeting/1999/index.html#Koe > n-May-20 I don't know anything about this... thanks for the pointer. > Scott Turner --KW 8-) -- : Kei

Re: Is their a *good* online tutorial and reference for Haskell?

1999-08-10 Thread Keith Wansbrough
ok too ugly)... PostScript files are really only accessible to CS people-in-the-know; the average Anonymous Coward is not going to have Ghostscript installed on their system. (I know some of them are already, but clearly from this comment some aren't). --KW 8-) -- : Keith Wansbrough, MSc, BSc

Re: Contexts

1999-08-13 Thread Keith Wansbrough
gs-bugs or Hugs-users list, but I can't find it because the archive page has been split into 51 pages and I'm not going to search all of them! [hugs-bugs moderator please take note!] HTH. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student,

Re: Contexts

1999-08-15 Thread Keith Wansbrough
f an *exported* binding, except by performing type inference on modules outside the current module. Rule 2 states that the exact types of all the variables bound in a module must be determined by that module alone, and not by any modules that import it." f is required to be monomorphic by the

Wanted: Union-Find library for Haskell

1999-08-16 Thread Keith Wansbrough
Hi all... has anyone implemented the Union-Find algorithm in Haskell? I've looked at the various libraries listed at haskell.org and found nothing, but don't want to re-invent the wheel if someone else has done it already. Thanks. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons)

Re: TclHaskell manual woes...

1999-08-16 Thread Keith Wansbrough
I wrote: > Looking forward to a LaTeX or Linuxdoc-DTD version of the > documentation, or at least HTML that passes WebLint and the HTML > validator: I wrote that, and yet sent a message that would surely fail any RFC822-lint program. Sorry about the long lines, everyone... Thanks Matthias f

Re: TclHaskell manual woes...

1999-08-15 Thread Keith Wansbrough
ttp://validator.w3.org/ For a discussion of MS-"HTML": http://language.perl.com/misc/ms-ascii.html HTH. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently

Re: Stylistic question about Haskell optional arguments

1999-08-17 Thread Keith Wansbrough
> I've got a stylistic question about Haskell. > What's the best way to add optional arguments to a > embedded DSL? > [..] > -- > (1) Combinators takes a list of attributes. >Now we have > >h1 :: [HtmlAttr] -> Html -> Html > >and might

Re: A Haskell-Shell

1999-08-23 Thread Keith Wansbrough
> And there is _no_ handle to the output of the command! An obvious hack is > to use redirecting; here is how you implement a simple date function in > Haskell: > > date :: IO String > date = > do system "date > /tmp/answer" >readFile "/tmp/answer" > [..] > I implemented these fu

Re: Licenses and Libraries

1999-08-23 Thread Keith Wansbrough
[..] > Ted C. > > P.S. If somebody could explain Monads in plain english it might not > hurt either. Someone already has: http://www.dcs.gla.ac.uk/~nww/Monad.html --KW 8-)

Wiki updates

1999-08-24 Thread Keith Wansbrough
ded a few of my own responses to the Haskell list in recent months. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and recently of the University of Glasgow, Scotland. [><]

Re: Haskell MIME types?

1999-08-25 Thread Keith Wansbrough
> | I just convinced my local sysadmin to attach a new MIME type to > | outgoing Haskell programs sent by our web server, namely > | "application/x-haskell". > : > | My goal in this is to get a browser to launch Hugs/Winhugs on the > | podium machine where I make lectures whenever I click on

As- and irrefutable- patterns

1999-08-25 Thread Keith Wansbrough
at.hs" (line 1): Undefined variable "foo" What have I missed? Replacing the lhs with foo@(~(x,y)) works, BTW. Thanks.. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : :

Re: ANN: The Haskell Wish List

1999-09-07 Thread Keith Wansbrough
point: how about giving the wish list items short codes, so they can be referred to by code rather than full name? They could be just sequence numbers, but perhaps something more mnemonic would be better. Thanks heaps for taking this on, Sven! --KW 8-) -- : Keith Wansbrough, MSc, BSc(

Sectioning tuples

1999-09-15 Thread Keith Wansbrough
zip xs (repeat y) -- OK The question: is it reasonable to expect (,y) to be a right section of the (,) operator, or would this syntax break something (or perhaps lead to confusing error messages)? --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : P

Re: Sectioning tuples

1999-09-15 Thread Keith Wansbrough
Marc wrote: > : The question: is it reasonable to expect (,y) to be a right section of > : the (,) operator, or would this syntax break something (or perhaps lead > : to confusing error messages)? > > I think it's because (,) isn't infix. Well, not exactly... the comma `,' is infix in some s

Re: Haskell Wish list: library documentation

1999-09-16 Thread Keith Wansbrough
lue-sky than that. --KW 8-) [1] @MastersThesis{ Wansbrough97:Modular, author="Keith Wansbrough", title="A Modular Monadic Action Semantics", school="Department of Computer Science, University of Auckland", year="1997", month=feb, documentURL="http://www.cl.cam.ac.uk/users/kw217/research/msc/thesis/index.html", }

Re: tuple component functions

1999-09-16 Thread Keith Wansbrough
for the tuples of n = 3,4,5 ? Yes! I often want fst3, snd3, thd3, at least. I suggest calling them "pi13" or "prj13" rather than "tuple31", though. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, U

Re: Wishlist: MixFix syntax

1999-10-11 Thread Keith Wansbrough
tors, may we > extend this to mixfix? E.g. Please see my note _Macros and Preprocessing in Haskell_, which makes a proposal for just this feature. http://www.cl.cam.ac.uk/users/kw217/research/papers.html Enjoy! --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---

Re: Haskell mailing list

1999-10-11 Thread Keith Wansbrough
Ralf Muschall writes: > [EMAIL PROTECTED] wrote: > > > set up comp.lang.haskell? > > I agree with the above. > > This is IMHO the best solution for a lot of reasons: I disagree. One major reason is the spam problem: a post to a newsgroup essentially guarantees putting your name on a spam maili

Re: Question on graphics

1999-10-12 Thread Keith Wansbrough
> > "Ronald" == Ronald J Legere <[EMAIL PROTECTED]> writes: > > > I am wondering however if there is anykind of small package > > to enable me to make simple plots (of functions for example).. > > This is for windows (98) machine, so I cant use Gif Writer, which > > seems sort

Re: Haskell Wish list: library documentation

1999-09-08 Thread Keith Wansbrough
Michael Hobbs wrote: > I think I might be able to clarify George's point with an example: > unzip. Presumably, the unzip function will stay, no matter what happens > with existential types, arrows, etc. The problem is, I don't know what > unzip *does*. (Actually, I do, but I'm taking the POV of a

Minimal complete definition for Enum

1999-07-07 Thread Keith Wansbrough
s seems to be a bug in the Haskell report too... the definition is missing from the example Prelude. Cc'd to Haskell list. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambridge, England. : : (and

Proposal: Substring library for Haskell

1999-05-18 Thread Keith Wansbrough
ea that should be implemented? I float the idea in case (1) someone else is already doing this, or (2) someone else is interested in doing it. It shouldn't be too hard, but I don't have time right now... --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland)

Re: Proposal: Substring library for Haskell

1999-05-18 Thread Keith Wansbrough
ars. Yes, obviously... this is for new programs (which people aren't writing because of Haskell's inefficiency in dealing with strings). --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) : : PhD Student, Computer Laboratory, University of Cambr

Unused identifiers in default case patterns

1999-06-25 Thread Keith Wansbrough
Section 2.4 of the Haskell 98 report says "Compilers that offer warnings for unused identifiers are encouraged to suppress such warnings for identifiers beginning with underscore. This allows programmers to use ``_foo'' for a parameter they expect to be unused." In GHC at least, a freque

Re: type of deleteBy

1999-12-06 Thread Keith Wansbrough
-> [a] ? Section 7.6 of the Library Report: "By convention, overloaded functions have a non-overloaded counterpart whose name is suffixed with ``By''." --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory,

Type inference and binding groups

2000-01-19 Thread Keith Wansbrough
some monotype tj? (modulo permutations, of course) References to published discussions of this would be useful, too, although I suspect this is an area where folklore rules... Thanks. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Labor

Re: HaskellDoc?

2000-03-22 Thread Keith Wansbrough
There seems to be some agreement at least that a clean and unintrusive syntax like POD or the ISE Eiffel stuff is preferable to something as noisy as XML; it certainly seems to me that it would be much more rapidly adopted. Regarding such a system's power, Jan Skibinski writes: > How come

Partial v0.1 released

2000-03-22 Thread Keith Wansbrough
Announcing the release of a new library for Haskell: Partial v0.1 The Partial library provides a partial order class. It also provides routines for generating a Hasse diagram from a set and a partial order. Renderers are provided for the abstract Hasse diagram representation into LaTeX (via Xy-

Re: ServiceShow for error messages

2000-03-31 Thread Keith Wansbrough
Sergey writes: > Maybe, there exists another possibility to print the values in the > error message like for >take (-1) xs, y % 0 > > The implementors declare the "internal" > class ServiceShow where serviceShows :: ... > invisible for the us

Re: improving error messages

2000-03-31 Thread Keith Wansbrough
Malcom and Sergey write: > instance ShowType a => ShowType [a] > where > showsType xs = ('[':) . showsType x . (']':) where ~(x:_) = xs Perhaps where [x] = [error "not used"] `asTypeOf` xs gives the idea better. --KW 8-) -- :

Re: doubly linked list

2000-04-27 Thread Keith Wansbrough
> I wonder if it is possible to simulate a doubly linked list in Haskell. No need to simulate it... it's perfectly possible. See my Wiki article. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambr

Re: doubly linked list

2000-04-27 Thread Keith Wansbrough
askell.org to no avail Good point! I have no idea... it looks like the Wiki has gone AWOL. If someone would tell me where my article has gone, I'd be very grateful! --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University

Re: doubly linked list

2000-04-27 Thread Keith Wansbrough
ment. But how do we manage to create a *circular* list this way? How can we know right at the beginning what the pointer to the end of the list will be? Take a look at mkDList. Here, we simply take the (first,last) pointers we get from `go', and *pass them back in* as the next and prev poin

Re: When is it safe to cheat?

2000-05-02 Thread Keith Wansbrough
ttacker can certainly guess within a few seconds (= a few trials) when your connection was negotiated. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambridge, UK. : : Native of Antipodean Auckland, New Zealand: 17

Re: Type of minimumBy

2000-05-17 Thread Keith Wansbrough
re useful than > > mimimumBy = foldl1 > maximumBy = foldl1 > > Why do you say the latter is "right"? > > Carl Witty > [EMAIL PROTECTED] > --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, Uni

Re: Type of minimumBy

2000-05-18 Thread Keith Wansbrough
Q = True isLE GT = False thenCmp :: Ordering -> Ordering -> Ordering EQ `thenCmp` o2 = o2 o1 `thenCmp` _ = o1 and a partial ordering class type POrdering = Maybe Ordering class POrd a where pcompare :: a -> a -> POrdering instance Ord a => POrd a where pcompare

Re: more detailed explanation about forall in Haskell

2000-05-19 Thread Keith Wansbrough
Peter Hancock writes: [..] > Please guys, you are making clowns of yourselves. Amen to that! I've just added the above subject line to my kill file, rather than stop reading the Haskell list altogether. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) --

Re: your mail

2000-05-25 Thread Keith Wansbrough
use `asTypeOf`, which is Haskell 98: inEnv e (unCont ma (inEnv (old `asTypeOf` e) . k))) --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambridge, UK. : : Native of Antipodean Auckland, New Zealand: 174d47'E, 3

Re: confused

2000-06-05 Thread Keith Wansbrough
Roy Haskell (!) writes: > I was recently browsing the web and came across an article HOW TO DO > EXCEPTIONS IN HASKELL (I think) and I'm very curious what it's all about. > The reason for my curiosity is simply that my name is Haskell and currently > reside in South Africa but am originally from

Re: Haskell pronounciation

2000-06-05 Thread Keith Wansbrough
t with `hask' (`a' like in `hat') instead of `batt'. Hope this helps. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambridge, UK. : : Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. : : http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] : ::

Re: When is an occurrence an occurrence

2000-06-09 Thread Keith Wansbrough
as a pair, and to require M.foo :: [..type..] foo= [..defn..] would seem strange. I'm with Ralf on this one. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambridge, UK. : : Native of Antipodean Auckland

Re: Instance of Functor for functions of >= 2 arguments

2000-06-24 Thread Keith Wansbrough
What you really need is a type lambda: type Func2 a b = /\c. a->(b->c) but this isn't provided in Haskell. --KW 8-) -- : Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---: : PhD Student, Computer Laboratory, University of Cambridge, UK. : : Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. : : http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] : ::

Re: Precision problem

2000-07-18 Thread Keith Wansbrough
mputer Scientist Should Know About Floating Point Arithmetic", journal="Computing Surveys", year="1991", volume="23", number="1", month=mar, } --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ Cambridge University Computer Laboratory.

Re: Haskell and the NGWS Runtime

2000-08-10 Thread Keith Wansbrough
to describe Microsoft technology. > >http://www.segfault.org/story.phtml?mode=2&id=39897e26-060c53e0 > > :-) Please: # - hash / octothorp(e) £ - pound C# - C sharp Three different characters. Down with American cultural imperialism. --KW 8-) -- Keit

Re: Overlapping types

2000-08-21 Thread Keith Wansbrough
' and 'prj', just as you describe, implemented in Gofer. I used this in my Masters thesis, @MastersThesis{ Wansbrough97:Modular, author="Keith Wansbrough", title="A Modular Monadic Action Semantics", school="Department of Computer Science, Unive

Re: Patterns Catalog

2000-09-11 Thread Keith Wansbrough
> I've thought of this too. > but I dont think there is anything out there > which fits the bill. > [I'd love someone to please correct me] [..] > I think it would be a good thing to organise > if anyone is willing to look ta this > (If no-one is interested/ would rather do > this) that person

Re: Patterns Catalog

2000-09-11 Thread Keith Wansbrough
it HAS been resurrected. It's at http://haskell.org/wiki/wiki and you should look at `CommonHaskellIdioms' --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ Cambridge University Computer Laboratory.

Re: Extensible data types?

2000-09-25 Thread Keith Wansbrough
> In the Clean Object I/O library we encountered a similar challenge and > solved it using type constructor classes. The solution can also be used in > Haskell. The basic idea is as follows: > I didn't read your message in detail, but I wonder if this is related to the trick TclHaskell / FranT

Re: Literate Programming

2000-09-26 Thread Keith Wansbrough
> > Huh?!? Is this a bug in Hugs? Is it confused by the `<' and > `>' in the HTML code? No! It is just doing what the > Haskell98 report says: > > C Literate comments > [...] > To capture some cases where one omits an ">" by mistake, > it is an error for a program line to appear adjacen

Re: Haskell Programming Environment

2000-10-25 Thread Keith Wansbrough
> I've been wanting to code one of these myself, but have had no time. Try and see > if stg-hugs is useable yet since that would be a much better environment to do > it in. It's now called GHCi, and is being written right now by the GHC team. Not sure when the estimated completion time is, but it

Re: Learning Haskell and FP

2001-01-04 Thread Keith Wansbrough
> I do not know if you actually wanted an answer to this, but I'm sick of > hearing this FAQ everywhere when the answer is so simple. There are > exactly two ways to do this (one of them is actually syntactic sugar for > the other). [..] > Can everyone include an answer to this FAQ everywhere, phl

Re: {-# LINE 100 "Foo.hs #-} vs. # 100 "Foo.hs"

2001-01-22 Thread Keith Wansbrough
> With all this talk of preprocessor generated information and whatnot, I > am reminded of a paper I read not too long ago but can't seem to find > anymore about a dedicated pre-processor for haskell based on the C > preprocessor but made to deal with haskell constructs a bit more sanely. This wa

Re: List of words

2001-05-02 Thread Keith Wansbrough
> I am relatively new to Haskell. > > Somebody told me that it is a very good language, because all the > people on its mailing list are so nice that they solve all > homeworks, even quite silly, of all students around, provided they > ask for a solution in Haskell. > > Is that true, or a littl

Re: List of words

2001-05-02 Thread Keith Wansbrough
e to enlighten us? >;-> --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ Cambridge University Computer Laboratory. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Negatively recursive data types

2001-07-04 Thread Keith Wansbrough
Hi... I'm currently looking at the semantics of recursive data types. One thing that Haskell allows, but the semantics for it is very hairy, is *negatively* recursive data types. That is, data types where the recursion occurs to the left of a function arrow. For example: data Neg a b = MkNe

Re: getting started with the glasgow haskell compiler

2001-08-09 Thread Keith Wansbrough
that are actually code. Lines without them are just comments. Or try \begin{code} module Main (main) where main = putStrLn "Hello World" \end{code} which is another way of marking code. The final way, probably the easiest, is simply to put your program in a file called Hello.hs ra

Re: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Keith Wansbrough
> But, to answer your emmediate question: > > ZMZM = [] - The list Nil constructor > Z1T = ( ) - The 1-tuple constructor IIRC, the "1" is the number of commas, so Z1T is the *pair* constructor. --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.a

Re: not naming modules Main

2001-11-19 Thread Keith Wansbrough
> I'm really frustrated that modules that you want to compile to > executables have to be named Main. I often have a module with a main > method that I use for testing or whatever (perhaps I want the gained > speed of an executable) but is, for the most part, a module I import > into others. I e

Re: Arrow notation, etc.

2001-10-12 Thread Keith Wansbrough
t here; that variables bound in a macro should not clash with other variables in the program (unless this is explicitly required). --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ Cambridge University Computer Laboratory. _

Re: Arrow notation, etc.

2001-10-12 Thread Keith Wansbrough
> Very good. Is there a concrete proposal for such macros? I think the > arrow notation would be a harder test case than any of the existing > syntactic sugar; I'd be curious to see what it looked like. (And is > there support for adding these macros to Haskell?) Sadly, there's not a concrete

Re: GCD

2001-12-11 Thread Keith Wansbrough
ways positive" Or, perhaps easier on the eye, "gcd x y is the greatest (positive) integer that divides both x and y." --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Computer Laboratory. _

Re: The Wisdom of Time

2002-01-07 Thread Keith Wansbrough
> what is the wisdom behind representing a TimeDiff as a struct of year, > month, week and so on, instead of simply the (fractional) number of > seconds, or similar? Firstly, I believe that the Time module is broken, and no one has yet come up with a satisfactory design. But the behaviour you de

Re: A Haskell specific preprocessor

2002-01-11 Thread Keith Wansbrough
e that a lazy language shouldn't need macros or a preprocessor (despite the liberal use of both in GHC, for example). --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Co

Re: Lambda over types.

2002-03-22 Thread Keith Wansbrough
rove > this point. (The terms are Haskell *types*.) Cool! Some time ago I wrote a Turing machine evaluator in Haskell types with undecidable instances. It's described at http://www.chttp://www.cl.cam.ac.uk/~kw217/research/misc/undec.html Enjoy! --KW 8-) -- Keith Wansbrough <[EMAIL P

Re: text/x-haskell and text/x-literate-haskell added to the GNOME MIME database

2002-04-18 Thread Keith Wansbrough
> These MIME types has now been added to the GNOME MIME database: > > text/x-haskell for *.hs > text/x-literate-haskell for *.lhs Note the following thread from August 1999: application/x-haskell has already been proposed and used. http://www.dcs.gla.ac.uk/mail-www/haskell/msg01843.html http://

Re: text/x-haskell and text/x-literate-haskell added to the GNOME MIME database

2002-04-18 Thread Keith Wansbrough
gt;reasonable for unrecognized subtypes of text, but not for >unrecognized subtypes of image or audio. [...] OK, that convinces me. --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of

Re: still random number problem

2002-07-25 Thread Keith Wansbrough
this helps! --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Computer Laboratory. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Design patterns in Haskell

2002-12-03 Thread Keith Wansbrough
> size. while there's really no substitute for experience, i really > believe we could benefit from some patterns. There was a list of design patterns for Haskell on the Wiki (back in the days when it worked): http://haskell.org/wiki/wiki?CommonHaskellIdioms --KW 8-) -- Keith

Re: Design patterns in Haskell

2002-12-04 Thread Keith Wansbrough
ing to try and restore the pages statically for the moment (i.e., non-editable), and then look at how to make them work properly. Assistance welcome! --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge

ANNOUNCE: Haskell Wiki resurrected

2002-12-05 Thread Keith Wansbrough
Hi all... last night I resurrected the Haskell Wiki, http://haskell.org/wiki/wiki This is a set of web pages on Haskell which can be edited and updated by anyone. The intention is to accumulate the combined wisdom of posters to the Haskell lists - if you ever reply to a FAQ with what you thin

New Wiki (was: Re: ANNOUNCE: Haskell Wiki resurrected )

2003-01-03 Thread Keith Wansbrough
mend UseMod, > http://www.usemod.com/cgi-bin/wiki.pl?UseModWiki > It is very easy to set up and provides useful features like online > browsing of Diffs and being much more robust than pywiki. --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw21

Re: Template Haskell

2003-01-06 Thread Keith Wansbrough
he correct URL, but I guess noone has posted yet so the archive hasn't been created. --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Computer Laboratory. ___ Haskell mailing list

Re: Lazy evaluation alternative

2003-01-26 Thread Keith Wansbrough
qual in the corresponding language. Unfortunately, operational equality is not preserved by either of the simulations.", } Enjoy! --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Computer Laboratory. ___

Re: time since the epoch

2003-02-06 Thread Keith Wansbrough
Stefan Karrmann <[EMAIL PROTECTED]> writes: > A sound base for a Time implementation should use TAI (temps atomique > international), c.f. . I disagree; I think UTC is quite sufficient, and will match the users' expectations much better. (executive summary: UTC is th

Re: escape from existential quantification

2003-02-27 Thread Keith Wansbrough
ent types, as long as it is paired with the appropriate accessor functions for those types. You can use it like this: case x of Foo n x f g h -> if snd (f x) then g x else 0 for example. --KW 8-) -- Keith Wansbrough <[EMAIL PROTECTED]> http://www.cl.cam.ac.uk/users/kw

  1   2   >