
Sorry for annoying you all, i'm just very eager to move on with this and solve it. so far i have; equalChar :: Char -> Char -> Bool equalChar x n | x == n = True | otherwise = False equalString :: String -> String -> Bool equalString [] [] = True equalString [] (c':s') = False equalString(c:s) [] = False equalString(c:s)(c':s') = equalChar c c'^ equalString s s' this function is to see if one string is equal to another. but when i compile this i get the error; - Instance of Integral Bool required for definition of equalString does anyone know why i am getting this error and what i will need to do to transform the function above so that it checks is a list a subsequence of another list Peter Stranney --------------------------------- Do you Yahoo!? Yahoo! Mail - You care about security. So do we.

On Sun, Oct 17, 2004 at 07:16:51AM -0700, Peter Stranney wrote:
equalString :: String -> String -> Bool equalString [] [] = True equalString [] (c':s') = False equalString(c:s) [] = False equalString(c:s)(c':s') = equalChar c c'^ equalString s s' ^^^^^^
this function is to see if one string is equal to another.
but when i compile this i get the error; - Instance of Integral Bool required for definition of equalString
You are using the raise-to-the-power-of operator, which requires it's second parameter to be Integral... (^) :: (Integral b, Num a) => a -> b -> a You might also want to look at the earlier `any prefix of tails' suggestion, as it makes the solution a rather simple one-liner. Good luck, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

Remi Turk
You might also want to look at the earlier `any prefix of tails' suggestion, as it makes the solution a rather simple one-liner.
Wouldn't that be looking for a sub*string*, and not a (general) sub*sequence* (which I think does not have to be contigous?) -kzm -- If I haven't seen further, it is by standing in the footprints of giants

On Sun, Oct 17, 2004 at 08:05:09PM +0200, Ketil Malde wrote:
Remi Turk
writes: You might also want to look at the earlier `any prefix of tails' suggestion, as it makes the solution a rather simple one-liner.
Wouldn't that be looking for a sub*string*, and not a (general) sub*sequence* (which I think does not have to be contigous?)
Hm, not "substring" as in String at least, but that solution does give the following results: Prelude List> sub "ell" "hello" True Prelude List> sub [3..5] [1..10] True Prelude List> sub [2,4] [1..5] False Prelude List> sub [2..6] [1..5] False Do you mean "subset" with "subsequence"? Groetjes, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

Remi Turk
Wouldn't that be looking for a sub*string*, and not a (general) sub*sequence* (which I think does not have to be contigous?)
Do you mean "subset" with "subsequence"?
No, since a set isn't ordered. I would say a subset needs to contain some of the elements of the superset, a subsequence needs to contain some elements of the supersequence in the same order, and a substring (for lack of a better term) is a contigous subsequence. But I may be wrong. -kzm PS: I feel queasy about "strand", since that has a different meaning in biology (DNA consists of two strands). -- If I haven't seen further, it is by standing in the footprints of giants

On Sun, Oct 17, 2004 at 10:10:44PM +0200, Ketil Malde wrote:
Remi Turk
writes: Do you mean "subset" with "subsequence"?
No, since a set isn't ordered.
I would say a subset needs to contain some of the elements of the superset, a subsequence needs to contain some elements of the supersequence in the same order, and a substring (for lack of a better term) is a contigous subsequence.
But I may be wrong.
Agreeing on terminology is always nice :D at least http://en.wikipedia.org/wiki/Subsequence seems to agree with you. In which case both Peter Stranney's and my solutions fail. Groetjes, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

Thanks guys for all your help, finally through code, sweat and tears i have found the solution;
isSubStrand:: String -> String -> Bool
isSubStrand [] [] = True
isSubStrand [] (y:ys) = False
isSubStrand (x:xs) [] = False
isSubStrand (x:xs) (y:ys)
| length(x:xs)>length(y:ys) = False
| take (length (x:xs)) (y:ys)==(x:xs) = True
| otherwise = isSubStrand (x:xs) ys
thanks again
Peter Stranney
Ketil Malde
You might also want to look at the earlier `any prefix of tails' suggestion, as it makes the solution a rather simple one-liner.
Wouldn't that be looking for a sub*string*, and not a (general) sub*sequence* (which I think does not have to be contigous?) -kzm -- If I haven't seen further, it is by standing in the footprints of giants Peter Stranney --------------------------------- Do you Yahoo!? Yahoo! Mail - You care about security. So do we.

On Sun, Oct 17, 2004 at 11:41:59AM -0700, Peter Stranney wrote:
Thanks guys for all your help, finally through code, sweat and tears i have found the solution;
isSubStrand:: String -> String -> Bool isSubStrand [] [] = True isSubStrand [] (y:ys) = False isSubStrand (x:xs) [] = False isSubStrand (x:xs) (y:ys) | length(x:xs)>length(y:ys) = False | take (length (x:xs)) (y:ys)==(x:xs) = True | otherwise = isSubStrand (x:xs) ys
thanks again Peter Stranney
Now that you found it, we might as well tell you the other solution: import List -- Point-free (beware of the monomorphism-restriction) isSubStrand' :: Eq a => [a] -> [a] -> Bool isSubStrand' = flip (.) tails . any . isPrefixOf -- and point-full isSubStrand'' x y = any (x`isPrefixOf`) (tails y) Groetjes, Remi "feeling mean" Turk -- Nobody can be exactly like me. Even I have trouble doing it.

Peter Stranney wrote:
isSubStrand:: String -> String -> Bool isSubStrand [] [] = True isSubStrand [] (y:ys) = False isSubStrand (x:xs) [] = False isSubStrand (x:xs) (y:ys) | length(x:xs)>length(y:ys) = False | take (length (x:xs)) (y:ys)==(x:xs) = True | otherwise = isSubStrand (x:xs) ys
Just to muddy the water a bit. . . What happens if the second string is infinite? Sam

Sam Mason writes:
Just to muddy the water a bit. . . What happens if the second string is infinite?
This version should do it: isSubSeq :: (Eq a) => [a] -> [a] -> Bool isSubSeq [] _ = True isSubSeq _ [] = False isSubSeq (x:xs) (y:ys) | x == y = isSubSeq xs ys | otherwise = isSubSeq (x:xs) ys Peter

Peter Simons wrote:
This version should do it:
isSubSeq :: (Eq a) => [a] -> [a] -> Bool isSubSeq [] _ = True isSubSeq _ [] = False isSubSeq (x:xs) (y:ys) | x == y = isSubSeq xs ys ^^^^^^^^
I think you want to refer to List.isPrefixOf here - your version is a sort of "ordered subset" test. I.e. I get: "abc" `isSubSeq` ".a.b.c." ===> True
| otherwise = isSubSeq (x:xs) ys
My version would've been: isSubSeq x = any (isPrefixOf x) . tails But Remi beat me to it (and for that I'll never forgive him! :-). Sam

On Sun, Oct 17, 2004 at 10:53:37PM +0100, Sam Mason wrote:
Peter Simons wrote:
This version should do it:
isSubSeq :: (Eq a) => [a] -> [a] -> Bool isSubSeq [] _ = True isSubSeq _ [] = False isSubSeq (x:xs) (y:ys) | x == y = isSubSeq xs ys ^^^^^^^^
I think you want to refer to List.isPrefixOf here - your version is a sort of "ordered subset" test. I.e. I get:
"abc" `isSubSeq` ".a.b.c." ===> True
as Ketil pointed out, this "subsequence" test may be exactly what the OP meant.
My version would've been:
isSubSeq x = any (isPrefixOf x) . tails
But Remi beat me to it (and for that I'll never forgive him! :-).
Sam
But I only gave the point-free and the point-wise version: You did the half-of-a-point version ;) (which I would actually have used myself too) *ducks and runs*[1] Groetjes, Remi [1] and falls asleep -- Nobody can be exactly like me. Even I have trouble doing it.

Peter Stranney
Thanks guys for all your help, finally through code, sweat and tears i have found the solution;
Well done! I hope you don't mind some further comments?
isSubStrand:: String -> String -> Bool isSubStrand [] [] = True isSubStrand [] (y:ys) = False
You can just call it "ys" here, since the [] case is handled above. Although I see the point of using the pattern to make it explicit. Or you could write the two lines as isSubStrand [] ys = null ys -- null returns a Bool, True iff []
isSubStrand (x:xs) [] = False isSubStrand (x:xs) (y:ys) | length(x:xs)>length(y:ys) = False
You may think of this as an optimization, but it is the opposite - it will count up both lists at each iteration, making the algorithm O(n^2) complexity. Here I'd drop the (x:xs) pattern, and just use xs and ys.
| take (length (x:xs)) (y:ys)==(x:xs) = True
This is also inefficient; length traverses the xs, and equality does it again (until a mismatch) - and look up "isPrefixOf" in the Prelude!
| otherwise = isSubStrand (x:xs) ys
BTW, in addition to "isPrefixOf", look at the function "tails" (also in the List module), and see if you can come up with a short, elegant and efficient solution using these two functions. :-) -kzm -- If I haven't seen further, it is by standing in the footprints of giants
participants (5)
-
Ketil Malde
-
Peter Simons
-
Peter Stranney
-
Remi Turk
-
Sam Mason