[Haskell-cafe] wxHaskell not able to link to libstdc++.so

2010-04-22 Thread Ahn, Ki Yung
? Or, is this a ghc problem? -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: wxHaskell not able to link to libstdc++.so

2010-04-22 Thread Ahn, Ki Yung
Just searched and found out that this is a ticket 4 months old http://hackage.haskell.org/trac/ghc/ticket/3798 but it seems that it's not only a GHCi problem. It doesn't compile with ghc either. 2010년 04월 22일 17:05, Ahn, Ki Yung 쓴 글: Dear Haskellers, I heard from a guy who was having

[Haskell-cafe] Re: Best links for Haskell Platform distro packages?

2010-07-17 Thread Ahn, Ki Yung
2010년 07월 17일 16:53, Don Stewart 쓴 글: Can distro maintainers confirm these are the best links for each distro package? Debian http://packages.debian.org/squeeze/haskell-platform (or should it be sid?) http://packages.debian.org/haskell-platform I am not a maintainer

[Haskell-cafe] Edison StandardSet has inefficient function implementation

2006-08-03 Thread Ahn, Ki Yung
) implemended using split. All other function implmentation just used its axiomaic description using CollX operations like filter and partition, which is O(n). It needs to be fixed. P.S. I haven't checked the darcs version yet. -- Ahn, Ki Yung ___ Haskell

[Haskell-cafe] The dark side of lazyness - memory leak

2006-08-07 Thread Ahn, Ki Yung
ly) = x == y lx == ly instance (Ord a, Ord b) = Ord (TT a b) where (TT x lx) (TT y ly) = x y || x == y lx ly This is really a panic. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-07 Thread Ahn, Ki Yung
. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-07 Thread Ahn, Ki Yung
have confidence that Haskell programs are robust. It seems it is too easy to blow up the memory or overflow the stack without intention. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: Haskell for Physicists

2009-10-01 Thread Ahn, Ki Yung
ed...@ymonad.com 쓴 글: Hi, I will give a seminar to physicists at USP (Universidade de São Paulo, Brazil) university and they asked me for a good title, something that can attract physicists. Anyone has some suggestions? (Will be a seminar about the use of Haskell to substitute C or Fortran in

[Haskell-cafe] Is cabal option --extra-lib-dirs working?

2009-12-31 Thread Ahn, Ki Yung
I had some problem with --extra-lib-dirs option in cabal-install. I've been trying installing bindings-yices package on hackage. Since yices may be installed in non-standard location, such as under your own home directory, one may have to use --extra-include-dirs and --extra-lib-dirs option.

[Haskell-cafe] HPong-0.1.2 fails to compile in Debian ghc 6.10.1

2009-04-23 Thread Ahn, Ki Yung
I don't know the exact reason but this should not fail since I have Debian packaged ghc 6.10.1 and OpenGL-2.2.1.1 on my system. I think this is because the filename of the OpenGL shared library is /usr/lib/libGL.so.1 rather than libGL.so. This is why we have two binary distributions for

[Haskell-cafe] Re: Visualizing Typed Functions

2009-05-07 Thread Ahn, Ki Yung
Duane Johnson wrote: With these functions visualized, one could make a kind of drag and drop interface for Haskell programming, although that isn't really my intention. I admit this is a little convoluted even for the purpose of visualization, but at least it's a starting place. Does

[Haskell-cafe] Re: ANNOUNCE: The Haskell Platform

2009-05-07 Thread Ahn, Ki Yung
Thanks for this great effort! Are we going to have a meta-package on hackage as well? (which makes it able to build it through cabal-install) -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Question concerning Haskell Foundation

2009-05-07 Thread Ahn, Ki Yung
that Haskell platform is also going to be provided as a meta-package on Hackage. So, the answers to 1) Yes, 2) No. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Purely logical programming language

2009-05-26 Thread Ahn, Ki Yung
Henning Thielemann wrote: On Tue, 26 May 2009, Jan Christiansen wrote: Hi, On 26.05.2009, at 21:24, Lauri Alanko wrote: Mercury also has type classes and other Haskellisms, so if you're interested in doing Prolog the Haskell way, you should definitely have a look at it. I have to admit

[Haskell-cafe] Scary type inference for monadic function definitions

2009-06-03 Thread Ahn, Ki Yung
Scary type inference for monadic function definitions (or, why you'd want to annotate types for monadic function definitions) This is a real example that I've experienced. I defined the following function. checkOneVerseByLineWith readLine v = do mg - readLine case mg of Just g

[Haskell-cafe] Re: Scary type inference for monadic function definitions

2009-06-03 Thread Ahn, Ki Yung
Ahn, Ki Yung 쓴 글: Scary type inference for monadic function definitions (or, why you'd want to annotate types for monadic function definitions) This is a real example that I've experienced. I defined the following function. checkOneVerseByLineWith readLine v = do mg - readLine

[Haskell-cafe] ANN: memscript-0.0.0.2 (Command line utility for memorizing scriptures or any other text)

2009-06-04 Thread Ahn, Ki Yung
memscript: Command line utility for memorizing scriptures or any other text http://hackage.haskell.org/cgi-bin/hackage-scripts/package/memscript memscript filename Run memscript with a UTF-8 (or ASCII since ASCII is a subset of UTF8) plain text file. Try to exactly guess the text line by line.

[Haskell-cafe] Re: Reflections on the ICFP 2009 programming contest

2009-06-29 Thread Ahn, Ki Yung
Similar to mine except that I implemented with all of the memory (data, instruction, input and output ports) with the Data.Map library. One thing to care about is the heap memory profiling. You'll need to make sure that Map.insert function do not pile up as thunk. This is a typical memory

[Haskell-cafe] Re: Reflections on the ICFP 2009 programming contest

2009-06-29 Thread Ahn, Ki Yung
John Meacham 쓴 글: I implemented the VM in C, it was pretty obviously geared towards such an implementation and it took all of an hour. Then I interfaced with it via the FFI. Why use just one language when you can use two? :) You could also have used Data.Binary. That's what I did. I wasn't

[Haskell-cafe] Re: Wondering about c type in haskell.

2009-06-29 Thread Ahn, Ki Yung
pointers from values for garbage collection purposes. (OCaml int types are like that too.) I hope this gives enough explanation. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: Wondering about c type in haskell.

2009-06-29 Thread Ahn, Ki Yung
Ahn, Ki Yung 쓴 글: Magicloud Magiclouds 쓴 글: Hi, There are times, when we need to make some system calls, or call C library. So we have to deal with C data types. For example, CPid, which is an integer, actually. So we can do fromIntegral pid. Then why do not we define type CPid = Integer

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

2009-07-02 Thread Ahn, Ki Yung
Kim-Ee Yeoh wrote: The add function illustrates the kind of do-sugaring we know and love that I want to use for Symantics. lam f = unZ $ do show_c0 - get let vname = v ++ show_c0 c0 = read show_c0 :: VarCount c1 = succ c0 fz :: Z a String -

[Haskell-cafe] here is how I made it type check

2009-07-02 Thread Ahn, Ki Yung
I don't know if this is what you want but I was at least able to make it to type check basically changing (fz . return) into simply return. I think the error message about the occurs check was because of the fz function is used wrong (or you didn't give it a correct type). {-# LANGUAGE

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

2009-07-02 Thread Ahn, Ki Yung
Edward Kmett 쓴 글: Actually the problem lies in your definition of fz, it has the wrong type to be used in lam. The Z you get out of fz as type Z b String, but you need it to have Z (a - b) String so that when you strip off the Z you have a Y String (a - b) matching the result type of lam.

[Haskell-cafe] Re: Goldman Sachs - your home for OCaml and Erlang?

2009-07-14 Thread Ahn, Ki Yung
Max Cantor wrote: I know that this is a bit off topic, but thought it would interest several readers. Apparently, GS, which. AFAIK, doesn't make a lot of noise in the FP space compared to some other banks, does use some FP: http://www.zerohedge.com/article/aleynikov-code-dump-uncovered The

[Haskell-cafe] Re: Haskell as a first language?

2009-07-14 Thread Ahn, Ki Yung
Before teaching any data structure course, one MUST learn functional languages with ADTs. It makes everything so easy to understand. So, it MUST be a first language in every institution. The biggest reason that one should learn functional languages with algebraic data type(ADT)s first is

[Haskell-cafe] Re: A Question of Restriction

2009-07-26 Thread Ahn, Ki Yung
Brian Troutwine wrote: Hello all. I would like to define a data type that is the super-set of several types and then each of the proper subset types. For example: data Foo = One | Two | Three | Four data Odd = One | Three data Even = Two | Four This, of course, does not work. It

[Haskell-cafe] Testing nested implication properties with QuickCheck?

2009-07-27 Thread Ahn, Ki Yung
) == C won't work when A, B, C are boolean expressions. Is there some trick to handle the latter? Thanks, -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Testing nested implication properties with QuickCheck?

2009-07-27 Thread Ahn, Ki Yung
won't work when A, B, C are boolean expressions. Is there some trick to handle the latter? Thanks, -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] yi compiles but does not launches

2008-09-26 Thread Ahn, Ki Yung
state. If anyone have succeeded using yi in Debian unstable please let me know how you got around from this problem. -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] [fun] HaskellDB Talk trailer

2008-10-16 Thread Ahn, Ki Yung
There is an impressive HaskellDB Talk trailer on the web. http://www.vimeo.com/1983774 Cheers to the HaskellDB developers :-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] How to getCh on MS Windows command line?

2008-11-09 Thread Ahn, Ki Yung
. Surprisingly, it works in WinHugs. However, I cannot use WinHugs for my purpose because the interactive calculator example in the book also uses beep characters and ANSI codes which do not work in WinHugs. Thanks for any hacks or suggestions, -- Ahn, Ki Yung

[Haskell-cafe] Do I need an account to report build of Hacakge packages?

2008-11-21 Thread Ahn, Ki Yung
I am just curious about how cabal report works. I recently figured out that there is a report command in cabal and it reports the reports generated by --build-reports option when building a package. Is this because I don't have an account on Hackage yet, or because of some other reasons? And if

[Haskell-cafe] Re: ANN: Real World Haskell, now shipping

2008-11-28 Thread Ahn, Ki Yung
using HDBC, and it just works using the binary package from debian. If you need more complicated examples, you can take a look at the hpodder source code or any other applications that use database. They are all on Hackage. -- Ahn, Ki Yung

[Haskell-cafe] Graham Hutton's calculator example for win32

2008-12-20 Thread Ahn, Ki Yung
://www.cs.nott.ac.uk/~gmh/Parsing.lhs -- Ahn, Ki Yung Calculator example from section 9.6 of Programming in Haskell, Graham Hutton, Cambridge University Press, 2007. Note: the definition for getCh in this example works with the Glasgow Haskell Compiler, but may not work with some Haskell systems

[Haskell-cafe] Haskell good for parallelism/concurrency on manycore?

2009-01-04 Thread Ahn, Ki Yung
on Haskell Server Programming while ago. P.S. If you happen to be a local Korean expert on this matter, sorry for my ignorance, and I'd be happy to forward their inquiry to you! -- Ahn, Ki Yung ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Fwd: Re: type class VS struct/functor]

2002-01-18 Thread Ahn Ki-yung
Hmm ... How do you solve this in Haskell ? Original Message Subject: Re: type class VS struct/functor Date: Sat, 19 Jan 2002 01:34:32 GMT From: [EMAIL PROTECTED] (Neelakantan Krishnaswami) Reply-To: [EMAIL PROTECTED] Organization: ATT Broadband Newsgroups: comp.lang.functional

1 line simple cat in Haskell

2002-11-12 Thread Ahn Ki-yung
. How would you suggest to neatly insert the error handling code into ? P.S. Instead of coding with C++, I want to write my server main code like this. server_main = mapM (=process.reply) where getReqS = getReq:getReqS Only if I had enough time ... :-p Using HDirect and so on ... -- Ahn Ki

Re: erreta, a couple of unimportant missing words :-(

2002-11-20 Thread Ahn Ki-yung
Ahn Ki-yung wrote: Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h \end

Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
answer for the question of my own, which is posted a couple There are mapM, filterM in the Haskell 98 Standard Library. But why no findM there ? As you can see from simple cat, it seems quite useful. I think fildM should be added to the module Monad. -- Ahn Ki-yung

Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Jorge Adriano wrote: Seems to me like the name findM could be misleading mapM :: (Monad m) = (a - m b) - [a] - m [b] filterM :: (Monad m) = (a - m Bool) - [a] - m [a] These take a monadic function and a list of elements. Yours works the other way around (takes a function and a list of 'monadic

simple cat by joining two infinite lists (intput/ouput)

2002-11-20 Thread Ahn Ki-yung
\begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (=return.isLeft) $ map (try . uncurry (=)) $ zip (hGetCharS stdin)

[Haskell-cafe] Tutorial for server programming in concurrent Haskell

2005-01-05 Thread Ahn Ki-yung
I've recently started a small tutorial for server programming in concurrent Haskell. http://kyagrd.dyndns.org/wiki/HaskellServerProgramming For newbies in Haskell and/or server programming, there should be an interoductory tutorial with concrete and simple examples before Simon Marlow's papers

[Haskell-cafe] Re: 1000 libraries

2009-01-21 Thread Ahn, Ki Yung
Don Stewart wrote: We've done it! Thanks for the good news. Maybe it's already getting more important organizing existing uesful set of libraries as mata-packages. Are there updates on haskell-platform? ___ Haskell-Cafe mailing list

[Haskell-cafe] tensor product of dynamic-sized bits

2009-01-21 Thread Ahn, Ki Yung
For some reasons, I am trying to write a small Haskell code for tensor products (See http://en.wikipedia.org/wiki/Tensor_product) of bits, which can expand or shrink their size and dimension as needed. Has anyone already done similar or more general work before? If so, I'd be happy use/consult

[Haskell-cafe] Re: tensor product of dynamic-sized bits

2009-01-21 Thread Ahn, Ki Yung
Ahn, Ki Yung 쓴 글: reduce (Bs (x:xs)) | all (x==) xs = x reduce (Rep x@(Rep _)) = x reduce x = x I already found a bug. The second equation of reduce reduce (Rep x@(Rep _)) = x is wrong because it flattens two dimensions into one. The reduce function should be: reduce x

[Haskell-cafe] Re: Type families not as useful over functions

2009-02-12 Thread Ahn, Ki Yung
My thoughts on type families: 1) Type families are often too open. I causes rigid variable type error messages because when I start writing open type functions, I often realize that what I really intend is not truly open type functions. It happens a lot that I had some assumptions on the

[Haskell-cafe] Re: speed: ghc vs gcc

2009-02-20 Thread Ahn, Ki Yung
Thomas Davie wrote: You need look no further than the debian language shootout that things really aren't as bad as you're making out – Haskell comes in in general less than 3x slower than gcc compiled C. Of note, of all the managed languages, this is about the fastest – none of the other

[Haskell-cafe] cabal-install 0.6.2 does not bootstrap with ghc-6.10.1 debian distribution

2009-03-07 Thread Ahn, Ki Yung
debian distribution ghc-6.10.1 (e.g., general linux binary ghc-6.10.1 or source compiled one) can try bootstrapping cabal-install 0.6.2 from scratch also finds the same problem, I think someone should make a ticket for cabal-install. Thanks, Ahn, Ki Yung

[Haskell-cafe] Re: cabal-install 0.6.2 does not bootstrap with ghc-6.10.1 debian distribution

2009-03-07 Thread Ahn, Ki Yung
Ahn, Ki Yung 쓴 글: Dear Haskellers and especially who are working on cabal-install and debian packaging, I sometimes clean up .ghc and .cabal in my home directory to start from scratch because of dependency loopholes (cabal-install does not have remove option yet, so it's hard to fix when

Re: [Haskell-cafe] cabal-install 0.6.2 does not bootstrap with ghc-6.10.1 debian distribution

2009-03-08 Thread Ahn, Ki Yung
Duncan Coutts 쓴 글: On Sat, 2009-03-07 at 17:51 -0800, Ahn, Ki Yung wrote: Dear Haskellers and especially who are working on cabal-install and debian packaging, I sometimes clean up .ghc and .cabal in my home directory to start from scratch because of dependency loopholes (cabal-install does

[Haskell-cafe] ANN: sparsebit 0.5 - Sparse Bitmaps for Pattern Match Coverage

2009-03-10 Thread Ahn, Ki Yung
was not able to make the haddock documentation appear in Hackage, although I have no problem generating documentation using cabal haddock locally. It would be nice if there is a way to see some diagnose of warning or error messages why haddock failed on Hackage. -- Ahn, Ki Yung

[Haskell-cafe] ANN: smartword 0.0.0.5 Web based flash card for Word Smart I and II vocabularies

2009-03-28 Thread Ahn, Ki Yung
:LICENSE Author: Ahn, Ki Yung Maintainer: Ahn, Ki Yung k...@pdx.edu === Web based online study tool for all vocabularies in Word Smart I and II, a poular book series for studying GRE vocabularies. I typed

[Haskell-cafe] Consuming anyToken with parsing with derivatives (derp) library in Hackage?

2011-11-11 Thread Ahn, Ki Yung
I was playing with derp recently, and many of the Char and Combinator of Parsec seem to be easily definable from derp. However, I haven't yet figured out a natural way to define anyToken or satisfy combiator of Parsec using derp. There is a way of course, to list all the unicode characters and

Re: [Haskell-cafe] How to Create Programming Language with Haskell?

2011-11-16 Thread Ahn, Ki Yung
Don't think this is what Shogo is looking for since the book is not about implementing a language WITH Haskell, but how to implement Haskell like languages with a more low level language (like C). 2011년 11월 16일 00:13, Anton Kholomiov 쓴 글: This can be very helpful: Implementation of FP

[Haskell-cafe] Problems translating Conor McBride's talk into Haskell + DataKind + KindPoly

2012-10-25 Thread Ahn, Ki Yung
Most part of Conor's talk at ICFP, until just before the last stage where he heavily uses true value dependency for compiler correctness all the code seemed to be able to translate into Haskell with the new hot DataKinds and PolyKinds extension. I tried it in GHC 7.4.1 and it was possible to

Re: [Haskell-cafe] Problems translating Conor McBride's talk into Haskell + DataKind + KindPoly

2012-10-25 Thread Ahn, Ki Yung
. I might have to write bug report. On 2012년 10월 25일 18:07, Ahn, Ki Yung wrote: Most part of Conor's talk at ICFP, until just before the last stage where he heavily uses true value dependency for compiler correctness all the code seemed to be able to translate into Haskell with the new hot