Johannes Waldmann wrote: > What methods and tools are there for i18n of Haskell programs? > > (I.e. I want output in several languages, > with the language configurable at runtime, > and I want to add languages without recompilation.) > > a typical source text (for my application) is here > http://141.57.11.163/cgi-bin/cvsweb/tool/src/Graph/Circle/Plain.hs?rev=1.2 > it contains (German) text strings all over the place. > > In Java/Eclipse, I would "Source -> Externalize Strings" > and this replaces each string by something like > Messages.getString("Foobar.0") where Messages is a global variable > (constructed at program start from reading a properties file) > > In Haskell, I see at least two problems: > a) reading the file is in IO > b) there are no "global variables". implicit parameters perhaps? > c) when I'm trying to be clever, I use "deriving Show/Read" or similar. > then i18n should rename the constructors/accessors? I rather not. > http://141.57.11.163/cgi-bin/cvsweb/tool/src/Grammatik/Type.hs.drift?rev=1.6
Fortunately, a) is unavoidable in general :) But assuming that the language loading only happens at startup, I'd go for an unsafePerformIO: module Main where main = do language <- getArgs initInternationalization language ... module Internationalization where initInternationalization lang = do ... writeIORef stringTable ... {-# NOINLINE stringTable #-} stringTable :: IORef (Data.Map String String) stringTable = unsafePerformIO $ newIORef $ Map.empty {-# NOINLINE getString #-} getString :: String -> String getString = unsafePerformIO $ do map <- readIORef stringTable return $ \s -> fromJust' s $ lookup s map where fromJust' (Just x) _ = x fromJust' Nothing s = "[untranslated message] " ++ s You can use (getString) just as you would use (Messages.getString("...")). Note that the language is fixed after first call to getString and it's not wise to call getString before initInternationalization. There is no way to change the language after startup which is probably what you want. If not, then you just have to float (\s ->) out of unsafePerformIO: getString = \s -> unsafePerformIO $ do ... return $ fromJust' ... Of course, you can also integrate the initialization into (getString). Regards, apfelmus _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell