Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Morphing Endo (ICFP Contest 2007) (Benjamin L.Russell)
   2. Re:  Morphing Endo (ICFP Contest 2007) (Benjamin L.Russell)
   3. Re:  Morphing Endo (ICFP Contest 2007) (Benjamin L.Russell)
   4. Re:  Morphing Endo (ICFP Contest 2007)
      (Rafael Gustavo da Cunha Pereira Pinto)
   5. Re:  Morphing Endo (ICFP Contest 2007) (Tillmann Rendel)
   6.  Looking for cunning ways to update a tree (Quergle Quergle)
   7. Re:  Looking for cunning ways to update a tree (Chris Eidhof)


----------------------------------------------------------------------

Message: 1
Date: Thu, 24 Jul 2008 11:46:34 +0900
From: Benjamin L.Russell <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Morphing Endo (ICFP Contest 2007)
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=iso-2022-jp

For everybody's reference, here is summary information of the exercise
(each quoted paragraph starts with a double-quote, and the entire
section ends with a single double-quote):

The 10th ICFP Programming Contest: July 20 - 23, 2007, organized by
Utrecht
http://save-endo.cs.uu.nl/

Problem ("Task") Description:
http://save-endo.cs.uu.nl/Endo.pdf

Background of Problem (from "[Chapter] 1  Background" of the
above-mentioned "Problem ('Task') Description":

"Department of Information and Computing Sciences
Utrecht University

"Tenth Interstellar Contest on Fuun Programming

"Morph Endo!

"Task Description

"Endo is an alien life form, belonging to the species of the Fuun.
Endo needs your help!  Earth’s environmental conditions can be harsh
for a life form not properly adapted. Endo had the bad luck of being
dropped on Earth by an Interstellar Garbage Collector. Both the life
form and its faithful space ship Arrow were severely hurt in the
crash, and even worse, after leaving the damaged space craft Endo was
hit by a cargo container that was also dropped by the Garbage
Collector.

"Endo is now in serious trouble. It cannot survive on planet Earth in
its present form, and Arrow is running low on power. According to
Arrow, who was the one to have contacted us, the only hope for Endo is
to change its DNA and thereby adapt it to the conditions of our
planet. To this end, Arrow has been able to come up with a form in
which Endo will survive. Unfortunately, given its current condition,
Arrow lacks the resources for coming up with proper DNA modifications
itself.

"Your task is therefore to help us find such a DNA sequence within 72
hours. Shortly thereafter, Arrow’s power will run out for good, and
since only Arrow can perform the genetic modification on Endo, this
would mean Endo’s definite end.

"Admittedly, we are partially responsible for the current state of
urgency. It took us a long time before realizing the nature of
Arrow’s emergency message and decoding the information that was
provided to us. We are sorry but nevertheless hope that you, the ICFP
programming contest audience, have the proper expertise to solve this
problem within the harsh time constraints.

"Fortunately, there’s also good news. When we weren’t yet aware of
the complete story of Endo and its struggle for life, we have been
working on decoding the specification of Fuun DNA. We now know that
Fuun DNA works significantly different from human DNA, and that the
process of DNA resequencing can be properly described as an algorithm.
The main purpose of this document is to describe this algorithm."

To solve the above task, you are given the following tools:

    *  Endo's DNA string (MD5 hash c496125ef1d22a61cb86aeb1a02c4092)
        http://save-endo.cs.uu.nl/endo.zip

    * the source picture
       http://save-endo.cs.uu.nl/source.png

    * the target picture
       http://save-endo.cs.uu.nl/target.png

The actual description of the problem is 20 pages long, which is too
long to quote here.

Correct me if I'm wrong, but because the prefix should not be too
long, and chemical process of modifying Endo with the prefix should
not consume too much energy, this appears to be an example of
constraint programming.  Since constraint programming can often be
carried out by constraint logic programming, I might suggest a logic
programming approach for this problem.

According to "Applications and libraries/Compilers and interpreters -
HaskellWiki"
(http://haskell.org/haskellwiki/Applications_and_libraries/Compilers_and_interpreters),
CHR (Constraint Handling Rules) is "A concurrent committed-choice
constraint logic programming language, implemented using GHC's
software transactional memory."  The URL listed for the associated PS
file is http://www.comp.nus.edu.sg/~sulzmann/manuscript/chr-stm.ps,
but when I click on the link, I get a "403 Forbidden" error.

However, I was able to find the following associated Web site with
Google:

Constraint Handling Rules (CHR)
http://www.cs.kuleuven.ac.be/~dtai/projects/CHR/

-- Benjamin L. Russell

On Wed, 23 Jul 2008 22:11:10 -0300, "Rafael Gustavo da Cunha Pereira
Pinto" <[EMAIL PROTECTED]> wrote:

>        Did any of you tried to do a Haskell implementation of the ICFPC
>2007 problem?
>
>        I was thinking of using it as a learning exercise, but I am afraid
>of the stack. My approach is:
>
>1) use Data.ByteString.Lazy.Char8 to read the contents of the DNA file
>2) create a recursive function process::ByteString -> a that will call
>itself.
>
>       I have a few problems:
>
>a) the DNA is 8MB long. How can I ensure the stack will hold a recursive
>call?
>b) there is an "abnormal ending" function called finish that is called
>anywhere in the code. Is it a good approach to return Empty to end
>processing?
>c) should I go "monadic", keeping the dna on a state monad?
>
>
>    Thanks



------------------------------

Message: 2
Date: Thu, 24 Jul 2008 15:13:25 +0900
From: Benjamin L.Russell <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Morphing Endo (ICFP Contest 2007)
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

On Thu, 24 Jul 2008 11:46:34 +0900, Benjamin L.Russell
<[EMAIL PROTECTED]> wrote:

>[...]
>
>However, I was able to find the following associated Web site with
>Google:
>
>Constraint Handling Rules (CHR)
>http://www.cs.kuleuven.ac.be/~dtai/projects/CHR/

The above-mentioned previous reference was just for the top page of
CHR.  A more refined search revealed a page with Haskell-specific
library downloads for CHR, as follows:

DOWNLOAD IMPLEMENTATIONS - Constraint Handling Rules (CHR)
http://www.cs.kuleuven.be/~dtai/projects/CHR/chr-impl.html

There, the following libraries for Haskell are listed:

    * HaskellCHR
      http://www.cs.mu.oz.au/~gjd/haskellchr/

    * STM-based CHR implementation, by Michael Stahl

http://www.cs.kuleuven.be/~dtai/projects/CHR/systems/stmchr-0.1.tar.gz

    * CCHR: STM-based CHR implementation by Lam and Sulzmann
       http://taichi.ddns.comp.nus.edu.sg/taichiwiki/CCHR

I have replaced the previously dead link for CHR at "Applications and
libraries/Compilers and interpreters - HaskellWiki"
(http://haskell.org/haskellwiki/Applications_and_libraries/Compilers_and_interpreters)
with the above-mentioned live one, and added links/descriptions for
the above-mentioned STM-based CHR implementation and for CCHR.

If I come up with any more specific information or ideas that seem
relevant for solving the problem, I'll post it in this thread.

-- Benjamin L. Russell



------------------------------

Message: 3
Date: Thu, 24 Jul 2008 16:41:01 +0900
From: Benjamin L.Russell <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Morphing Endo (ICFP Contest 2007)
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

On Wed, 23 Jul 2008 22:11:10 -0300, "Rafael Gustavo da Cunha Pereira
Pinto" <[EMAIL PROTECTED]> wrote:

>[...]
>
>       I have a few problems:
>
>a) the DNA is 8MB long. How can I ensure the stack will hold a recursive
>call?

Forgive me if I'm wrong, but on a hunch, but this sounds like an issue
that could possibly be solved using tail recursion.

For example, according to "Recursion in a monad - HaskellWiki"
(http://haskell.org/haskellwiki/Recursion_in_a_monad), here is a
monadic do-block reads 'n' lines from stdin, using a linear recursive
process:

main = f 3
 
f 0 = return []
f n = do v  <- getLine
         vs <- f (n-1)
         return $! v : vs

This runs as follows:

    $ runhaskell A.hs
    1
    2
    3
    ["1","2","3"]

Rewriting the code to make it use a linear iterative process (using
tail recursion) results in the following code:

f 0 acc = return (reverse acc)
f n acc = do
    v  <- getLine
    f (n-1) (v : acc)

Here, "acc" stands for an accumulator, which is a register (here, a
variable simulating a register) to store temporary values.  This
rewrite enables the process to use constant stack space.

Using this idea, it may be possible to rewrite your recursive function
process::ByteString -> a to use constant stack space.

-- Benjamin L. Russell



------------------------------

Message: 4
Date: Thu, 24 Jul 2008 07:56:09 -0300
From: "Rafael Gustavo da Cunha Pereira Pinto" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Morphing Endo (ICFP Contest 2007)
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

Ops, forgot to copy the list.

On Thu, Jul 24, 2008 at 07:54, Rafael Gustavo da Cunha Pereira Pinto <
[EMAIL PROTECTED]> wrote:

>
>
>
>
> 2008/7/23 Benjamin L. Russell <[EMAIL PROTECTED]>:
>
>>
>> Correct me if I'm wrong, but because the prefix should not be too
>> long, and chemical process of modifying Endo with the prefix should
>> not consume too much energy, this appears to be an example of
>> constraint programming.  Since constraint programming can often be
>> carried out by constraint logic programming, I might suggest a logic
>> programming approach for this problem.
>>
>>
>
>     The DNA is actually a representation of a turing machine (like BF
> language). Using brute-force and constraints would take too long. There is a
> report at http://www.cs.uu.nl/research/techreps/repo/CS-2007/2007-029.pdf,
> that shows how this DNA string was made: it is the output of a compiler for
> a functional programming language specially tailored for this contest.
> which, in turn, was written in Haskell.
>
>     The basic idea is to disassemble, find the function calls and add
> prefxes that do the appropriate calls.
>
>
> --
> Rafael Gustavo da Cunha Pereira Pinto
> Electronic Engineer, MSc.
>



-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20080724/75d8865e/attachment-0001.htm

------------------------------

Message: 5
Date: Thu, 24 Jul 2008 13:11:25 +0200
From: Tillmann Rendel <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Morphing Endo (ICFP Contest 2007)
To: "Benjamin L.Russell" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-2022-JP

Benjamin L.Russell wrote:

> Correct me if I'm wrong, but because the prefix should not be too
> long, and chemical process of modifying Endo with the prefix should
> not consume too much energy, this appears to be an example of
> constraint programming.  Since constraint programming can often be
> carried out by constraint logic programming, I might suggest a logic
> programming approach for this problem.

Note that you have to execute the modified Endo to find out how many
points a prefix will be awarded, which takes several seconds to several
hours depending on your implementation. Since DNA is Turing complete,
you cannot hope to evaluate a modified Endo without executing it.

I therefore suggest to implement a DNA interpreter to produce RNA from
DNA, and a RNA interpreter which produces pictures from RNA, and then to
look at these pictures for clues how to proceed.

  Tillmann


------------------------------

Message: 6
Date: Thu, 24 Jul 2008 19:29:23 +0100
From: "Quergle Quergle" <[EMAIL PROTECTED]>
Subject: [Haskell-begin] Looking for cunning ways to update a tree
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

Hello all,

This is a really helpful list: I've learned half a dozen new things just by
reading this month's traffic. Anyway...I have the following bit of code that
updates a tree structure given a route to a leaf:

data Tree a = Leaf a | Node (Tree a) (Tree a)
              deriving (Show, Eq)
data PathSelector = GoLeft | GoRight
                    deriving (Show, Eq)
type Path = [PathSelector]

selectChild (Node left _) GoLeft = left
selectChild (Node  _ right ) GoRight = right

updateNode (Node _ right) GoLeft newLeft = Node newLeft right
updateNode (Node left _) GoRight newRight = Node left newRight

updateLeaf new (Leaf previous) = Leaf new

updateTree :: Tree a -> Path -> a -> Tree a
updateTree tree path newValue = case path of
                                 [] -> updateLeaf newValue tree
                                 (p:ps) -> updateNode tree p (updateTree'
(selectChild tree p) ps newValue)

I wanted to rewrite updateTree without using explicit recursion.
Unfortunately, the best I could come up with is:

upDownRecurse :: (a -> b -> a) -> (a -> c) -> (a -> b -> c -> c) -> a -> [b]
-> c
upDownRecurse down bottoming up = upDownRecurse'
    where upDownRecurse' acc [] = bottoming acc
          upDownRecurse' acc (x:xs) = up acc x (upDownRecurse' (down acc x)
xs)

updateTree' :: Tree a -> Path -> a -> Tree a
updateTree' tree path newValue = upDownRecurse selectChild (updateLeaf
newValue) updateNode tree path

So what's the sexier way of doing this?

Cheers,

-- Matt
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20080724/8a1b753f/attachment-0001.htm

------------------------------

Message: 7
Date: Fri, 25 Jul 2008 01:44:01 +0200
From: Chris Eidhof <[EMAIL PROTECTED]>
Subject: Re: [Haskell-begin] Looking for cunning ways to update a tree
To: Quergle Quergle <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

Hey Matt,

On 24 jul 2008, at 20:29, Quergle Quergle wrote:

> Hello all,
>
> This is a really helpful list: I've learned half a dozen new things  
> just by reading this month's traffic. Anyway...I have the following  
> bit of code that updates a tree structure given a route to a leaf:
>
> [...]
>
> I wanted to rewrite updateTree without using explicit recursion.  
> Unfortunately, the best I could come up with is:
>
> [...]
>
> So what's the sexier way of doing this?

The trick here is to define a fold for a tree. A fold is a function  
that does all the recursion, and you can then define other functions  
in terms of that fold. The type of the fold function is based on the  
structure of your data.

So, for the fold of the tree, you basically first have to take two  
functions:

 > leaf :: a -> r
 > node :: r -> r -> r

The leaf function will act on Leaf's, and take a value of type a and  
turn it into a result. The node function will first compute the result  
for the recursive parts (so this is where the recursion happens), and  
then needs to combine those results. The full type of our function  
foldTree looks like this:

 > foldTree :: (a -> r) -> (r -> r -> r) -> Tree a -> r

And the implementation looks like this:

 > foldTree leaf node (Leaf a) = leaf a
 > foldTree leaf node (Node a b) = node (foldTree leaf node a)  
(foldTree leaf node b)

Now, to find a value in the tree using your Path type, we want the  
following type:

 > findTree :: Tree a -> Path -> a

So suppose we give our foldTree two arguments to handle both the Node  
and the Leaf, we will end up with a function that has type:

 > Tree a -> r

Now, what will we choose for r? Of course, it has to be Path a -> a!

We now need a function (a -> Path a -> a) and a function (Path a -> a)  
-> (Path a -> a) -> (Path a -> a). When we remove unnecessary  
parentheses, the type is (Path a -> a) -> (Path a -> a) -> Path a -> a

The first one is easy, we just ignore the second argument:

 > findLeaf a _ = a

The second one takes three arguments: the left value, the right value  
and the path. Based on the path we need to choose wheter to choose the  
left or the right value:

 > findNode left right (p:ps) = case p of
 >   GoLeft  -> left ps
 >   GoRight -> right ps

Now we can take these parts and compose them into the findTree function:

 > findTree t p = foldTree findLeaf findNode t p

And because Haskell will save us from unnecessary typing, we could  
also write it shorter:

 > findTree = foldTree const findNode

Note that we didn't use any recursion in our findTree! It would be  
cool if you could try to come up with a definition of updateTree in  
terms of foldTree.

Have fun,
-chris

P.S.: Here's the full code:

 > foldTree :: (a -> r) -> (r -> r -> r) -> Tree a -> r
 > foldTree leaf node (Leaf a)   = leaf a
 > foldTree leaf node (Node a b) = node (rec a) (rec b)
 >  where rec = foldTree leaf node
 >
 > findTree :: Tree a -> Path -> a
 > findTree = foldTree const findNode
 >  where findNode left right (p:ps) = case p of
 >          GoLeft  -> left  ps
 >          GoRight -> right ps



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 1, Issue 13
****************************************

Reply via email to