Re: [Haskell-cafe] how to nicely implement phantom type coersion?

2005-12-08 Thread Thomas Jäger
Hello, Since you're already using GADTs, why not also use them to witness type equality: import GHC.Exts data Patch a b = Patch Int Int data Sequential a c where Sequential :: Patch a b - Patch b c - Sequential a c data MaybeEq :: * - * - * where NotEq :: MaybeEq a b IsEq :: MaybeEq

Re: [Haskell-cafe] ReaderT and concurrency

2005-11-16 Thread Thomas Jäger
Kurt, There are basically two ways of doing that, namely monad transformers and implicit parameters (we actually use both techniques in lambdabot). Implicit parameters save you a lot of conversions or explicit passing of variables because you only need one monad (the IO monad); however they are

Re: [Haskell-cafe] Functional dependencies and type inference

2005-08-22 Thread Thomas Jäger
Simon, I believe there may be some nasty interactions with generalized newtype-deriving, since we can construct two Leibniz-equal types which are mapped to different types using fundeps: class Foo a where foo :: forall f. f Int - f a instance Foo Int where foo = id newtype Bar =

Re: [Haskell-cafe] Control.Monad.Cont fun

2005-07-25 Thread Thomas Jäger
Hello Andrew, On 7/25/05, Andrew Pimlott [EMAIL PROTECTED] wrote: getCC :: Cont r (Cont r a) getCC = ccc (\(c :: Cont r a - (forall b. Cont r b)) - let x :: forall b. Cont r b = c x in x) gives [Error] ghc-6.2 accepts this: getCC :: Cont r (Cont r a) getCC =

[Haskell-cafe] Re: Control.Monad.Cont fun

2005-07-23 Thread Thomas Jäger
Hi, Sorry, I have to do a small correction to an earlier post of mine. On 7/9/05, I wrote: In order to move the function (\jmp - jmp `runC` jmp) into callCC, the following law, that all instances of MonadCont seem to satisfy, is very helpful. f = callCC g === callCC (\k - f = g ((=) k .

[Haskell-cafe] Re: Control.Monad.Cont fun

2005-07-09 Thread Thomas Jäger
Hello Tomasz, This stuff is very interesting! At first sight, your definition of getCC seems quite odd, but it can in fact be derived from its implementation in an untyped language. On 7/7/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: Some time ago I wanted to return the escape continuation out

[Haskell-cafe] Re: [Haskell] best way to do generic programming?

2005-07-01 Thread Thomas Jäger
Arka, as you already mentioned, you want to have a look at the Scrap your Boilerplate approach. import Data.Generics ... data Expr = Const Int | Var String | Add Expr Expr deriving (Typeable, Data) will derive the necessary Data instance and allow you to define optimizeDeep :: Data a = a -

Re: [Haskell-cafe] Why I Love Haskell In One Simple Example

2005-06-28 Thread Thomas Jäger
Hi Mads, Since ghc-6.4 there's another feature that is enabled by such explicit foralls in type signatures, namely scoped type variables. Consider foo :: Num a = a - a - a foo x y = x + z where z = 2 * y Now since adding type signatures is a good thing, you want to give z an explicit type

Re: [Haskell-cafe] implicit parameters THANK YOU!

2005-03-22 Thread Thomas Jäger
On Mon, 21 Mar 2005 20:29:35 -0500 (Eastern Standard Time), S. Alexander Jacobson [EMAIL PROTECTED] wrote: I just discovered implicit parameters. To everyone involved with making them, THANK YOU. They are blazingly useful/powerful for server handler style libraries where you want to make a

Re: [Haskell-cafe] implicit parameters THANK YOU!

2005-03-22 Thread Thomas Jäger
Hello again, Sorry, I made a little mistake. a :: Int a = let ?foo = 0 in b where b :: (?foo :: Int) = Int b = let ?foo = 1 in c where c = ?foo The meaning of this code depends on the flag -f(no)-monomorphism-restriction since with the monomorphism turned on, `c' gets the

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Thomas Jäger
On Mon, 14 Feb 2005 11:07:48 +0100, Daniel Fischer And could one define \f g h x y - f (g x) (h y) point-free? sure, ((flip . ((.) .)) .) . (.) Thomas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Thomas Jäger
Hi, On Mon, 14 Feb 2005 14:40:56 +0100, Daniel Fischer wrote: \f g h x y - f (g x) (h y) ((flip . ((.) .)) .) . (.) Cool! But I must say, I find the pointed version easier to read (and define). It certainly is. In fact, I transformed it automatically using a toy lambdabot plugin, i've

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Thomas Jäger
On Mon, 14 Feb 2005 16:46:17 +0100, Lennart Augustsson [EMAIL PROTECTED] wrote: Remi Turk wrote: import Control.Monad.Reader k :: a - b - a k = return s :: (a - r - b) - (a - r) - a - b s = flip (=) . flip This can be even written as s = ap. It can be done without importing

Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-11 Thread Thomas Jäger
Hi, On Thu, 10 Feb 2005 16:18:19 -0800, Iavor Diatchki [EMAIL PROTECTED] wrote: because I don't like the current situation with (n+k)-patterns: Everybody says they're evil, but hardly anybody can explain why he thinks so. I think 'evil' may be a little too strong. I think the usual

Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Thomas Jäger
Is there also a Wiki page about things you should avoid? Since I couldn't find one, I started one on my own: http://www.haskell.org/hawiki/ThingsToAvoid I consider 'length', guards and proper recursion anchors. [Moving the discussion from the wiki to the mailing list until we've

Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Thomas Jäger
On Thu, 10 Feb 2005 12:50:16 +0100 (MET), Henning Thielemann [EMAIL PROTECTED] wrote: On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote: Altogether, the spirit of the page seems to be use as little syntactic sugar as possible which maybe appropriate if it is aimed at newbies, who