-- Read and show integers from the standard input stream
{-
   The file name should generally be the same as the module name.
   But these short modules are not used as a library elsewhere,
   so the file name does not matter.
-}

module Main where

{-
   Data.Text (UTF-16) is sometimes more efficient than strings, and has
   the same interface (ineract, words, unlines, ec) as strings (sort of).

   It is generally more efficient that strings a pipeline of text funtions
   may have to allocate the space for the characters only once.
-}

import qualified Data.Text as T
import qualified Data.Text.Read as R
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (toLazyText)
import Data.Text.Lazy.Builder.Int (decimal)
import qualified Data.Text.IO as TextIO (interact)

{-
   (.)    :: (a->b) -> (c->a) -> c -> b
   map             :: a->b -> [a] ->[b]        ; apply function to every item in sequence
   either :: (a->c) -> (b->c) -> Either a b -> c
   T.words         :: T.Text->[T.Text]         ; breaks text into words at whitespace
   T.unlines       :: [T.Text] -> T.Text       ; ends every text with a newline
   TextIO.interact :: (T.Text->T.Text) -> IO (); the input and the output is text
 -}

main :: IO()
main = TextIO.interact (T.unlines . map (intToText . readInt) . T.words)

-- Converting T.Text to Int requires more care than 'read' takes as we must
-- deal with input that is not merely decimal digits.
readInt :: T.Text -> Int
readInt text = either error fst (R.decimal text)

-- Using 'T.pack . show :: Int -> T.Text' would be easier, but possibly
-- not as efficient as the following:
intToText :: Integral a => a -> T.Text
intToText = toStrict . toLazyText . decimal

--  ------------For GNU Emacs ------------
--  Local Variables:
--  compile-command: "ghc -Wall main3T.hs"
--  End: