Re: [Haskell-cafe] Rigid skolem type variable escaping scope

2012-08-22 Thread Lauri Alanko
Quoting Matthew Steele mdste...@alum.mit.edu: {-# LANGUAGE Rank2Types #-} class FooClass a where ... foo :: (forall a. (FooClass a) = a - Int) - Bool foo fn = ... newtype IntFn a = IntFn (a - Int) bar :: (forall a. (FooClass a) = IntFn a) - Bool bar (IntFn fn)

Re: [Haskell-cafe] Rigid skolem type variable escaping scope

2012-08-22 Thread Lauri Alanko
Quoting Matthew Steele mdste...@alum.mit.edu: 1) bar ifn = case ifn of IntFn fn - foo fn 2) bar ifn = foo (case ifn of IntFn fn - fn) I can't help feeling like maybe I am missing some small but important piece from my mental model of how rank-2 types work. As SPJ suggested, translation to

Re: [Haskell-cafe] Type trickery

2011-03-16 Thread Lauri Alanko
On Wed, Mar 16, 2011 at 12:05:56PM +, Andrew Coppin wrote: withContainer ∷ (∀ s. Container s → α) → α Hmm, yes. That will work, but I wonder if there's some way of doing this that doesn't limit the scope of the container to one single span of code... You can just pack the container into

Re: [Haskell-cafe] Splittable random numbers

2011-01-22 Thread Lauri Alanko
On Sat, Jan 22, 2011 at 12:40:04AM -0500, Ryan Newton wrote: On Wed, Nov 10, 2010 at 11:33 AM, Lauri Alanko l...@iki.fi wrote: So a naive implementation of split would be: split g = (mkGen seed, g') where (seed, g') = random g Just to be clear, that is the same as Burton Smith's

Re: [Haskell-cafe] Lambda Calculus: Bound and Free formal definitions

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 02:20:34PM +1030, Mark Spezzano wrote: 5.3 BOUND: = If E1 = \x.xy then x is bound If E2 = \z.z then is not even mentioned So E = E1 E2 = (\x.xy)(\z.z) = (\z.z)y -- Error: x is not bound but should be by the rule of 5.3 Your final = here is beta equality.

[Haskell-cafe] Formatting function types

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 07:04:11AM -0600, Larry Evans wrote: On 12/29/10 22:40, Daryoush Mehrtash wrote: Why do people put ; in do {}, or , in data fields, at the beginning of the line? -- It reflects the parse tree better by putting the combining operators (e.g. ';' and ',') at the

Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 10:39:29AM -0600, Larry Evans wrote: Lauri, I assume then that you want to draw special attention to the return type instead of the first argument type. Only to the fact that the return type is of a different nature than the argument types, and that all the argument

Re: [Haskell-cafe] Do we need Monad fail (or MonadFail)?

2010-12-21 Thread Lauri Alanko
On Tue, Dec 21, 2010 at 08:31:08AM -0700, Jonathan Geddes wrote: I'd love for the compiler to give an error (or maybe just a warning) in the case that I have a pattern match in a monad that just blows up (throws an exception) on a pattern match failure. You will be interested to know that

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 07:04:16PM +1030, John Lask wrote: it is often desirable to have the same field names for many records in the same module. very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on.

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 03:17:39PM +0200, Michael Snoyman wrote: data PetOwner data FurnitureOwner data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner } These are clearly related uses, so as I said, you can use a type class to overload the accessor name in a

Re: [Haskell-cafe] Gödel' s System T

2010-11-11 Thread Lauri Alanko
On Thu, Nov 11, 2010 at 04:04:07PM +, Aaron Gray wrote: On 11 November 2010 11:43, Petr Pudlak d...@pudlak.name wrote: Thanks Dan, the book is really interesting, all parts of it. It looks like I'll read the whole book. Watch out for the decidability issue though :-

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Lauri Alanko
On Wed, Nov 10, 2010 at 11:59:28AM +0200, John Smith wrote: http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution The problem with this is that it conflates two orthogonal features: type-directed name resolution proper (also known as ad hoc overloading), and a fancy

Re: [Haskell-cafe] Splittable random numbers

2010-11-10 Thread Lauri Alanko
On Thu, Nov 04, 2010 at 05:38:12PM +, Simon Peyton-Jones wrote: There's lots of material on generators that generate a linear sequence of random numbers, but much less on how to generate a tree of random numbers, which is what Haskell's System.Random API requires. I'd like to understand

Re: [Haskell-cafe] Edit Hackage

2010-10-29 Thread Lauri Alanko
On Thu, Oct 28, 2010 at 01:55:12PM -0700, Don Stewart wrote: The number of subscribers to the Haskell Reddit, for example, is double the -cafe@, and there are comparable numbers of questions being asked on the Stack Overflow [haskell] tag, as here -- so anyone who only reads -cafe@ is already

Re: [Haskell-cafe] In what language...?

2010-10-25 Thread Lauri Alanko
On Mon, Oct 25, 2010 at 10:10:56PM +0100, Andrew Coppin wrote: Type theory doesn't actually interest me, I just wandered what the hell all the notation means. That sounds like an oxymoron. How could you possibly learn what the notation means without learning about the subject that the notation

Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Lauri Alanko
On Thu, Oct 07, 2010 at 02:45:58PM -0700, Nicolas Pouillard wrote: On Thu, 07 Oct 2010 18:03:48 +0100, Peter Wortmann sc...@leeds.ac.uk wrote: Might be off-topic here, but I have wondered for a while why Haskell doesn't support something like follows: do case (- m) of ... With the

Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Lauri Alanko
On Sun, Jun 21, 2009 at 05:53:04PM +0100, Andrew Coppin wrote: I've written a simple interpretter that takes any valid Lambda expression and performs as many beta reductions as possible. When the input is first received, all the variables are renamed to be unique. Question: Does this

Re: [Haskell-cafe] Purely logical programming language

2009-05-26 Thread Lauri Alanko
On Tue, May 26, 2009 at 09:10:10PM +0200, Matthias Görgens wrote: The model in Prolog, however, looks more like the model used in most strict functional languages. It uses impure predicates to affect the outside world. Do you know of any attempt to do for logic programming what Monads did

Re: [Haskell-cafe] IO trouble

2009-05-12 Thread Lauri Alanko
On Tue, May 12, 2009 at 04:59:36PM -0400, Xiao-Yong Jin wrote: f :: a - b g :: (a - b) - c - d gf :: c - d gf = g f Now I want to handle exceptions in f and redefine f as in f' f' :: a - IO (Either e b) So my question is how to define gf' now to use f' instead of f? gf' ::

Re: Laws and partial values (was: [Haskell-cafe] mapM_ - Monoid.Monad.map)

2009-01-24 Thread Lauri Alanko
On Fri, Jan 23, 2009 at 08:10:38PM -0500, rocon...@theorem.ca wrote: I'd like to argue that laws, such as monoid laws, do not apply to partial values. But I haven't thought my position through yet. Before you do, you may want to read Fast and Loose Reasoning is Morally Correct:

Re: [Haskell-cafe] How to check object's identity?

2009-01-04 Thread Lauri Alanko
On Sun, Jan 04, 2009 at 04:19:38PM +0800, Evan Laforge wrote: If you don't have set-car!, then identity and equality are impossible to differentiate. There's still eqv?. (I wish people wouldn't use eq? as an example of an identity-comparison operation. It's as underdefined as unsafePtrEq.) So

Re: [Haskell-cafe] Rotating backdrop (aka learning Haskell)

