Re: Thanks, and new question re existensials

1999-01-02 Thread Koen Claessen
ions in the monad "C res m" need to be polymorphic in "res". A really silly restriction, which could have been avoided by local quantification. Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: Thanks, and new question re existensials

1999-01-03 Thread Koen Claessen
| > data Expr a = Val a | forall b . Apply (b -> a) b Sorry, I meant: data Expr a = Val a | forall b . Apply (Expr (b -> a)) (Expr b) :-) Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL

Re: Making argv a constant

1997-01-17 Thread Koen Claessen
ns in Haskell if we wish to, instead of using stdin and stdout for that. Regards, Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ | |--| | Visiting student at OGI,Portland, Oregon, USA. |

Re: Type inference bug?

1996-10-28 Thread Koen Claessen
e in class declaration | *** ambiguous type : Sequence a b => b -> Int | *** assigned to: len Doesn't Haskell do the same if you say: class Cow a where pig :: a -> Int fly :: Int In this case fly is also too general. I am not sure, since I haven&#

Re: Type inference bug?

1996-10-29 Thread Koen Claessen
roblem hasn't got anything to do with the number of type variables. Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ | |--| | Visiting student at OGI,Portland, Oregon, USA. |

Monads, Functors and typeclasses

1997-05-08 Thread Koen Claessen
is message because I would like to know if there is a Real Reason for Haskell not to define its Monad class in this way. I also would like to know other people's opinions about this. Do people find this Really Important, like me? Or is it considered theorectical whining? Monads play such an important role nowadays in Haskell-like languages, that it is important to get its definition right. ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ Regards, Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ | |--| | Visiting student at OGI,Portland, Oregon, USA. |

Re: Monads, Functors and typeclasses

1997-05-12 Thread Koen Claessen
lift :: (Functor m, Monad m) => m a -> t m a Suppose this (and it was in my case) was a library given to me by someone else; I would have to change that library. Also, to a category theorist, the context (Functor m, Monad m) must seem rather superfluous. Regards, Koen. -- |

Re: Monads, Functors and typeclasses

1997-05-13 Thread Koen Claessen
Jones, Meijer and Jones, "Type classes: an exploration of the design space", http://www.cse.ogi.edu/~simonpj/multi.ps.gz, to appear on the Haskell Workshop 1997, Amsterdam. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ | |--| | Visiting student at OGI,Portland, Oregon, USA. |

Laws for Monads with zero and plus

1997-05-13 Thread Koen Claessen
t;= \x -> SIGMA n_i === SIGMA (m >>= \x -> n_i) And conclude, for nullary SIGMA: m >>= \x -> zero === zero So, there seems to be a connection between law (9?) and law (7?). Who can enlighten me in this matter? Thanks, Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ | |--| | Visiting student at OGI,Portland, Oregon, USA. |

Re: Monads, Functors and typeclasses

1997-05-13 Thread Koen Claessen
oin" than ">>=". | It's all very well for mathematicians. Do we have to be mathematicians to | make use of monoidal programming ideas? I don't know what you mean by this. The addition of join to the Monad class has no effect on the user of Monads, and increases

Re: Monads, Functors and typeclasses

1997-05-13 Thread Koen Claessen
early just syntactic sugar; the first one has further implications (that I can't oversee at the moment), but very nicely coincides with the second one. --- Regards, Koen. -- | Koen Claessen, [EMAIL

Re: Laws for Monads with zero and plus

1997-05-14 Thread Koen Claessen
report mean that compilers can use them to transform monadic programs? Even if the programmer specified a "monad" for which these laws don't hold? Regards, Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse.ogi.edu/~kcclaess/ |

Re: Monads, Functors and typeclasses

1997-05-14 Thread Koen Claessen
ut also explicitly giving an instance for C. This seems a simple but effective solution. But, does this raise any other problems? Regards, Koen. -- | Koen Claessen, [EMAIL PROTECTED] | | http://www.cse

Re: Superclass defaults.

1997-05-22 Thread Koen Claessen
| Alex Ferguson, quoting Phil Wadler, quoting Koen Claessen: | | > > At the moment you make an instance of a class that has default definitions | > > for one of its superclasses, and there is no corresponding instance for | > > that class, we implicitly insert the

Re: Working with newtype

1997-05-29 Thread Koen Claessen
> MyList b myMap = map ... Restricted types are at the moment in Hugs and Gofer, but not in the standard Haskell definition. I like them much better than newtype (you don't have an extra constructor). The only disadvantage is that they can't be recursive; they just create a new type.

Announcing TkGofer Version 2.0

1997-09-09 Thread Koen Claessen
rom http://www.informatik.uni-ulm.de/pm/ftp/tkgofer.html We are working on porting TkGofer to Hugs, but we are still waiting for Hugs to get multiple parameter type classes. :) For specific questions you may mail to Ton Vullinghs ([EMAIL PROTECTED]) or Koen Claessen ([EMAIL PROTECTED]).

Re: import qualified Prelude

1997-10-03 Thread Koen Claessen
o.foo, we will just use Foo.foo! So, is there a reason why the following rule is not used: If it is ambiguous about what name to use, then qualified names should be used. You could probably even formalize this in a nice way. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED],

Re: Defining search trees as monads

1997-10-01 Thread Koen Claessen
d have type: return :: Ord a => a -> M a Since Haskell uses this definition of a monad, you can't define this in Haskell either. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Haskell: Heterogeneous lists?

1997-11-17 Thread Koen Claessen
-- = [g^0 a, g^1 a, ..] String = fix g f' :: Show a => a -> (a -> a) -> Fun f' a g = F' (iterate g a) (fix g) I found that this trick solves most cases from real programming where we need existential types. Though having existential types

Monads and their operational behavior

1997-11-24 Thread Koen Claessen
re description system. Then a last remark: When encountering problems like these (turning up in everyday programming and almost impossible to solve even for experienced programmers), I always sigh and wish there were good solutions to this. Space behavior is a big problem! And way more i

Re: Monads and their operational behavior

1997-11-26 Thread Koen Claessen
is no space leak. But this is not what you want, because now we are forced to have "foo" only on toplevel... Who knows a solution? Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Contexts in datatypes

1997-12-10 Thread Koen Claessen
n't it work like this in Haskell? Do contexts in datatypes make sense if it doesn't work like this? I couldn't find a description of how patterns of datatypes with contexts work in the Haskell report. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Monads and their operational behavior

1997-11-26 Thread Koen Claessen
that this equality holds | both denotationally and operationally | | do {x <- foo; return x} = foo | | For all I know, the answer to this question is | "yes, with sufficient sneakiness". Aha! Show us how!! Many attempts of my side failed, because it is very difficult

Re: Punning: Don't fix what ain't broken.

1998-02-12 Thread Koen Claessen
'. It is confusing otherwise! But of course, introducing these kind of changes will break existing Haskell programs... Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: the overloading of ==

1998-03-12 Thread Koen Claessen
(Monad m, Eq (m a)) => (a -> Bool) -> m a -> Bool See Peyton Jones, Jones and Meijer '97 (ICFP/Haskell workshop paper) for more details. I think Simon must have lifted this restriction from the newest version of GHC. But I am not sure. Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Standard Haskell

1998-03-26 Thread Koen Claessen
`Either` d) It is also nice in combination with "lifting the restriction of one parameter in type classes": class a :-->: b where ... * Further, Why don't you name the generalised map for Functors and Monads, mapM, and rename mapM to the more consistent mapL

Re: Operators (was: Standard Haskell)

1998-03-29 Thread Koen Claessen
type a :=> b = F a b type a :-> b = SP a b If class names are also subject to this convention, then we can write things like: class a :< b where-- subtyping coerce :: a -> b foo :: (a :< Int) => a -> a -> Int foo x y = coerce x + coerce y I like it!

Re: strictness of List.transpose

1998-04-01 Thread Koen Claessen
With z ~(a:as) ~(b:bs) = z a b : zipWith z as bs | zipWith _ _ _= [] You cannot do this, since the first line of the definition will now _always_ match. This means that you get an error when zipWith reaches at least one empty list. Regards, Koen. -- Koen Claessen, [EMAIL PROTECT

RE: Pattern Match Success Changes Types

1998-05-12 Thread Koen Claessen
it is way too difficult, if not impossible. There is a reason that lambda-bound variables are not generalized: because of decidability of type checking. But maybe it is different with patterns, I don't know. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

RE: Pattern Match Success Changes Types

1998-05-12 Thread Koen Claessen
On Tue, 12 May 1998, Mariano Suarez Alvarez wrote: | On Tue, 12 May 1998, Koen Claessen wrote: | | > map :: (a -> b) -> [a] -> [b] | > map f (x:xs) = f x : map f xs | > map f xs = xs | | Where is the CSE in theis def of map? Why is it naive? (Hugs & ghc

Re: classes and instances

1998-06-08 Thread Koen Claessen
constructor classes? Presumably, the type `p' will have only one associated `e' with it, which can be expressed as a parameter to `p'. class ResourcePool p where newp :: p e -> e -> p e Hope this helps, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.

Re: FW: Exceptions are too return values!

1998-06-10 Thread Koen Claessen
ikely to crash! Another question: Is "handle" strict in the following argument: handle :: (IOError -> IO a) -> IO a -> IO a ^ (meaning: will "handle f (return bottom)" be bottom?) Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED]

Re: Declared type too general?

1998-06-21 Thread Koen Claessen
It happened several times that my students got into problems with this. The problem is that _if_ it happens, it is often a quite ununderstandable error message. Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: what is leaking?

1998-06-27 Thread Koen Claessen
total = 3 + (4 + (myFoldl (+) 4 [5..10])) So there is no way to add 3 and 4, unless you require the runtime system to look for associative operators partially applied to closures. Which is undoable, in my opinion. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalm

Re: Structure of monads in an abstract form?

1998-07-04 Thread Koen Claessen
nt) of Nothing -> Nothing Just err -> fail err cont Unfortunately the Haskell type system is often too restrictive to encode the wanted features. I have for example no idea how to do lists in this setting, without doing dirty type hacks in Haskell (but it _is_ possible... :-). Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

ST in pure Haskell

1998-07-31 Thread Koen Claessen
o not care about space or time efficiency, so a lookup table implemented as a list would work. I recently got some new insights about how this might be possible. Has anyone done this before? Or is there a proof that it is not possible? Regards, Koen. -- Koen Claessen, [EMAIL PROTEC

Nedit5 Highlight Pattern for Haskell

1998-09-22 Thread Koen Claessen
highlighting for Nedit !! Koen Claessen, September 1998 nedit.highlightPatterns: \ Haskell:1:0{\n\ comments1:"{-":"-}"::Comment::\n\ comments2:"--":"$"::Comment::\n\ comments3:"#!":"$"::Com

Re: declaring properties

1998-10-23 Thread Koen Claessen
k for "strict" functions). But how can you be sure that the theorems your tool proves are actually conform the Clean semantics? (read: How do you convince the user of the tool?) Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: topdelcs / decls

1998-10-23 Thread Koen Claessen
vsort", using the flipped ordering: revsort :: Ord a => [a] -> [a] ord.revsort = (rev ord).sort I really like these ideas, and the paper has a few more examples. Unfortunately there seem to be some semantic issues wrong with it (what to do if you have multiple record in yo

RE: type error, why?

1998-10-27 Thread Koen Claessen
in Lava, I even added the following: type Triple m n p = Both m (Both n p) untriple m = (x, y, z) where (x, m') = unboth m (y, z) = unboth m' type Quadruple m n p q = ... ... Which makes things a little bit more general to use. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: MonadZero

1998-11-03 Thread Koen Claessen
n: controlReactor Of type: Reactor () Because: Reactor is not an instance of MonadZero <= The pattern "Open" is not unfailable <= The datatype "Position" has more than one constructor. Nobody would complain about this, it is clear where the error comes from

RE: MonadZero (concluded?)

1998-11-05 Thread Koen Claessen
-> m a | mzero :: m a I hope you mean: class Monad m => MonadPlus m where mplus :: m a -> m a -> m a mzero :: m a mzero = mfail "mzero" -- maybe? Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Two prelude/library matters

1998-11-06 Thread Koen Claessen
map k m) join mm = mm >>= id Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Simon's Mail

1998-11-27 Thread Koen Claessen
27;:'r':'t':' ':xs) = ... ... Wouldn't it be nice to write it as: lex :: String -> [Lex] lex ("-- " ++ xs) = lex (dropWhile (/= '\n' xs)) lex ("import " ++ xs) = ... ... -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: how to exploit existentials

1999-02-18 Thread Koen Claessen
ht I needed existential types, but I didn't need them at all. I think this might be the case more often. Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: how to exploit existentials

1999-02-18 Thread Koen Claessen
Koen Claessen (me) wrote about transforming away existentials: | > I have applied this method several times when I thought I needed | > existential types, but I didn't need them at all. I think this might be | > the case more often. Christian Sievers answered: | I believ

RE: Contexts on data type declarations

1999-05-18 Thread Koen Claessen
I apply a similar trick to help somebody who posed a question. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology. - >From [EMAIL PROTECTED] Tue May 18 15:43:07 1999 Date: Tue,

Re: Contexts on data type declarations

1999-05-25 Thread Koen Claessen
of the concrete representation of the datatype. Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Proposal: Substring library for Haskell

1999-05-26 Thread Koen Claessen
you would want to use char-vectors for Strings, but do not underestimate the benefit of having lazy streams of characters. Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Field names

1999-07-01 Thread Koen Claessen
t;<< Hbc says: >>> "Hash { (#) = 3 }" Bug: Error: Prelude.read: no parse <<< Ghc says: >>> "Hash{#=3}" Fail: PreludeText.read: no parse <<< The question is: should operators be allowed to be valid field names or not? Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-02 Thread Koen Claessen
sn't want to be reminded of his banana period anymore :-) Regards, Koen. -- Koen Claessen, [EMAIL PROTECTED], http://www.cs.chalmers.se/~koen, Chalmers University of Technology.

Re: Deriving Enum

1999-07-11 Thread Koen Claessen
nicely with Clean's zip-comprehensions, which are denoted by: [ a+b | a <- [1..] & b <- [1..] ] (this evaluates to: [ 2, 4, 6, ..] You can write this in haskell as: [ a+b | (a,b) <- [1..] & [1..] ] For a suitable definition of (&), for example: (&

Re: diagonalisation

1999-07-19 Thread Koen Claessen
s, Koen. (*) Thanks to Arjan van IJzendoorn for his help in choosing variable names. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: Again: Referential Equality

1999-07-27 Thread Koen Claessen
[1] O'Donnell, J., Generating netlists from executable circuit specifications in a pure functional language, Functional Programming Glasgow, 1993. [2] Moran, A. and Sands, D., Improvement in a Lazy Context: An Operational Theory for Call-By-Need, POPL '99, 1999. -- Koen Claes

Re: A Haskell-Shell

1999-08-20 Thread Koen Claessen
s a terrible hack! I would really like it to be possible in Hugs to get a handle to the input and output of a system command. Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

module Unix.hs

1999-08-21 Thread Koen Claessen
Hi all, I am just sending this because there were some people who thought it could be useful. It works for Hugs98, but some hacks I use might be specific to our local system. I think a built-in module with the same function signatures would be extremely useful! Regards, Koen. -

Re: Haskell MIME types?

1999-08-25 Thread Koen Claessen
t has already allowed for introduction of lots of "viruses" because their web applications allow starting up arbitrary MS Word scripts... Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-77

Num classes (was: Function algebra)

1999-10-07 Thread Koen Claessen
er construct in the whole Haskell language is so commonly used as Numbers, and certainly no other construct *forces* me to look at the report, browse preludes etc. so often! (As soon as I want to do something more complicated than +, that is.) Regards, Koen. -- Koen Claessen http://www.cs

Re: Referential Transparency

1999-10-08 Thread Koen Claessen
tions returning the same result if called with the same arguments? Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Partial Type Declarations

1999-11-17 Thread Koen Claessen
sig Bool composedObject = object1 <#> object2 I would welcome any comments and suggestions (and proofs of (un)soundness of formal definitions of the semantics :-) Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

QuickCheck

1999-12-01 Thread Koen Claessen
there are slight differences in function names between these presentations. Comments are very welcome! The implementation is Haskell'98 compatible. Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-

Re: Dynamic scopes in Haskell

1999-12-02 Thread Koen Claessen
in practise. One possible problem though is that you lose equality on types like "N a". If you really want equality *and* sharing, (but care a little bit less about some particular laws that Haskell "has" -- which are by the way not defined anywhere anyway) you might want to tak

Re: Dynamic scopes in Haskell

1999-12-03 Thread Koen Claessen
e of an "optimization" (eta-expansion) which is done for class methods, thus losing sharing). Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: Dynamic scopes in Haskell

1999-12-03 Thread Koen Claessen
- reader monads (we have seen the memoizing solution), - writer monads (where the monoid is commutative), - "distribution monads" (I recently came up with this name for a kind of reader monad which can split its environment up in two independent parts and distribute it over

Re: Reflection (was: Relection)

2000-01-25 Thread Koen Claessen
:: Reflective a => Name -> Maybe a Or maybe a more interesting type would be: lookup :: Name -> Dyn I like some of the ideas behind reflection, but I am not sure if I like the exact way you propose this extension. But I don't know enough about reflection to propose s

Re: `partition', laziness policy

2000-01-20 Thread Koen Claessen
ards, Koen. PS. By the way, several people have already pointed out that, if the example is rewritten as: partition2 p = foldr (\x ~(ys, zs) -> if p x then (x:ys,zs) else (ys,x:zs)) ([],[]) (one twiddle more), the implementations are in fact equivalent. -- Koen Cl

RE: Haskell 98: partition; and take,drop,splitAt

2000-01-31 Thread Koen Claessen
like sending mail to one person, or a cgi script on the web. (I hope you have not already done this, but if you have, I missed it and I couldn't find anything like it in your old messages). Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424

Re: Haskore installation

2000-02-02 Thread Koen Claessen
declared. So that both Haskore and QuickCheck (and any other program that is broken after this Haskell98 "fix") can just import this module and co-exist happily! (As I understand, this module is now part of the Hugs/GHC distribution tree.) /Koen. -- Koen Claessen http://www.cs

Re: "Typo" in Haskell 98 Random library

2000-02-02 Thread Koen Claessen
ath starting at gen1 intersects with a "split"-path starting at gen2". (In reality, this can never be the case because generators have a bounded representation, but we might adapt the definition to "split"-paths of reasonable le

Re: more on Random

2000-02-04 Thread Koen Claessen
;next", use "Random.split" or "Random.next". (And there you have your prefix -- for free!) Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] -

Re: rounding in haskell

2000-02-08 Thread Koen Claessen
Hello ASCII artists, Maybe the rounding issue, which doesn't seem to have much to do with Haskell anymore at this point, can be taken offline? Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROT

Re: Random numbers

2000-03-24 Thread Koen Claessen
of generating an infinite list of random seeds form one random seed. This could be achieved if StdGen was an instance of `Random', but somehow this cannot be done (since a StdGen does not have any bounds). Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46

Re: improving error messages

2000-04-03 Thread Koen Claessen
cannot be shown, but it is easy to show the type of a function. So, it is a good idea to keep the classes Show and ShowType/Typeable separately. /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] --

Re: Type signatures in instance declarations?

2000-04-10 Thread Koen Claessen
ut not the comments). Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: Use of irrefutable

2000-04-20 Thread Koen Claessen
guage ;-) where these tricks are necessary (for example constructing a loop over lists), but I don't see why the standard "lift1" function should use lazy map. It can lead to worse space behavior too ... Maybe one of the Hawk implementors can enlighten us on this subject? Regards, Koen

RE: lines --- to derive, or not to derive ;-)

2000-05-10 Thread Koen Claessen
\n' (you forgot to reverse acc in the recursion base case...) /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: deriving Functor

2000-05-12 Thread Koen Claessen
kell") which will make this easy to do. There already is a preprocessor that does similar things, called "PolyP". Regards, Koen. References: http://www.cs.chalmers.se/~patrikj/poly/ http://www.students.cs.uu.nl/people/jwit/GenericHaskell.html -- Koen Claessen http://www.c

Re: Block simulation / audio processing

2000-05-18 Thread Koen Claessen
d be happy to send a preliminary version of Lava, and to explain how it is implemented and how to modify it to deal with other domains than digital hardware. Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL

RE: Block simulation / audio processing

2000-05-18 Thread Koen Claessen
onads. Regards, Koen. [1] Koen Claessen, David Sands, "Observable Sharing for Functional Circuit Description", ASIAN '99, Phuket, Thailand, 1999. http://www.cs.chalmers.se/~koen/Papers/obs-shar.ps -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-7

RE: import List(..)

2000-05-22 Thread Koen Claessen
ax (such as >>=, return, mfail, fromInteger, etc.). What happens in general when one uses this special notation in a module which redefines these operators? I think the easiest thing to do is just to make the translation *always* refer to their prelude definitions. Just my 2 öre... Regards, Koen.

Re: Modular interpreters (Was: )

2000-05-26 Thread Koen Claessen
TypesIn :: (Either a b, (a,b), [b]) -> x -> x > specTypesIn _ = id Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: unsafeinterleaveIO

2000-05-30 Thread Koen Claessen
:: Handle -> IO String getContents h = unsafeInterleaveIO $ do x <- hGetChar h xs <- getContents h return (x:xs) Note that we have to use "unsafeInterleaveIO" at every element of the list (at every recursive call

Re: poll: polymorphic let bindings in do

2000-06-04 Thread Koen Claessen
7;s syntatic sugar (one doesn't even need the whole do-notation). Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: poll: polymorphic let bindings in do

2000-06-04 Thread Koen Claessen
thout it. I could have said: fun var x = .. var .. x .. program = runST (do var <- newSTRef [] .. fun var a .. fun var b ..) But that is not the point. I just went through my code and looked at how many definitions in do-notation actually were polymorphic. /Koen. -- Koen

Re: "Boxed imperatives" to implement pure functions

2000-06-06 Thread Koen Claessen
correctness using algebraic methods. Both are available from: http://www.cse.ogi.edu/~jl/biblio-functional.html Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED]

Re: Results: poll: polymorphic let bindings in do

2000-06-06 Thread Koen Claessen
us all a pointer to your work! :-) (I want to read about it!!), Koen. (ceterum censeo restrictionem monomorfismi esse delendam) -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: numericEnumFromThenTo strangeness

2000-07-10 Thread Koen Claessen
seemingly inconsistent design. /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: monadic source of randomness

2000-08-15 Thread Koen Claessen
n also be used for computations that need to create fresh identifiers. These kind of things do not need to be single-threaded (and often require non-single threadedness). Regards, Koen. [1] Koen Claessen and John Hughes, "QuickCheck: A Lightweight Tool for Random Testing of Haskell Programs&quo

Literate Programming

2000-09-26 Thread Koen Claessen
word at last week's ICFP :-): > bfReplace :: [b] -> Tree a -> Tree b > bfReplace xs = deQ . bfReplaceQ xs . singletonQ Now we just have to define bfReplaceQ. Which introduces large whitespaces in my text! It is interesting to notice that the "\begin{code

Num class

2000-10-18 Thread Koen Claessen
s will be broken by lifting this restriction? /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: cpp superior to ghc . . .

2000-10-25 Thread Koen Claessen
known for ages we can all lambda-lift them to top-level... Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmer

Parser Combinators in C

2000-11-22 Thread Koen Claessen
ome people have looked at my code and thought nobody would ever be able to write code like that! Well, I wrote and used this code for real! :-) I guess we functional programmers are (considered to be) weird sometimes :-) :-) Or maybe it is just me... -- Koen Claessen http://www.cs.chalmer

Re: Church' List constructors (was: "Green Card" ...)

2000-11-29 Thread Koen Claessen
rcons : | In ghc algebraic types are really implemented in a similar way :-) Well, not really. This implementation does not give you sharing between lists. Everytime you use "forlist", the list is reevaluated. In GHC, this does not happen of course. Regards, Koen. -- Koen Claessen

Showing Haskell

2000-11-29 Thread Koen Claessen
/Kurser/afp/Cgi/show-haskell.cgi?file=Cgi.hs&title=Module+Cgi (I used it in my course, so there is some extra junk there.) You can click on the bottom of the page, and look at the implementation of the "show-haskell" script. Regards, Koen. -- Koen Claessen http://www.cs.c

fixity for (\\)

2001-01-17 Thread Koen Claessen
\\ (bs \\ (cs \\ ds)) /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers University of Technology, Gothenburg, Sweden

Re: Specifications of 'any', 'all', 'findIndices'

2001-01-23 Thread Koen Claessen
, this is debatable) *possible* implementation, and the compiler writer is free to implement this in whatever way (s)he likes. As long as the implementation has the same functional behavior as the specification in the report. /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-

Re: 'any' and 'all' compared with the rest of the Report

2001-01-23 Thread Koen Claessen
cussed implementations of "any". Or did you mean something else? /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL PROTECTED] - Chalmers Univ

Re: binary files in haskell

2001-02-06 Thread Koen Claessen
one could also say: Byte.write Byte.read So that the context (Byte.) can be left out when unambiguous, and one can just say: write read /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:[EMAIL

Re: binary files in haskell

2001-02-06 Thread Koen Claessen
ure and using more consistent naming conventions. /Koen. (*) What actually happened to the excellent proposal somebody made a while ago for Haskell98: import M = Monad ? I like it a lot! -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailt

Re: Negatively recursive data types

2001-07-04 Thread Koen Claessen
Keith Wansbrough wondered: | Does anyone have an example of a useful data type | involving negative recursion? Here is an example straight from practice. If we want to implement a datatype of predicate logic formulas, it is convenient to use higher-order syntax: type Name = String da

  1   2   >