Re: [Haskell-cafe] Tracer for Haskell showing substitutions

2010-02-02 Thread Ezra Lalonde

Hi,

"Hat": The Haskell Tracer.
http://www.haskell.org/hat/
>From the site:
Hat helps locating errors in programs. Furthermore, it is useful for
understanding how a (correct) program works, especially for teaching and
program maintenance. Hat is not a time or space profiler. Hat can be used
for programs that terminate normally, that terminate with an error message
or that terminate when interrupted by the programmer.

"Vital"/"Pivotal": it's dead, but it may be interesting to you anyway.
http://www.cs.kent.ac.uk/projects/pivotal/
http://www.cs.kent.ac.uk/projects/vital/
>From the site:
 Pivotal has similar goals to its predecessor system, Vital. In particular:
* Documents are live in the sense that, if a document is changed, the
displayed values are automatically re-evaluated. Thus documents are always
in a consistent state.
* Direct manipulation of ADT values is supported. That is, an end user
is able to manipulate the text of a Haskell module simply by point-and-click
mouse operations on displayed values. 



Pen and paper work too.

Ezra.



Ulrik Rasmussen-2 wrote:
> 
> Hi all,
> 
> I was wondering if someone has written a tracer/debugger that shows you
> how a given Haskell expression is evaluated, by generating all the
> intermediate states of the expression until it is in normal form?
> 
> For instance, given the following code:
> 
>> take' 0 xs = []
>> take' n (x:xs) = x : take' (n-1) xs
>> exp = take' 2 [1,2,3,4,5,6]
> 
> the trace of 'exp' would generate something like this:
> 
>> exp = take' 2 [1,2,3,4,5,6]
>> exp = (\n (x:xs) -> x : take' (n-1) xs) 2 [1,2,3,4,5,6]
>> exp = 1 : take' (2-1) [2,3,4,5,6]
>> exp = 1 : take' 1 [2,3,4,5,6]
>> exp = 1 : (\n (x:xs) -> x : take' (n-1) xs) 1 [2,3,4,5,6]
>> exp = 1 : 2 : take' (1-1) [3,4,5,6]
>> exp = 1 : 2 : take' 0 [3,4,5,6]
>> exp = 1 : 2 : (\0 xs -> []) 0 [3,4,5,6]
>> exp = 1 : 2 : []
>> exp = [1,2]
> 
> That is, all the substitutions performed when evaluating 'exp' from left
> to right.
> 
> I was thinking that something like this could be rather useful when
> teaching or learning Haskell.
> 
> 
> Thanks,
> 
> Ulrik
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

-- 
View this message in context: 
http://old.nabble.com/Tracer-for-Haskell-showing-substitutions-tp27421880p27424789.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread Ezra Lalonde

Using the same basic structure you did, and foldr, I think below is the
simplest method:


import Data.Maybe

searchList :: (a -> Bool) -> [a] -> Maybe [a]
searchList p xs = foldr (\x acc -> if p x then Just (x: fromMaybe [] acc)
else acc) Nothing xs


ghci> searchList (=='o') "A quick brown fox"
Just "oo"
ghci> searchList (==' ') "A quick brown fox"
Just "   "
ghci> searchList (=='z') "A quick brown fox"
Nothing


>From maybe gets rid of the Maybe, so that our recursive call works:
ghci> fromMaybe [] (Just [1..3])
[1,2,3]

That's why we got the error below when we tried without fromMaybe; on
subsequent applications of foldr, the type would have to change.

:1:51:
Couldn't match expected type `[a]'
   against inferred type `Maybe [a]'
In the expression: if p x then Just (x : acc) else acc
In the first argument of `foldr', namely
`(\ x acc -> if p x then Just (x : acc) else acc)'
In the expression:
foldr (\ x acc -> if p x then Just (x : acc) else acc) Nothing xs


I have a feeling that using fromMaybe is not the best way, but it gets the
job done for now.

On that note; if somebody with some more experience would chime in, that'd
be awesome. ;)

Ezra


dima.neg wrote:
> 
> How can I do this using foldr?
> 
> searchList p [] = Nothing
> searchList p (x:xs)
>   | p x = Just (x:filter p xs)
>   | otherwise = searchList p xs
> 
> 
> I try this: 
> searchList p xs = foldr (\x acc -> if p x then Just (x:acc) else acc)
> Nothing xs
> but don't work.
> 
> Thanks
> 

-- 
View this message in context: 
http://old.nabble.com/Recursive-to-foldr-tp26368900p26399795.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Help to solve simple problem !

2009-11-10 Thread Ezra Lalonde

The following program should work:

===compress.hs=
toList :: (Eq a) => [a] -> [[a]]
toList [] = []
toList x = start : toList end
where (start, end) = span (==(head x)) x

toTuple :: [a] -> (a, Int)
toTuple x = (head x, length x)

compress :: Eq a => [a] -> [(a, Int)]
compress x = map toTuple $ toList x
=

The important thing to understand here, is the "span" function from the
Prelude, and apply it recursively. 
*Main> span (=='A') "AAABCC"
("AAA","BCC")
*Main> span (=='h') "hhhaskell"
("hhh","askell")

I've used a function "toList" to separate each part of the string into a
separate element of a list:
*Main> toList "AAABCC"
["AAA","B","CC"]
*Main> toList "EEEZZZRR!!"
["EEE","ZZZ","RR","","!!"]

>From there, "toTuple" takes the first letter of the string, and puts it with
its length in a tuple:
*Main> toTuple "EEE"
('E',3)
*Main> toTuple "E"
('E',5)

Because of how it's defined, we also get the following:
*Main> toTuple "Ezra"
('E',4)

But that won't matter if we only use it after "toList", as in "compress".

Also, I've used your type signature for my solution, not your example
output; if you want it to be displayed like that, you'll have to write your
own function for printing.

This solution is probably not optimal, but it's a start.

Hope that helps,
Ezra


Aneto wrote:
> 
> Hi ! I am beginner in Haskell and have problems with this problem:
> compress :: Eq a => [a] -> [(a, Int)]
> If you have string "AAABCCC" it transforms it to : {A, 3} {B,1} {C,3}
> 
> Could you help me with it ?
> Thank you in advance !
> 

-- 
View this message in context: 
http://old.nabble.com/Help-to-solve-simple-problem-%21-tp26249028p26292205.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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