
On Sun, Jun 14, 2009 at 11:14 AM, Gjuro Chensen
Gjuro Chensen wrote:
/cut
I dont know everyone will see this, but I would like thank everyone who found time to help, and not spam too much doing it:D. Well, I did it! Its not great (especially comparing to those one line solutions, wow!), but it works.
Nice work. For fun, I'm going to semi-formally transform your solution into the one-liner that was given (multiple times). Systematic transformation is one of the great joys of functional programming. I don't know if you'll find this interesting, but I do, so here goes: myIsUpper = isUpper for ASCII, so let's just assume that.
module Main where
startsWithUpper :: String -> Bool startsWithUpper []= False startsWithUpper string = if myIsUpper(head(string)) then True else False
We can transform this to: startsWithUpper string = isUpper (head string) Under the precondition that the input is not []. So this function has become less general. Now a few systematic transformations to make this smaller: startsWithUpper string = isUpper (head string) startsWithUpper = \string -> isUpper (head string) startsWithUpper = isUpper . head That last step because: f . g = \x -> f (g x) checkAll string = check (words string) checkAll = \string -> check (words string) checkAll = check . words For the same reason as above. check :: [String] -> Bool
check []=False check x = if all startsWithUpper x then True else False
Rewriting the second clause after observing that "if p then True else False" is the same as "p". check [] = False check x = all startsWithUpper x I'm going to take Jochem's suggestion and change the empty clause to True: "all words start with an upper case letter" is equivalent to "there is no word which does not start with an upper case letter", which is true for an empty list. check [] = True check x = all startsWithUpper x Now, in ghci: ghci> all undefined [] True Since this returned True for undefined, it will return True for any argument whatsoever there (this is called the "monotone" property, and all Haskell functions obey it). Therefore, we can remove the empty list clause: check x = all startsWithUpper x And systematic transformations: check = \x -> all startsWithUpper x check = all startsWithUpper So that leaves us with: starsWithUpper = isUpper . head checkAll = check . words check = all startsWithUpper Substituting the local definitions: checkAll = all (isUpper . head) . words The last thing: we made startsWithUpper less general in the process; it is undefined for empty strings. We need to verify that words never returns any empty strings. I did this using SmallCheck: ghci> import Test.SmallCheck ghci> smallCheck 10 $ \string -> all (not . null) (words string) Depth 0: Completed 1 test(s) without failure. Depth 1: Completed 2 test(s) without failure. Depth 2: Completed 5 test(s) without failure. Depth 3: Completed 16 test(s) without failure. Depth 4: Completed 65 test(s) without failure. Depth 5: Completed 326 test(s) without failure. Depth 6: Completed 1957 test(s) without failure. Depth 7: Completed 13700 test(s) without failure. Depth 8: Completed 109601 test(s) without failure. Depth 9: Completed 986410 test(s) without failure. Depth 10: Completed 9864101 test(s) without failure. So I am reasonably confident that words never gives me any empty strings. Tada! Your solution is almost exactly the same as the one-liners! :-) Luke