[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 do it, but I got stuck 
and I had to make the generic list structure mono-kinded with kind 
signatures rather not use the PolyKinds extension.


I wonder if this is just a but of GHC 7.4.1's implementation of 
PolyKinds, or a limitation of the DataKind design.


I attached a literate Haskell script with this message that illustrates 
this problem.


Thanks in advance for any comments including whether it runs in later 
versions or still has problems, and discussions about the DataKinds and 
PolyKinds extension.


Ki Yung
I ran into problems when I tryed doing some of
the Conor's talk at ICFP 2012 in Haskell with
DataKinds and PolyKinds extension, using GHC 7.4.1.

I am wondering whether this is a bug in GHC 7.4.1
(maybe fixed in GHC 7.6.x? haven't tried since
I haven't installed 7.6.x yet), or a limitation of
datatype promotion itself. The problem happens when
I try to use promoted list datatype.

Here is a code that illustrates this problem:

 {-# LANGUAGE GADTs, DataKinds, PolyKinds, KindSignatures #-}

 data GList x i j where
   GNil   :: GList x i i
   GCons  :: x i j  - GList x j k
- GList x i k
 
 
 append :: GList x i j  - GList x j k
- GList x i k
 append GNilys  = ys
 append (  GCons x xs)  ys  =
   GCons x (append xs ys)


Instantiating to a plain regular list works

 data Elem a i j where
   MkElem :: a - Elem a () ()
 
 type List' a = GList (Elem a) () ()
 
 nil' = GNil {-~-} :: List' a
 
 cons' :: a - List' a - List' a
 cons' = GCons . MkElem

Instantiating to a length indexed list works

 data Nat = Z | S Nat
 
 data ElemV a i j where
   MkElemV :: a - ElemV a (S n) n
 
 type Vec a n = GList (ElemV a) n Z
 
 vNil = GNil {-~-} :: Vec a Z
 
 vCons :: a - Vec a n - Vec a (S n)
 vCons = GCons . MkElemV

Good, then let's do some more things with DataKinds.

Promoting Bool works as well as Nat.

 data RelB :: Bool - Bool - * where
   MkRelB :: RelB b b
 
 l1 = GCons MkRelB GNil

But, I have some problems with promoting [Bool] !!!

 data RelBL :: [Bool] - [Bool] - * where
   MkRelBL :: RelBL bs bs

I can only with mono-kinded list structure.
Below is a momomorphization of GList.

 data MyList (x :: [Bool] - [Bool] - *) i j where
   MyNil   :: MyList x i i
   MyCons  :: x i j  - MyList x j k
 - MyList x i k
 
 l3 = MyCons MkRelBL MyNil

However when I try to do this with the poly-kinded GList,
I get a kind error. Is this a bug of GHC 7.4.1 or is this
a limitation of DataKind extension?

 l4 = GCons MkRelBL GNil

tmp.lhs:74:22:
Couldn't match kind `BOX' against `*'
Kind incompatibility when matching types:
  k0 :: BOX
  [Bool] :: *
In the second argument of `GCons', namely `GNil'
In the expression: GCons MkRelBL GNil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-10-25 Thread Ahn, Ki Yung

Promotion works for user defined lists such as

data List a = Nil | Cons a (List a)

And, if I use (List Bool) instead of [Bool] everything works out.
It's only the Haskell list type constructor [] is being a problem.

In the Giving Haskell a promotion paper, it says that Haskell lists 
are natively promoted. I believe this means that it is treated 
specially somehow. I don't know how it is implemented but what GHC 7.4.1 
does specially for Haskell lists has some problems. So, it's clearly not 
a limitation of DataKind and PolyKind extension, but that special 
routine for [] is the issue.


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
DataKinds and PolyKinds extension.

I tried it in GHC 7.4.1 and it was possible to do it, but I got stuck
and I had to make the generic list structure mono-kinded with kind
signatures rather not use the PolyKinds extension.

I wonder if this is just a but of GHC 7.4.1's implementation of
PolyKinds, or a limitation of the DataKind design.

I attached a literate Haskell script with this message that illustrates
this problem.

Thanks in advance for any comments including whether it runs in later
versions or still has problems, and discussions about the DataKinds and
PolyKinds extension.

Ki Yung


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 languages by Simon Peyton
Jones

http://research.microsoft.com/en-us/um/people/simonpj/papers/slpj-book-1987/index.htm



2011/11/16 Shogo Sugamoto eseh...@gmail.com mailto:eseh...@gmail.com

Hi,Cafe.

I want to create my own Programming Language with Haskell, and I learn
how to do it.
I read:

WikiBooks of Write Yourself a Scheme in 48 Hours,
Real World Haskell of Chapter Using Parsec,
Source of HJS,
Book of Introduction of Functional Programming Using Haskell.

Ok,What is another good source creating my own Programming Language
with Haskell?
Thanks :)

esehara

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 combine them with |, which is extremely inefficient,
even if you limit yourself that satisfy combinator be compile time
template haskell function, it still seems a bit silly.

For things like space, it seems reasonable to list all take the sum of
them, since there are handful of them. But things like consume anything
that is not a space ought to be defined as a complement or negation of
the space parser.

In general CFG is not closed under negation, but most of the time what
we want to take a negation is really for regular fragment of the
language, like consuming anything that is not a linebreak to lex/parse
one line comments.

In Matt's Standford talk, he mentioned some vision about going beyond
CFG and he mentioned negation, but in the library implementation I
didn't find that. Is it already possible with some trick?

Is there a standard way to define such combinators with derp? Or, is it
the case that there a way to do it in the scheme library but not
implemented in Haskell derp package? I read through the scheme
implementation too but there didn't seem to be a combinator for tacking
negations either.

Ki Yung Ahn


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 but I suggest the link above since it is the way 
to have them both, by searching package by package name.

I believe haskell-platform package name is not likely to change.
So, that URL will consistently serve the purpose even after major stable 
releases.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-22 Thread Ahn, Ki Yung
Dear Haskellers,

I heard from a guy who was having problems with wxHaskell using GHC
6.10.x.  I tried it myself and had the exact same problem occurring
using GHC 6.12.x as well.  I am using the debian unstable version of
ghc6 package.

kya...@kyagrd:~/tmp$ head bb.hs
import Graphics.UI.WX
import Graphics.UI.WXCore (bitmapGetSize)

main = start viewer

viewer :: IO ()
viewer = do
bm - bitmapCreateFromFile ~/sample.jpg
size - bitmapGetSize bm
f - frame [text := viewer, on paint := onPaint bm, clientSize :=size]


kya...@kyagrd:~/tmp$ runghc bb.hs
bb.hs: command line: can't load .so/.DLL for: stdc++ (libstdc++.so:
cannot open shared object file: No such file or directory)
kya...@kyagrd:~/tmp$ ghc bb.hs
bb.o: In function `r43M_info':
(.text+0x48): undefined reference to
`wxzm0zi12zi1zi4_GraphicsziUIziWXziWindow_zdfDimensionsObject_closure'
bb.o: In function `r43O_info':
(.text+0xa8): undefined reference to
`wxzm0zi12zi1zi4_GraphicsziUIziWXziWindow_zdfPaintObject_closure'
...

The problem is there is no libstdc++.so in my Debian system as well as
the guy who uses Ubunto.  What exists is libstdc++.so.6.

kya...@kyagrd:~/tmp$ ls /usr/lib/libstdc++.*
/usr/lib/libstdc++.so.6@  /usr/lib/libstdc++.so.6.0.13

I wonder how wxHaskell was even able to successfully configure and
compile at all.  I didn't have wx package installed before, and I
installed it just today and it successfully configured and compiled but
unable to dynamically link to libstdc++.so.

More serious problem is that wxHaskell doesn't work even making a
symbolic link of libstdc++.so from libstdc++.so.6.

I've also tried running ldconfig -v and ldconfig -p as a root, but still
get the same problem.

Is this a commom problem with the libraries linking to libstdc++.so or
is this just the wxHaskell problem?  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 problems with wxHaskell using GHC
 6.10.x.  I tried it myself and had the exact same problem occurring
 using GHC 6.12.x as well.  I am using the debian unstable version of
 ghc6 package.
 
 kya...@kyagrd:~/tmp$ head bb.hs
 import Graphics.UI.WX
 import Graphics.UI.WXCore (bitmapGetSize)
 
 main = start viewer
 
 viewer :: IO ()
 viewer = do
 bm- bitmapCreateFromFile ~/sample.jpg
 size- bitmapGetSize bm
 f- frame [text := viewer, on paint := onPaint bm, clientSize :=size]
 
 
 kya...@kyagrd:~/tmp$ runghc bb.hs
 bb.hs:command line: can't load .so/.DLL for: stdc++ (libstdc++.so:
 cannot open shared object file: No such file or directory)
 kya...@kyagrd:~/tmp$ ghc bb.hs
 bb.o: In function `r43M_info':
 (.text+0x48): undefined reference to
 `wxzm0zi12zi1zi4_GraphicsziUIziWXziWindow_zdfDimensionsObject_closure'
 bb.o: In function `r43O_info':
 (.text+0xa8): undefined reference to
 `wxzm0zi12zi1zi4_GraphicsziUIziWXziWindow_zdfPaintObject_closure'
 ...
 
 The problem is there is no libstdc++.so in my Debian system as well as
 the guy who uses Ubunto.  What exists is libstdc++.so.6.
 
 kya...@kyagrd:~/tmp$ ls /usr/lib/libstdc++.*
 /usr/lib/libstdc++.so.6@  /usr/lib/libstdc++.so.6.0.13
 
 I wonder how wxHaskell was even able to successfully configure and
 compile at all.  I didn't have wx package installed before, and I
 installed it just today and it successfully configured and compiled but
 unable to dynamically link to libstdc++.so.
 
 More serious problem is that wxHaskell doesn't work even making a
 symbolic link of libstdc++.so from libstdc++.so.6.
 
 I've also tried running ldconfig -v and ldconfig -p as a root, but still
 get the same problem.
 
 Is this a commom problem with the libraries linking to libstdc++.so or
 is this just the wxHaskell problem?  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] 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.  --extra-include-dirs work well and locates the
 header for the yices C binding, but --extra-lib-dirs option does not
seem to work well.

Would this be a cabal-install bug, or some package misconfiguration?


kya...@kyavaio:~/tmp/bindings-yices-0.1$ cabal configure
Resolving dependencies...
Configuring bindings-yices-0.1...
cabal: Missing dependency on a foreign library:
* Missing header file: yices_c.h
* Missing C library: yices
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is
already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and --extra-lib-dirs= to specify where it is.
kya...@kyavaio:~/tmp/bindings-yices-0.1$ cabal configure
--extra-include-dirs=/home/kyagrd/yices-1.0.21/include
Resolving dependencies...
Configuring bindings-yices-0.1...
cabal: Missing dependency on a foreign library:
* Missing C library: yices
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is
already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and --extra-lib-dirs= to specify where it is.
kya...@kyavaio:~/tmp/bindings-yices-0.1$ cabal configure
--extra-include-dirs=/home/kyagrd/yices-1.0.21/include
--extra-lib-dirs=/home/kyagrd/yices-1.0.21/lib
Resolving dependencies...
Configuring bindings-yices-0.1...
cabal: Missing dependency on a foreign library:
* Missing C library: yices
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is
already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and --extra-lib-dirs= to specify where it is.
kya...@kyavaio:~/tmp/bindings-yices-0.1$
kya...@kyavaio:~/tmp/bindings-yices-0.1$ ls
/home/kyagrd/yices-1.0.21/include/
yices_c.h  yicesl_c.h
kya...@kyavaio:~/tmp/bindings-yices-0.1$ ls /home/kyagrd/yices-1.0.21/lib/
libyices.a  libyices.so
kya...@kyavaio:~/tmp/bindings-yices-0.1$ ls -al
/home/kyagrd/yices-1.0.21/include/
합계 40
drwxr-xr-x 2 kyagrd kyagrd  4096 2009-07-17 20:58 .
drwxr-xr-x 6 kyagrd kyagrd  4096 2009-07-07 23:19 ..
-rw-r--r-- 1 kyagrd kyagrd 27948 2009-05-05 19:03 yices_c.h
-rw-r--r-- 1 kyagrd kyagrd  1786 2009-05-05 19:03 yicesl_c.h
kya...@kyavaio:~/tmp/bindings-yices-0.1$ ls -al
/home/kyagrd/yices-1.0.21/lib/
합계 8936
drwxr-xr-x 2 kyagrd kyagrd4096 2009-12-30 19:29 .
drwxr-xr-x 6 kyagrd kyagrd4096 2009-07-07 23:19 ..
-rw-r--r-- 1 kyagrd kyagrd 5167710 2009-05-05 19:03 libyices.a
-rwxr-xr-x 1 kyagrd kyagrd 3955648 2009-05-05 19:03 libyices.so

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 a lot of tasks, and how it can be used in some problems instead of 
Matlab, Mathematica, etc.)


Thanks,
Edgar


You should also see the well known Haskell story in this area:

http://bayern.stanford.edu/~brant/lightning/

___
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
How should I you use QuickCheck for testing a property that is a nested
implecation such as (A == B) == C ?

The problem is (==) in QuickCheck is that its type is Testable prop =
Bool - prop - Property  rather than Testable prop = prop - prop -
Property.  So, A == (B == C) would work but (A == B) == 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
How should I use QuickCheck for testing a property that is a nested
implecation such as (A == B) == C ?

The problem is (==) in QuickCheck is that its type is Testable prop =
Bool - prop - Property  rather than Testable prop = prop - prop -
Property.  So, A == (B == C) would work but (A == B) == 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] 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 seems that such a thing should
possible to express entirely in the type system, but I cannot think of
how. Would someone be so kind as to explain how this sort of thing can
be accomplished?


You might want to look at Johan Nordlander's O'Haskell.  It's a dialect 
of Haskell with such subtyping, designed and implemented while ago. 
Recently there was a proposal (but not an implementation yet) of 
subtyping data types in general with recursion and including GADTs 
http://portal.acm.org/citation.cfm?id=1411286.1411297 (I want to work on 
this again some time later again).  But neither of these work is not 
implemented as an extension feature in major Haskell implementations 
like GHC or Hugs.  I want to push this work further some time later on. 
FYI, there exist a functional language which you can express this kind 
of idea though. For example, in OCaml, you can use polymorphic variants.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 link you gave seems controversial.  But there is a more relative 
product based on OCaml that GS actually uses (or have used): 
http://www.lexifi.com/press_2002-09-02.html


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 because understanding recursive 
definitions.  If you recursion first, understanding iteration and 
mutable data structures are dead simple and easy: they are just 
alternate representation or optimization.


However, when you learn while loops and for loops first, your brain gets 
damaged and a lot of students gets stuck when they first see the Tower 
of Hanoi, the notorious in-place quicksort routine written in imperative 
languages, you'll get to think of recursion as some stack blowing up 
monster that must be unrolled and managed manually.  Furthermore, 
learning data structures in most traditional imperative language 
literature gives you the impression that linked list and binary trees 
are brain-fucking spaghetti monsters of memory pointers all the cells, 
which is a dead simple recursive definition in functional languages with 
ADTs.


Personally, I never really understood what linked list was before I 
learned ML and Haskell, although I've used doubly linked list in a C++ 
standard library, which was to me a black box that meets the 
specification in some huge standard document, for two years.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 - Z b String
 fz = Z . f . unZ
  put (show c1)
  s - (fz . return) vname
  return $ (\\ ++ vname ++  -  ++ s ++ )


Now with lam, I get this cryptic error message (under 6.8.2):

Occurs check: cannot construct the infinite type: b = a - b
When trying to generalise the type inferred for `lam'
  Signature type: forall a1 b1.
  (Y String a1 - Y String b1) - Y String (a1 -
b1)
  Type to generalise: forall a1 b1.
  (Y String a1 - Y String b1) - Y String (a1 -
b1)
In the instance declaration for `Symantics (Y String)'

Both the two types in the error message are identical, which suggests
no generalization is needed.  I'm puzzled why ghc sees an infinite type.

Any ideas on how to proceed?


Not an answer, but just a different error message from GHC 6.10.3 when I 
  tried loading up your code.


kya...@kyavaio:~/tmp$ ghci EvalTaglessF.hs
GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( EvalTaglessF.hs, interpreted )

EvalTaglessF.hs:264:14:
Couldn't match expected type `b1' against inferred type `b'
  `b1' is a rigid type variable bound by
   the type signature for `fz' at EvalTaglessF.hs:263:31
  `b' is a rigid type variable bound by
  the type signature for `lam' at EvalTaglessF.hs:248:26
  Expected type: Z b1 String
  Inferred type: Z b String
In the expression: Z . f . unZ
In the definition of `fz': fz = Z . f . unZ

EvalTaglessF.hs:264:22:
Couldn't match expected type `a1' against inferred type `a'
  `a1' is a rigid type variable bound by
   the type signature for `fz' at EvalTaglessF.hs:263:17
  `a' is a rigid type variable bound by
  the type signature for `lam' at EvalTaglessF.hs:248:16
  Expected type: Z a1 String
  Inferred type: Z a String
In the second argument of `(.)', namely `unZ'
In the second argument of `(.)', namely `f . unZ'
Failed, modules loaded: none.



I hope this gives you a hint, if any.  I am not exactly sure about how 
to solve this but I might try using scoped type variables extension 
somehow if I were in your shoe.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 NoMonomorphismRestriction,TypeSynonymInstances,FlexibleInstances,MultiParamTypeClasses,ScopedTypeVariables #-}
  -- Haskell' Committee seems to have agreed to remove the restriction

-- Tagless Typed lambda-calculus with integers and the conditional
-- in the higher-order abstract syntax.
-- Haskell itself ensures the object terms are well-typed.
-- Here we use the tagless final approach.

{- 
module EvalTaglessF where

class Symantics repr where
  l:: (repr t1 - repr t2) - repr (t1-t2)
  a:: repr (t1-t2) - repr t1 - repr t2
  i:: Int - repr Int
  (+:) :: repr Int - repr Int - repr Int		-- addition
  ifz  :: repr Int - repr t - repr t - repr t	-- if zero
  fix  :: repr ((a-b) - (a-b)) - repr (a-b)
  -- Let :: repr t1 - (repr t1 - repr t) - repr t

-- compared to EvalTaglessI, everything is in lower-case now

-- Since we rely on the metalanguage for typechecking and hence
-- type generalization, we have to use `let' of the metalanguage.
infixl 9 `a`


-- It is quite challenging to show terms. Yet, in contrast to the GADT-based
-- approach (EvalTaglessI.hs), we are able to do that, without
-- extending our language with auxiliary syntactic forms.
-- Incidentally, showing of terms is just another way of _evaluating_
-- them, to strings.

type VarCount = Int			-- to build the names of variables
newtype S t = S (VarCount - (String,VarCount))
evals (S t) = t

instance Symantics S where
l f  = S $ \c0 -
   let vname = v ++ show c0
   c1 = succ c0
   (s,c2) = evals (f (S $ \c - (vname,c))) c1
   in ((\\ ++ vname ++ -  ++ s ++ ),c2)
a e1 e2  = S $ \c0 -
	   let (s1,c1) = evals e1 c0
	   (s2,c2) = evals e2 c1
   in (( ++ s1 ++   ++ s2 ++ ),c2)
i n  = S $ \c - (show n,c)
e1 +:e2  = S $ \c0 -
	   let (s1,c1) = evals e1 c0
	   (s2,c2) = evals e2 c1
   in (( ++ s1 ++  +  ++ s2 ++ ),c2)
ifz e1 e2 e3 = S $ \c0 -
	   let (s1,c1) = evals e1 c0
	   (s2,c2) = evals e2 c1
	   (s3,c3) = evals e3 c2
   in ((ifz  ++ s1 ++   ++ s2 ++   ++ s3 ++),c3)
fix e = S $ \c0 -
	   let (s1,c1) = evals e c0
   in ((fix  ++ s1 ++ ),c1)

tshow t = fst $ evals t 0

-- We no longer need variables or the environment and we do
-- normalization by evaluation.

-- Denotational semantics. Why?
newtype D t = D t			-- This is not a tag. Why?
evald:: D t - t
evald (D t) = t

instance Symantics D where
l f  = D $ \x - evald (f (D x))
a e1 e2  = D $ (evald e1) (evald e2)
i n  = D $ n
e1 +: e2 = D $ evald e1 + evald e2
ifz e1 e2 e3 = D $ if evald e1 == 0 then evald e2 else evald e3
fix e= D $ hfix (evald e) where hfix f = f (hfix f)

{-
We can also give operational semantics, by implementing the function of the
following signature:

evalo :: (forall repr. Symantics repr = repr t) -
	 (forall repr. Symantics repr = repr t)

The signature has rank-2 type and hence this file requires a PRAGMA
declaration {-# LANGUAGE Rank2Types #-}

The implementation of evalo is exactly the partial evaluator of the
tagless final paper. Please see the paper for details.

-}

-- Tests
-- Truly the tests differ from those in EvalTaglessI.hs only in the case
-- of `syntax`: (i 1) vs (I 1), etc.

test0d = evald $ l(\vx - vx +: (i 2)) `a` (i 1) -- 3

term1 = l (\vx - ifz vx (i 1) (vx +: (i 2)))
test11d = evald $ term1
test11s = tshow $ term1 -- (\\v0- (ifz v0 1 (v0 + 2)))

test12d = evald (term1 `a` (i 2))	-- 4, as Haskell Int
-- test14  = evald (term1 `a` vx)   -- Type error! Not in scope: `vx'


term2 = l (\vx - l (\vy - vx +: vy))
-- *EvalTaglessF :t term2
-- term2 :: (Symantics repr) = repr (Int - Int - Int)

test21  = evald term2
test23d = evald (term2 `a` (i 1) `a` (i 2)) -- 3

termid = l(\vx - vx)
testid = evald termid -- testid :: t1 - t1

term2a = l (\vx - l(\vy - vx `a` vy))
{- The meta-language figured the (polymorphic) type now
 *EvalTaglessF :t term2a
 term2a :: (Symantics repr) = repr ((t1 - t2) - t1 - t2)
-}


-- No longer hidden problems
-- term3 = l (\vx - ifz vx (i 1) vy) -- Not in scope: `vy'

-- The following is a type error, we can't even enter the term
-- term4 = l (\vx - ifz vx (i 1) (vx `a` (i 1)))
{- Now we get good error messages!

Couldn't match expected type `t1 - Int'
   against inferred type `Int'
  Expected type: repr (t1 - Int)
  Inferred type: repr Int
In the first argument of `a', namely `vx'
In the third argument of `ifz', namely `(vx `a` (i 1))'
-}



-- (x+1)*y = x*y + y

-- why is this less of a cheating? Try showing the term
-- Now, 

[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.


To get there replace your definition of fz with:

  fz :: Z a String - Z (a - b) String
  fz = Z . Y . unY . f . unZ


I think this seems to be the Yeoh wanted.

Mine was just blinded hack just to make it type check without looking at 
what program means.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 leak profiling with most purely functional lazy data 
structures.  I only tried the first problem, and it was good enough 
performance.  But I don't have an idea how may timesteps it takes for 
the Operations Clear Sky.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 able to make any time on sunday though so didn't end up
submitting a final entry which is too bad. this was an interesting one.

John



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-06-29 Thread 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,
and convert Haskell Integer with C Int internally. So the user does
not have to care about the type convert (everywhere, which is ugly).
And, specially, when doing something like serialisation, for Haskell
Integer, the user does not have to do things with precision. But for
CPid, without the fromIntegral, we have to specify its precision,
well, on different machine/OS, the precision may not be the same.


Integer is not a fixed length chunk of bits.  It can be arbitrarily 
large as long as there is memory left in the system.  It's theoretically 
more clean being close to a mathematical definition of integers, but 
internally a complicated beast.  So defining CPid as Integer is just not 
sane.


In addition, we cannot use Int either.  Int is not a 32 bit or 64 bit 
word.  The Haskell 98 standard does not require that, and in most 
implementations it is 2^31 singed bits using one bit as a mark to 
distinguish 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-cafe


[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,
and convert Haskell Integer with C Int internally. So the user does
not have to care about the type convert (everywhere, which is ugly).
And, specially, when doing something like serialisation, for Haskell
Integer, the user does not have to do things with precision. But for
CPid, without the fromIntegral, we have to specify its precision,
well, on different machine/OS, the precision may not be the same.


Integer is not a fixed length chunk of bits.  It can be arbitrarily 
large as long as there is memory left in the system.  It's theoretically 
more clean being close to a mathematical definition of integers, but 
internally a complicated beast.  So defining CPid as Integer is just not 
sane.


In addition, we cannot use Int either.  Int is not a 32 bit or 64 bit 
word.  The Haskell 98 standard does not require that, and in most 
implementations it is 2^31 singed bits using one bit as a mark to 
distinguish pointers from values for garbage collection purposes. (OCaml 
int types are like that too.)


I hope this gives enough explanation.


I wrote this and thought that you might already know this.  For 
convenience of serialization, wouldn't defining Data.Binary instances 
for C types be enough in the library level?


--
  Ahn, Ki Yung

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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.  If
your guess is wrong it will show you a diff like output comparing
your guess and the original verse.  This will repeat until you get
all the verses right.

For the test data I included four beloved Psalms (1,23,121,127)
from the Old Testament, each in Revised Korean Version (RKV) and
New International Version (NIV), which I happened to have had to
memorize.  You can use it for any other text you'd want to memorize,
such as your favorite poems, quotes, or whatsoever.

No craft or ticks, really simple and straightforward utility but
serves well for the purpose.  I used readline because that was
the only sane way I know of handling multibyte inputs.



 an example usage 

kya...@kyagrd:~/cscs/memscript$ memscript 001en.txt
% Blessed is the man who does not walk in the counsel of the wicked or
stand in the way of sinners or sit in the seat of mockers.
% But his delight is in the law of the LORD, and on his law he meditates
night and day.
===
 But his delight is in the law of the LORD, and on his law he meditates
day and night.
---
 But his delight is in the law of the LORD, and on his law he meditates
night and day.
===
% But his delight is in the law of the LORD, and on his law he meditates
day and night.
% He is like a tree planted by streams of water, which yields its fruit
in season and whose leaf does not wither. Whatever he does prospers.
% Not so the wicked! They are like chaff that the wind blows away.
% The wicked will not stand in the judgment, nor sinners in the assembly
of the righteous.
===
 Therefore the wicked will not stand in the judgment, nor sinners in
the assembly of the righteous.
---
 The wicked will not stand in the judgment, nor sinners in the assembly
of the righteous.
===
% Therefore the wicked will not stand in the judgment, nor sinners in
the assembly of the righteous.
% For the LORD watches over the way of the righteous, but the way of the
wicked will perish.
kya...@kyagrd:~/cscs/memscript$

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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  - return Just (v==g)
Nothing - return Nothing

My intention was to use it something like this:

checkOneVerseByLineWith (readline % )

where readline is the library function from System.Console.Readline.

As you can see, there is an obvious mistake which I forgot to
group (Just (v==g)) in parenthesis.  However, GHC or any other
Haskell 98 compliant implementation will infer a type for you
and this will type check!  Try it yourself if in doubt.

Of course, checkOneVerseByLineWith (readline % ) won't type check
because checkOneVerseByLineWith has strange type.  The reason why
the above definition type checks is because ((-) r) is an instance
of Monad.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
  case mg of
Just g  - return Just (v==g)
Nothing - return Nothing
 
 My intention was to use it something like this:
 
 checkOneVerseByLineWith (readline % )
 
 where readline is the library function from System.Console.Readline.
 
 As you can see, there is an obvious mistake which I forgot to
 group (Just (v==g)) in parenthesis.  However, GHC or any other
 Haskell 98 compliant implementation will infer a type for you
 and this will type check!  Try it yourself if in doubt.
 
 Of course, checkOneVerseByLineWith (readline % ) won't type check
 because checkOneVerseByLineWith has strange type.  The reason why
 the above definition type checks is because ((-) r) is an instance
 of Monad.

Oh, I happened to be importing Control.Monad.Trans somehow,
it just doesn't work with Prelude import itself.
And, there were already some discussions on this last year:

[Haskell-cafe] The danger of Monad ((-) r)
http://www.mail-archive.com/haskell-cafe@haskell.org/msg23680.html
Tomasz Zielonka
Tue, 15 May 2007 03:05:30 -0700




___
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 that I am not very familiar with Mercury. But if you 
are looking for doing Prolog the Haskell way advertiseyou can also 
have a look at Curry/advertise. Curry is a lazy functional logic 
programming language that has a Haskell like syntax 
(http://www.curry-language.org/).


You forgot to mention, that you will give a talk about Curry soon, where 
Matthias might want to attend:

  http://iba-cg.de/hal4.html

:-)


By the way, did Curry solved the problem of how to deal with IO and 
backtracking issues? (where and  where not should IO happen kind of a 
thing)  I haven't used Curry that much but I remember that there was an 
issue of IO and non-determinism.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 anyone know of 
another system or better representation?




You must to take a look at this:

Tangible Functional Programming
http://www.youtube.com/watch?v=faJ8N0giqzw

And, a little bit off topic but cool stuff:

Vacuum: visualize Haskell data structures live
http://www.youtube.com/watch?v=X4-212uMgy8


@ It seems that we are getting pretty close to the point that youtube is 
getting to be a better reference than a paper, at least for 
practitioners. A lot of talks are on youtube :)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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/listinfo/haskell-cafe


[Haskell-cafe] Re: Question concerning Haskell Foundation

2009-05-07 Thread Ahn, Ki Yung

Don Stewart wrote:

vigalchin:

Hello,

 With Haskell Foundation,

 1) Can we still publish packages on Hackage?

 2) Is Hackage going away?


???

-- Don


Don, I think he's referring to your recent announcement about the 
Haskell platform.  And, at that thread you also mentioned 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] 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 Linux because editline library has the same 
naming issues in Debian.  So, this may be Debian packaging problem of 
OpenGL bindings.


But the interesting thing is that I was able to work around this in 
Debian, by temporarily making a symbolic link libGL.so pointing to 
libGL.so.1 and it hpong built successfully.  Once it builds, hpong still 
runs even if I delete the symbolic link libGL.so.  So, there is also a 
possibility that what may be wrong is with the build system (cabal or ghc).


Thanks in advance for related library packaging mangers and developers, 
and here are the details of failure:


kya...@kyagrd:~/cscs/stlcwpat$ uname -a
Linux kyagrd 2.6.26-2-686 #1 SMP Thu Mar 26 01:08:11 UTC 2009 i686 GNU/Linux
kya...@kyagrd:~/cscs/stlcwpat$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.10.1
kya...@kyagrd:~/cscs/stlcwpat$ which ghc
/usr/bin/ghc

kya...@kyagrd:~/cscs/stlcwpat$ cabal update
Downloading the latest package list from hackage.haskell.org

kya...@kyagrd:~/cscs/stlcwpat$ cabal install HPong
Resolving dependencies...
Configuring HPong-0.1.2...
Preprocessing executables for HPong-0.1.2...
Building HPong-0.1.2...
[1 of 1] Compiling Main ( HPong.hs, 
dist/build/hpong/hpong-tmp/Main.o )

Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package base-3.0.3.0 ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package containers-0.2.0.0 ... linking ... done.
Loading package transformers-0.1.4.0 ... linking ... done.
Loading package data-accessor-0.2.0.2 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package utility-ht-0.0.4 ... linking ... done.
Loading package data-accessor-template-0.2.1.1 ... linking ... done.
Loading package OpenGL-2.2.1.1 ... command line: can't load .so/.DLL 
for: GL (libGL.so: cannot open shared object file: No such file or 
directory)

cabal: Error: some packages failed to install:
HPong-0.1.2 failed during the building phase. The exception was:
exit: ExitFailure 1
kya...@kyagrd:~/cscs/stlcwpat$ ghc-pkg list
/usr/lib/ghc-6.10.1/./package.conf:
ALUT-2.1.0.0, Cabal-1.6.0.1, Diff-0.1.2, GLUT-2.1.1.2, HDBC-2.1.0,
HDBC-postgresql-2.1.0.1, HGL-3.2.0.0, HUnit-1.2.0.3,
OpenAL-1.3.1.1, OpenGL-2.2.1.1, QuickCheck-2.1.0.1, Stream-0.2.2,
X11-1.4.5, X11-xft-0.3, array-0.2.0.0, arrows-0.4.1, base-3.0.3.0,
base-4.0.0.0, binary-0.5, bytestring-0.9.1.4, cairo-0.10.0,
cgi-3001.1.7.1, containers-0.2.0.0, convertible-1.0.2,
directory-1.0.0.2, editline-0.2.1.0, fgl-5.4.2.2, filepath-1.1.0.1,
(ghc-6.10.1), ghc-prim-0.1.0.0, gio-0.10.0, glade-0.10.0,
glib-0.10.0, gstreamer-0.10.0, gtk-0.10.0, gtkglext-0.10.0,
gtksourceview2-0.10.0, haskell-src-1.0.1.3, haskell98-1.0.1.0,
hpc-0.5.0.2, hslogger-1.0.8, html-1.0.1.2, integer-0.1.0.0,
irc-0.4.3, mtl-1.1.0.2, network-2.2.0.1, old-locale-1.0.0.1,
old-time-1.0.0.1, packedstring-0.1.0.1, parallel-1.1.0.0,
parsec-3.0.0, pretty-1.0.1.0, process-1.0.1.0, random-1.0.0.1,
regex-base-0.93.1, regex-compat-0.92, regex-posix-0.93.1, rts-1.0,
soegtk-0.10.0, stm-2.1.1.2, svgcairo-0.10.0, syb-0.1.0.0,
syb-with-class-0.5.1, tagsoup-0.6, template-haskell-2.3.0.0,
terminfo-0.3.0.1, time-1.1.2.3, unix-2.3.1.0, utf8-string-0.3.4,
xhtml-3000.2.0.1, xmonad-0.8.1, xmonad-contrib-0.8.1, zlib-0.5.0.0
/home/kyagrd/.ghc/i386-linux-6.10.1/package.conf:
Cabal-1.6.0.1, Cabal-1.6.0.2, GLFW-0.3, HGL-3.2.0.0, HTTP-3001.1.3,
HTTP-4000.0.4, HTTP-4000.0.5, InfixApplicative-1.0.1,
QuickCheck-1.2.0.0, QuickCheck-2.1.0.1, Stream-0.3.1, arrows-0.4.1,
binary-0.5.0.1, cgi-3001.1.7.1, data-accessor-0.2.0.2,
data-accessor-monads-fd-0.2, data-accessor-template-0.2.1.1,
derive-0.1.4, extensible-exceptions-0.1.1.0, filepath-1.1.0.2,
fingertree-0.0, ghc-paths-0.1.0.5, haddock-2.4.1,
haskell98-1.0.1.0, irc-0.4.3, lazysmallcheck-0.3,
(monads-fd-0.0.0.1), network-2.2.0.1, network-2.2.1,
old-time-1.0.0.2, parsec-2.1.0.1, pointedlist-0.3.1,
process-1.0.1.1, pureMD5-0.2.4, random-1.0.0.1, regex-tdfa-1.0.0,
rosezipper-0.1, sparsebit-0.5, split-0.1.1, terminfo-0.3.0.2,
transformers-0.1.4.0, uniplate-1.2.0.3, unix-compat-0.1.2.1,
utility-ht-0.0.4, vty-3.1.8.4, yi-0.6.0, zlib-0.4.0.4, zlib-0.5.0.0

kya...@kyagrd:~/cscs/stlcwpat$ ls /usr/lib/*GL*
/usr/lib/libGL.so.1@   /usr/lib/libGLU.so.1.3.070300
/usr/lib/libGL.so.180.44   

[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
Name:smartword
Synopsis:Web based flash card for Word Smart I and II
vocabularies
Version: 0.0.0.5
Homepage:http://kyagrd.dyndns.org/~kyagrd/project/smartword/
Category:Web,Education
License: BSD3
License-file: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 the
vocabulary data and wrote the program in 2004, because I got too boring
just going over the strange English words.  If you don't read Korean,
you can just ignore the Korean translation. Source code is outdated, so
never even think of using it as a web programming reference.  However,
it will still be helpful as a neat web application when one tries to
squeeze GRE vocabularies into the volatile memory of human brain.

Installation:

You can either compile CGI binaries with GHC or use Hugs to run lhs as a
CGI script.  Copy all .cgi files and data directories (book1, book1.ans,
book2, book2.ans) into your webserver CGI directory (usually cgi-bin).

Usage:

If you get it wright the flash card goes away, but if you didn't get it
the flash card goes to the bottom of the deck again. So, it won't end
until you get all of them right.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-03-10 Thread Ahn, Ki Yung
sparsebit - Sparse Bitmaps for Pattern Match Coverage
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/sparsebit

This library packages the functional peal paper 'Sparse Bitmaps for
Pattern Match Coverage' submitted to ICFP 2009 by Ki Yung Ahn and Tim
Sheard. You can look up the tutorial-like paper and the talk slides,
which are availabel at:
  http://kyagrd.dyndns.org/wiki/SparseBitmapsForPatternMatchCoverage

Abstract:
  Pattern matching coverage over Algebraic Data Types(ADTs) has most
often been studied in the context of pattern compilation algorithms.
However, it is worth considering the pattern matching coverage problem
in isolation, since general solutions will be independent of the
specifics of any implementation or language.
  We define an intuitive and mathematically well-established bit masking
semantics for pattern match coverage. We design and implement a sparse
bitmap data structure, which realizes this semantics in a compact and
flexible manner. This bitmap data structure supports computing coverage
solutions of large programs incrementally from coverage solutions of
sub-programs. It can also be used as a common data representation for
pattern coverage shared between different tools (e.g., compilers,
linting tools, software analysis tools) that need pattern match coverage
information.


Additional source files Type.hs and TestType.hs packaged with this
library provides the examples and QuickCheck extracted from the paper to
demonstrate how to use this library.


Some additional notes:

Personally, I am very happy to upload my first project on Hackage.  If
you are looking for simple and elegant way of describing pattern match
coverage or testing exhaustiveness of pattern matching, we hope this may
give you a better insight.  This is a reference implementation, but I
think it is still usable to some extent.  One might want to define
monadic version of the library functions and operators since the type
representation in the program analysis tools might be monadic for
implementation reasons (easy to generate fresh type variables) and
performance reasons (to exploit sharing while unification of type
variables).  And in such cases, more optimized implementation of tensor
product may be possible as well.  And there are some other issues
discussed in the paper as well.

I 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 not have
 remove option yet, so it's hard to fix when such loophole happens).

 Today, I had some time in the airport and decided to start from scratch
 again because of the dependency loophole with process 1.0.1.1 and
 haddock.  I downloaded the most recent version of cabal-install the
 version 0.6.2, and found out that the ./bootstrap.sh does not work.
 
 If you could provide any details on how it does not work that would be
 much appreciated. Eg a log of the output from running the bootstrap.
 
 Duncan
 

I am using Debian unstable.

The version of GHC debian package is 6.10.1+dfsg1-13,
and installed Haskell libraries (debian packages) are:

kya...@kyavaio:~$ ghc-pkg list
/usr/lib/ghc-6.10.1/./package.conf:
Cabal-1.6.0.1, Diff-0.1.2, HGL-3.2.0.0, HUnit-1.2.0.3,
QuickCheck-2.1.0.1, Stream-0.2.2, X11-1.4.5, array-0.2.0.0,
arrows-0.4.1, base-3.0.3.0, base-4.0.0.0, binary-0.5,
bytestring-0.9.1.4, cairo-0.10.0, cgi-3001.1.7.1,
containers-0.2.0.0, directory-1.0.0.2, editline-0.2.1.0,
fgl-5.4.2.2, filepath-1.1.0.1, gconf-0.10.0, (ghc-6.10.1),
ghc-prim-0.1.0.0, gio-0.10.0, glade-0.10.0, glib-0.10.0,
gnomevfs-0.10.0, gstreamer-0.10.0, gtk-0.10.0, gtkglext-0.10.0,
gtksourceview2-0.10.0, haskell98-1.0.1.0, hpc-0.5.0.2,
html-1.0.1.2, integer-0.1.0.0, irc-0.4.3, mtl-1.1.0.2,
network-2.2.0.1, old-locale-1.0.0.1, old-time-1.0.0.1,
packedstring-0.1.0.1, parallel-1.1.0.0, parsec-3.0.0,
pretty-1.0.1.0, process-1.0.1.0, random-1.0.0.1, rts-1.0,
stm-2.1.1.2, svgcairo-0.10.0, syb-0.1.0.0, syb-with-class-0.5.1,
tagsoup-0.6, template-haskell-2.3.0.0, time-1.1.2.3, unix-2.3.1.0,
utf8-string-0.3.4, xhtml-3000.2.0.1


Bootstrap fails like this:

kya...@kyavaio:~/tmp/cabal-install-0.6.2$ sh bootstrap.sh
Checking installed packages for ghc-6.10.1...

The Haskell package 'parsec' is required but it is not installed.
If you are using a ghc package provided by your operating system
then install the corresponding packages for 'parsec' and 'network'.
If you built ghc from source with only the core libraries then you
should install these extra packages. You can get them from hackage.

Error during cabal-install bootstrap:
The Haskell package 'parsec' is required but it is not installed.



P.S. Note, parsec and network are installed in the system using debian
distribution packages.

--
  Ahn, Ki Yung

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-03-07 Thread 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 such loophole happens).

Today, I had some time in the airport and decided to start from scratch
again because of the dependency loophole with process 1.0.1.1 and
haddock.  I downloaded the most recent version of cabal-install the
version 0.6.2, and found out that the ./bootstrap.sh does not work. So,
I had to bootstrap from version 0.6.2 and do cabal update and cabal
upgrade cabal-install to upgrade to 0.6.2.

I am not sure whether this is a cabal-install problem or debian
dstribution ghc-6.10.1 packaging probelm, since I have not tried to test
 this with any other ghc-6.10.1 distribution.

If anyone who are not using 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 such loophole happens).
 
 Today, I had some time in the airport and decided to start from scratch
 again because of the dependency loophole with process 1.0.1.1 and
 haddock.  I downloaded the most recent version of cabal-install the
 version 0.6.2, and found out that the ./bootstrap.sh does not work. So,
 I had to bootstrap from version 0.6.2 and do cabal update and cabal
 upgrade cabal-install to upgrade to 0.6.2.

Sorry for my typo.  What I meant was: I was able to bootstrapped from
version 0.6.0 and then upgrade to 0.6.2.

 I am not sure whether this is a cabal-install problem or debian
 dstribution ghc-6.10.1 packaging probelm, since I have not tried to test
  this with any other ghc-6.10.1 distribution.
 
 If anyone who are not using 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 languages that offer safety and garbage collection etc get 
as close as Haskell does.


Bob


OCaml and Clean seems to be pretty fast too.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 arguments or the range of the type function.
Then, we need help of type classes to constrain the result of
open type functions. For example, try to define HList library
using type families instead of type classes with functional
dependencies. One will soon need some class constraints.
Sometimes, we can use associated type families, but
many times it may become tedious when there are multiple
arguments and result have certain constraints so that
we might end up associating/splitting them over multiple
type classes. In such cases, it may be more simple working
with functional dependencies alone, rather than using
both type classes and type families. I wish we had closed
kinds so that we can define closed type functions as well as
open type functions.

2) Type families are not good when we need to match types
back and forth (e.g. bijective functions), or even multiple
ways. We need the help of functional dependencies for these
relational definitions. I know that several people are
working on the unified implementation for both type families
and functional dependencies. Once GHC have common background 
implementation, type families will truly be syntactic sugar

of type classes with functional dependencies, as Mark Jones
advocates, or maybe the other way around too.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 that and cite the work. Otherwise, I should think
about cleaning up and packaging this as a library. My code is like this
right now:

 data Bits = O -- all 1 bits of any size and dimension
   | I -- all 0 bits of any size and dimension
   | Bs [Bits] -- row of bits possibly nested
   | Rep Bits  -- repeating of bits (e.g. O = Rep O = Bs [O,O])
   deriving (Eq,Show)

bitwise-and

 O   . _   = O
 _   . O   = O
 (Rep O) . _   = O
 _   . (Rep O) = O
 (Bs (O:xs)) . _   | all (O==) xs  = O
 _   . (Bs (O:xs)) | all (O==) xs  = O
 I   . y   = y
 x   . I   = x
 (Rep I) . y   = y
 x   . (Rep I) = x
 (Bs (I:xs)) . y   | all (I==) xs  = y
 x   . (Bs (I:ys)) | all (I==) ys  = x
 (Bs xs) . (Bs ys) = reduce $ Bs (zipWith (.) xs ys)
 (Rep x) . (Bs ys) = reduce $ Bs (xs .. ys) where xs=repeat x
 (Bs xs) . (Rep y) = reduce $ Bs (xs .. ys) where ys=repeat y
 (Rep x) . (Rep y) = reduce $ Rep (x . y)

 (..) = zipWith (.)

bitwise-or

 O   .| y   = y
 x   .| O   = x
 (Rep O) .| y   = y
 x   .| (Rep O) = x
 (Bs (O:xs)) .| y   | all (O==) xs  = y
 x   .| (Bs (O:ys)) | all (O==) ys  = x
 I   .| _   = I
 _   .| I   = I
 (Rep I) .| _   = I
 _   .| (Rep I) = I
 (Bs (I:xs)) .| _   | all (I==) xs  = I
 _   .| (Bs (I:ys)) | all (I==) ys  = I
 (Bs xs) .| (Bs ys) = reduce $ Bs (xs .|. ys)
 (Rep x) .| (Bs ys) = reduce $ Bs (xs .|. ys) where xs=repeat x
 (Bs xs) .| (Rep y) = reduce $ Bs (xs .|. ys) where ys=repeat y
 (Rep x) .| (Rep y) = reduce $ Rep (x .| y)

 (.|.) = zipWith (.|)

tensor product

 O   .* _   = O
 _   .* O   = O
 (Rep O) .* _   = O
 _   .* (Rep O) = O
 (Bs (O:xs)) .* _   | all (O==) xs  = O
 _   .* (Bs (O:ys)) | all (O==) ys  = O
 I   .* I   = I
 I   .* (Rep y) = I .* y
 (Rep I) .* y   = I .* y
 (Bs (I:xs)) .* y   | all (I==) xs  = I .* y
 I   .* y   = reduce $ Rep y
 x   .* (Rep I) = x .* I
 x   .* (Bs (I:xs)) | all (I==) xs  = x .* I
 x   .* I   = x
 (Bs xs) .* (Bs ys) = reduce $ Bs (xs .*. ys)
 (Bs xs) .* (Rep y) = reduce $
  Bs (map (reduce . Rep) $ xs .*. [y])
 (Rep x) .* y   = reduce $ Rep (x .* y)

 [] .*. _  = []
 (x:xs) .*. ys = (reduce $ Bs [x .* y | y-ys]) : (xs .*. ys)

reducing  from Bs [O,O,..] to O and from Bs [I,I,..] to I

 reduce (Bs (x:xs)) | all (x==) xs = x
 reduce (Rep x@(Rep _)) = x
 reduce x   = x

Some example run on Hugs:

Main Bs [I,O]

Bs [I,O]

Main Bs [I,O] .| Bs [O,Bs [I,I,I,I] .* Bs [I,O,O,O,O]]

Bs [I,Rep (Bs [I,O,O,O,O])]

Main Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]

Bs [I,Bs [I,Bs [I,O,O,O,O],Bs [I,O,O,O,O],Bs [I,O,O,O,O]]]

Main Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]

Bs [I,Bs [I,Bs [I,I,I,O,O],Bs [I,I,I,O,O],Bs [I,O,O,O,O]]]

Main Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]
   .| Bs [O, Bs [O,I,I,I] .* Bs [O,O,O,I,I]]

Bs [I,Bs [I,I,I,Bs [I,O,O,I,I]]]

Main Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]
   .| Bs [O, Bs [O,I,I,I] .* Bs [O,O,O,I,I]]
   .| Bs [O, Bs [O,O,I,I] .* Bs [O,I,I,O,O]]

I

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 = x
 reduce (Bs (x:xs)) | all (x==) xs = reduce x
 reduce (Bs xs) = Bs (map reduce xs)
 reduce (Rep O) = O
 reduce (Rep I) = I
 reduce (Rep x) = Rep (reduce x)
 reduce x   = x

This is why I am looking for existing work, because I am
not yet very sure about my code I'm using.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-01-04 Thread Ahn, Ki Yung
Dear Haskellers,

I just got an inquiry from a research department head
of a Korean company seriously considering to adopt
functional languages because they heard that functional
languages can do good at parallel programming on manycore
platforms.

They want to know what technologies out there implemented
in functional languages, such as Erlang or Haskell, that
can help them write more maintainable programs that are
better at utilizing parallelism and avoiding bugs related
to synchronization. They are also very interested in Cilk,
as well as Haskell or Erlang.

My first thought is that maybe Cilk would work better for
them just because it would not be easy to recruit Erlang or
Haskell programmers experienced in network, security, or
concurrent/parallel programming.  I myself can answer basic
inquiries such as what libraries to look for to implenent
such and so, but not able to give advice on large scale
projects such as unified security solution package. So,
it wouldn't be practical form them to launch a project
without inviting an Erlang or Haskell expert in their domain
as a project manager from overseas, which I don't think they
are very willing to do.

Are there Haskell consultants or Haskell experts on this
subject, who believes that Haskell based approach might work
better for them, or Haskell can be useful along with other
approaches (e.g. DSL, prototyping, formal modeling of policies)?
If so, I would like to recommend them trying contact you, and try
my best to help communicating with them, if needed.  They know
English, of course, but may not be familiar with functional
programming orlanguage-oriented programming jargons such as DSLs,
oops, I mean language middleware :-)


For your information:

The company is a network security company whose main products
are VPN and firewall appliances and their management software.
Their research department is in search of better technologies
to implement their future UTM (unified threat management)
solutions utilizing the manycore platforms.

In Korea, there are some research groups and few companies
using OCaml, but almost no Erlang or Haskell communities.
This company is preferring local researchers or consultants
for advice or consulting, but there's no local group using
Haskell seriously, as far as I know, even in research yet.
That's why this person contacted me, just because I wrote
a small tutorial 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://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-12-20 Thread Ahn, Ki Yung
In Graham Hutton's Programming in Haskell there is an interactive
calculator example using ANSI code to implement the UI on the terminal.
This example doesn't work on MS Windows XP or other MS OSes based on NT
kernel, since their command line does not support ANSI very well.

But, thanks to ansi-terminal on Hackage, I was able to extract minimal
code from the package to make a win32 version of the calculator example
in Hutton's book.

calculatorWin32.lhs and Win32ANSI.hs is an implementation for win32.
I extracted the win32 console API bindings for setting cursor positions
from ansi-terminal project and put them in Win32ANSI.hs. I had to put
this in a separate file because I had an issue with ghci.  To run this,
I had to compile the console API bindings with ghc first and then run
ghci as follows

 C:\ ghc -c Win32ANSI.hs
 C:\ ghci calculatorWin32.lhs

Without compiling the object code, ghci cannot find the proper link for
win32 console API FFI bindings.

 C:\ ghci calculatorWin32.lhs
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 3] Compiling Parsing  ( Parsing.lhs, interpreted )
[2 of 3] Compiling Win32ANSI( Win32ANSI.hs, interpreted )

During interactive linking, GHCi couldn't find the following symbol:
  getconsolescreenbufferi...@8
This may be due to you not asking GHCi to load extra object files,
archives or DLLs needed by your current session.  Restart GHCi, specifying
the missing library using the -L/path/to/object/dir and -lmissinglibname
flags, or simply by naming the relevant files on the GHCi command line.
Alternatively, this link failure might indicate a bug in GHCi.
If you suspect the latter, please send a bug report to:
  glasgow-haskell-b...@haskell.org


Is this a bug or a natural behavior of ghci? This is strange to me
since ghci finds the proper link for the functions in the other C
libraries such as getch in conio.h.


In addition, I am attaching a patched calculator.lhs which works
for Unix/Linux on both GHC 6.8.x and GHC 6.10.1. The one currently
on the book homepage only works for GHC 6.8.x but not GHC 6.10.1.
This is due to the bug fix of hSetBuffering in GHC 6.10.1.

To run these calculator example you will also need Parsing.lhs from
the book hompage.http://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, such as Hugs.  Moreover, the use of control characters
may not work on some systems, such as WinHugs.

Note: This code works for both GHC versions 6.8.x and 6.10.1 on Unix/Linux.
   Previous code on the webpage only worked on GHC 6.8.x.  -- Ahn, Ki Yung

 import Parsing
 import System.IO

Parser for expressions
--

 expr  :: Parser Int
 expr  =  do t - term
 do symbol +
e - expr
return (t + e)
  +++ do symbol -
 e - expr
 return (t - e)
  +++ return t
 
 term  :: Parser Int
 term  =  do f - factor
 do symbol *
t - term
return (f * t)
  +++ do symbol /
 t - term
 return (f `div` t)
  +++ return f

 factor:: Parser Int
 factor=  do symbol (
 e - expr
 symbol )
 return e
   +++ integer

Derived primitives
--

 getCh :: IO Char
 getCh = do hSetEcho stdin False
hSetBuffering stdin NoBuffering
c - getChar
hSetEcho stdin True
hSetBuffering stdin LineBuffering
return c

 beep  :: IO ()
 beep  =  putStr \BEL
 
 cls   :: IO ()
 cls   =  putStr \ESC[2J

 type Pos  =  (Int,Int)
 
 goto  :: Pos - IO ()
 goto (x,y)=  putStr (\ESC[ ++ show

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

2008-11-28 Thread Ahn, Ki Yung

Andrew Coppin 쓴 글:


Then again, one day I sat down and tried to draw a diagram of the 
essential concepts, techniques and syntax of Haskell and how they're 
related... The result looked like alphabet soup! It's not clear how you 
start to explain anything without immediately needing to explain 20 
other things you just used to explain the first thing. (Somebody 
commented recursive tutorials for a recursive language. It was meant 
as an insult, but I actually kinda like it...) Given that that's the 
case, I'm not really sure that I could do any better than the Three 
Kings, so maybe I should just shuffle off and keep my comments to 
myself. :-/


If one needs introductory Haskell programming tutorial explaining about 
the language concepts from first principles, then one should read a 
textbook written for that purpose such as Programming in Haskell.


Real World Haskell is a collection of practical tips and know-hows to 
get things done at work rather than a step-by-step Haskell tutorial. And 
I believe that many other O'Reilly books are like that.


What I *haven't* done yet is read the chapters where they try to claim 
that database programming is possible in Haskell. I'll have to do that 
at some point. Maybe this is where they reveal the Secret Formula that 
makes this stuff actually work properly... but somehow I doubt it.


What do you mean by that they are trying database programming is 
possible in Haskell?  I've done very simple database programming in 
Haskell 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 I make an account, where how I put that information in cabal
config file?

I've looked into the cabal config file and tried to change this myself
before, but it wasn't very self explanatory to me.  For instance, I
tried to make the build-reports on by default, deleting haskell comment
like double dashes -- and put True flag after the colon, but keep
getting parse error from cabal.  I looked up the manual but it says that
the config file is self explanatory, which isn't to me at all.  Are
there any documentations on this available anywhere?


=== error messages when I tried to report the build log ===

[EMAIL PROTECTED]:~$ cabal report
Sending:
POST http://hackage.haskell.org/buildreports HTTP/1.1
Content-Type: text/plain
Content-Length: 281
Accept: text/plain


Creating new connection to hackage.haskell.org
Received:
HTTP/1.1 404 Not Found
Date: Fri, 21 Nov 2008 23:52:14 GMT
Server: Apache/2.2.3 (Debian)
Alternates: {HTTP_NOT_FOUND.html.var 1 {type text/html} {charset
iso-8859-2} {language cs} {length 745}}, {HTTP_NOT_FOUND.html.var 1
{type text/html} {charset iso-8859-1} {language de} {length 766}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-1}
{language en} {length 611}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-8859-1} {language es} {length 759}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-1}
{language fr} {length 771}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-8859-1} {language ga} {length 813}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-1}
{language it} {length 692}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-2022-jp} {language ja} {length 749}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset euc-kr} {language
ko} {length 703}}, {HTTP_NOT_FOUND.html.var 1 {type text/html}
{charset iso-8859-1} {language nl} {length 688}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-2}
{language pl} {length 707}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-8859-1} {language pt-br} {length 753}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-1}
{language ro} {length 689}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-8859-5} {language sr} {length 716}},
{HTTP_NOT_FOUND.html.var 1 {type text/html} {charset iso-8859-1}
{language sv} {length 722}}, {HTTP_NOT_FOUND.html.var 1 {type
text/html} {charset iso-8859-9} {language tr} {length 755}}
Vary: accept-language,accept-charset
Content-Length: 418
Content-Type: text/html; charset=iso-8859-1


cabal: Unrecognised response from server.
[EMAIL PROTECTED]:~$ cabal --version
cabal-install version 0.6.0
using version 1.6.0.1 of the Cabal library

___
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
What I mean by getCh is the non-buffered non-echoed version of getChar,
which Hugs used to provided as an extension but not any more.

Is there any way to have a non-buffered non-echoed single character
input function on MS Windows command line using only the libraries in
the MS Windows distribution packages of either GHC or Hugs?

The reason to why this is important for me is because I am translating
Graham Hutton's Programming in Haskell into Korean (soon to be
published), which illustrates interactive programming with the example
of a calculator that responds instantly for every keystroke of numbers
and arithmetic operations running on text mode.  It is very important to
consider the readers who only have access to MS Windows systems, because
Korean OS market share is completely skewed towards MS Windows for very
embarrassing reasons that I do not even want to mention.  And, isn't GHC
developed in MSR anyway?  :-)


I remember that this is an old problem for both of the two most widely
used Haskell implementation, Hugs and GHC.

In ghc 6.8 getChar had a bit strange behavior.  As far as I remember it
always worked as if it were NoBuffering.  Fortunately, in the recently
released ghc 6.10, this has been fixed.  We now actually have to set the
buffering mode to NoBuffering with hSetBufferring to get the
non-buffered behavior of getChar.  But, it still isn't working on MS
Windows.

In Hugs, hSetBuffering neither works on Unix terminal nor on MS Windows
command line.  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 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] yi compiles but does not launches

2008-09-26 Thread Ahn, Ki Yung
I wanted to try out yi after seeing it demonstrated in the
Haskell symposium.  So, I installed cabal as described here
http://hackage.haskell.org/trac/hackage/wiki/CabalInstall

I am using Debian unstable with debian distributed GHC 6.8.2.x
but it seems that yi requries GHC 6.8.3 to compile. So, I manually
installed GHC 6.8.3 using the binary distribution from ghc homepage.

When I install yi with cabal install yi it succeeds and installs
yi version 0.4.6 However, when I run yi it starts but immediately
get stuck with the following error message:

Custom yi (/home/kyagrd/.yi/yi-i386-linux) could not be launched!

The custom file yi-i386-linux does not exist and I don't have
any idea what that is.

Same thing happens with the development version 0.4.7 from
darcs repository.

I did this from complete scratch.  I removed the .cabal and .ghc
directory and started from scratch in a clean 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] The dark side of lazyness - memory leak

2006-08-07 Thread Ahn, Ki Yung

I'm facing the dark side of lazyness recently.

Typical pattern is like this.

My code was working fine and I was happy.
I just wanted to inspect some properties of my code so
I made a slight chane go the code such as adding counter
argument or attaching axulary data filed to original data for
tracing how the data has been constructed.
All of a sudden the program runs out of memory or overflows
the stack.

One problem is that it comes up unexptectedly. Another even
worse problem is that sometimes I get no idea for the exact
loation causing the leak!


It really panics facing such darkness of lazy evaluation.
Just a small innocent looking fix for inspection or tracing
blow things up, sometime with no clue for its reason.

When I put a debugging or tracing operating in my software
that can be toggled, how could I be sure that turning on
those features won't crash my software written in Haskell?

Are there appraoches to detect and fix these kind of problem?

Haskell may be type safe but not safe at all from unexpteded
diversion, not because of the programmers' mistake but just
because of the lazyness.


I have posted an wiki article including one example of this dark
side of lazyness I encountered when I tried to count the number
of basic operations in sorting algorithm.
This was a rather simple situation and we figured out how to
cure this by self equality check ( x==x ) forcing evaluation.



There are wose cases not being able to figure out the cure.
I wrote a fucntion for analyzing some property of a graph,
which worked fine.

fixOnBy t p f x = if t x' `p` t x then x else fixOnBy t p f x' where x' = f x

fixSize f x = fixOnBy Set.size (==) f x

sctAnal gs = null cgs || all (not . null) dcs
 where
   gs' = fixSize compose $ Set.fromList [(x,y,cs) | To _ x y cs-Set.toList gs]
   cgs = [z | z@(x,y,cs)-Set.toList gs', x==y]
   dcs = [ [c| c@(a,D,b)-Set.toList cs , a==b] | (_,_,cs)-cgs]
   compose gs = trace (## ++show (Set.size gs)) $ foldr Set.insert gs $ do
 (x1,y1,cs1) - Set.toList gs
 (_,y2,cs2)  -  takeWhileFst y1 $ Set.toList $ setGT
(y1,Al(-1),Set.empty) gs
 return (x1,y2,cs1 `comp` cs2)
   takeWhileFst y = takeWhile (\(y',_,_) - y==y')

This fucntion makes a transitive closure of the given set of relations
by fixpoint iteration on the size of the set of weighted edegs.

Sample output is like this.

*Main main
## 170
## 400
## 1167
## 2249
## 2314
False


When I add an extra data field for tracing how the new item was made
(e.g. tag [a,b,c] on a-c if it was generated by a-b and b-c)
It suddenly overflows the stack even before printing out the trace.
The following is the code that leaks memory.

sctAnal gs = null cgs || all (not . null) dcs
 where
   gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y
cs-Set.toList gs]
   cgs = [z | z@(TT (x,y,cs) _)-Set.toList gs', x==y]
   dcs = [[c| c@(a,D,b)-Set.toList cs , a==b] | TT (_,_,cs) _-cgs]
   compose gs = trace (## ++show (Set.size gs)) $ foldr checkInsert gs $ do
 TT (x1,y1,cs1) l1 - Set.toList gs
 TT (_,y2,cs2) l2 - takeWhileTTfrom y1 . Set.toList $ setGT (TT
(y1,Al(-1),Set.empty) []) gs
 return $ TT (x1,y2,cs1 `comp` cs2) (l1++y1:l2)
   takeWhileTTfrom y = takeWhile (\(TT (y',_,_) _) - y==y')
   checkInsert x s
   | Set.member x s = s
   | otherwise  = Set.insert x s

data TT a b = TT a b deriving (Show)
instance (Eq a, Eq b) = Eq (TT a b) where
 (TT x lx) == (TT y ly) = lx==lx  ly==ly  x == y
instance (Ord a, Ord b) = Ord (TT a b) where
  (TT x lx)  (TT y ly) = lx==lx  ly==ly  x  y


The really intersting thing happens when I just make the Ord derived
the stack does not overflow and starts to print out the trace.
(It is not the result that I want though. My intention is to ignore the
tags in the set operation)

data TT a b = TT a b deriving (Show,Eq,Ord)

I believe my Eq and Ord instances are even more stricter than the
derived ones. Is there some magic in deriving that prevents
memory leak?

I've even followed the instance declaration that would be the
same as deriving but the that leaks memory.

data TT a b = TT a b deriving (Show)
instance (Eq a, Eq b) = Eq (TT a b) where
 (TT x lx) == (TT y 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


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

2006-08-07 Thread Ahn, Ki Yung

Recently, I'm facing the dark side of laziness
-- the memory leak because of laziness.

Typical pattern that I encounter the problem is like this.

My code was working fine and I was happy.
I just wanted to inspect some properties of my code so
I made a slight chage go the code such as adding counter
argument or attaching auxiliary data filed to original data for
tracing how the data has been constructed.
All of a sudden the program runs out of memory or overflows
the stack.

One problem is that it comes up unexpectedly. Another even
worse problem is that sometimes I get no idea for the exact
location causing the leak!

It really panics facing such darkness of lazy evaluation.
Just a small innocent looking fix for inspection or tracing
blow things up, sometime with no clue for its reason.

When we implement a debugging or tracing option in the
software and let the user toggle those features, how could
we be sure that turning on those features won't crash the
software written in Haskell?

Are there standardized approaches for detecting and fixing
these kind of problems?

Haskell may be type safe but not safe at all from unexpanded
diversion, which is not because of the programmers' mistake
but just because of the laziness.


I have posted an wiki article including one example of adding
a counter to count the number of basic operations in sorting algorithm.

http://www.haskell.org/haskellwiki/Physical_equality

This was a rather simple situation and we figured out how to
cure this by self equality check ( x==x ) forcing evaluation.



There are worse cases not being able to figure out the cure.
I wrote a function for analyzing some property of a graph,
which worked fine.

fixOnBy t p f x = if t x' `p` t x then x else fixOnBy t p f x' where x' = f x

fixSize f x = fixOnBy Set.size (==) f x

sctAnal gs = null cgs || all (not . null) dcs
where
  gs' = fixSize compose $ Set.fromList [(x,y,cs) | To _ x y cs-Set.toList gs]
  cgs = [z | z@(x,y,cs)-Set.toList gs', x==y]
  dcs = [ [c| c@(a,D,b)-Set.toList cs , a==b] | (_,_,cs)-cgs]
  compose gs = trace (## ++show (Set.size gs)) $ foldr Set.insert gs $ do
(x1,y1,cs1) - Set.toList gs
(_,y2,cs2)  -  takeWhileFst y1 $ Set.toList $ setGT
(y1,Al(-1),Set.empty) gs
return (x1,y2,cs1 `comp` cs2)
  takeWhileFst y = takeWhile (\(y',_,_) - y==y')

This function makes a transitive closure of the given set of relations
by fixpoint iteration on the size of the set of weighted edges.

Sample output is like this.

*Main main
## 170
## 400
## 1167
## 2249
## 2314
False


When I add an extra data field for tracing how the new relation was
constructed, (e.g. tag [a,b,c] on a-c if it came from a-b and b-c)
it suddenly overflows the stack even before printing out the trace.
The following is the code that leaks memory.

sctAnal gs = null cgs || all (not . null) dcs
where
  gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y
cs-Set.toList gs]
  cgs = [z | z@(TT (x,y,cs) _)-Set.toList gs', x==y]
  dcs = [[c| c@(a,D,b)-Set.toList cs , a==b] | TT (_,_,cs) _-cgs]
  compose gs = trace (## ++show (Set.size gs)) $ foldr checkInsert gs $ do
TT (x1,y1,cs1) l1 - Set.toList gs
TT (_,y2,cs2) l2 - takeWhileTTfrom y1 . Set.toList $ setGT (TT
(y1,Al(-1),Set.empty) []) gs
return $ TT (x1,y2,cs1 `comp` cs2) (l1++y1:l2)
  takeWhileTTfrom y = takeWhile (\(TT (y',_,_) _) - y==y')
  checkInsert x s
  | Set.member x s = s
  | otherwise  = Set.insert x s

data TT a b = TT a b deriving (Show)
instance (Eq a, Eq b) = Eq (TT a b) where
 (TT x lx) == (TT y ly) = lx==lx  ly==ly  x == y
instance (Ord a, Ord b) = Ord (TT a b) where
 (TT x lx)  (TT y ly) = lx==lx  ly==ly  x  y


The really intersting thing happens when I just make the Ord derived
the stack does not overflow and starts to print out the trace.
(It is not the result that I want though. My intention is to ignore the
tags in the set operation)

data TT a b = TT a b deriving (Show,Eq,Ord)

I believe my Eq and Ord instances defined above are even more
stricter than the derived ones. Is there some magic in deriving
that prevents memory leak?

I've even followed the instance declaration like the following
that would be the same as deriving but still leaks memory.

data TT a b = TT a b deriving (Show)
instance (Eq a, Eq b) = Eq (TT a b) where
 (TT x lx) == (TT y 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


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

2006-08-07 Thread Ahn, Ki Yung

On 8/7/06, Spencer Janssen [EMAIL PROTECTED] wrote:


Forcing evaluation using (==) is a bit of a hack.  Luckily, we have a
better function to force evaluation: seq (which has type a - b - b).
 seq x y evaluates x to weak head normal form before returning
y.

Let's try another feature of Haskell to force evaluation: strict data
fields.  A ! in front of a field in a data declaration signifies
strictness.  In the example below, whenever we construct a value with
TT, the second argument is evaluated.

\begin{code}
data TT a b = TT a !b
\end{code}

Perhaps your instances will work correctly with this data declaration?


Surely I've tried that.

Unfortunately seq and the strict data declaration is not helpful in general.
They are only helpful on base values such as Int or Bool.
What they do is just making sure that it is not a thunk.
That is if it was a list it would just evaluate to see the cons cell
but no further.

Someone wrote a deepSeq module for forcing deep evaluation, which is
like doing self equality strictness hack like x==x.
However, we should be able to locate what is the source of the memory
leak to apply such strictness tricks.
I've tried plugging in x==x like hack almost everywhere I could but
still hard to find the right hack.


I think this is one of the most frustrating drawbacks developing
software in lazy languages like Haskell.
I am a fan of lazy langnauge; I like laziness and infinite data
structures and clean semantics.
But this is really painful. We 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-cafe


[Haskell-cafe] Edison StandardSet has inefficient function implementation

2006-08-03 Thread Ahn, Ki Yung

Edision does not yet have all the asymtotic description of its functions.
I got the Edision 1.2 source and looked into the code whether the
container implementations meet the expected asymtotic bounds.

In the module Data.Coll.StandardSet which packages Data.Set,
some functions which can be O(log n) is implemented as O(n).

Data.Set has a split and splitMember running in O(log n).
With those functions we can implement OrdCollX operations like
filterLT, filterLE, filterGT, filterGE,
partitionLT_GE, partitionLE_GT, partitionLT_GT all in O(log n).
However, only partitionLT_GT was O(log n) 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-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 about web server implementation in Haskell.

This tutorial consists of two famous examples, Echo and Chat,
with the source code and makefile to be downloaded, compliled and tested
right away.

I hope this could be some helpt to those who want to start server
programming in Haskell.

Server programming in modern fucntional language with concurrency support
is a real pleasure! You should also try Erlang if you havnt' tried yet.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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{code}

This is my answer for the question of my own,

which is posted a couple
  

of days before.

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



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
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{code}

This is my 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


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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 elements').
I'd expect the definition of findM to be:

findM'  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM' f [] = return Nothing
findM' f (x:xs) = do { b - f x; if b then return (Just x) else findM' f xs }

This one doesn't serve your purpose though.
J.A.
  


I appreciate your comment.
I agree that the type of findM should be the one you suggested,
and it still fits my original purpose. It's no more than a step arout.

\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) (hCat stdin)
where hCat h = try (hGetLine h=putStrLn) : hCat h

\end{code}

I expetct the next Haskell Library Report includes findM.
It's obviously useful.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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) (hPutCharS stdout)
where
hGetCharS h = hGetChar h : hGetCharS h
hPutCharS h = hPutChar h : hPutCharS h

\end{code}

Joining input list and output list by uncurried =
IO errors such as EOF are enclosed by try.
findM finds those EOF or IO errors.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



1 line simple cat in Haskell

2002-11-12 Thread Ahn Ki-yung
If you are steaming with compicated codes, then how about taking a break.
Let's play with a simple cat.

\begin{code}

main = mapM (=putChar) getCharS where getCharS = getChar:getCharS

\end{code}

Tested with ghc.
Works good except that you get some messages on stderror
because eof is not handled.

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-yung


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



[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
References: [EMAIL PROTECTED]

On Sat, 19 Jan 2002 10:14:22 +0900, =?EUC-KR?B?vsix4r+1?=
[EMAIL PROTECTED]
wrote:

 What does ML struct/functor have anything better than type classes ? 
 For the user type classes feels like implicit functor istantiations
 to specific sturucture, and struct/functor seems just bugglling the
 user to do more typing which can be automated by using type classes.

The advantage of functors shows up when you need to have multiple
implementations of a module for a type. For instance, suppose you
want to implement a set, and you write the functors (OCaml below):

  module type EQ =
sig
  type t
  val eq : t - t - bool
end

  module type SET =
sig
  type elt
  type set

  val empty : set
  val add : elt - set - set
  val mem : elt - set - bool
end

  module Set(Eq : EQ) : SET with type elt = Eq.t = 
struct
  type elt = Eq.t
  type set = elt list
  
  let empty = []
  
  let add elt set = elt :: set
  
  let rec mem elt set =
match set with
|   [] - false
|   x :: xs - if Eq.eq x elt then true else mem elt xs
end 

Now, suppose you want two kinds of sets of string, one of which is
case-sensitive and one of which is not. You can easily do this with
functors like so

  module SensitiveCase =
struct
  type t = string
  let eq s s' = (s = s')
end

  module InsensitiveCase =
struct
  type t = string
  let eq s s' = (String.lowercase s) = (String.lowercase s')
end

  module SensitiveSet = Set(SensitiveCase)  
  module InsensitiveSet = Set(InsensitiveCase)

Each of these Set types takes a string, but the membership test is
different. This is an annoying case in Haskell, because you can make a
String a member of the Eq typeclass in only one way.

However, I think it's true that typeclasses are less verbose in the
common case. Personally, I want a language with both typeclasses and
functors, so that I can use either as the problem requires.


Neel

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe