-- Copyright (C) 2008 Eric Kow
--
-- This program is free software; you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation; either version 2, or (at your option)
-- any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program; see the file COPYING.  If not, write to
-- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
-- Boston, MA 02110-1301, USA.

-- |
-- Copyright   : 2008 Eric Kow
-- License     : GPL
-- Maintainer  : darcs-devel@darcs.net
-- Stability   : experimental
-- Portability : portable
--
-- This modules provides rudimentary natural language generation
-- (NLG) utilities.  That is, generating natural language from a
-- machine representation.  Initially, only English is supported at
-- all.  Representations are implemented for:
--
--  * countable nouns (plurality); and
--  * lists of clauses (foo, bar and/or baz).

module Darcs.Util.English where

import Darcs.Prelude

import Data.Char (toUpper)
import Data.List (isSuffixOf)

import Darcs.Util.Printer ( Doc, vcat, text )

-- | > englishNum 0 (Noun "watch") "" == "watches"
--   > englishNum 1 (Noun "watch") "" == "watch"
--   > englishNum 2 (Noun "watch") "" == "watches"
englishNum :: Countable n => Int -> n -> ShowS
englishNum :: Int -> n -> ShowS
englishNum Int
x = if Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then n -> ShowS
forall a. Countable a => a -> ShowS
singular else n -> ShowS
forall a. Countable a => a -> ShowS
plural

-- | Things that have a plural and singular spelling
class Countable a where
    plural :: a -> ShowS
    singular :: a -> ShowS

-- | This only distinguishes between nouns with a final -ch,
--   and nouns which do not.
--   More irregular nouns will just need to have their own type
--
--   > plural (Noun "batch") "" == "batches"
--   > plural (Noun "bat")   "" == "bats"
--   > plural (Noun "mouse") "" == "mouses" -- :-(
newtype Noun = Noun String
data Pronoun = It

instance Countable Noun where
    -- more irregular nouns will just need to have their own type
    plural :: Noun -> ShowS
plural (Noun String
s) | String
"ch" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
s = String -> ShowS
showString String
s ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  String -> ShowS
showString String
"es"
    plural (Noun String
s) | String
"y" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
s
                      Bool -> Bool -> Bool
&& String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
                      Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
last (ShowS
forall a. [a] -> [a]
init String
s) Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
"aeiou" =
                            String -> ShowS
showString (ShowS
forall a. [a] -> [a]
init String
s) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"ies"
    plural (Noun String
s) = String -> ShowS
showString String
s ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
's'
    singular :: Noun -> ShowS
singular (Noun String
s) =  String -> ShowS
showString String
s

instance Countable Pronoun where
    plural :: Pronoun -> ShowS
plural Pronoun
It = String -> ShowS
showString String
"them"
    singular :: Pronoun -> ShowS
singular Pronoun
It = String -> ShowS
showString String
"it"

-- | > singular This (Noun "batch") "" == "this batch"
--   > plural   This (Noun "batch") "" == "these batches"
data This = This Noun

instance Countable This where
    plural :: This -> ShowS
plural (This Noun
s)   = String -> ShowS
showString String
"these "  ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Noun -> ShowS
forall a. Countable a => a -> ShowS
plural Noun
s
    singular :: This -> ShowS
singular (This Noun
s) = String -> ShowS
showString String
"this "   ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Noun -> ShowS
forall a. Countable a => a -> ShowS
singular Noun
s

-- | Given a list of things, combine them thusly:
--
--   > orClauses ["foo", "bar", "baz"] == "foo, bar or baz"
andClauses, orClauses :: [String] -> String
andClauses :: [String] -> String
andClauses = String -> [String] -> String
itemize String
"and"
orClauses :: [String] -> String
orClauses = String -> [String] -> String
itemize String
"or"

anyOfClause :: [String] -> Doc
anyOfClause :: [String] -> Doc
anyOfClause [String]
names = if [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
names Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then String -> Doc
text String
"any of" else Doc
forall a. Monoid a => a
mempty

itemizeVertical :: Int -> [String] -> Doc
itemizeVertical :: Int -> [String] -> Doc
itemizeVertical Int
indent = [Doc] -> Doc
vcat ([Doc] -> Doc) -> ([String] -> [Doc]) -> [String] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text (String -> Doc) -> ShowS -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
indent Char
' ' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"- ") String -> ShowS
forall a. [a] -> [a] -> [a]
++))

-- Should not be called with an empty list since this usually
-- prints an extra space. We allow it for compatibility.
itemize :: String -> [String] -> String
itemize :: String -> [String] -> String
itemize String
_ [] = String
"" -- error "precondition in Darcs.Util.English.itemize"
itemize String
_ [String
x] = String
x
itemize String
sep [String
x,String
x'] = [String] -> String
unwords [String
x, String
sep, String
x']
itemize String
sep (String
x:String
x':[String]
xs) = String -> String -> [String] -> String
itemize' String
x String
x' [String]
xs where
  itemize' :: String -> String -> [String] -> String
itemize' String
y String
y' [] = [String] -> String
unwords [String
y String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
",", String
sep, String
y']
  itemize' String
y String
y' (String
y'':[String]
ys) = [String] -> String
unwords [String
y String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
",", String -> String -> [String] -> String
itemize' String
y' String
y'' [String]
ys]

presentParticiple :: String -> String
presentParticiple :: ShowS
presentParticiple String
v | String -> Char
forall a. [a] -> a
last String
v Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'e' = ShowS
forall a. [a] -> [a]
init String
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"ing"
                     | Bool
otherwise = String
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"ing"

-- | Capitalize the first letter of a word
capitalize :: String -> String
capitalize :: ShowS
capitalize []     = []
capitalize (Char
x:String
xs) = Char -> Char
toUpper Char
x Char -> ShowS
forall a. a -> [a] -> [a]
: String
xs