Reputation: 21
This is one of my functions which involve a few other more.
main' :: IO ()
main' = do putStr "Enter a string: "
yx <- getLine
let a = chunks yx
let counter = (length . concat . map pairToList) a
let c = 0
let loop = do
let b = a !! c
let kk = xx b
let c = c + 1
let q = oncemore kk
when (c /= (counter)) loop
pp(q)
My question will be at the bottom in bold
I'll let here the rest of the functions expecting new ways to sort my problem. At the end I have an image of how the final output should looks like. (I'm repeating the above code in the bottom one)
module Bigtext where
import Char
import Hugs.Prelude
import Data.List
import Control.Monad
cap :: Char -> Char
cap c = if c >= 'a' && c <= 'z' then chr (ord c - 32) else c
letter' :: Char -> [String]
pp :: [String]->IO()
pp = putStr . concatMap (++"\n")
letter' 'A' = [" AA ",
"A A",
"AAAA",
"A A",
"A A"]
letter' 'B' = ["BBB ",
"B B",
"BBB ",
"B B",
"BBB "]
letter' 'C' = [" CCC",
"C ",
"C ",
"C ",
" CCC"]
letter' 'D' = ["DDD ",
"D D",
"D D",
"D D",
"DDD "]
letter' 'E' = ["EEEE",
"E ",
"EEE ",
"E ",
"EEEE"]
letter' 'F' = ["FFFF",
"F ",
"FFF ",
"F ",
"F "]
letter' 'G' = [" GGG ",
"G ",
"G GG",
"G G",
" GGG "]
letter' 'H' = ["H H",
"H H",
"HHHH",
"H H",
"H H"]
letter' 'I' = ["III",
" I ",
" I ",
" I ",
"III"]
letter' 'J' = [" J",
" J",
" J",
"J J",
" JJJ "]
letter' 'K' = ["K K",
"K K ",
"KK ",
"K K ",
"K K"]
letter' 'L' = ["L ",
"L ",
"L ",
"L ",
"LLLL"]
letter' 'M' = ["M M",
"MM MM",
"M M M",
"M M",
"M M"]
letter' 'N' = ["N N",
"NN N",
"N N N",
"N NN",
"N N"]
letter' 'O' = [" OOO ",
"O O",
"O O",
"O O",
" OOO "]
letter' 'P' = ["PPPP ",
"P P",
"PPPP ",
"P ",
"P "]
letter' 'Q' = [" QQQ ",
"Q Q ",
"Q Q ",
"Q QQ ",
" QQQQQ"]
letter' 'R' = ["RRRR ",
"R R",
"RRRR ",
"R R ",
"R RR"]
letter' 'S' = [" SSS ",
"S ",
" SSS ",
" S",
"SSSS "]
letter' 'T' = ["TTTTTT",
" TT ",
" TT ",
" TT ",
" TT "]
letter' 'U' = ["U U",
"U U",
"U U",
"U U",
" UUU "]
letter' 'V' = ["V V",
"V V",
" V V ",
" V V ",
" V "]
letter' 'W' = ["W W",
"W W",
"W W W",
" W W W ",
" W W "]
letter' 'X' = ["X X",
" X X ",
" X ",
" X X ",
"X X"]
letter' 'Y' = ["Y Y",
" Y Y ",
" Y ",
" Y ",
" Y "]
letter' 'Z' = ["ZZZZZ",
" Z ",
" Z ",
" Z ",
"ZZZZZ"]
letter' ' ' = [" ",
" ",
" ",
" ",
" "]
letter' c = letter' (cap c)
letter :: Char -> IO()
letter c = pp(letter' (cap c))
zipAll :: [[String]] -> [String]
zipAll = map unwords . transpose
chunk :: Int -> [a] -> [[a]]
chunk _ [] = []
chunk n xs = first : chunk n rest where (first, rest) = splitAt n xs
splitSkip :: Int -> [a] -> [[a]]
splitSkip n xs = transpose $ chunk n xs
chunks yx = words yx
pairToList :: a -> [a]
pairToList x = [x]
xx b = zipAll (map (letter' . head) (splitSkip (length b) b))
type MyString = [String]
oncemore :: MyString -> MyString
oncemore kk = kk ++ kk
main' :: IO ()
main' = do putStr "Enter a string: "
yx <- getLine
let a = chunks yx
let counter = (length . concat . map pairToList) a
let c = 0
let loop = do
let b = a !! c
let kk = xx b
let c = c + 1
let q = oncemore kk
when (c /= (counter)) loop
pp(q)
This is the expected output:
This is where I am at the moment
main' :: IO ()
main' = do putStr "Enter a string: "
yx <- getLine
let a = chunks yx
let counter = (length . concat . map pairToList) a
let c = 0
let loop c = do
let c' = c + 1
let b = a !! (c'-1)
let kk = xx b
if c' /= counter
then return kk
else loop c'
**kk <- loop c**
pp(kk)
In the line kk <- loop c if I change c for a number, its possible to get a word (depending of how many words your input has) the problem is: How do I print all the index's?? for example if I have 3 words, how do I print it out without hard code?
Sorry about my english... And thank you for your time.
Upvotes: 1
Views: 245
Reputation: 12749
The whole thing can be accomplished with the following:
module Main where
import Data.List (transpose)
import Data.Char (ord, chr, toUpper)
pp :: [String] -> IO ()
pp = putStr . unlines
letter :: Char -> [String]
{- letter definitions go here -}
-- anything else gets a square of ?'s
letter _ = ["?????",
"? ?",
"? ?",
"? ?",
"?????"]
bigify :: String -> [String]
bigify = map unwords . transpose . map (letter . toUpper)
main :: IO ()
main = do putStr "Enter a string: "
getLine >>= pp . concatMap bigify . words
In main
, we get a line of text, break it into words, and for each word, bigify
the word into lines, concatenate the lines, and pp
the whole thing.
The bigify
function maps each character in its word argument, passing each character to toUpper
and then letter
, which converts it to a list of lines for the upper-case version of that character. The result is a list with an element per character where each element is a list of lines for that character. This is transpose
d into a list with an element per line where each element is a list of pieces of each character for that line. These elements are joined with unwords
to form a list of lines.
Upvotes: 0
Reputation: 120711
Haskell variables aren't “variable” in the sense that programmers usually interpret the word, namely, they aren't mutable. Basically, any Haskell variable is just a local constant. Hence your loop construct doesn't make sense, namely
let c = 0
let loop = do
...
let c = c + 1
when (c /= counter) loop
does not work at all.
let c = c + 1
. This does not modify the existing c
, instead it just defines a completely separate variable c
which, because it's in a narrower scope, shadows the former c = 0
. This shadowing binding is even used in the definition itself, i.e. to calculate c
the runtime needs to know the value of c
, to which it needs to calculate c
, to which... and so on.What you actually want there is
let c = 0
let loop c = do
...
let c' = c + 1
when (c' /= counter) $ loop c'
loop 0 -- actually invoke the loop, starting from 0.
But even so, this loop doesn't really accomplish anything – you merely define some local variables in each iteration, but never actually do anything of lasting impact with them.
You could in each iteration commit some actual IO
action, such as printing out a single big letter. You could also yield some result from the loop, which seems to be what you're asking in this question. For instance, to broadcast the last “state” of q
to the outside, you'd need to replace the when
(which shortcuts to return ()
if the condition is not fulfilled) with
let loop c = do
let q = ...
let c' = c + 1
if c' == counter
then return q
then loop c'
q <- loop 0
But I dispute that this is sensible; instead, a much better approach is to concatenate all the letters still in list form (that doesn't require any ugly index/length juggling nor any IO or explicit loops, just map
and concat
), and then printing the entire result in one clean putStr
.
Upvotes: 4