Computer Science Canada

Exercise: Palindromes and Isograms

Author:  wtd [ Fri May 09, 2008 1:31 am ]
Post subject:  Exercise: Palindromes and Isograms

Write a program which reads in a line of input, splits it up into words, then outputs (in order) words that are either palindromes or isograms.

Please note that words containing spaces may be input by surrounding them with quotes. Quotes may be input themselves by escaping them with a backslash.

Again, please identify the language you choose to use.

Author:  Saad [ Fri May 09, 2008 4:50 pm ]
Post subject:  Re: Exercise: Palindromes and Isograms

Haven't coded in haskell for a while but I decided to try it anyway
Haskell:
import Char

separateWords :: String -> [String]
separateWords line@(x:xs) | x == '\"' = separateWords_ "" [] xs True
                          | otherwise = separateWords_ "" [] xs False

separateWords_ :: String -> [String] -> String -> Bool -> [String]
separateWords_ currentWord allWords (x:xs) True | x == '\"' = separateWords_ "" (allWords ++ [currentWord]) xs False
                                                | otherwise = separateWords_ (currentWord ++ [x]) allWords xs True

separateWords_ "" allWords [] _ = allWords
separateWords_ "" allWords (x:xs) False | x == '\"' = separateWords_ "" (allWords) xs True
                                        | x == ' ' = separateWords_ "" (allWords) xs False
                                       
separateWords_ currentWord allWords (x:xs) False| x == '\"' = separateWords_ "" (allWords ++ [currentWord]) xs True
                                                | x == ' ' = separateWords_ "" (allWords ++ [currentWord])  xs False
                                                | otherwise = separateWords_ (currentWord ++ [x]) allWords xs False
separateWords_ currentWord allWords [] _ = allWords ++ [currentWord]

isPalindrome :: String -> Bool
isPalindrome string = word == reverse word
                where
                    word = filter isAlpha string

isIsograph :: String -> Bool
isIsograph string = not $ any (\letters -> length letters /= 1) $ group $ sort string
                   
main = getLine >>= \input -> print $ filter (\word -> isPalindrome word || isIsograph word) $ separateWords $ map (toLower) input

Author:  md [ Fri May 09, 2008 5:40 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

For those of us who are lazy (me), what's an isogram. And does it have to be a palindrome of real words?

Author:  rizzix [ Fri May 09, 2008 8:26 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

Here's mine: < see code below >

Edit: syntax tags are getting to be really annoying

Author:  rizzix [ Fri May 09, 2008 8:32 pm ]
Post subject:  Re: RE:Exercise: Palindromes and Isograms

md @ Fri May 09, 2008 5:40 pm wrote:
For those of us who are lazy (me), what's an isogram. And does it have to be a palindrome of real words?


An isogram is-a palindrome, so just check for palindromes Razz

Author:  Saad [ Fri May 09, 2008 8:51 pm ]
Post subject:  Re: Exercise: Palindromes and Isograms

As rizzix pointed out before, I did have errors in my code. I make a couple of errors that I should have caught (I did test it just not thoroughly enough). Error is now fixed what I thought were the errors.
code:
import Char
import List

separateWords :: String -> [String]
separateWords line@(x:xs) | x == '\"' = separateWords_ "" [] xs True
                          | otherwise = separateWords_ [x] [] xs False
    where
        separateWords_ :: String -> [String] -> String -> Bool -> [String]
        separateWords_ currentWord allWords (x:xs) True | x == '\"' = separateWords_ "" (allWords ++ [currentWord]) xs False
                                                        | otherwise = separateWords_ (currentWord ++ [x]) allWords xs True
                                                       
        separateWords_ "" allWords [] _ = allWords
        separateWords_ "" allWords (x:xs) False | x == '\"' = separateWords_ "" (allWords) xs True
                                                | x == ' ' = separateWords_ "" (allWords) xs False
                                               
        separateWords_ currentWord allWords (x:xs) False| x == '\"' = separateWords_ "" (allWords ++ [currentWord]) xs True
                                                        | x == ' ' = separateWords_ "" (allWords ++ [currentWord])  xs False
                                                        | otherwise = separateWords_ (currentWord ++ [x]) allWords xs False
        separateWords_ currentWord allWords [] _ = allWords ++ [currentWord]

isPalindrome :: String -> Bool
isPalindrome string = word == reverse word
                where
                    word = map toLower $ filter isAlpha string

isIsograph :: String -> Bool
isIsograph string = all (\letters -> length letters == 1) $ group $ sort string
                   
main = getLine >>= \input -> mapM_ (print) $ filter (\word -> isPalindrome word || isIsograph word) $ separateWords input


And a sample output
code:
>ghc a.hs
>Exit code: 0
>main
Race qux foo foof Saad sad "race car" "cars"
"Race"
"qux"
"foof"
"sad"
"race car"
"cars"
>Exit code: 0


rizzix @ Fri May 09, 2008 8:32 pm wrote:
md @ Fri May 09, 2008 5:40 pm wrote:
For those of us who are lazy (me), what's an isogram. And does it have to be a palindrome of real words?


An isogram is-a palindrome, so just check for palindromes Razz


From the definition from wikipedia

An isogram (also known as a "nonpattern word") is a logological term for a word or phrase without a repeating letter. Link here

Author:  richcash [ Fri May 09, 2008 8:56 pm ]
Post subject:  Re: Exercise: Palindromes and Isograms

Well, on wikipedia, one of the defintions for isograms says a word with each letter appearing exactly once. Only under the latter definition that isograms are words where each letter appears the same number of times would palindromes be a subset of isograms.

So there might be some ambiguity here unless one of those definitions is implied for CS problems.

Edit : ^Saad beat me to it.

Author:  rizzix [ Fri May 09, 2008 9:08 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

Oh interesting... I thought it was `just` single letter words like aaa, bbb, etc

Saad: Shouldn't you account for single-quoted strings?

wtd: way to go, for making it so ambiguous Razz

Author:  wtd [ Fri May 09, 2008 10:06 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

In this case, it's defined as a word with no repeating letters.

And no, you don't have to check to make sure the "words" are valid.

Author:  rizzix [ Fri May 09, 2008 10:31 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

OK, so what about strings like: 'abc def ghi'

The space character appears twice. Would that be considered an isogram?

Author:  wtd [ Fri May 09, 2008 10:38 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

No, it does not count. That would be an isogram. Isograms for the purposes of this exercise are case-insensitive.

Author:  rizzix [ Fri May 09, 2008 10:45 pm ]
Post subject:  Re: RE:Exercise: Palindromes and Isograms

wtd @ Fri May 09, 2008 10:38 pm wrote:
Isograms for the purposes of this exercise are case-insensitive.


You know that only makes it longer, not shorter Razz

Author:  btiffin [ Fri May 09, 2008 10:47 pm ]
Post subject:  Re: Exercise: Palindromes and Isograms

Here's one in REBOL. It does not handle escaped quotes with backslash, but caret instead.
REBOL:
#!rebol -c
rebol []
line: ask "? "
words: parse/all line " "
probe words
foreach word words [
    mod: uppercase trim/all copy word
    if equal? mod reverse copy mod [print ["Palindrome:" word]]
    iso: copy []
    foreach ch mod [
        alter iso ch
    ]
    if equal? length? iso length? word [print ["Isogram:" word]]
]
Output:

$ ./palins.r
? "Naomi, sex at noon taxes, I moan" aba "was saw" shockingly
["Naomi, sex at noon taxes, I moan" "aba" "was saw" "shockingly"]
Palindrome: Naomi, sex at noon taxes, I moan
Palindrome: aba
Palindrome: was saw
Isogram: shockingly

Author:  rizzix [ Fri May 09, 2008 11:10 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

Here everything inclusive of the case-check:
Haskell:
import List (nub)
import Char (toLower)

main = getLine >>= (mapM_ putStrLn) . (filter isIsoOrPalin) . strings []
    where strings rs []        = reverse rs
          strings rs ('\'':xs) = let (ys, ss) = esc_single xs [] in strings (ys:rs) ss
          strings rs ('"':xs)  = let (ys, ss) = esc_double xs [] in strings (ys:rs) ss
          strings rs (' ':xs)  = let (ys, ss) = word xs [] in strings (ys:rs) ss
          strings rs xs        = let (ys, ss) = word xs [] in strings (ys:rs) ss
         
          esc_single ('\\':'\'':xs) rs = esc_single xs ('\'':rs)
          esc_single [] rs             = (reverse rs, [])
          esc_single ('\'':xs) rs      = (reverse rs, xs)
          esc_single (x:xs) rs         = esc_single xs (x:rs)
         
          esc_double ('\\':'"':xs) rs  = esc_double xs ('"':rs)
          esc_double [] rs             = (reverse rs, [])
          esc_double ('"':xs) rs       = (reverse rs, xs)
          esc_double (x:xs) rs         = esc_double xs (x:rs)
         
          word (' ':xs) rs = (reverse rs, xs)
          word (x:xs)   rs = word xs (x:rs)
          word []       rs = (reverse rs, [])
         
          isIsoOrPalin xs = let rs = filter ((/=) ' ') (map toLower xs)
                            in xs == reverse xs || nub rs == rs


btiffin: is parse a builtin function?

Author:  btiffin [ Sat May 10, 2008 12:11 am ]
Post subject:  Re: Exercise: Palindromes and Isograms

Quote:
btiffin: is parse a builtin function?

Yep, and I'm just using the string splitting feature. In block mode it includes Icon like pattern matching with to, thru charset matching, datatypes and literals, bobloblaw, with expression evaluation on every match step. Smile

In the case I used, the rule was simply " ", meaning split using space as a delimiter. I really should have included ^- for tabs as well. And my code would probably FAIL given that I didn't bother to properly parse for backslash escaped quotes. Sad REBOL uses caret for escaping.

Cheers

Author:  btiffin [ Sat May 10, 2008 1:48 am ]
Post subject:  Re: Exercise: Palindromes and Isograms

Update to the REBOL version. I was so excited about getting a chance to use alter that I skipped the obvious, and I added tabs to the delimters this time. alter is short for alternate, it scans a series! and either inserts or removes the value. Its use is normally limited to handling flags, so I thought this would be another use, but unique is more appropriate.
REBOL:
#!rebol -c
rebol []
line: ask "? "
words: parse/all line " ^-"
probe words
foreach word words [
    mod: uppercase trim/all copy word
    if equal? mod reverse copy mod [print ["Palindrome:" word]]
    if equal? length? unique mod length? mod [print ["Isogram:" word]]
]

wtd; Your exercises are cutting into my breaks! Smile

Author:  Saad [ Sat May 10, 2008 11:50 am ]
Post subject:  Re: Exercise: Palindromes and Isograms

rizzix wrote:
Saad Shouldn't you account for single-quoted strings?


Correct again. However I realised a better way of doing it with help from regular expressions

Was done with GHC version 6.8.2

Compiled via
code:
ghc <name> -package regex-compat-0.71.0.1

Haskell:
import List (sort, group)
import Char (toLower, isAlpha)
import Text.Regex

main = getLine >>= \input -> mapM_ putStrLn $ filter (\word -> isPalindrome word || isIsograph word) $ separateWords [] $ fixString input
    where
        fixString string = subRegex (mkRegex "( *\\\\*(\'|\") *)") string "~"
       
        separateWords :: [String] -> String -> [String]
        separateWords allWords "" = allWords
        separateWords allWords (' ':rest) = separateWords allWords rest
        separateWords allWords ('~':rest) = let (word, _:remainder) = span (\char -> char /= '~') rest in separateWords (allWords ++ [word]) remainder
        separateWords allWords string = let (word, remainder) = span (\char -> char /= ' ' && char /= '~') string in separateWords (allWords ++ [word]) remainder
       
        isPalindrome :: String -> Bool
        isPalindrome string = let word = map toLower $ filter isAlpha string in word == reverse word

        isIsograph :: String -> Bool
        isIsograph string = all (\letters -> length letters == 1) $ group $ sort $ map toLower $ filter isAlpha string


Basically I replace all the quotation types with a ~ and then its simple string manipulation

Author:  rizzix [ Sat May 10, 2008 2:10 pm ]
Post subject:  RE:Exercise: Palindromes and Isograms

what if the word was 'abc ~ def'

Author:  Saad [ Sat May 10, 2008 2:22 pm ]
Post subject:  Re: RE:Exercise: Palindromes and Isograms

rizzix @ Sat May 10, 2008 2:10 pm wrote:
what if the word was 'abc ~ def'


It was done assuming that the words entered would be valid words.

However another version based on the same idea but with support of characters like ~ (although wtd could make what he wants more clear if he wants that kind of support or not)
Haskell:
import List (sort, group)
import Char (toLower, isAlpha)

main = getLine >>= \input -> mapM_ putStrLn $ filter (\word -> isPalindrome word || isIsograph word) $ separate input
    where
        separate :: String -> [String]
        separate line = separateWords [] line
            where
                separateWords :: [String] -> String -> [String]

                separateWords allWords "" = allWords
                separateWords allWords (' ':rest) = separateWords allWords rest
                   
                separateWords allWords ('\\':'\'':rest) = let (word, _:_:remainder) = span (\char -> char /= '\\') rest in separateWords (allWords ++ [word]) remainder
                separateWords allWords ('\\':'\"':rest) = let (word, _:_:remainder) = span (\char -> char /= '\\') rest in separateWords (allWords ++ [word]) remainder
                separateWords allWords ('\'':rest) = let (word, _:remainder) = span (\char -> char /= '\'') rest in separateWords (allWords ++ [word]) remainder
                separateWords allWords ('\"':rest) = let (word, _:remainder) = span (\char -> char /= '\"') rest in separateWords (allWords ++ [word]) remainder

                separateWords allWords string = let (word, remainder) = span (\char -> char /= ' ') string in separateWords (allWords ++ [word]) remainder
               
        isPalindrome :: String -> Bool
        isPalindrome string = let word = map toLower $ filter (\x -> x /= ' ') string in word == reverse word
   
        isIsograph :: String -> Bool
        isIsograph string = all (\letters -> length letters == 1) $ group $ sort $ map toLower string

Author:  rizzix [ Sat May 10, 2008 2:39 pm ]
Post subject:  Re: Exercise: Palindromes and Isograms

Here's another approach to this, using Parser Combinators.

Scala:
import scala.util.parsing.combinator.lexical._;
import scala.util.parsing.input.CharArrayReader.EofCh

object Test extends Application {
    case class Word(str : String)
   
    def isIsoPalin(s : List[Char]) =  s == s.reverse || s.removeDuplicates == s
   
    object Lexer extends Lexical {
        type Token = Word
       
        val sq = '\''; val dq = '"'; val bs = '\\'
       
        def whitespace = ' '?
       
        def token = (
            sq ~ ((bs ~ sq | chrExcept(sq, EofCh))+) ~ sq ^^ {case _ ~ xs ~ _ => Word(deflate(xs))}
          | dq ~ ((bs ~ dq | chrExcept(dq, EofCh))+) ~ dq ^^ {case _ ~ xs ~ _ => Word(deflate(xs))}
          | rep(' ') ~ (chrExcept(' ', EofCh)+)           ^^ {case _ ~ xs     => Word(xs mkString "")}
        );
       
        private def deflate(xs : List[Any]) : String = xs match {
            case (bs ~ c) :: ys => c.toString + deflate(ys)
            case y :: ys => y + deflate(ys)
            case _ => ""
        }
    }
   
    var scanner = new Lexer.Scanner(readLine)
   
    while (!scanner.atEnd) {
        scanner.first match {case Word(str) => if (isIsoPalin(str.toList.filter {_ != ' '} )) println(str)}
        scanner = scanner.rest
    }
}


Edit: fixed some bugs, cleaned up code.


: