[Haskell-cafe] Trees (Rose Trees?)

2008-07-21 Thread Ryan Bloor
hi
 
I was curious as to whether my implementation of a Rose Tree and a sumTree 
function was correct. The aumTree adds up the elements of a tree.
 
data Tree a = Leaf a | Node [Tree a]
 
sumTree :: Tree Int - Int
sumTree (Node []) = 0
sumTree (Node xs) = sum (map sumTree xs)
 
The problem with this is I get a pattern matching error. Am I representing 
trees right... see below.
 
Also, would an empty tree be represented by ... Node [] with this 
implementation?
How would I represent a tree of the form... Tree (Node 2(Node 6 Empty Empty) 
Empty) taken from a binary one.
Like this? Node [ [Leaf 2], Node [ Leaf 6,Node[],Node[] ], Node[] ] 
 
Ryan
 
 
_
Find the best and worst places on the planet
http://clk.atdmt.com/UKM/go/101719807/direct/01/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help

2007-12-10 Thread Ryan Bloor
hi I am writing a basic Parser from scratch. So far I have functions;# 
removeSpaces# match - which checks if a string is a substring of another# 
orParser which combines two parser's abilities# Basic pasrers like... parseInt, 
parseTrue, parseFalse, parseBoolusing the orParser on True and False.What I 
want to do now is have a parseBinaryOp that recognises:parseBinaryOp + (5 + 
2) if  gives [(EInt 5, EInt 2, if)]So I 
think that I have to split the initial string into four parts.+ becomes op'(' 
becomes tokenF')' becomes tokenB5 becomes e12 becomes e2parseBinaryOp :: 
String - String - [(Expr, Expr, String)]parseBinaryOp op str = let 
(tokenF,e1,op,e2,tokenB) =I am not sure how to go about separating the string 
for how I need itusing my other functiuons. Ryan
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] parsebinaryoperations

2007-12-09 Thread Ryan Bloor
hi
 
I have a function parseInt... which needs an error guard for when the input is 
not an Int.
 
parseInt :: ParserparseInt [] = []parseInt xs = let (digits, rest) = span 
isDigit (removeSpace xs)in [(EInt (read digits), removeSpace 
rest)]
 
Also... I have a function that does this... parseBinaryOp + (5 + 2) if  
gives...[(Int 5, Int 2, if)]
so, op is '+' or . I am unsure of how to begin... 
 
parseBinaryOp :: String - String - [(Expr, Expr, String)]parseBinaryOp op str
 
Thankyou
 
Ryan
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help

2007-12-09 Thread Ryan Bloor
hi I have a function parseInt... which needs an error guard for when the input 
is not an Int. parseInt :: ParserparseInt [] = []parseInt xs = let (digits, 
rest) = span isDigit (removeSpace xs)in [(EInt (read digits), 
removeSpace rest)] Also... I have a function that does this... parseBinaryOp 
+ (5 + 2) if  gives...[(Int 5, Int 2, if)]so, op is '+' or . I am 
unsure of how to begin...  parseBinaryOp :: String - String - [(Expr, Expr, 
String)]parseBinaryOp op str Thankyou Ryan
_
Get free emoticon packs and customisation from Windows Live. 
http://www.pimpmylive.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] binaryop

2007-12-09 Thread Ryan Bloor
hi  sorry for vagueness.  I am writing a basic Parser from scratch. So far I 
have functions;  # removeSpaces # match - which checks if a string is a 
substring of another # orParser which combines two parser's abilities # Basic 
pasrers like... parseInt, parseTrue, parseFalse, parseBoolusing the orParser on 
True and False.  What I want to do now is have a parseBinaryOp that recognises: 
parseBinaryOp + (5 + 2) if  gives 
[(EInt 5, EInt 2, if)]  So I think that I have to split the initial string 
into four parts.  + becomes op '(' becomes tokenF ')' becomes tokenB 5 
becomes e1 2 becomes e2  parseBinaryOp :: String - String - [(Expr, Expr, 
String)]parseBinaryOp op str = let (tokenF,e1,op,e2,tokenB) =  I am not sure 
how to go about separating the string for how I need itusing my other 
functiuons. Ryan
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Need help please.

2007-12-09 Thread Ryan Bloor
hi I am writing a basic Parser from scratch. So far I have functions;# 
removeSpaces# match - which checks if a string is a substring of another# 
orParser which combines two parser's abilities# Basic pasrers like... parseInt, 
parseTrue, parseFalse, parseBoolusing the orParser on True and False.What I 
want to do now is have a parseBinaryOp that recognises:parseBinaryOp + (5 + 
2) if  gives [(EInt 5, EInt 2, if)]So I 
think that I have to split the initial string into four parts.+ becomes op'(' 
becomes tokenF')' becomes tokenB5 becomes e12 becomes e2parseBinaryOp :: 
String - String - [(Expr, Expr, String)]parseBinaryOp op str = let 
(tokenF,e1,op,e2,tokenB) =I am not sure how to go about separating the string 
for how I need itusing my other functiuons. Ryan
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] general

2007-12-08 Thread Ryan Bloor
hi
 
I have a problem.
 
Function A is a function that passes its input into B
Function B is a function that does something once. 
 
How do I make it so function A is done multiple times without adding a third 
function?
 
Ryan
_
Who's friends with who and co-starred in what?
http://www.searchgamesbox.com/celebrityseparation.shtml___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] general-revised

2007-12-08 Thread Ryan Bloor
hi
 
I have four functions below: What I want to do is have a way to parse more than 
one digit or more than one string head in ParseTrue. Any ideas...
 
removeSpace:: String - StringremoveSpace = dropWhile (`elem` space)
   where space = [' ']
 
match :: String - String - (Bool, String)match word str| ((isPrefixOf) 
(removeSpace word) (removeSpace str)) = (True,rest)   | otherwise = (False,str) 
where rest = drop (length (removeSpace word)) (removeSpace str) parseDigit 
:: String - [(Int, String)]parseDigit (x:xs)  | isDigit x = [(read [x],xs)] | 
otherwise = []
 
parseTrue :: String - (Bool, String)parseTrue x = match True x
 
 
 
Ryan 
 
 
 
 
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] do... error

2007-12-08 Thread Ryan Bloor
hi
 
 test :: Parser (Char,Char) test  = do x - item   item 
  y - item   return (x,y)
 
How come this brings an error saying that after do {} it must end with an 
expression.
 
Ryan
_
Get free emoticon packs and customisation from Windows Live. 
http://www.pimpmylive.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] annoying output

2007-12-08 Thread Ryan Bloor
hi
 
The code below does almost what I want but not quite! It outputs...parseInt 
12444a gives...
[(EInt 1,2444a),(EInt 2,444a),(EInt 4,44a),(EInt 4,4a),(EInt 4,a)]
 
What I want is: [(EInt 12444, a)]
 
data Expr = EInt {vInt :: Int} -- integer values | EBool {vBool :: Bool} -- 
boolean values
 
parseInt :: Parser parseInt (x:xs) | (isDigit x  xs /= []) = [(EInt (read 
[x]),xs)] ++ parseInt xs | isDigit x  xs == [] = [(EInt (read [x]),[])] | 
otherwise = []
 
Thanks
 
Ryan
 
 
 
 
_
Who's friends with who and co-starred in what?
http://www.searchgamesbox.com/celebrityseparation.shtml___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] parser

2007-12-06 Thread Ryan Bloor
hi
 
Can anyone advise me on how to check whether a string contains ints, chars, 
bools, etc 
 
2345 + 6767 shoudl give IntAdd (2345) (6767)
2345 should give IntT 2345
 
Ryan
_
Who's friends with who and co-starred in what?
http://www.searchgamesbox.com/celebrityseparation.shtml___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] matching

2007-12-05 Thread Ryan Bloor
hi
 
I have a matching problem... I am wanting to identify whether or not a string 
is an opening substring of another (ignoring leading spaces). I have this:
word is a single word and str is a string.
 
match :: String - String - (Bool, String)match word str   | 
if removeSpace str `elem` (removeSpace word) ++ rest = (True, rest) 
 | otherwise == (False,str)  where rest = str
 
Any help?
 
Ryan  
 
 
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
hi
 
I am having trouble with a function that is supposed to eliminate spaces from 
the start of a String and return the resulting string. I reckon a dropWhile 
could be used but the isSpace bit is causing me problems...
 
words :: String - String
words a = case dropWhile isSpace a of
  - 
 s:ss - (s:word) : words rest
   where (word,rest) = break isSpace ss
 
 
Thanks
 
Ryan
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
HI
 
I will try and explain it better. 
I am meaning to write a function that takes a string,  apple and 
eliminates the spaces at the start ONLY. called removeSpace :: String 
- String
 
I decided to use the function 'dropWhile' and another one 'isSpace' in the 
'removeSpace' function.
 
 removeSpace:: String - String removeSpace a = case dropWhile isSpace a of 
 - 
 
I get stuck here... I am not sure how to go about this function. 
 
Any ideas.
 
Ryan
 
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] missed clause???

2007-11-11 Thread Ryan Bloor
hi
 
I was testing my code when I came across a strange predicament. The input is a 
list of ints and a Results type which is of type 
[(int,...),(Int..)..]. I am comparing each int from the list to the 
first element in each member of results. But it works for 1-9 but not for 10 
onwards why? 
Have I missed a clause anywhere.. it only does the first one after that. 
 
--Print the points of eight games
poolsPoints :: [Int] - Results - Int
poolsPoints [] [] = 0
poolsPoints [] _ = 0
poolsPoints _ [] = 0
poolsPoints (x:xs) ((a,b,c,d,e):t) 
| (x == a  cd) = 1 + poolsPoints xs t
| (x == a  cd) = 1 + poolsPoints xs t
| (x == a  c==0  d==0) = 2 + poolsPoints xs t
| (x == a  c==d  c0) = 3 + poolsPoints xs t
| otherwise = 0 + poolsPoints [x] t
 
Thanks
 
Ryan
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FW: please help... small problem

2007-11-10 Thread Ryan Bloor
hi
 
I've attempted to cut down this module... but I cannot see where... can someone 
help... 
 
Ryan 
 
thanks


From: [EMAIL PROTECTED]: Subject: FW: please help... small problemDate: Fri, 9 
Nov 2007 21:57:30 +


sorry heres the code I always do that.


From: [EMAIL PROTECTED]: Subject: please help... small problemDate: Fri, 9 Nov 
2007 21:44:35 +

hi Is there anyway to cut down this code and to not use auxillary functons, but 
instead use pattern matching? The code basically splits up a list 'rslis' into 
a list of lists - but so each word is split up and the integers have been 
parsed. so [hi ryan 1,hi jeff 2] becomes [[hi,ryan 1], 
[hi,jeff, 2]].The code is far too long. I don't wanna use premade functions 
too much... pattern matching is required.  Ryan

The next generation of MSN Hotmail has arrived - Windows Live Hotmail 

Are you the Quizmaster? Play BrainBattle with a friend now! 
_
100’s of Music vouchers to be won with MSN Music
https://www.musicmashup.co.uk

Football.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] recursion issues...

2007-11-10 Thread Ryan Bloor
hiya
 
I was wondering how I would get the second function do recursively do the 
function for poolNews xs tried that and it fails. 
 
Ryan
 
 
--Give wins, draws a rating.
 
poolNews :: Result - PoolNews - PoolNews
poolNews (a,b,c,d,e) (home,away,goaless,scoredraw) 
 | c  d = (home+1,away,goaless,scoredraw) 
 | c  d = (home,away+1,goaless,scoredraw)  
 |(c == 0)  (d == 0) = (home+1,away,goaless+1,scoredraw) 
  | otherwise = (home,away,goaless,scoredraw+1)
 

--Do for all Results
poolNewsB :: Results - PoolNews
poolNewsB (x:xs) = poolNews x (0,0,0,0)
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] please help... small problem

2007-11-09 Thread Ryan Bloor
hi
 
Is there anyway to cut down this code and to not use auxillary functons, but 
instead use pattern matching? The code basically splits up a list 'rslis' into 
a list of lists - but so each word is split up and the integers have been 
parsed. so [hi ryan 1,hi jeff 2] becomes [[hi,ryan 1], 
[hi,jeff, 2]].The code is far too long. I don't wanna use premade functions 
too much... pattern matching is required.  Ryan
_
100’s of Music vouchers to be won with MSN Music
https://www.musicmashup.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FW: please help... small problem

2007-11-09 Thread Ryan Bloor
sorry heres the code
 
I always do that.


From: [EMAIL PROTECTED]: Subject: please help... small problemDate: Fri, 9 Nov 
2007 21:44:35 +


hi Is there anyway to cut down this code and to not use auxillary functons, but 
instead use pattern matching? The code basically splits up a list 'rslis' into 
a list of lists - but so each word is split up and the integers have been 
parsed. so [hi ryan 1,hi jeff 2] becomes [[hi,ryan 1], 
[hi,jeff, 2]].The code is far too long. I don't wanna use premade functions 
too much... pattern matching is required.  Ryan

The next generation of MSN Hotmail has arrived - Windows Live Hotmail 
_
Get free emoticon packs and customisation from Windows Live. 
http://www.pimpmylive.co.uk

Football.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] words function

2007-11-08 Thread Ryan Bloor
hi
 
I am trying to create a function that uses the words function... I am doing the 
same thing to each element in a list so I am using mapping techniques.
 
Code...
 
 --Define the main first function rStrings2Results :: ([String] - String) - 
[[String]] - [String] rStrings2Results f(head:tail) = (f head : 
rStrings2Results f tail)
 
I just want take a list and on the first member (hello my name is ryan) to 
say [(hello, my, name, is, ryan),..] using the words 
function.
_
100’s of Music vouchers to be won with MSN Music
https://www.musicmashup.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help please

2007-11-04 Thread Ryan Bloor
hello, I am struggling with rose trees
in Haskell. I need to construct an algebraic data type definition for
family trees and a representation of the tree below. Also I need to
construct a function that returns a persons children when given both a
family tree and a name. The same is needed but for a getParents
function. 

1

 

  2 3   4

   5 6 7   8910 11

 

That is the rose tree that I seek. Where each number above is equivalent to 
(String, String) 

 

Data Tree a = Empty | Leaf a | Node a [(Tree a)]

 

example :: Tree (String, String) 

example = Node (a,b) -- root node

[ ...define tree.] -- 
end of tree


_
100’s of Music vouchers to be won with MSN Music
https://www.musicmashup.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Rose Tree

2007-11-03 Thread Ryan Bloor
Hello,
 
 
I need help... I am having trouble with rose trees.
 
 1
 
  2 3   4
   5 6 7   8910 11
 
That is the rose tree that I seek. 
 
Data Tree a = Empty | Leaf a | Node a [(Tree a)]
 
example :: Tree (String, String) 
example = Node (a,b) -- root node
[ ] -- end of tree
 
What I want to do is create two functions that return either the children or 
parents of a given input, here a String. 
 String - Tree - [String] I think 
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Java - Haskell adjustment

2007-10-15 Thread Ryan Bloor
Hi, its Ryan here...

I've just come from an intensive course in java and have been thrown into the 
imperative world of haskell. 

The problem that I have is extremely simple in java but I am having trouble 
adjusting my old mindset. 

A multiset is a collection of items. 
Each item may occur one or more times in the multiset. All items are of the 
same type. 

The scenario we could use is a students' grades for their A levels: 3A, 4B and 
2C grades for our pupil 'x'. 
A multiset may be implemented by a list... so ['A', 'A', 'A', 'B', 'B', 'B', 
'B, 'C', 'C'] but this very ineffiecient and tedious. 

How might one set out into putting this into action thanks...

Any help that complements my ideas is welcome

_
Feel like a local wherever you go.
http://www.backofmyhand.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe