module Main where

import qualified Data.List as List -- (sort, groupBy)
import Data.Ord (comparing)
import Data.Tuple (swap)
import Text.Printf (printf)

main :: IO()
main = interact (unlines . (map format) . sortByNum . count . words)

-- descreasing sort by number, then increasing sort by word
sortByNum :: [(String,Int)] -> [(String,Int)]
sortByNum = List.sortBy cmp
  where
    cmp :: (Ord a, Ord b) => (a, b) -> (a, b) -> Ordering
    cmp = flip (comparing snd) `mappend` (comparing snd)

count :: [String] -> [(String,Int)]
count = map (\ws->(head ws, length ws)) . List.groupBy (==) . List.sort

format :: (String,Int) -> String
format (s,l) = printf "%15s %3d" s l