[Haskell-cafe] PhD student on Real-life datatype-generic programming

2007-06-13 Thread Johan Jeuring

===
Vacancy PhD student on Real-life datatype-generic programming
Software Technology,
Utrecht University,
The Netherlands.
===

Within the Software Technology group of the Information and Computing  
Sciences department of Utrecht University there is a vacancy for a  
PhD student to work on Real-life datatype-generic programming. The  
position is funded by NWO, the Netherlands Organisation for  
Scientific Research.


 
-

Project summary:

Datatype-generic programming has been around for more than 10 years  
now. We think a lot of progress has been made in the last decade. As  
an example, there are more than 10 proposals for generic-programming  
libraries or language extensions just for the lazy functional- 
programming language Haskell.


Although generic programming has been applied in several  
applications, it lacks users for real-life projects. This is  
understandable. Developing a large application takes a couple of  
years, and choosing a particular approach to generic programming for  
such a project involves a risk. Few approaches that have been  
developed over the last decade are still supported, and there is a  
high risk that the chosen approach will not be supported anymore, or  
that it will change in a backwards-incompatible way in a couple of  
years time.


We propose to create an environment that supports developing real- 
life applications using generic-programming techniques. We will focus  
on developing:
- a library or a mixture of a library with a language extension for  
which we will guarantee continuing support.
- an example of a real-life application fundamentally using generic- 
programming techniques. This application will serve as a showcase for  
generic-programming support for software development and evolution.
- generic-programming design patterns. The usage of the generic- 
programming techniques in real-life projects will exhibit recurrent  
patterns, and will give valuable advice for and help with developing  
other applications using generic-programming techniques.


Thus we will show how generic programming can be used to develop  
powerful tools in little time, and that the resulting tools are easy  
to maintain, adapt, and reuse.
 
-


Requirements: Master degree in Computer Science, or equivalent. Good  
knowledge of functional programming, and several advanced computer  
science techniques. Knowledge of Haskell, parsing, rewriting,  
strategies, generic programming, etc. will be useful.


Terms of employment: the PhD student should start as soon as  
possible, but no later than January 1, 2008.  The position is for  
four years (after one year there will be an evaluation), full-time.  
Gross salary starts with € 1956,-- per month in the first year and  
increases to € 2502,-- in the fourth year of employment.  The salary  
is supplemented with a holiday bonus of 8% and an end-of-year bonus  
of 3%.  In addition we offer: a pension scheme, partially paid  
parental leave, facilities for child care, flexible employment  
conditions in which you may trade salary for vacation days or vice  
versa. Conditions are based on the Collective Employment Agreement of  
the Dutch Universities.


More information about the project can be found on http:// 
www.cs.uu.nl/~johanj/publications/nwo-ew2006.pdf


More information about the Software Technology group on http:// 
www.cs.uu.nl/wiki/Center


More information about the Information and Computing Sciences  
department on http://www.cs.uu.nl/


More information about this vacancy can be obtained from Johan  
Jeuring ([EMAIL PROTECTED], http://www.cs.uu.nl/~johanj/,  +31 6  
40010053).


Send your application in pdf (or another non-proprietary format)  to

[EMAIL PROTECTED]   

with a cc to [EMAIL PROTECTED]

on or before July 31, 2007. We expect to arrange interviews in  
September.


Mention vacancy nr 62712.





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


Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Janis Voigtlaender

L.Guo wrote:

Hi all:

I already have one matrix of type [[a]] to store one image.

What I want to do is to devide the image into severial small blocks in same 
size.


In the sense of dividing an image like

abcd
efgh
ijkl
mnop

into the sequence of images

[
ab
ef
,
cd
gh
,
ij
mn
,
kl
op
]

when the block size is 2?


To do that, I wrote this tool function.

chop  :: Int - [a] - [[a]]
chop _ [] = []
chop n ls = take n ls : chop n (drop n ls)

But I do not know how to use it to write the function.


Hmm, if you have no idea how chop could help you to write your
divide function, what was your motivation for writing chop in the
first place?

Could it be that the following applies:

http://www.haskell.org/haskellwiki/Homework_help ?

If the problem you are trying to solve corresponds to my example above,
it might get you started to think about what you can do by combining tow
applications of chop with two applications of map.

Ciao,
Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Janis Voigtlaender

Henning Thielemann wrote:

On Wed, 13 Jun 2007, L.Guo wrote:



I already have one matrix of type [[a]] to store one image.

What I want to do is to devide the image into severial small blocks in same 
size.

To do that, I wrote this tool function.

chop  :: Int - [a] - [[a]]
chop _ [] = []
chop n ls = take n ls : chop n (drop n ls)



I assume that it is more efficient to use 'splitAt' instead of 'take' and
'drop'.



But I do not know how to use it to write the function.



chop blockHeight (map (chop blockWidth) image)


That would divide

abcd
efgh
ijkl
mnop

into

[
[
ab
cd
,
ef
gh
]
,
[
ij
kl
,
mn
op
]
]

at block size 2. In any case, the original poster was not very clear
about what they want...

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Henning Thielemann

On Wed, 13 Jun 2007, L.Guo wrote:

 I already have one matrix of type [[a]] to store one image.

 What I want to do is to devide the image into severial small blocks in same 
 size.

 To do that, I wrote this tool function.

 chop  :: Int - [a] - [[a]]
 chop _ [] = []
 chop n ls = take n ls : chop n (drop n ls)

I assume that it is more efficient to use 'splitAt' instead of 'take' and
'drop'.

 But I do not know how to use it to write the function.

chop blockHeight (map (chop blockWidth) image)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ANNOUNCE: Harpy -- run-time code generation library

2007-06-13 Thread Martin Grabmueller
[Moved to haskell-cafe]

Daniel Mahler schrieb:
 Given your reservation regarding LLVM,
 you may be interested in vmgen, developed and used as a part of  gforth.
 It is also claimed that a JVM built with vmgen had performance comparable
 to state of the art JITs.
 If I remember the author of both gforth (including vmgen) and the
 experimantal JVM,
 is Anton Ertl.
 Personally I have never used it, and do not know how good it is,
 so I am not trying to push it.

[...]

 Anyway as I said, I do not know how much mileage you could get out of it,
 but it seemed to be worth mentioning, given what you said about LLVM.

Thanks for the pointer to vmgen.  From a brief look at the docs and the source
code, though, it seems that it supports the generation of threaded interpreters
(which are efficient, but not as efficient as real native code) only,
whereas we are interested in real code generation.

Greetings,
  Martin




signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
Andrew Coppin wrote:
 I'm trying to construct a function
 
  all_trees :: [Int] - [Tree]
 
 such that all_trees [1,2,3] will yield
 
 [
 Leaf 1,
 Leaf 2,
 Leaf 3,
 Branch (Leaf 1) (Leaf 2),
 Branch (Leaf 1) (Leaf 3),
 Branch (Leaf 2) (Leaf 1),
 Branch (Leaf 2) (Leaf 3),
 Branch (Leaf 3) (Leaf 1),
 Branch (Leaf 3) (Leaf 2),
 Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),
 Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),
 Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
 Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),
 Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),
 Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),
 Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),
 Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
 Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),
 Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),
 Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),
 Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
 ]

Here's a way to do this.

First, some imports and the definition of Tree.

import Data.List
import Control.Applicative
import qualified Data.Foldable as Foldable
import Data.Traversable as Traversable
import Control.Monad.State

data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show)

Let's assume that someone has given us a function

 trees :: a - [Tree a]

that builds a list of all possible trees whose leaves are all equal to
(Leaf x) where x is the argument given. In other words,

 trees 1 = [
Leaf 1
  , Branch (Leaf 1) (Leaf 1)
  , Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1))
  , Branch (Branch (Leaf 1) (Leaf 1)) (Leaf 1)
  , Branch (Leaf 1) (Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1)))
  , ... ]

Is this of any use? It is, the idea is to not put single elements into
the leaves, but something more clever. For instance, we can put the list
itself into the leaves

 trees [1,2,3] :: [Tree [Int]]

Now, we can view the inner list as a monad. Thus, we have a tree of
nondeterministic values but want to have a nondeterministic tree. Can we
flatten it somehow?

 ? :: Tree [a] - [Tree a]

Indeed we can, for this is nothing more than a generalization of the
well-known

 sequence :: Monad m = [m a] - m [a]

from lists to trees:

 sequence :: Monad m = Tree (m a) - m (Tree a)

Setting  m a = [a]  then gives the desired

 sequence :: Tree [a] - [Tree a]

In fact, the generalization works for many types and the pattern behind
is captured by applicative functors and Data.Traversable.

instance Traversable Tree where
traverse f (Leaf a) = Leaf $ f a
traverse f (Branch x y) =
   Branch $ traverse f x * traverse f y

instance Functor Tree where
fmap = fmapDefault

instance Foldable.Foldable Tree where
foldMap = foldMapDefault

Explaining how this works exactly would explode this mail, but the
haddocks for Data.Traversable are a good start to learn more. What
counts is that we now have

 Traversable.sequence :: Monad m = Tree (m a) - m (Tree a)

for free and we can formulate our idea

-- all possible trees whose leaves are from the given list
mutlisetTrees :: [a] - [Tree a]
mutlisetTrees xs = concatMap Traversable.sequence $ trees xs

This gives

 mutlisetTrees [1,2,3] = [
Leaf 1
  , Leaf 2
  , Leaf 3
  , Branch (Leaf 1) (Leaf 1)
  , Branch (Leaf 1) (Leaf 2)
  , Branch (Leaf 1) (Leaf 3)
  , Branch (Leaf 2) (Leaf 1)
  , Branch (Leaf 2) (Leaf 2)
  , Branch (Leaf 2) (Leaf 3)
  , Branch (Leaf 3) (Leaf 1)
  , Branch (Leaf 3) (Leaf 2)
  , Branch (Leaf 3) (Leaf 3)
  , Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1))
  , ...]

A good try, but this gives all combinations of elements from [1,2,3].
This was to be expected, because

   do
x - [1,2,3]
y - [1,2,3]
return (x,y)

analogously gives all pairs [(1,1),(1,2),(1,3),(2,1),...].

How to make permutations out of this? The idea is to incorporate state
into our monad, namely the list of elements not yet used. Every time we
generate a new nondeterministic value, we choose it from this list and
supply all subsequent monadic action a list where this value is removed.
 Here's the code:

-- all possible trees whose leaves are
-- a permutation of the given list
permTrees :: [a] - [Tree a]
permTrees xs = concat . takeWhile (not . null) . map
(flip evalStateT xs . Traversable.sequence) $ trees select
where
select = StateT $ \xs -
[(z,ys++zs) | (ys,z:zs) - zip (inits xs) (tails xs)]

all_trees = permTrees

Instead of putting [1,2,3] into the leaves of our trees, we put a
monadic action called select in there. We can put state on top of the
list monad with the StateT monad transformer so that select has the type

 select :: StateT [a] [] a



Now, all that remains is to implement  trees. For that, we note that a
tree with n leaves always has the form

 n leaves = Branch (k leaves) (n-k leaves)

for some k. This reminds us of the multiplication of power series and
hints that we should build a list

 trees = [1 leaves, 2 leaves, 3 leaves, 4 leaves, ...]

which is 

[Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bulat Ziganshin
Hello Malcolm,

Wednesday, June 13, 2007, 1:55:43 PM, you wrote:
 In addition, we are in the process of setting up a separate server called
 code.haskell.org

thank you, it's all are great news. some questions:

when you plan to make code.haskell.org available?

is its funding will be reliable? for example, if we don't get money
from Google in 2008 year?

i hope that this server will be established as comfortable place for
collective work, including wiki, bug tracker, darcs, so on, so on


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Malcolm Wallace
  In addition, we are in the process of setting up a separate server
  called
  code.haskell.org
 
 when you plan to make code.haskell.org available?

When it is ready.  Wait for further announcements.

 is its funding will be reliable? for example, if we don't get money
 from Google in 2008 year?

No funding source is ever secure.  With existing and promised money, we
have enough to keep *.haskell.org running for at least a couple of years
into the future.  If that ever dries up, then the community will have to
think of something else.

 i hope that this server will be established as comfortable place for
 collective work, including wiki, bug tracker, darcs, so on, so on

That is the plan.

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


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Mirko Rahn

Andrew Coppin wrote:


such that all_trees [1,2,3] will yield



[
Leaf 1,
Leaf 2,
Leaf 3,
Branch (Leaf 1) (Leaf 2),
Branch (Leaf 1) (Leaf 3),
Branch (Leaf 2) (Leaf 1),
Branch (Leaf 2) (Leaf 3),
Branch (Leaf 3) (Leaf 1),
Branch (Leaf 3) (Leaf 2),
Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),
Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),
Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),
Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),
Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),
Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
]


Just another way (assuming the given order is not relevant), based on 
the idea that it is quite easy to insert a new node on all possible 
positions in an already existing tree.


data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show

decomp (Branch l r) = [(l,flip Branch r),(r,Branch l)]
decomp _= []

insert x t = Branch x t
   : Branch t x
   : [re b | (part,re) - decomp t, b - insert x part]

all_trees [] = []
all_trees (x:xs) =
let this = Leaf x
more = all_trees xs
in this : more ++ concatMap (insert this) more

/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Construct all possible trees

2007-06-13 Thread Tom Pledger

*Andrew Coppin wrote:
*

| I'm trying to construct a function
| 
|   all_trees :: [Int] - [Tree]
| 
| such that all_trees [1,2,3] will yield

:

If you write a helper function that takes an N element list, and returns 
all 2^N ways of dividing those elements into 2 lists, e.g.


   splits ab -- [(ab,),(b,a),(a,b),(,ab)]

then you can use it both for dividing the initial list into kept and 
discarded elements, and for dividing a list between a left subtree and a 
right subtree.


Regards,
Tom

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


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Henning Thielemann

On Thu, 14 Jun 2007, Tom Pledger wrote:

 *Andrew Coppin wrote:
 *

  | I'm trying to construct a function
  |
  |   all_trees :: [Int] - [Tree]
  |
  | such that all_trees [1,2,3] will yield
  :

 If you write a helper function that takes an N element list, and returns
 all 2^N ways of dividing those elements into 2 lists, e.g.

 splits ab -- [(ab,),(b,a),(a,b),(,ab)]

 then you can use it both for dividing the initial list into kept and
 discarded elements, and for dividing a list between a left subtree and a
 right subtree.

This one was discussed recently:
 http://www.haskell.org/pipermail/haskell-cafe/2007-May/025767.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Mirko Rahn


apfelmus wrote:

Explanation and the code:


import Data.List
import Control.Applicative
import qualified Data.Foldable as Foldable
import Data.Traversable as Traversable
import Control.Monad.State

data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show)



instance Traversable Tree where
traverse f (Leaf a) = Leaf $ f a
traverse f (Branch x y) =
   Branch $ traverse f x * traverse f y

instance Functor Tree where
fmap = fmapDefault

instance Foldable.Foldable Tree where
foldMap = foldMapDefault



permTrees xs = concat . takeWhile (not . null) . map
(flip evalStateT xs . Traversable.sequence) $ trees select
where
select = StateT $ \xs -
[(z,ys++zs) | (ys,z:zs) - zip (inits xs) (tails xs)]



trees x = ts
where ts = concat $ ([Leaf x] :) $ convolution Branch ts ts



convolution f xs ys = tail $
zipWith (zipWith f) (inits' xs) $ scanl (flip (:)) [] ys



inits' xs = []:case xs of
[] - []
(x:xs) - map (x:) $ inits' xs


But something is wrong here. Unfortunately, I cannot say what, but for 
example the following trees are missing in permTrees [1,2,3,4]:


Branch (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)) (Leaf 4)
Branch (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 4)) (Leaf 3)
Branch (Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 2)) (Leaf 4)
Branch (Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 4)) (Leaf 2)
Branch (Branch (Branch (Leaf 1) (Leaf 4)) (Leaf 2)) (Leaf 3)
Branch (Branch (Branch (Leaf 1) (Leaf 4)) (Leaf 3)) (Leaf 2)
Branch (Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3)) (Leaf 4)
Branch (Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 4)) (Leaf 3)
Branch (Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1)) (Leaf 4)
Branch (Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 4)) (Leaf 1)
Branch (Branch (Branch (Leaf 2) (Leaf 4)) (Leaf 1)) (Leaf 3)
Branch (Branch (Branch (Leaf 2) (Leaf 4)) (Leaf 3)) (Leaf 1)
Branch (Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2)) (Leaf 4)
Branch (Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 4)) (Leaf 2)
Branch (Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1)) (Leaf 4)
Branch (Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 4)) (Leaf 1)
Branch (Branch (Branch (Leaf 3) (Leaf 4)) (Leaf 1)) (Leaf 2)
Branch (Branch (Branch (Leaf 3) (Leaf 4)) (Leaf 2)) (Leaf 1)
Branch (Branch (Branch (Leaf 4) (Leaf 1)) (Leaf 2)) (Leaf 3)
Branch (Branch (Branch (Leaf 4) (Leaf 1)) (Leaf 3)) (Leaf 2)
Branch (Branch (Branch (Leaf 4) (Leaf 2)) (Leaf 1)) (Leaf 3)
Branch (Branch (Branch (Leaf 4) (Leaf 2)) (Leaf 3)) (Leaf 1)
Branch (Branch (Branch (Leaf 4) (Leaf 3)) (Leaf 1)) (Leaf 2)
Branch (Branch (Branch (Leaf 4) (Leaf 3)) (Leaf 2)) (Leaf 1)

One could guess it has something to do with the special structure of the 
missing trees, but at one hand permTrees [1,2,3] gives all trees and at 
the other in permTrees [1,2,3,4,5] are also other structures missing, like


Branch (Leaf 3) (Branch (Branch (Leaf 2) (Leaf 1)) (Branch (Leaf 4) 
(Leaf 5)))


So please, what's going on here?

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Redefining Disjunction

2007-06-13 Thread PR Stanley

Hi
Can you think of a fourth way of redefining disjunct using pattern matching?
vee :: Bool - Bool - Bool
vee _ True = True
vee True _ = True
vee _ _ = False

ve :: Bool - Bool - Bool
ve True True = True
ve True False = True
ve False True = True
ve False False = False

v :: Bool - Bool - Bool
v True b = True
v b True = True
v b False = b
v False b = b

Thanks
Paul

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


Re: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Chris Mears
PR Stanley [EMAIL PROTECTED] writes:

 Hi
 Can you think of a fourth way of redefining disjunct using pattern matching?
 vee :: Bool - Bool - Bool
 vee _ True = True
 vee True _ = True
 vee _ _ = False

In the same spirit:

f False False = False
f _ _ = True
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Bayley, Alistair
 [mailto:[EMAIL PROTECTED] On Behalf Of PR Stanley
 
 Hi
 Can you think of a fourth way of redefining disjunct using 
 pattern matching?
 vee :: Bool - Bool - Bool
 vee _ True = True
 vee True _ = True
 vee _ _ = False

How many ways do you want? I think this is correct, and is only strict
in the first arg:

v :: Bool - Bool - Bool
v True _ = True
v False b = b

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Ilya Tsindlekht
On Wed, Jun 13, 2007 at 02:37:37PM +0100, PR Stanley wrote:
 Hi
 Can you think of a fourth way of redefining disjunct using pattern matching?
 vee :: Bool - Bool - Bool
 vee _ True = True
 vee True _ = True
 vee _ _ = False
 
 ve :: Bool - Bool - Bool
 ve True True = True
 ve True False = True
 ve False True = True
 ve False False = False
 
 v :: Bool - Bool - Bool
 v True b = True
 v b True = True
 v b False = b
 v False b = b
 
Most obvious is
v :: Bool-Bool-Bool
v False False = False
v _ _ = True
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
Mirko Rahn wrote:
 apfelmus wrote:

 data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show)
 
 permTrees xs = concat . takeWhile (not . null) . map
 (flip evalStateT xs . Traversable.sequence) $ trees select
 where
 select = StateT $ \xs -
 [(z,ys++zs) | (ys,z:zs) - zip (inits xs) (tails xs)]
 
 trees x = ts
 where ts = concat $ ([Leaf x] :) $ convolution Branch ts ts
 
 But something is wrong here. Unfortunately, I cannot say what, but for
 example the following trees are missing in permTrees [1,2,3,4]:

 Branch (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)) (Leaf 4)
 [...]

 So please, what's going on here?

Tricky, tricky :) It turns out that the function trees which generates
all possible tree shapes doesn't miss any shape but it doesn't generate
them ordered by tree size:

 ghci mapM_ print $ take 11 $ trees 1
 Leaf 1
 Branch (Leaf 1) (Leaf 1)
 Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1))
 Branch (Branch (Leaf 1) (Leaf 1)) (Leaf 1)
 Branch (Leaf 1) (Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1)))
 Branch (Branch (Leaf 1) (Leaf 1)) (Branch (Leaf 1) (Leaf 1))
 Branch (Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1))) (Leaf 1)
 Branch (Leaf 1) (Branch (Branch (Leaf 1) (Leaf 1)) (Leaf 1))
 Branch (Branch (Leaf 1) (Leaf 1))
(Branch (Leaf 1) (Branch (Leaf 1)  (Leaf 1)))
 Branch (Branch (Leaf 1) (Branch (Leaf 1) (Leaf 1)))
(Branch (Leaf 1) (Leaf 1))
 Branch (Branch (Branch (Leaf 1) (Leaf 1)) (Leaf 1)) (Leaf 1)

The missing tree with 4 leaves appears after one with 5 leaves but
permTerms stops searching as soon as it encounters a tree shape that
doesn't has more leaves than possible elements to permute.

Actually, the definition of trees is not what I originally intended,
it's equivalent to Jon Fairbairn's fair product. My original intention was

  trees x = concat ts
where ts = [Leaf x] : map concat (convolution (liftM2 Branch) ts ts)

Here, (ts !! (k-1)) is to contain a list of all trees with exactly k
leaves. The nature of convolution makes it clear that (ts) doesn't hang,
that it doesn't miss a tree and that it it doesn't contain duplicate
trees. Moreover, it generates all trees ordered by size and permTrees
works :)


Nevertheless, the fair product approach

  trees x = ts
where ts = Leaf x : map (uncurry Branch) (ts  ts)

seems to generate each possible shape exactly once (although not ordered
by size). But how to proof that?

The extremal principle comes to rescue. Assuming that the function does
not hang (no _|_ inside®), we can prove that it doesn't miss and
doesn't duplicate trees:

- Assume that trees are missing from the list. Among those, choose the
one with the least height. If this tree t is a (Leaf a), it's in the
list, contradiction. If it's a (Branch x y), x and y must be in the list
or one of them would have a smaller height than t. But then, (x,y)
appears in the fair product and (Branch x y) is in the list, contradiction.

- Assume that there is a duplicate, i.e. there are
  t  = Branch x  y
  t' = Branch x' y'
with x = x' and y = y' in the list. Choose the very first duplicate,
i.e. such that t is the first ever duplicated tree in the list. But
since the list doesn't hang, x and y must come before t in the list. But
x and x' are already duplicates themselves which contradicts the fact
that t is the first.


As a last note, the given definition of convolution is no good for
finite lists (i.e. multiplication of polynomials). It should actually be

convolution (*) [x1,x2] [y1,y2]
 == [[x1*y1],[x1*y2, x2*y1],[x2*y2]]

The fair product can be adapted to implement this.


Regards,
apfelmus

PS:
 PPS: A naive parsing algorithm is not as efficient as it could
 be because parses from different permutations can be reused for
 parsing larger ones. Note that the same observation carries over
 to the algorithm presented here, and I'm not sure,
 but I think it does the sharing.

Now, I'm quite sure that it does not share because select may be
called multiple times with the same argument (i.e. equal
sub-permutations) and this of course means that things get recalculated.

Note that Mirko's algorithm does proper sharing of sub-permutations.

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


[Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein

Hi all,

We've had a discussion on #haskell about how we can make a function
that reads in serialized values of an open data type, such as

class (Show a, Read a) = MyClass a where
   typeTag :: a - String
   ... operations on the open data type...

data Obj = forall a. MyClass a = Obj { unObj :: a }

We would like to write a function like,

oread :: String - Obj

The problem here is that unlike with 'read,' the calling context of
'oread' does not fix the implementation of Read that we want to use.
The best we've been able to come up with was to build a table that
maps type names to types:

type TypeTable = Map String Obj

oread :: TypeTable - String - Obj
oread types s = Obj $ read repr `asTypeOf` unObj (types ! tag) where
   tag = takeWhile (/= ' ') s
   repr = drop 1 $ dropWhile (/= ' ') s

instance Show Obj where
   show (Obj x) = typeTag x ++   ++ show x

As far as we can see, we'll have to create this table manually,
without support from the compiler. My suggestion would be to put the
code constructing the table for each module at the top of that module,
to keep it together with the exports and imports, like this:

module Foo.Foo (export1, export2, fooFooTypes) where

import Foo.Bar
import Foo.Baz
import Data.Map

fooFooTypes = fooBarTypes `union` fooBazTypes `union` fromList
   [ (Foo.Foo.Ty1, Obj (undefined :: Ty1))
   , (Foo.Foo.Ty2, Obj (undefined :: Ty2)) ]

However, this is still kind of boring. Is there a better way? If not,
would it be a good idea to have compiler support for building this
kind of type table?

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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Benja Fallenstein wrote:
 Hi all,
 
 We've had a discussion on #haskell about how we can make a function
 that reads in serialized values of an open data type, such as
 
 [...]
 However, this is still kind of boring. Is there a better way? If not,
 would it be a good idea to have compiler support for building this
 kind of type table?

Since Show instances can overlap (e.g. (show (1::Int)) == (show
(1::Integer))), we need to tag with the type.  Reminds me of Typeable.
Since GHC lets us derive Typeable with a guarantee of different types
being distinct (at least for a single compile-and-run session...), maybe
that can be leveraged somehow? (I see that was sort of mentioned in the
IRC discussion)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGcAyNHgcxvIWYTTURAlI5AKC8bdbK/oL+B3Btlox9hfP4Lga1GwCgliZu
Vi+be1mSEZnsoSAm3VgNaHo=
=1x5R
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread brad clawsie
 is its funding will be reliable? for example, if we don't get money
 from Google in 2008 year?

in irc some time ago i brought up the topic of something like the
freebsd or wikimedia foundations, but for haskell. if you can give me
a secure and trustworthy method of payment, and as a bonus, a tax
receipt (what is known as 501-c-3 status in the US), i will gladly
start writing checks on a yearly basis. i am sure others would join
me. 

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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein

Hi Isaac,

2007/6/13, Isaac Dupree [EMAIL PROTECTED]:

Since Show instances can overlap (e.g. (show (1::Int)) == (show
(1::Integer))), we need to tag with the type.


Indeed. But that's the easy part :-)


Reminds me of Typeable.
Since GHC lets us derive Typeable with a guarantee of different types
being distinct (at least for a single compile-and-run session...), maybe
that can be leveraged somehow?


We can perhaps use it to go from the type to the type tag, but as far
as I understand we can not, unfortunately, use it to go from the type
tag to the type. (We *may* be able to use the TypeRep as the key of
the map I proposed in my earlier mail, but we can't use it to replace
the map, afaiu.)

The problem is that, in the type system, a TypeRep is not actually
associated with the type that it represents, nor is there (afaik) an
internal table that associates TypeReps with the types they represent.

In Data.Generics, there are some functions that let you take a
DataTypeRep and use it to create a value of the corresponding type.
However, the code doesn't use the DataTypeRep to get the type. The
relevant function looks like this:

fromConstr :: Data a = Constr - a

Like 'read' gets the 'Read' instance, this gets the 'Data' instance
from its return type (you have to call it in a context that constrains
the return type). So, you can *not* use it to write a function like
this:

data D = forall a. Data a = D a
fromConstrD :: Constr - D

because, in the type system, you wouldn't be able to use the Constr to
get the Data instance corresponding to the Constr's TypeRep.

Hope that makes sense ... I'm not explaining it too well :-/

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


Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bryan Burgers

 is its funding will be reliable? for example, if we don't get money
 from Google in 2008 year?

in irc some time ago i brought up the topic of something like the
freebsd or wikimedia foundations, but for haskell. if you can give me
a secure and trustworthy method of payment, and as a bonus, a tax
receipt (what is known as 501-c-3 status in the US), i will gladly
start writing checks on a yearly basis. i am sure others would join
me.


Similarly, the Perl community has a foundation, and I believe giving
to it is tax-deductible. You could look in to how they do it.

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


Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Greg Fitzgerald

is its funding will be reliable? for example, if we don't get money from

Google in 2008 year?

Some hosting companies, like http://turtol.com/ offer pay once, keep
forever.  Would that be an option?

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


Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bryan O'Sullivan

Bryan Burgers wrote:


Similarly, the Perl community has a foundation, and I believe giving
to it is tax-deductible. You could look in to how they do it.


Setting up a 501(c)(3) foundation is a morass of paperwork.  If people 
within the US are interested in writing tax deductible cheques, a far 
less onerous thing to do would be to look at the Software Freedom 
Conservancy (http://conservancy.softwarefreedom.org/).  This offers many 
advantages not available to a small group, not least protection from 
personal liability for individual volunteer contributors.


I've worked before with the lawyers and administrators at the SFC and 
its parent organisation, the Software Freedom Law Center, and they are 
wonderful, motivated people.


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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Bulat Ziganshin
Hello Benja,

Wednesday, June 13, 2007, 6:12:25 PM, you wrote:

 We've had a discussion on #haskell about how we can make a function
 that reads in serialized values of an open data type, such as

look at Data.Generics.Text which may be implements exactly what you
need


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein

Hi Bulat,

2007/6/13, Bulat Ziganshin [EMAIL PROTECTED]:

 We've had a discussion on #haskell about how we can make a function
 that reads in serialized values of an open data type, such as

look at Data.Generics.Text which may be implements exactly what you
need


Unfortunately not. Data.Generics.Text provides

gread :: Data a = ReadS a

That is, you have to constrain its return type to the particular type
you want to read. What I'm looking for is a way to read any type
implementing a certain class (deciding the type to use based on a type
tag) and returning the result in an existential wrapper.

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


Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Andrew Coppin

Jon Fairbairn wrote:

I'm trying to construct a function

  all_trees :: [Int] - [Tree]

such that all_trees [1,2,3] will yield

[
Leaf 1,
Leaf 2,
Leaf 3,
Branch (Leaf 1) (Leaf 2),
Branch (Leaf 1) (Leaf 3),
Branch (Leaf 2) (Leaf 1),
Branch (Leaf 2) (Leaf 3),
Branch (Leaf 3) (Leaf 1),
Branch (Leaf 3) (Leaf 2),
Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),
Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),
Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),
Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),
Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),
Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
]



Why does it stop there? That's not all the trees, surely?


Really? OK, what other trees do *you* think you can construct from the 
numbers 1, 2 and 3?



Otherwise I'd suggest something like this:

  

module Main where



derive some classes for demo purposes

  

data Tree = Leaf Integer | Branch Tree Tree deriving (Show, Eq, Ord)



   A fair product (can't find one in the libraries):

  

as  bs
= strip 1 [[(a,b) | b -bs] | a - as]
  where
  strip n [] = []

  strip n ll = heads
   ++ strip (n+1) (tails ++ rest)
   where (first_n, rest) = splitAt n ll
 heads = [a | (a:_) - first_n]
 tails = [as | (_:as) - first_n]



   works by generating a list of lists representing the product
   matrix and then repeatedly stripping off the leading
   edge. I'm sure something like this must be in a library
   somewhere, but I couldn't find it in quick search. Once
   we've got that, all_trees is simple:

  

all_trees l
= at 
  where at = map Leaf l ++ map (uncurry Branch) (at  at)



... and mutter something about using bulk operations and
laziness.
  


I'll have to sit down and think about why that works... ;-)

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


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Andrew Coppin

Colin DeVilbiss wrote:

On 6/12/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Based on the sample output, I'm guessing that the desired output is
every tree which, when flattened, gives a permutation of a non-empty
subset of the supplied list.  This limits the output to trees with up
to n leaves.


Every possible tree, using the supplied elements as leaf elements, 
without ever duplicating them. (Note, however, that the initial list may 
contain duplicates in the first place, so you can't just test for and 
remove duplicates in the produced lists; you must avoid repeating 
elements by construction.)



Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),


If I'm guessing the desired output correctly, this must be a typo?


Erm... yes.


I'd be tempted to solve the list-only problem first (generate all
sub-permutations of a list), then solve the tree problem (generate
all un-flattenings of a list).


I can already create all possible 2-element trees. It seems like there 
should be a way to recurse that... but without duplicating elements.


Hmm, I don't know - there's probably several correct solutions to this 
problem. ;-)


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


Re: [Haskell-cafe] found monad in a comic

2007-06-13 Thread Andrew Coppin

Paul Johnson wrote:

Marc A. Ziegert wrote:

http://xkcd.com/c248.html
( join /= coreturn )

IMHO this could be a beautiful and easy way to explain monads.
comments?

  
I read it as a take on Godel Escher Bach, especially the stuff about 
counterfactual situations.  But you are right.  Actually its more 
about the recursive do notation and fixpoints: you can borrow data 
from the future as long as you are careful.  But yes, they are a form 
of monad.


...is everybody else looking at a different web page to me? *blinks*

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


[Haskell-cafe] ghc-pkg list says a package is installed, but ghci won't load its exposed module (HDBC-ODBC)

2007-06-13 Thread Thomas Hartman
ghc-pkg list says a package is installed, but ghci won't load its 
module (HDBC-ODBC) 
Any advice? 
[EMAIL PROTECTED] ~/haskellInstalls/HDBC-odbc-1.0.1.0 
$ ghc-pkg list 
c:/ghc/ghc-6.6.1\package.conf: 
Cabal-1.1.6.2, GLUT-2.1.1, HAppS-0.8.4, HDBC-1.0.1, 
HDBC-odbc-1.0.1.0, HUnit-1.1.1, HaXml-1.13.2, OpenGL-2.2.1, 
QuickCheck-1.0.1, Win32-2.1.1, base-2.1.1, cgi-3001.1.1, 
fgl-5.4.1, 
filepath-1.0, (ghc-6.6.1), haskell-src-1.0.1, haskell98-1.0, 
html-1.0.1, mtl-1.0.1, network-2.0.1, parsec-2.0, regex-base-0.72, 
regex-base-0.91, regex-compat-0.71, regex-posix-0.71, 
regex-tdfa-0.92, rts-1.0, stm-2.0, template-haskell-2.1, 
time-1.1.1, xhtml-3000.0.2 
. 
Prelude :m + Database.HDBC.ODBC 
module main:Database.HDBC.ODBC is not loaded 
. 
$ ghc-pkg.exe describe HDBC-odbc 
name: HDBC-odbc 
version: 1.0.1.0 
license: LGPL 
copyright: Copyright (c) 2005-2006 John Goerzen 
maintainer: John Goerzen [EMAIL PROTECTED] 
stability: Alpha 
homepage: 
package-url: 
description: 
category: 
author: 
exposed: True 
exposed-modules: Database.HDBC.ODBC 
hidden-modules: Database.HDBC.ODBC.Connection 
Database.HDBC.ODBC.Statement Database.HDBC.ODBC.Types 
Database.HDBC.ODBC.Utils Database.HDBC.ODBC.TypeConv 
import-dirs: C:\\Program Files\\Haskell\\HDBC-odbc-1.0.1.0\ 
\ghc-6.6.1 
library-dirs: C:\\Program Files\\Haskell\\HDBC-odbc-1.0.1.0\ 
\ghc-6.6.1 
hs-libraries: HSHDBC-odbc-1.0.1.0 
extra-libraries: odbc32 
extra-ghci-libraries: 
include-dirs: C:\\Program Files\\Haskell\\HDBC-odbc-1.0.1.0\ 
\ghc-6.6.1\\include 
 
includes: 
depends: base-2.1.1 mtl-1.0.1 HDBC-1.0.1 parsec-2.0 
hugs-options: 
cc-options: 
ld-options: 
framework-dirs: 
frameworks: 
haddock-interfaces: C:\\Program Files\\Common Files\\HDBC- 
odbc-1.0.1.0\\doc\\ht 
ml\\HDBC-odbc.haddock 
haddock-html: C:\\Program Files\\Common Files\\HDBC-odbc-1.0.1.0\\doc\ 
\html 

---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Lennart Augustsson

This doesn't enumerate them in the order you want, but maybe it doesn't
matter.

module Trees where

combinations :: [a] - [[a]]
combinations [] = [[]]
combinations (x:xs)
   = combinations xs ++ [ x:xs' | xs' - combinations xs ]

data Tree = Leaf Int | Branch Tree Tree
   deriving (Show)

trees [x] = [Leaf x]
trees (x:xs) = [ s | t - trees xs, s - insert x t ]

insert x t@(Leaf y) = [Branch s t, Branch t s]  where s = Leaf x
insert x (Branch l r) = [Branch l' r | l' - insert x l] ++
   [Branch l r' | r' - insert x r]

allTrees xs = [ t | ys - combinations xs, not (null ys), t - trees ys ]

 -- Lennart


On 6/12/07, Andrew Coppin [EMAIL PROTECTED] wrote:


I'm trying to construct a function

  all_trees :: [Int] - [Tree]

such that all_trees [1,2,3] will yield

[
Leaf 1,
Leaf 2,
Leaf 3,
Branch (Leaf 1) (Leaf 2),
Branch (Leaf 1) (Leaf 3),
Branch (Leaf 2) (Leaf 1),
Branch (Leaf 2) (Leaf 3),
Branch (Leaf 3) (Leaf 1),
Branch (Leaf 3) (Leaf 2),
Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),
Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),
Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),
Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),
Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),
Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),
Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),
Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
]



So far I'm not doing too well. Here's what I've got:

data Tree = Leaf Int | Branch Tree Tree

pick :: [x] - [(x,[x])]
pick = pick_from []

pick_from :: [x] - [x] - [(x,[x])]
pick_from ks [] = []
pick_from ks [x] = []
pick_from ks xs = (head xs, ks ++ tail xs) : pick_from (ks ++ [head xs])
(tail xs)

setup :: [Int] - [Tree]
setup = map Leaf

tree2 :: [Tree] - [Tree]
tree2 xs = do
  (x0,xs0) - pick xs
  (x1,xs1) - pick xs0
  return (Branch x0 x1)

all_trees ns = (setup ns) ++ (tree2 $ setup ns)

Clearly I need another layer of recursion here. (The input list is of
arbitrary length.) However, I need to somehow avoid creating duplicate
subtrees...

(BTW, I'm really impressed with how useful the list monad is for
constructing tree2...)

___
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] Re: Construct all possible trees

2007-06-13 Thread Jon Fairbairn
Andrew Coppin [EMAIL PROTECTED] writes:

 Jon Fairbairn wrote:
  I'm trying to construct a function
 
all_trees :: [Int] - [Tree]
 
  such that all_trees [1,2,3] will yield
 
  [
  Leaf 1,
  Leaf 2,
  Leaf 3,
  Branch (Leaf 1) (Leaf 2),
  Branch (Leaf 1) (Leaf 3),
  Branch (Leaf 2) (Leaf 1),
  Branch (Leaf 2) (Leaf 3),
  Branch (Leaf 3) (Leaf 1),
  Branch (Leaf 3) (Leaf 2),
  Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),
  Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),
  Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
  Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),
  Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),
  Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),
  Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),
  Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
  Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),
  Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),
  Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),
  Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
  ]
 
 
  Why does it stop there? That's not all the trees, surely?
 
 Really? OK, what other trees do *you* think you can
 construct from the numbers 1, 2 and 3?

Oh, you mean with each member of the list appearing at most
once? Why didn't you /say/ so? :-P


Trees with all the elements of a list in that order:

 the_trees:: [Integer] - [Tree]
 the_trees [x] = [Leaf x]
 the_trees l = zipWith Branch (concat (map the_trees (tail $ inits l)))
  (concat (map the_trees (tail $ tails l)))

 combinations [] = []
 combinations (h:t)
 = [h]:combinations t ++ (concat $ map insertions $ combinations t)
   where insertions l = zipWith (\a b - a ++ h: b)
(inits l)
(tails l)

Trees with all the members of a list appearing at most once
(in any order)

 combination_trees l = concat $ map the_trees $ combinations l

* * *

It looks like Lennart was writing something very similar at
the same time as me.  That obviously means that this is the
/right/ approach :-). As with his version, the order isn't
exactly as you listed them, but it's not far off ...


-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Stefan O'Rear
On Wed, Jun 13, 2007 at 05:12:25PM +0300, Benja Fallenstein wrote:
 However, this is still kind of boring. Is there a better way? If not,
 would it be a good idea to have compiler support for building this
 kind of type table?

The compiler does build exactly such a table - it's called a symbol
table.  If you aren't afraid of massive overkill, you can use hs-plugins
to write String - exists a. Read a = a   .

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


Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein

2007/6/14, Stefan O'Rear [EMAIL PROTECTED]:

On Wed, Jun 13, 2007 at 05:12:25PM +0300, Benja Fallenstein wrote:
 However, this is still kind of boring. Is there a better way? If not,
 would it be a good idea to have compiler support for building this
 kind of type table?

The compiler does build exactly such a table - it's called a symbol
table.  If you aren't afraid of massive overkill, you can use hs-plugins
to write String - exists a. Read a = a   .


Now *there* is an idea. :-) Hah.

Massive overkill, indeed, but you'd call 'eval' only once for every
type tag, of course, and cache the result, so the overhead would be
O(1) per run of the application.

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


[Haskell-cafe] Happy, GLR and GHC 6.6

2007-06-13 Thread Iván Pérez Domínguez
Hi everyone,

   As we all know, FiniteMap was deprecated, and with GHC-6.6 Data.Map
must be used instead. Some function names in Data.Map clash with names
in prelude, and Map is usually imported qualified.

Happy generates GLR parsers (-l), but the templates it uses keep calling
FiniteMap functions. When Data.Map is imported, it's not imported
qualified and some function names are ambiguous.

I've been using a modified template to generate a GLR parser with
GHC-6.6 and it seems to work just fine (there are few changes, not a big
deal anyway).

I just got the most recent version of Happy and the problem remains, so
I applied my changes to GLR_Lib.lhs and ran a diff. The result is
attached to this mail.

Hope it helps someone else.

Cheers,
Ivan.

PS. I seem to recall having sent this mail months ago. Couldn't find it,
though. In case it's been sent twice, I apologise.

diff -rN old-happy/templates/GLR_Lib.lhs new-happy/templates/GLR_Lib.lhs
46c46
 import Data.Map
---
 import qualified Data.Map as Map
116a117,119
 #if __GLASGOW_HASKELL__ = 603
 type Forest   = Map.Map ForestId [Branch]
 #else
117a121
 #endif
143a148,150
 #if __GLASGOW_HASKELL__ = 603
ns_map = Map.toList f 
 #else
144a152
 #endif
153a162,164
 #if __GLASGOW_HASKELL__ = 603
  = case runST Map.empty [0..] (tp toks) of
 #else
154a166
 #endif
292a305,307
 #if __GLASGOW_HASKELL__ = 603
  = chgS $ \f - ((), Map.insert i [] f)
 #else
293a309
 #endif
303a320,325
 #if __GLASGOW_HASKELL__ = 603
case Map.lookup i f of 
  Nothing   - chgS $ \f - (False, Map.insert i [b] f)   
  Just bs | b `elem` bs - return True
  | otherwise   - chgS $ \f - (True,  Map.insert i (b:bs) f)
 #else
308c330
 
---
 #endif
313a336,338
 #if __GLASGOW_HASKELL__ = 603
  = useS $ \s - Map.findWithDefault no_such_node i s
 #else
314a340
 #endif

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


Re: [Haskell-cafe] Happy, GLR and GHC 6.6

2007-06-13 Thread Stefan O'Rear
On Thu, Jun 14, 2007 at 12:38:27AM +0200, Iván Pérez Domínguez wrote:
 Hi everyone,
 
As we all know, FiniteMap was deprecated, and with GHC-6.6 Data.Map
 must be used instead. Some function names in Data.Map clash with names
 in prelude, and Map is usually imported qualified.
 
 Happy generates GLR parsers (-l), but the templates it uses keep calling
 FiniteMap functions. When Data.Map is imported, it's not imported
 qualified and some function names are ambiguous.
 
 I've been using a modified template to generate a GLR parser with
 GHC-6.6 and it seems to work just fine (there are few changes, not a big
 deal anyway).
 
 I just got the most recent version of Happy and the problem remains, so
 I applied my changes to GLR_Lib.lhs and ran a diff. The result is
 attached to this mail.
 
 Hope it helps someone else.

Why don't you just send a darcs patch?  That would be easier for
everyone :)

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


Re: [Haskell-cafe] found monad in a comic

2007-06-13 Thread Dan Piponi

Marc asked:


http://xkcd.com/c248.html
( join /= coreturn )

IMHO this could be a beautiful and easy way to explain monads.
comments?


I'll eat my hat if there isn't a formal way of looking at this. I'm
not qualified to put it together coherently but it goes something like
this: modal logic has Kripke semantics based on the notion of many
worlds. For the right modal logic, the many worlds idea captures the
notion of counterfactual worlds. We can also extend the Curry-Howard
isomorphism to include modal logic. Some of the laws of modal logic
(or their duals) correspond to monad (or comonad) laws (see laws 4 and
t here: http://en.wikipedia.org/wiki/Kripke_semantics). These laws
translate into rules about what worlds 'accessible' from what other
worlds. So that cartoon may have a formal interpretation in terms of
monads...
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread L.Guo
Hi, Henning Thielemann.

Thanks for your help. That is usful.

I have wrote the target function like this, and tested.

mkBlocks (w,h) = map concat . concat . transpose . chop h . map (chop w)


Hi, Dr. Janis Voigtlaender.

This is not a homework, though likely to be one.

I just use Haskell to write tools being used in my work. This is one of them.

I need to locate the difference between my coded image and standard coded image.
And both coded in 16x16 macroblocks. That is why I ran into this problem.

Anyway, thanks for your advice.

--   
L.Guo
2007-06-14


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


[Haskell-cafe] TorDNSEL

2007-06-13 Thread Tim Newsham

I wanted to point out:
   http://exitlist.torproject.org/

written in Haskell.  I haven't seen any announcements or info on this list 
(apologies if someone else mentioned it already).  For the record, I'm not 
affiliated with the project in any way.


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] TorDNSEL

2007-06-13 Thread Donald Bruce Stewart
newsham:
 I wanted to point out:
http://exitlist.torproject.org/
 
 written in Haskell.  I haven't seen any announcements or info on this list 
 (apologies if someone else mentioned it already).  For the record, I'm not 
 affiliated with the project in any way.
 

Is the source available?

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


Re: [Haskell-cafe] TorDNSEL

2007-06-13 Thread Tim Newsham

I wanted to point out:
   http://exitlist.torproject.org/


Is the source available?


Yup.  It's all there on the page:

  You can download the current revision from the hidden service or from
  a local mirror. It's probably wise to check out the current version from
  the darcs repository hosted on the aformentioned hidden service.

  http://p56soo2ibjkx23xo.onion/dist/tordnsel-0.0.5.tar.gz
  http://exitlist.torproject.org/tordnsel-0.0.5.tar.gz


-- Don


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe