[web-devel] [Yesod] rendering different templates for different languages

Ian Duncan iand675 at gmail.com
Mon Feb 21 09:05:26 CET 2011


I'm sure there's not a way to do it with 100% accuracy, but doesn't RoR have an English pluralization engine that does a pretty decent job 95% of the time?

On Feb 21, 2011, at 2:21 AM, Michael Snoyman <michael at snoyman.com> wrote:

> There's no way to automatically pluralize an arbitrary word. English
> is the best example of this: cat -> cats, octopus -> octopi, cherry ->
> cherries. There's no universal rule governing this; each word needs to
> be specified manually by the translator. Hebrew is a little easier,
> but still has plenty of exceptions: sometimes male nouns have female
> plural endings and vice-versa. And don't even get into compound nouns.
> 
> As tempting as it is, I don't think there are any ways to make this a
> generic process: each language likely needs to have its own specific
> logic applied.
> 
> Michael
> 
> On Mon, Feb 21, 2011 at 9:37 AM, Ian Duncan <iand675 at gmail.com> wrote:
>> My reasoning for typeclasses is this:
>> Keep in mind this is just a mental exercise, not saying that this would
>> compile...
>> Suppose for your example we wanted to translate it into french:
>> -- Nouns for languages have some way to decide gender, if that matters for
>> the given language
>> class Translate a where
>> toPlural :: Noun a -> Int -> [Words a]
>> data French = French {
>>     ... stuff ...
>>     languageCode = "FR"
>> }
>> instance Translate French where
>> toPlural = frenchPluralizationEngine
>> From there we go with something like your .trans files: we give each
>> language the extension according to their language code. So basket.fr is the
>> french translation:
>> Vous avez #{toPlural 'chien' (maleDogs myBasket)} et #{femaleCats 'chatte'
>> myBasket)} dans votre charrette.
>> This would be pluralized by chien being run through a pluralization engine
>> if necessary
>> I know my thinking is rough so far since you've obviously given it a lot of
>> thought, but does my concept make sense?
>> --
>> Ian Duncan
>> 
>> On Monday, February 21, 2011 at 1:20 AM, Michael Snoyman wrote:
>> 
>> Let's look at a more concrete example: you have an online store
>> selling male dogs and female cats. So you would have:
>> 
>> data Basket = Basket { maleDogs :: Int, femaleCats :: Int }
>> 
>> What you need is a function such as:
>> 
>> renderBasket :: Basket -> String
>> 
>> for each language. In English, this could be something like:
>> 
>> pluralize :: Int -> (String, String) -> String
>> pluralize 1 (x, _) = x
>> pluralize _ (_, x) = x
>> 
>> renderBasket (Basket dogs cats) = concat
>> [ "You have decided to purchase "
>> , show dogs
>> , pluralize dogs ("dog", "dogs")
>> , " and "
>> , show cats
>> , pluralize cats ("cat", "cats")
>> ]
>> 
>> In Hebrew, some words (like years) have a singular, plural *and* dual
>> form, so pluralize for Hebrew may look like:
>> 
>> pluralize :: Int -> (String, Maybe String, String) -> String
>> pluralize 1 (x, _, _) = x ++ " אחד" -- in Hebrew, the "one" comes
>> after the word, all other numbers before
>> pluralize 2 (_, Just x, _) = x -- for dual form, you never show
>> the number, it is assumed
>> pluralize i (_, _, x) = show i ++ " " ++ x -- for the plural, put
>> the number before
>> 
>> If we could build up a library in Haskell of such helper functions, I
>> think it would make translating applications much simpler. But this is
>> the point where we would need a lot of collaboration: I can help out
>> on English and Hebrew (and if I still remember it, Spanish), but I
>> don't know a thing about Japanese, Russian, or most other languages in
>> the world.
>> 
>> I'm not sure how much it would really help to use typeclasses here,
>> however. I think for the most part it will just be an issue of having
>> a separate module for each language. What I'd *really* like to figure
>> out is how to make a nice, easy-to-use wrapper around all of this for
>> translators, who will likely not know any Haskell. Perhaps a language
>> similar to Hamlet:
>> 
>> # strings-english.trans
>> Hello: Hello
>> Person name age: ##{name} is #{age} #{pluralize age "year" "years"} old.
>> Basket dogs cats: You have purchased #{dogs} #{pluralize dogs
>> "dog" "dogs"} and #{cats} #{pluralize cats "cat" cats"}.
>> 
>> Michael
>> 
>> On Mon, Feb 21, 2011 at 8:57 AM, Ian Duncan <iand675 at gmail.com> wrote:
>> 
>> And of course in some languages such as Japanese, there are barely any
>> gender distinctions or such things as pluralization at all. Perhaps we need
>> pluralization, conjugation, and 'genderization' typeclasses with instances
>> defined for different language datatypes?
>> 
>> --
>> Ian Duncan
>> 
>> On Monday, February 21, 2011 at 12:46 AM, Michael Snoyman wrote:
>> 
>> The other day I was speaking with a woman on the train. She was
>> telling me about her daughters. I wanted to ask her how old they are,
>> but I got the pluralization wrong and instead of saying "bnot kama"
>> (plural) I said "bat kama," (singular) to which she responded 36.
>> 
>> tl;dr: You can offend people just was well with pluralization issues
>> as with gender issues.
>> 
>> Michael
>> 
>> On Mon, Feb 21, 2011 at 8:40 AM, Max Cantor <mxcantor at gmail.com> wrote:
>> 
>> Of course, you just pointed out one of the big difficulties with i18n.  I
>> dont think you're wife would take kindly to you referring to her in the male
>> gender.  so now, you need the person's gender too.  i18n is hard :(  the
>> whole would should switch to esperanto.
>> 
>> max
>> 
>> On Feb 21, 2011, at 2:25 PM, Michael Snoyman wrote:
>> 
>> A proper i18n solution is high on my wish list right now, but I've
>> purposely avoided implementing one so far since I'd rather wait until
>> I think we have a good solution as opposed to implementing an
>> acceptable solution now. But let me share my ideas, it might help you
>> out here.
>> 
>> In general, it's very uncommon that you need a completely separate set
>> of templates for each language. Your markup, classes, styles, and
>> logic will likely be identical for each language, and creating a
>> separate template for each will just result in a lot of pain in the
>> long run. Instead, you're likely better off having a single template
>> and just translating strings.
>> 
>> I've blogged about this before[1]. My idea is to use a datatype for
>> your translatable strings, and then have a function that takes a
>> language and a value and returns the translated string. A simple
>> example:
>> 
>>    data Strings = Hello | Person String Int
>>    toEnglish Hello = "Hello"
>>    toEnglish (Person name age) = name ++ " is " ++ show age ++ "
>> years old" -- obviously need to check if person is 1 year old and
>> correct
>> 
>>    toHebrew Hello = "שלום"
>>    toHebrew (Person name age) = name ++ " הוא בן " ++ show age ++ " שנים"
>> 
>> The nice thing about this approach is you have the full power of
>> Haskell to address typical translation issues, such as pluralization,
>> word order and gender matching. (As a counter example, at work, we use
>> XSLT for this, and then you get the full power of XSLT for solving the
>> problem ::cringe::.)
>> 
>> You can then use the languages[2] function from Yesod to help you out:
>> 
>>    getRenderString = chooseFunc `fmap` languages
>>       where
>>         chooseFunc [] = toEnglish -- default language
>>         chooseFunc ("en":_) = toEnglish
>>         chooseFunc ("he":_) = toHebrew
>>         chooseFunc (_:x) = chooseFunc x
>> 
>> Then you can write a handler function like:
>> 
>> getPersonR name age = do
>>    render <- getRenderString
>>    defaultLayout [$hamlet|
>> <h1>#{render Hello}
>> <p>#{render $ Person name age}
>> |]
>> 
>> Which will work for English and Hebrew just fine. Ideally, I would
>> like to add support to Hamlet for this directly, involving a String
>> rendering function similar to the URL rendering function already in
>> place. But for the moment, this should work.
>> 
>> I'd love to hear peoples opinions about this.
>> 
>> Michael
>> 
>> [1] http://docs.yesodweb.com/blog/i18n-in-haskell
>> [2]
>> http://hackage.haskell.org/packages/archive/yesod-core/0.7.0.1/doc/html/Yesod-Request.html#v:languages
>> 
>> On Sun, Feb 20, 2011 at 11:19 PM, Dmitry Kurochkin
>> <dmitry.kurochkin at gmail.com> wrote:
>> 
>> Hi all.
>> 
>> I want a handler to render different templates for different languages.
>> I have getCurrentLanguage function and now I try to do something like:
>> 
>>    getRootR = do
>>        currentLanguage <- getCurrentLanguage
>>        defaultLayout $ do
>>            addWidget $(widgetFile $ currentLanguage ++ "/homepage")
>> 
>> This results in:
>> 
>>    GHC stage restriction: `currentLanguage'
>>      is used in a top-level splice or annotation,
>>      and must be imported, not defined locally
>> 
>> This makes sense to me, because TH is calculated at compile time. I
>> would like to hear ideas how to work around this restriction. Perhaps
>> there is an existing solution in Yesod?
>> 
>> At the moment, the best I could think of is smth like this:
>> 
>>    getRootR = do
>>        currentLanguage <- getCurrentLanguage
>>        defaultLayout $ do
>>            case currentLanguage of
>>                "en" -> addWidget $(widgetFile  "en/homepage")
>>                ... and so on for each language ...
>> 
>> Obviously, this is not a solution taking in account that there are many
>> languages and many handlers.
>> 
>> I was considering creating a global (template file name -> rendered
>> template) map. But I am not sure this is really feasible.
>> 
>> Regards,
>>  Dmitry
>> 
>> _______________________________________________
>> web-devel mailing list
>> web-devel at haskell.org
>> http://www.haskell.org/mailman/listinfo/web-devel
>> 
>> _______________________________________________
>> web-devel mailing list
>> web-devel at haskell.org
>> http://www.haskell.org/mailman/listinfo/web-devel
>> 
>> _______________________________________________
>> web-devel mailing list
>> web-devel at haskell.org
>> http://www.haskell.org/mailman/listinfo/web-devel
>> 
>> 



More information about the web-devel mailing list