2008-05-25 Thread Lauri Alanko
On Tue, May 20, 2008 at 09:15:57AM +0100, Yann Golanski wrote: 1- Get a list out of a file: I managed to do that using the following: parseImageFile :: FilePath - IO [String] parseImageFile file = do inpStr - readFile file return $ filter (/=) (breaks (=='\n')

Re: [Haskell-cafe] one-way monads

2008-05-20 Thread Lauri Alanko
On Tue, May 20, 2008 at 07:54:33AM +0200, Zsolt SZALAI wrote: Here comes IO and one-way monads, where the internal state can not be extacted, and seems, that the internal data is global to the program. Hows that could be? Is it just because main::IO() or because the implementation of IO uses

Re: [Haskell-cafe] Monad for HOAS?

2008-05-14 Thread Lauri Alanko
On Wed, May 14, 2008 at 03:59:23PM +0100, Edsko de Vries wrote: You mention that a direct implementation of what I suggested would break the monad laws, as (foo) and (Let foo id) are not equal. But one might argue that they are in fact, in a sense, equivalent. Do you reckon that if it is

Re: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread Lauri Alanko
Please note that if you're using GHC, bang patterns are often much more convenient than $! or seq when you want to enforce strictness: http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html Lauri ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] haskell and reflection

2007-09-11 Thread Lauri Alanko
On Tue, Sep 11, 2007 at 07:33:54AM -0700, Greg Meredith wrote: Our analysis suggested the following breakdown - Structural reflection -- all data used in the evaluation of programs has a programmatic representation - Procedural reflection -- all execution machinery used in the

Re: [Haskell-cafe] positive Int

2007-08-02 Thread Lauri Alanko
On Thu, Aug 02, 2007 at 02:08:33PM -0700, David Roundy wrote: This would be a very nice type to have (natural numbers), but is a tricky type to work with. Subtraction, for instance, wouldn't be possible as a complete function... Of course it would. It would just have the type Nat - Nat -

Re: [Haskell-cafe] infinite list of random elements

2007-07-30 Thread Lauri Alanko
On Mon, Jul 30, 2007 at 02:40:35PM -0700, Chad Scherrer wrote: Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's).

[Haskell-cafe] Interactively used EDSLs

2005-10-17 Thread Lauri Alanko
and piping processes would fill this description, but I don't think such a thing exists. Yet I do have a vague recollection that there are some existing DSLs that can be used in such a way. Does anyone have suggestions? Thanks. Lauri Alanko [EMAIL PROTECTED

Re: [Haskell-cafe] Type conversion problems

2004-06-13 Thread Lauri Alanko
this helps. Lauri Alanko [EMAIL PROTECTED] ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Eval in Haskell

2003-06-02 Thread Lauri Alanko
in the environment. Some schemes do, though.) Lauri Alanko [EMAIL PROTECTED] ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Eval in Haskell

2003-06-02 Thread Lauri Alanko
on whether it was already bound. Lauri Alanko [EMAIL PROTECTED] ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Interpret haskell within haskell.

2002-12-22 Thread Lauri Alanko
haven't yet managed to write up a more lucid exposition of the issue...) Lauri Alanko [EMAIL PROTECTED] ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Interpret haskell within haskell.

2002-12-20 Thread Lauri Alanko
and static types. Strangely enough, I haven't found any real research on this particular subject. There's lots of work on related areas, eg. dynamic types and intensional polymorphism, but nothing that's really motivated by eval and reflection. Any suggestions for references are welcome. :) Lauri

Formatting function types

2002-11-18 Thread Lauri Alanko
. For right-associative ones (such as the function arrow), the One True Way is this: Handle - Ptr a - Int - IO () Nuff said. Lauri Alanko [EMAIL PROTECTED] ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http

OT: broken mail threads

2002-08-20 Thread Lauri Alanko
sources. If you find yourself using one of these programs, could you please check your configuration or maybe consider switching to a more well-behaving user agent? This would make your messages much easier to follow. Thanks. Lauri Alanko [EMAIL PROTECTED

Re: functions not in type classes

2002-01-19 Thread Lauri Alanko
(Lift z) = z runTerm (a : b) = runTerm a runTerm b -- ... I never actually pursued this idea to the end, though, so I don't know if this would be useful in practice. But still, it's a neat idea, and gives a reason why const should be in a class. :) Lauri Alanko [EMAIL PROTECTED