Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Kim-Ee Yeoh
Ronald Guida wrote: Here is the brief explanation I came up with: Arrows and monads are abstract data types used to construct Domain Specific Embedded Languages (DSELs) within Haskel. A simple arrow provides a closed DSEL. A monad is a special type of arrow that creates an open

Re: [Haskell-cafe] Explaining monads

2007-08-16 Thread Kim-Ee Yeoh
Paul Hudak wrote: [I]n the one-of-many ways that I view monads, a monad is just a high-order function that abstracts away function composition. In particular, if I have an action f, and an action g, I can think of them as recipes, because I can combine them via f = g. It's only after I

Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-16 Thread Kim-Ee Yeoh
Aaron Denney wrote: On 2007-08-15, Pekka Karjalainen [EMAIL PROTECTED] wrote: A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals. text = If you want to have multiline string literals \ \in your source code, you can break

Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Kim-Ee Yeoh
Lennart Augustsson wrote: On 8/16/07, Kim-Ee Yeoh [EMAIL PROTECTED] wrote: 'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does assembling at compile time mean here: s = I will not write infinite loops ++ s But if the strings are all

Re: [Haskell-cafe] Re: Bathroom reading

2007-08-17 Thread Kim-Ee Yeoh
ok-4 wrote: Someone mentioned the Blow your mind page. One example there really caught my attention. 1234567 = (1357,246) foldr (\a ~(x,y) - (a:y,x)) ([],[]) I've known about lazy match since an early version of the Haskell report, but have never actually used it. Last night,

Re: [Haskell-cafe] Compile-time v run-time

2007-08-17 Thread Kim-Ee Yeoh
If RAM was treated as an extension of non-volatile storage instead of the other way round, we'd already be there. Put another way, would suspending program to disk achieve the same results? Jon Fairbairn wrote: Something I've wanted to experiment with for a long time and never got round

Re: [Haskell-cafe] Question of a manual computation on Reader Monad.

2007-08-25 Thread Kim-Ee Yeoh
一首诗 wrote: runReader (do { b - Reader $ show; return b } ) -- This is the initial expression, it should equals show runReader (Reader $ show = \b - return b) -- remove do notion I'm not sure that's the right un-do-ization. It so happens that the exponent monad ((-) r) and the

Re: [Haskell-cafe] Elevator pitch for Haskell.

2007-09-10 Thread Kim-Ee Yeoh
Devin Mullins wrote: As for the latter, the reason I hear most often is I want to be able to use the language at my job.* -- snip -- * This is somewhat odd, as the strong majority of vocal Rubyists /are/ using it at their job. Not without risk though. Their necks get wrung if things

Re: [Haskell-cafe] Where are the haskell elders?

2010-04-05 Thread Kim-Ee Yeoh
Something I've noticed is the phenomenon of Help Vampires [1] on this list. Amy Hoy: As soon as an open source project, language, or what- have-you achieves a certain notoriety—its half-life, if you will— they swarm in, seemingly draining the very life out of the community itself. She

Re: [Haskell-cafe] Graphical graph reduction

2008-02-23 Thread Kim-Ee Yeoh
dainichi wrote: Now to the point: Wouldn't it be great if I had a visual tool that visually showed me the graph while the above evaluation unfolded? I could use it to show some of my co-workers to whom laziness is a mystery, what it's all about. Check out

Re: [Haskell-cafe] Functional programmer's intuition for adjunctions?

2008-03-05 Thread Kim-Ee Yeoh
ajb-2 wrote: In Haskell, natural transformations are functions that respect the structure of functors. Since you can't avoid respecting the structure of functors (the language won't let you do otherwise), you get natural transformations for free. (Free as in theorems, not free as in

Re: [Haskell-cafe] Wrong Answer Computing Graph Dominators

2008-04-17 Thread Kim-Ee Yeoh
Dan Weston wrote: Here, any path means all paths, a logical conjunction: and [True, True] = True and [True ] = True and [ ] = True Hate to nitpick, but what appears to be some kind of a limit in the opposite direction is a curious way of arguing that: and [] = True.

Re: [Haskell-cafe] Wrong Answer Computing Graph Dominators

2008-04-19 Thread Kim-Ee Yeoh
Dan Weston wrote: f . and == and . map f where f = (not x ||) If and is defined with foldr, then the above can be proven for all well-typed f, and for f = (not x ||) in particular, even if ys is null. The law is painlessly extended to cover the null case automatically (and is

Re: [Haskell-cafe] Couple of formal questions

2008-05-02 Thread Kim-Ee Yeoh
I'm not sure there's a proof as such, more like a definitional absence of distinction between initiality and finality. In other words, the CPO framework is orthogonal to such extremality considerations. Perhaps someone here knows about work enriching CPOs in that direction. -- Kim-Ee

Re: [Haskell-cafe] Short circuiting and the Maybe monad

2008-05-16 Thread Kim-Ee Yeoh
Dan Piponi-2 wrote: In fact, you can use the Reader monad as a fixed size container monad. Interesting that you say that. Reader seems to me more as an anti-container monad. -- View this message in context:

Re: Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-27 Thread Kim-Ee Yeoh
Andrew Coppin wrote: So, after an entire day of boggling my mind over this, I have brought it down to one simple example: (id 'J', id True) -- Works perfectly. \f - (f 'J', f True) -- Fails miserably. Both expressions are obviously perfectly type-safe, and yet the type

Re: Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Kim-Ee Yeoh
Roberto Zunino-2 wrote: Alas, for code like yours: foo = \f - (f 'J', f True) there are infinite valid types too: (forall a. a - Int) - (Int, Int) (forall a. a - Char)- (Char, Char) (forall a. a - (a,a)) - ((Char,Char),(Bool,Bool)) ... and it is much less clear if a

Re: Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Kim-Ee Yeoh
... uh, as He pleases. Anyway, the original point of it was semantic. Let's first explore the meaning of the most general type. Type functions give one answer, intersection types another. -- Kim-Ee (yeoh at cs dot wisc dot edu) -- View this message in context: http://www.nabble.com/Aren%27t

Re: [Haskell-cafe] More on performance

2008-06-05 Thread Kim-Ee Yeoh
Jon Harrop wrote: On Wednesday 04 June 2008 11:05:52 Luke Palmer wrote: Given unbounded time and space, you will still arrive at the same result regardless of the complexity. Given that the set of computers with unbounded time and space is empty, is it not fruitless to discuss its

[Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Kim-Ee Yeoh
Does anyone know if it's possible to write the following: ** :: (Applicative m, Applicative n) = m (n (a-b)) - m (n a) - m (n b) Clearly, if m and n were monads, it would be trivial. Rereading the original paper, I didn't see much discussion about such nested app. functors. Any help

Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Kim-Ee Yeoh
On Oct 12, 2009, at 11:22 AM, Kim-Ee Yeoh wrote: ** :: (Applicative m, Applicative n) = m (n (a-b)) - m (n a) - m (n b) -- View this message in context: http://www.nabble.com/%3C**%3E-for-nested-applicative-functors--tp25858792p25859274.html Sent from the Haskell - Haskell-Cafe mailing

Re: [Haskell-cafe] Is there a null statement that does nothing?

2009-10-27 Thread Kim-Ee Yeoh
Hi Brent, Re: 'if expressions, not statements' is an elegant clarification, one definitely for the haskellwiki, if not there already. Just for completeness' sake, bottom is a value for any expression. Wouldn't making the else clause optional by defaulting to undefined worthy of consideration

Re: [Haskell-cafe] pointfree-trouble

2009-12-22 Thread Kim-Ee Yeoh
Here's another way of writing it: data Matrix a = Matr {unMatr :: [[a]]} | Scalar a deriving (Show, Eq) -- RealFrac constraint removed reMatr :: RealFrac a = ([[a]] - [[a]]) - (Matrix a - Matrix a) reMatr f = Matr . f . unMatr -- this idiom occurs a lot, esp. with newtypes Affixing

Re: [Haskell-cafe] pointfree-trouble

2009-12-22 Thread Kim-Ee Yeoh
the reMatr function pointfree, as reMatr = Matr . (flip (.) unMatr) is not working. any ideas/explanation why it doesnt work? Kim-Ee Yeoh wrote: Here's another way of writing it: data Matrix a = Matr {unMatr :: [[a]]} | Scalar a deriving (Show, Eq) -- RealFrac constraint removed

Re: [Haskell-cafe] (liftM join .) . mapM

2009-12-29 Thread Kim-Ee Yeoh
I'd write it as foo f = join .$ sequence . (f $) where (.$) :: (.$) :: Functor f = (a - b) - ((x - f a) - (x - f b)) x .$ y = (x $) . y is part of my line-noise toolbox. This join .* sequence family of functions is quite common. Should really have a name for them. Tony Morris-4 wrote:

Re: [Haskell-cafe] Finally tagless and abstract relational Algebra

2009-12-29 Thread Kim-Ee Yeoh
Günther Schmidt wrote: Initially I had simply imported the CSV files into empty tables in a database and done the calculations directly in SQL, never ever again! [snip] But my 1st goal here is to express the algorithm. Sounds like you want a better DSL than SQL. You're in massive

Re: [Haskell-cafe] Finally tagless and abstract relational Algebra

2009-12-29 Thread Kim-Ee Yeoh
The code we want to write is that which matches the way we think [snip] My way is to think hard about what the best way to think about things is. I'm in two minds. On the one hand, we're in violent agreement: The code we /want/ to write is that which matches the way we /want/ to think,

Re: [Haskell-cafe] Functor and Haskell

2009-04-22 Thread Kim-Ee Yeoh
Daryoush Mehrtash-2 wrote: I am not sure I follow how the endofunctor gave me the 2nd functor. As I read the transformation there are two catagories C and D and two functors F and G between the same two catagories. My problem is that I only have one functor between the Hask and List

Re: [Haskell-cafe] Functor and Haskell

2009-04-22 Thread Kim-Ee Yeoh
Daryoush Mehrtash-2 wrote: singleton :: a - [a] singleton x = [x] Here F is the identity functor, and G is the list functor. And yes, C=D= category of (a subset of) Haskell types. Are you saying the function that goes from list functor to singleton funtor is a natural

Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh
Hi Vasili, This isn't really a shadowing/redefinition issue. Here's a perfectly legitimate snippet that compiles fine: f 0 = 0 f otherwise = 1+otherwise Redefinition is when you have: g = let otherwise = not in x -- Kim-Ee VasiliIGalchin wrote: swishParse :: String - String -

Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh
I meant, of course, g = let otherwise = not in otherwise Sorry for the noise. -- Kim-Ee Kim-Ee Yeoh wrote: Hi Vasili, This isn't really a shadowing/redefinition issue. Here's a perfectly legitimate snippet that compiles fine: f 0 = 0 f otherwise = 1+otherwise Redefinition

Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh
Whoops, you're right. Interestingly, the shadowing warnings vary between the 2 examples I gave, i.e. shadowing within 'function definition' vs 'binding group'. Felipe Lessa wrote: On Sun, Jun 28, 2009 at 12:49:12AM -0700, Kim-Ee Yeoh wrote: This isn't really a shadowing/redefinition

Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Kim-Ee Yeoh
Could you suggest a better word pair to describe the dichotomy then? How about 'calculated' vs 'user-imposed' (or even, 'explicitly- signatured')? Dan Piponi-2 wrote: I really dislike this error message, and I think the terms are ambiguous. I think the words 'expected' and 'inferred' apply

[Haskell-cafe] Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Kim-Ee Yeoh
I'm trying to write HOAS Show instances for the finally-tagless type-classes using actual State monads. The original code: http://okmij.org/ftp/Computation/FLOLAC/EvalTaglessF.hs Two type variables are needed: one to vary over the Symantics class (but only as a phantom type) and another to

Re: [Haskell-cafe] Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-03 Thread Kim-Ee Yeoh
Hi Edward, Your runPretty version fits the bill nicely, thank you. I might still retain the state monad version because it allows generalizations beyond pretty-printing. As for fixing the original bug, I've found that the real magic lies in the incantation (Y . unY) inserted at the appropriate

Re: [Haskell-cafe] Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-11 Thread Kim-Ee Yeoh
Kim-Ee Yeoh wrote: As for fixing the original bug, I've found that the real magic lies in the incantation (Y . unY) inserted at the appropriate places. Aka unsafeCoerce, changing the phantom type |a|. The type of (Y . unY) is (Y . unY) :: forall a b c. Y c a - Y c b so modulo (Y c

Re: [Haskell-cafe] n00b question: defining datatype

2009-07-23 Thread Kim-Ee Yeoh
Consider data Task = Task { title :: String, completed :: Bool, subtasks :: Maybe [Task] } Iain Barnett wrote: Hi, I'm trying to get my head around datatypes, and wondering how I might define a simple Task datatype in Haskell. data Task = Task { title :: String, completed :: Bool }

Re: [Haskell-cafe] Essentials about type classes?

2009-09-11 Thread Kim-Ee Yeoh
Hi Fredrik, Temaran wrote: data Dar = Dar String String deriving (Show, Eq) class Bar a where foo :: a - Int instance Bar Dar where foo(Dar n c) = length c but it keeps generating the same error; ERROR ./Bar.hs:16 - Inferred type is not general enough *** Expression:

Re: [Haskell-cafe] Lazy vs correct IO [Was: A round of golf]

2008-09-19 Thread Kim-Ee Yeoh
oleg-30 wrote: I have not expected to see this Lazy IO code. After all, what could be more against the spirit of Haskell than a `pure' function with observable side effects. What could even be more against the spirit of Haskell than the original theme of this thread, i.e. code that

Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread Kim-Ee Yeoh
re: the importance of existential-cleansing On the one hand, it's easy to concur that existentials are simpler than the alternatives, the tortuous elimination of CC Shan's translucent existential being a case in point. And it's also easy to dismiss such caprice as a penchant for Houdinian

Re: [Haskell-cafe] Problems with strictness analysis?

2008-11-04 Thread Kim-Ee Yeoh
David Menendez-2 wrote: On Mon, 3 Nov 2008, Luke Palmer wrote: I was actually being an annoying purist. f is strict means f _|_ = _|_, so strictness is a semantic idea, not an operational one. I think Luke was commenting on the terminology, not the optimization. We have a tendency to

Re: Re: [Haskell-cafe] Problems with strictness analysis?

2008-11-05 Thread Kim-Ee Yeoh
Luke Palmer-2 wrote: I would like to know or to develop a way to allow abstract analysis of time and space complexity. In the same way that type inference and strictness analysis can be seen as instances of abstract interpretation, so can complexity inference. I agree that the interplay

Re: [Haskell-cafe] FW: RE Monad Description For Imperative Programmer

2007-08-08 Thread Kim-Ee Yeoh
Claus Reinke wrote: there is usually a way to interpret monadic structures built in this way (a 'run' operation of some kind). The run operation of type (m a - a) is the (comonadic) coreturn. Many monads are almost comonads too, for a meaning of almost to be made precise. Claus Reinke

Re: [Haskell-cafe] Monad Description For Imperative Programmer

2007-08-08 Thread Kim-Ee Yeoh
Seth Gordon wrote: Functors are a generalization from lists to things that can be mapped over in general, and then monads are a generalization of functors. Way to go! That way lies true co/monadic enlightenment. Put another way, monads are no more about (only) IO/sequencing than fmap is

Re: [Haskell-cafe] Explaining monads

2007-08-10 Thread Kim-Ee Yeoh
Brian Brunswick-5 wrote: g f ??? g ??? f application a a-b flip ($) b monad bind m a a-m b= m b comonad cobind w a w a-b= w b arrowarr a b arr b c arr

Re: [Haskell-cafe] Explaining monads

2007-08-11 Thread Kim-Ee Yeoh
Ronald Guida wrote: Here's my interpretation of the table: -- Structure | Subject | Action| Verb | Result +--+++-- function| a | a-b

Re: [Haskell-cafe] Explaining monads

2007-08-12 Thread Kim-Ee Yeoh
David Menendez wrote: This is probably because no one has found a compelling use case for comonadic-style programming in Haskell. There have been some interesting papers, such as Comonadic functional attribute evaluation by Uustalu and Vene, but nothing as compelling as Wadler's Monads

Re: [Haskell-cafe] Explaining monads

2007-08-13 Thread Kim-Ee Yeoh
Ronald Guida wrote: Given the question What is a Monad, I would have to say A Monad is a device for sequencing side-effects. There are side-effects and there are side-effects. If the only monad you use is Maybe, the only side-effect you get is a slight warming of the CPU. Dave Menendez

Re: [Haskell-cafe] Looking for pointfree version

2009-02-11 Thread Kim-Ee Yeoh
On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless. pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1) Edsko de Vries wrote: Perfect! Beautiful. I was hoping there'd be a simple solution like that. Thanks!

Re: [Haskell-cafe] forall ST monad

2009-02-15 Thread Kim-Ee Yeoh
Peter Verswyvelen-2 wrote: I could try to read the article a couple of times again, but are there any other good readings about these existentially quantified types and how the ST monad works? The primary source is if I'm not mistaken, the following State in Haskell paper:

Re: Re: [Haskell-cafe] Looking for pointfree version

2009-02-15 Thread Kim-Ee Yeoh
import Control.Applicative data Pair a = a :*: a instance Functor Pair where f `fmap` (x :*: y) = f x :*: f y instance Applicative Pair where (f :*: g) * (x :*: y) = f x :*: f y The last f needs to be a g. pure x = x :*: x pointfree :: (a - b - c) - Pair a -

Re: [Haskell-cafe] forall ST monad

2009-02-16 Thread Kim-Ee Yeoh
Peter Verswyvelen-2 wrote: I'm having trouble understanding the explanation of the meaning of the signature of runST at http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types I could try to read the article a couple of times again, but are there any other good readings

Re: [Haskell-cafe] forall ST monad

2009-02-16 Thread Kim-Ee Yeoh
. Februar 2009 19:04 schrieb Kim-Ee Yeoh: Despite its rank-2 type, runST really doesn't have anything to do with existential quantification. First, I thought so too but I changed my mind. To my knowledge a type (forall a. T[a]) - T' is equivalent to the type exists a. (T[a] - T'). It’s the same

Re: [Haskell-cafe] forall ST monad

2009-02-19 Thread Kim-Ee Yeoh
Jonathan Cast-2 wrote: Summary: Existential types are not enough for ST. You need the rank 2 type, to guarantee that *each* application of runST may (potentially) work with a different class of references. (A different state thread). Interesting. What's going on in the example that

Re: [Haskell-cafe] forall ST monad

2009-02-19 Thread Kim-Ee Yeoh
There's a lot to chew on (thank you!), but I'll just take something I can handle for now. Dan Doel wrote: An existential: exists a:T. P(a) is a pair of some a with type T and a proof that a satisfies P (which has type P(a)). In Haskell, T is some kind, and P(a) is some type

Re: [Haskell-cafe] forall ST monad

2009-02-19 Thread Kim-Ee Yeoh
Jonathan Cast-2 wrote: Taking the `let open' syntax from `First-class Modules for Haskell' [1], we can say let open runST' = runST in let ref = runST' $ newSTRef 0 !() = runST' $ writeSTRef ref 1 !() = runST' $ writeSTRef ref 2 in runST' $ readSTRef ref This

Re: [Haskell-cafe] forall ST monad

2009-02-20 Thread Kim-Ee Yeoh
Wolfgang Jeltsch-2 wrote: Am Montag, 16. Februar 2009 19:22 schrieb Wolfgang Jeltsch: First, I thought so too but I changed my mind. To my knowledge a type (forall a. T[a]) - T' is equivalent to the type exists a. (T[a] - T'). It’s the same as in predicate logic – Curry-Howard in action.

Re: [Haskell-cafe] forall ST monad

2009-02-25 Thread Kim-Ee Yeoh
Heinrich Apfelmus wrote: Now, (forall a. T[a]) - S is clearly true while exists a. (T[a] - S) should be nonsense: having one example of a marble that is either red or blue does in no way imply that all of them are, at least constructively. (It is true classically, but I

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-18 Thread Kim-Ee Yeoh
Oleg, Let me try to understand what you're saying here: (1) Church encoding was discovered and investigated in an untyped setting. I understand your tightness criterion to mean surjectivity, the absence of which means having to deal with junk. (2) Church didn't give an encoding for

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-23 Thread Kim-Ee Yeoh
to lists. The enclosed code shows the list encoding that has constant-time cons, head, tail and trivially expressible fold and zip. Kim-Ee Yeoh wrote: So properly speaking, tail and pred for Church-encoded lists and nats are trial-and-error affairs. But the point is they need not be if we

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-26 Thread Kim-Ee Yeoh
Both are excellent points, thank you. Your mention of general recursion prompts the following: in 1995, ten years after publication of Boehm-Berarducci, Launchbury and Sheard investigated transformation of programs written in general recursive form into build-foldr form, with an eye towards the

Re: [Haskell-cafe] Which advanced Haskell topics interest you

2012-10-04 Thread Kim-Ee Yeoh
Something to consider is that it's not so much whether the material is basic, advanced, or intermediate; it's that the way it's being presented is boring and ineffective. Take the Head First Java book, which was deliberately engineered to overcome precisely this hitherto neglected aspect of

Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-23 Thread Kim-Ee Yeoh
On Tue, Oct 16, 2012 at 9:37 PM, AUGER Cédric sedri...@gmail.com wrote: As I said, from the mathematical point of view, join (often noted μ in category theory) is the (natural) transformation which with return (η that I may have erroneously written ε in some previous mail) defines a monad

Re: [Haskell-cafe] [Off-topic] How unimportant it is whether submarines can swim (EWD1056)

2012-10-30 Thread Kim-Ee Yeoh
On Sun, Oct 28, 2012 at 11:29 AM, Rustom Mody rustompm...@gmail.com wrote: In particular, there is one small notational point that he insisted on towards the end of his career (and life) viz. where traditional mathematicians write *f(x) *and functional programmers write *f x*, he would write

Re: [Haskell-cafe] Compilers: Why do we need a core language?

2012-11-20 Thread Kim-Ee Yeoh
Is it impossible (very hard) to directly translate high-level language into machine code? There's a context to your question I don't understand, so let me ask: Wouldn't it be easier to break a big step into smaller baby steps? And if it's indeed easier why wouldn't you choose that route? --

Re: [Haskell-cafe] cabal configure cabal build cabal install

2012-11-26 Thread Kim-Ee Yeoh
Nice tip, Albert! Good to know! One question I have is, is (runghc Setup.lhs) equivalent to (cabal) in runghc Setup.lhs $ [configure, build, install] ? On Mon, Nov 26, 2012 at 8:08 AM, Brent Yorgey byor...@seas.upenn.eduwrote: [cabal haddock, if you want] cabal copy cabal register Even

Re: [Haskell-cafe] How to incrementally update list

2012-11-28 Thread Kim-Ee Yeoh
I want to incrementally update list lot of times, but don't know how to do this. Are you using the right data structure for the job? Maybe you want an array instead? -- Kim-Ee On Wed, Nov 28, 2012 at 6:43 PM, Branimir Maksimovic bm...@hotmail.comwrote: Problem is following short program:

Re: [Haskell-cafe] How to incrementally update list

2012-11-30 Thread Kim-Ee Yeoh
On Sat, Dec 1, 2012 at 1:16 AM, Mark Thom markjordant...@gmail.com wrote: Is there a paper or other single resource that will help me thoroughly understand non-strictness in Haskell? If performance is utterly vital the best resource is Core, as in, the ability to read it. The order of

Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-11-30 Thread Kim-Ee Yeoh
Ben, Now, on to Bind: the standard finite structure example for Bind is most probably the substitution thingy ... Danger of conflating a bunch of things here: (1) the substitution monadic effect is always also applicative and always also unital/pointed because monads are always applicative and

Re: [Haskell-cafe] Is anyone working on a sparse matrix library in Haskell?

2012-12-01 Thread Kim-Ee Yeoh
On Sun, Dec 2, 2012 at 10:52 AM, wren ng thornton w...@freegeek.org wrote: My goal for all this is in setting up the type system, not performance. I figure there are other folks who know and care a lot more about the numerical tricks of giving the actual implementations. You've got my support

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Kim-Ee Yeoh
On Tue, Dec 4, 2012 at 4:53 PM, Joerg Fritsch frit...@joerg.cc wrote: is a shallow embedded DSL == an internal DSL and a deeply embedded DSL == an external DSL or the other way around? Roughly speaking, yes. But a deep DSL doesn't mean you've got to have a parser tokenizer IO input. You can

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Kim-Ee Yeoh
Simulation and Synthesis, The Internals and Externals of Kansas Lava for a fuller definition. http://www.ittc.ku.edu/csdl/fpg/sites/default/files/Gill-10-TypesKansasLava.pdf Other communities may have their own definitions. On 4 December 2012 10:01, Kim-Ee Yeoh k...@atamo.com wrote: On Tue

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Kim-Ee Yeoh
On Wed, Dec 5, 2012 at 8:32 AM, Tillmann Rendel ren...@informatik.uni-marburg.de wrote: I mean internal == embedded, independently of deep vs. shallow, following Martin Fowler [1]. [1]

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-05 Thread Kim-Ee Yeoh
On Dec 5, 2012, at 2:59 AM, Kim-Ee Yeoh wrote: On Wed, Dec 5, 2012 at 8:32 AM, Tillmann Rendel ren...@informatik.uni-marburg.de wrote: I mean internal == embedded, independently of deep vs. shallow, following Martin Fowler [1]. [1] http://martinfowler.com/bliki

Re: [Haskell-cafe] Exploring Programming Language Theory

2012-12-08 Thread Kim-Ee Yeoh
SPJ's IFPL is an excellent starting point to learn the innards of Haskell. It allows a well-acculturated individual to grab the base of the trunk and start climbing the branches, which means reading the research papers (SPJ's website, mainly though not exclusively), all the way to the leaves

Re: [Haskell-cafe] Exploring Programming Language Theory

2012-12-08 Thread Kim-Ee Yeoh
I should add that IFPL has important chapters written by authors other than Simon. -- Kim-Ee On Sun, Dec 9, 2012 at 5:58 AM, Kim-Ee Yeoh k...@atamo.com wrote: SPJ's IFPL is an excellent starting point to learn the innards of Haskell. It allows a well-acculturated individual to grab the base

Re: [Haskell-cafe] mtl: Why there is Monoid w constraint in the definition of class MonadWriter?

2012-12-08 Thread Kim-Ee Yeoh
The only thing we can tell from the Monad laws is that that function f should be associative. That f is associative is a very small step away from f forming a monoid. What about listen :: m a - m (w, a)? What laws should it hold that are compatible with those of the monad and those of tell?

Re: [Haskell-cafe] MPTC or functional dependencies?

2012-12-21 Thread Kim-Ee Yeoh
Petr, Your subject header is misleading: FDs don't make sense without MPTCs. As you acknowledge at the end, what you're ultimately asking is: to FD or not to FD. Note also, the contemporary debate has shifted to TFs (type families) vs FDs. -- Kim-Ee On Fri, Dec 21, 2012 at 7:38 PM, Petr P

Re: [Haskell-cafe] arr considered harmful

2012-12-21 Thread Kim-Ee Yeoh
Hey Conal, I have something (another circuits formulation) that's almost an arrow but doesn't support arr. Have you seen Adam Megacz's generalized arrows? http://www.cs.berkeley.edu/~megacz/garrows/ -- Kim-Ee On Fri, Dec 21, 2012 at 7:55 AM, Conal Elliott co...@conal.net wrote: If you

Re: [Haskell-cafe] Substituting values

2012-12-21 Thread Kim-Ee Yeoh
This is reminiscent of the Either (exception) monad where Left values, the exceptions, pass through unaltered, and Right values are transformable, i.e. acted on by functions. But I have no idea what you're trying to achieve in the bigger picture. Help us help you by fleshing out your use case.

Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Kim-Ee Yeoh
Hi David, it looks like Rustom's aware that haskell's not lisp. What he really wants methinks is a way to suppress type classes altogether! That or a NoOverloadedNumerals extension. -- Kim-Ee On Thu, Dec 27, 2012 at 4:03 PM, David Virebayre dav.vire+hask...@gmail.com wrote: Prelude :t

Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Kim-Ee Yeoh
On Thu, Dec 27, 2012 at 11:48 PM, Rustom Mody rustompm...@gmail.com wrote: On Thu, Dec 27, 2012 at 8:26 PM, Kim-Ee Yeoh k...@atamo.com wrote: What he really wants methinks is a way to suppress type classes altogether! That or a NoOverloadedNumerals extension. I'm not really sure about

Re: [Haskell-cafe] Object Oriented programming for Functional Programmers

2012-12-30 Thread Kim-Ee Yeoh
There's OOHaskell, which you can google for. The name's such a nice example of an aptronym: it's the Overlooked Object-oriented Haskell. -- Kim-Ee On Mon, Dec 31, 2012 at 2:58 AM, Daniel Díaz Casanueva dhelta.d...@gmail.com wrote: Hello, Haskell Cafe folks. My programming life (which has

Re: [Haskell-cafe] Object Oriented programming for Functional Programmers

2013-01-04 Thread Kim-Ee Yeoh
On Fri, Jan 4, 2013 at 7:27 PM, David Thomas davidleotho...@gmail.comwrote: Well, hidden - it *is* right there in the type signature still, it just doesn't *look* like an argument. If you squint hard enough, (=) looks like (-). Or maybe the other way round. Whatever. :) It also might be

Re: [Haskell-cafe] A Meetup Group for MN Haskellers

2013-01-12 Thread Kim-Ee Yeoh
Hey Danny, Good job taking the lead! Wish you all success because I think meetups have so many underrated benefits. (Where I am in a city 10 million, i.e. Jakarta, Indonesia, you'd think it would be a piece of cake, but so far no dice. Me and another guy are working on this ) Have you

Re: [Haskell-cafe] Type hierarchy

2013-01-16 Thread Kim-Ee Yeoh
On Wed, Jan 16, 2013 at 11:22 PM, Thiago Negri evoh...@gmail.com wrote: The C spec allows the use of GLboolean values where GLenums are expected. Some fixes off the top of my head (caveats apply): * define a lift :: GLboolean - GLenum * use a typeclass GLenumlike * if there aren't too many of

Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-23 Thread Kim-Ee Yeoh
On Thu, Jan 24, 2013 at 6:23 AM, wren ng thornton w...@freegeek.org wrote: NotOnHackage: a package repository just like Hackage, except the packages are just documentation on why there is no such package. Love the idea! It'll make us even more unique among other PLs and even more ways to be

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 7:09 PM, Roman Cheplyaka r...@ro-che.info wrote: Thus, your recursion is well-founded — you enter the recursion with the input strictly smaller than you had in the beginning. Perhaps you meant /productive/ corecursion? Because the definition A ::= B A you gave is

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 7:47 PM, Roman Cheplyaka r...@ro-che.info wrote: Or perhaps you meant that the production itself, when interpreted as a definition, is corecursive? I was merely thrown off by your mention of well-founded and the assertion that you're left with a strictly smaller input.

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 8:03 PM, Roman Cheplyaka r...@ro-che.info wrote: It may become more obvious if you try to write two recursive descent parsers (as recursive functions) which parse a left-recursive and a non-left-recursive grammars, and see in which case the recursion is well-founded

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 10:04 PM, Tillmann Rendel ren...@informatik.uni-marburg.de wrote: The recursion is well-founded if (drop n1 text) is smaller then text. So we have two cases, as Roman wrote: If the language defined by B contains the empty string, then n1 can be 0, so the recursion is

Re: [Haskell-cafe] RFC: rewrite-with-location proposal

2013-02-25 Thread Kim-Ee Yeoh
On Mon, Feb 25, 2013 at 9:42 PM, Simon Peyton-Jones simo...@microsoft.comwrote: One idea I had, which that page does not yet describe, is to have an implicit parameter, something like ?loc::Location** +1 Implicit params has a bad rap in some circles because of counterintuitive behavior when

Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Kim-Ee Yeoh
Question is: does the task even have to involve the the production of Haskell code? Is it possible that both the student and the community-at-large would benefit further from expository-style artifacts? Some possible activities: (1) producing documentation for popular packages that cater to

Re: [Haskell-cafe] Need some advice around lazy IO

2013-03-19 Thread Kim-Ee Yeoh
On Tue, Mar 19, 2013 at 2:01 PM, Konstantin Litvinenko to.darkan...@gmail.com wrote: Yes. You (and Dan) are totally right. 'Let' just bind expression, not evaluating it. Dan's evaluate trick force rnf to run before hClose. As I said - it's tricky part especially for newbie like me :) To place

Re: [Haskell-cafe] Parsec community and up-to-date documentation

2013-03-24 Thread Kim-Ee Yeoh
On Mon, Mar 25, 2013 at 5:19 AM, Konstantine Rybnikov k...@k-bx.com wrote: as a beginner had a lot of headache starting from outdated documentation in various places, lack of more tutorials, confusion between Text.Parsec and Text.ParseCombinator modules and so on. You're indeed right. While

Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-03 Thread Kim-Ee Yeoh
Hi Tillmann, On Wed, Apr 3, 2013 at 11:59 PM, Tillmann Rendel ren...@informatik.uni-marburg.de wrote: From the type-theoretic point of view, I guess this is related to your view of what a polymorphic function is. Do you have a reference to the previous conversation? but we moved further and

Re: [Haskell-cafe] Possible GSoC project

2013-04-04 Thread Kim-Ee Yeoh
On Thu, Apr 4, 2013 at 10:03 PM, Ketil Malde ke...@malde.org wrote: Not very much, some knowledge of string edit distance and dynamic programming would be good, but if not, it's something I can straighten out with a student in an afternoon, I think. Just a suggestion: People love quizzes

Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-04 Thread Kim-Ee Yeoh
On Fri, Apr 5, 2013 at 3:04 AM, Simon Heath icefo...@gmail.com wrote: I humbly suggest reStructuredText rather than Markdown, which is what is used by the Python community for documentation. Since it's specifically made for documentation it may be nicer. But, I don't want to spark a format

Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-04 Thread Kim-Ee Yeoh
On Fri, Apr 5, 2013 at 10:44 AM, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: I don't think so; this was one of the big issues recently when people were trying to get Gruber to actually _do_ something with Markdown as there were all these corner cases. In that case, surely this is an

Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-04 Thread Kim-Ee Yeoh
(Folks, let's rescue this increasingly tendentious thread.) Some points to ponder: (1) Any can be often be clarified to mean all, depending on how polymorphic functions are exegeted. In a homotopy-flavored explanation of natural transformation, its components (read parametric instances) exist

  1   2   >