[Pkg-haskell-commits] [bustle] 01/06: Imported Upstream version 0.4.7

Hector Oron zumbi at moszumanska.debian.org
Tue Sep 23 22:29:49 UTC 2014


This is an automated email from the git hooks/post-receive script.

zumbi pushed a commit to branch master
in repository bustle.

commit 9ba4748b9ee22ee3a755d609532252cb8531b2f7
Author: Héctor Orón Martínez <zumbi at debian.org>
Date:   Wed Sep 24 00:02:06 2014 +0200

    Imported Upstream version 0.4.7
---
 Bustle.hs                      |   2 +
 Bustle/Application/Monad.hs    |  23 ++--
 Bustle/Diagram.hs              |   4 +-
 Bustle/Loader.hs               |   5 +-
 Bustle/Monitor.hs              |  11 +-
 Bustle/Noninteractive.hs       |   9 +-
 Bustle/StatisticsPane.hs       |  35 +++---
 Bustle/Translation.hs          |  25 ++++
 Bustle/UI.hs                   |  30 ++---
 Bustle/UI/AboutDialog.hs       |  15 +--
 Bustle/UI/DetailsView.hs       |  27 +++--
 Bustle/UI/FilterDialog.hs      |   5 +-
 Bustle/UI/Recorder.hs          |   8 +-
 Bustle/Util.hs                 |   3 +-
 INSTALL                        |  31 +++--
 Makefile                       |  57 +++++++--
 NEWS                           |  46 +++++++
 Setup.hs                       | 113 ++++++++++++++++-
 bustle.cabal                   |  38 ++++--
 bustle.sh                      |   3 +
 c-sources/bustle-pcap.c        |   4 +-
 c-sources/pcap-monitor.c       |  37 ++++--
 data/bustle.appdata.xml.in     |  24 ++++
 data/bustle.desktop.in         |   9 ++
 data/bustle.png                | Bin 1282 -> 0 bytes
 data/bustle.ui                 |  19 +--
 data/icons/16x16/bustle.png    | Bin 0 -> 519 bytes
 data/icons/22x22/bustle.png    | Bin 0 -> 716 bytes
 data/icons/256x256/bustle.png  | Bin 0 -> 8774 bytes
 data/icons/32x32/bustle.png    | Bin 0 -> 1049 bytes
 data/icons/48x48/bustle.png    | Bin 0 -> 1669 bytes
 data/icons/scalable/bustle.svg | 266 +++++++++++++++++++++++++++++++++++++++++
 po/en.po                       | 164 +++++++++++++++++++++++++
 po/messages.pot                | 157 ++++++++++++++++++++++++
 34 files changed, 1035 insertions(+), 135 deletions(-)

diff --git a/Bustle.hs b/Bustle.hs
index a6e8a75..a5cb5c5 100644
--- a/Bustle.hs
+++ b/Bustle.hs
@@ -25,6 +25,7 @@ import System.Environment (getArgs)
 import System.Exit (exitFailure)
 import Control.Monad (when)
 import Bustle.Noninteractive
+import Bustle.Translation
 import Bustle.UI
 
 usage :: Bool
@@ -49,6 +50,7 @@ runOne _ _ = usage True
 
 main :: IO ()
 main = do
+    initTranslation
     args <- getArgs
 
     case args of
diff --git a/Bustle/Application/Monad.hs b/Bustle/Application/Monad.hs
index 43526a1..6d7f3c9 100644
--- a/Bustle/Application/Monad.hs
+++ b/Bustle/Application/Monad.hs
@@ -58,24 +58,25 @@ newtype Bustle config state a = B (ReaderT (BustleEnv config state) IO a)
   deriving (Functor, Monad, MonadIO)
 
 newtype BustleEnv config state =
-    BustleEnv { unBustleEnv :: IORef (config, state) }
+    BustleEnv { unBustleEnv :: (config, IORef state) }
 
 readConfig :: MonadIO m
            => BustleEnv config state
            -> m config
-readConfig = liftM fst . liftIO . readIORef . unBustleEnv
+readConfig = return . fst . unBustleEnv
 
 readState :: MonadIO m
           => BustleEnv config state
           -> m state
-readState  = liftM snd . liftIO . readIORef . unBustleEnv
+readState  = liftIO . readIORef . snd . unBustleEnv
 
 putState :: MonadIO m
          => state
          -> BustleEnv config state
          -> m ()
 putState new e = liftIO $ do
-    modifyIORef (unBustleEnv e) $ \(conf, _) -> (conf, new)
+    let (_, r) = unBustleEnv e
+    liftIO $ writeIORef r new
 
 instance MonadState state (Bustle config state) where
   get = B $ ask >>= readState
@@ -83,13 +84,9 @@ instance MonadState state (Bustle config state) where
 
 instance MonadReader config (Bustle config state) where
     ask = B $ ask >>= readConfig
-    -- FIXME: I don't actually think it's possible to implement local without
-    -- keeping two refs or something. I guess I could make a temporary ioref,
-    -- and propagate any changes to the actual state part of the ref to the
-    -- outside world. This would break horribly in the face of threads. Or we
-    -- could do something like:
-    --   MVar (BConfig, MVar BState)
-    local = error "Sorry, Dave, I can't let you do that."
+    local f (B act) = B $ local (mapBustleEnv (\(e, r) -> (f e, r))) act
+      where
+        mapBustleEnv g = BustleEnv . g . unBustleEnv
 
 embedIO :: (BustleEnv config state -> IO a) -> Bustle config state a
 embedIO act = B $ do
@@ -101,5 +98,5 @@ makeCallback (B act) x = runReaderT act x
 
 runB :: config -> state -> Bustle config state a -> IO a
 runB config s (B act) = do
-    r <- newIORef (config, s)
-    runReaderT act $ BustleEnv r
+    r <- newIORef s
+    runReaderT act $ BustleEnv (config, r)
diff --git a/Bustle/Diagram.hs b/Bustle/Diagram.hs
index 585eba4..d558beb 100644
--- a/Bustle/Diagram.hs
+++ b/Bustle/Diagram.hs
@@ -341,8 +341,8 @@ draw s = draw' s
                     in drawArc cx cy dx dy <$>
                           topx <*> topy <*> bottomx <*> bottomy <*> caption
           SignalArrow {} -> drawSignalArrow <$> epicentre
-                                            <*> Just . shapex1
-                                            <*> Just . shapex2
+                                            <*> (Just . shapex1)
+                                            <*> (Just . shapex2)
                                             <*> shapey
           DirectedSignalArrow { } -> drawDirectedSignalArrow <$> epicentre
                                                              <*> shapex
diff --git a/Bustle/Loader.hs b/Bustle/Loader.hs
index 74165c3..121d8df 100644
--- a/Bustle/Loader.hs
+++ b/Bustle/Loader.hs
@@ -29,10 +29,13 @@ import Control.Exception
 import Control.Monad.Error
 import Control.Arrow ((***))
 
+import Text.Printf
+
 import qualified Bustle.Loader.OldSkool as Old
 import qualified Bustle.Loader.Pcap as Pcap
 import Bustle.Upgrade (upgrade)
 import Bustle.Types
+import Bustle.Translation (__)
 import Bustle.Util (io)
 
 data LoadError = LoadError FilePath String
@@ -58,7 +61,7 @@ readLog f = do
             Right input -> do
                 let oldResult = fmap upgrade $ Old.readLog input
                 case oldResult of
-                    Left e  -> throwError $ LoadError f ("Parse error " ++ show e)
+                    Left e  -> throwError $ LoadError f (printf (__ "Parse error %s") (show e))
                     Right r -> return r
 
 isRelevant :: Event
diff --git a/Bustle/Monitor.hs b/Bustle/Monitor.hs
index 15fb531..aa36e0c 100644
--- a/Bustle/Monitor.hs
+++ b/Bustle/Monitor.hs
@@ -22,7 +22,6 @@ module Bustle.Monitor
 -- * Types
     Monitor
   , BusType(..)
-  , DebugOutput(..)
 
 -- * Methods
   , monitorNew
@@ -60,7 +59,6 @@ instance GObjectClass Monitor where
 foreign import ccall "bustle_pcap_monitor_new"
     bustle_pcap_monitor_new :: CInt
                     -> CString
-                    -> CInt
                     -> Ptr (Ptr ())
                     -> IO (Ptr Monitor)
 foreign import ccall "bustle_pcap_monitor_stop"
@@ -74,23 +72,16 @@ data BusType = BusTypeNone
   deriving
     Enum
 
-data DebugOutput = NoDebugOutput
-                 | DebugOutput
-  deriving
-    Enum
-
 -- Throws a GError if the file can't be opened, we can't get on the bus, or whatever.
 monitorNew :: BusType
            -> FilePath
-           -> DebugOutput
            -> IO Monitor
-monitorNew busType filename debugOutput =
+monitorNew busType filename =
     wrapNewGObject mkMonitor $
       propagateGError $ \gerrorPtr ->
         withCString filename $ \c_filename ->
           bustle_pcap_monitor_new (fromIntegral $ fromEnum busType)
                                   c_filename
-                                  (fromIntegral $ fromEnum debugOutput)
                                   gerrorPtr
 
 monitorStop :: Monitor
diff --git a/Bustle/Noninteractive.hs b/Bustle/Noninteractive.hs
index 6ad6b58..cc64a9f 100644
--- a/Bustle/Noninteractive.hs
+++ b/Bustle/Noninteractive.hs
@@ -33,6 +33,7 @@ import Control.Monad.Error
 import Text.Printf
 
 import Bustle.Loader
+import Bustle.Translation (__)
 import Bustle.Types
 import Bustle.Stats
 
@@ -44,18 +45,14 @@ process filepath analyze format = do
     ret <- runErrorT $ readLog filepath
     case ret of
         Left (LoadError _ err) -> do
-            warn $ concat [ "Couldn't parse "
-                          , filepath
-                          , ": "
-                          , err
-                          ]
+            warn $ printf (__ "Couldn't parse '%s': %s") filepath err
             exitFailure
         Right (warnings, log) -> do
             mapM warn warnings
             mapM_ (putStrLn . format) $ analyze log
 
 formatInterface :: Maybe InterfaceName -> String
-formatInterface = maybe "(no interface)" formatInterfaceName
+formatInterface = maybe (__ "(no interface)") formatInterfaceName
 
 runCount :: FilePath -> IO ()
 runCount filepath = process filepath frequencies format
diff --git a/Bustle/StatisticsPane.hs b/Bustle/StatisticsPane.hs
index 90d5bb6..8e895a8 100644
--- a/Bustle/StatisticsPane.hs
+++ b/Bustle/StatisticsPane.hs
@@ -28,6 +28,7 @@ import Control.Monad (forM_)
 import Text.Printf
 import Graphics.UI.Gtk hiding (Markup)
 import Bustle.Stats
+import Bustle.Translation (__)
 import Bustle.Types (Log)
 import qualified Bustle.Markup as Markup
 import Bustle.Markup (Markup)
@@ -89,7 +90,7 @@ addTextRenderer col store expand f = do
     cellLayoutPackStart col renderer expand
     set renderer [ cellTextSizePoints := 7 ]
     cellLayoutSetAttributes col renderer store $ \x ->
-        [ cellTextMarkup := Just . Markup.unMarkup $ f x ]
+        [ cellTextMarkup := (Just . Markup.unMarkup) $ f x ]
     return renderer
 
 addMemberRenderer :: TreeViewColumn
@@ -152,7 +153,7 @@ newCountView method signal = do
   set countView [ treeViewHeadersVisible := False ]
 
   nameColumn <- treeViewColumnNew
-  treeViewColumnSetTitle nameColumn "Name"
+  treeViewColumnSetTitle nameColumn (__ "Name")
   set nameColumn [ treeViewColumnResizable := True
                  , treeViewColumnExpand := True
                  ]
@@ -167,7 +168,7 @@ newCountView method signal = do
   treeViewAppendColumn countView nameColumn
 
   countColumn <- treeViewColumnNew
-  treeViewColumnSetTitle countColumn "Frequency"
+  treeViewColumnSetTitle countColumn (__ "Frequency")
   treeViewColumnSetMinWidth countColumn 120
 
   -- Using a progress bar here is not really ideal, but I CBA to do anything
@@ -177,7 +178,7 @@ newCountView method signal = do
   cellLayoutSetAttributes countColumn countBar countStore $
       \(FrequencyInfo {fiFrequency = count}) ->
       [ cellProgressValue :=> do
-          upperBound <- maximum . map fiFrequency <$>
+          upperBound <- (maximum . map fiFrequency) <$>
                         listStoreToList countStore
           -- ensure that we always show *something*
           return $ 2 + (count * 98 `div` upperBound)
@@ -196,7 +197,7 @@ newTimeView = do
   set timeView [ treeViewHeadersVisible := True ]
 
   nameColumn <- treeViewColumnNew
-  treeViewColumnSetTitle nameColumn "Method"
+  treeViewColumnSetTitle nameColumn (__ "Method")
   set nameColumn [ treeViewColumnResizable := True
                  , treeViewColumnExpand := True
                  ]
@@ -205,11 +206,11 @@ newTimeView = do
       Markup.formatMember (tiInterface ti) (tiMethodName ti)
   treeViewAppendColumn timeView nameColumn
 
-  addTextStatColumn timeView timeStore "Total"
-                (printf "%.1f ms" . tiTotalTime)
-  addTextStatColumn timeView timeStore "Calls" (show . tiCallFrequency)
-  addTextStatColumn timeView timeStore "Mean"
-                (printf "%.1f ms" . tiMeanCallTime)
+  addTextStatColumn timeView timeStore (__ "Total")
+                (printf (__ "%.1f ms") . tiTotalTime)
+  addTextStatColumn timeView timeStore (__ "Calls") (show . tiCallFrequency)
+  addTextStatColumn timeView timeStore (__ "Mean")
+                (printf (__ "%.1f ms") . tiMeanCallTime)
 
   return (timeStore, timeView)
 
@@ -224,9 +225,9 @@ formatSizeInfoMember si =
 
 formatSize :: Int -> Markup
 formatSize s
-    | s < maxB = value 1 `mappend` units "B"
-    | s < maxKB = value 1024 `mappend` units "KB"
-    | otherwise = value (1024 * 1024) `mappend` units "MB"
+    | s < maxB = value 1 `mappend` units (__ "B")
+    | s < maxKB = value 1024 `mappend` units (__ "KB")
+    | otherwise = value (1024 * 1024) `mappend` units (__ "MB")
   where
     maxB = 10000
     maxKB = 10000 * 1024
@@ -245,7 +246,7 @@ newSizeView methodIcon_ signalIcon_ = do
   set sizeView [ treeViewHeadersVisible := True ]
 
   nameColumn <- treeViewColumnNew
-  treeViewColumnSetTitle nameColumn "Member"
+  treeViewColumnSetTitle nameColumn (__ "Member")
   set nameColumn [ treeViewColumnResizable := True
                  , treeViewColumnExpand := True
                  ]
@@ -258,8 +259,8 @@ newSizeView methodIcon_ signalIcon_ = do
   addMemberRenderer nameColumn sizeStore True formatSizeInfoMember
   treeViewAppendColumn sizeView nameColumn
 
-  addStatColumn sizeView sizeStore "Smallest" (formatSize . siMinSize)
-  addStatColumn sizeView sizeStore "Mean" (formatSize . siMeanSize)
-  addStatColumn sizeView sizeStore "Largest" (formatSize . siMaxSize)
+  addStatColumn sizeView sizeStore (__ "Smallest") (formatSize . siMinSize)
+  addStatColumn sizeView sizeStore (__ "Mean") (formatSize . siMeanSize)
+  addStatColumn sizeView sizeStore (__ "Largest") (formatSize . siMaxSize)
 
   return (sizeStore, sizeView)
diff --git a/Bustle/Translation.hs b/Bustle/Translation.hs
new file mode 100644
index 0000000..dadc6e6
--- /dev/null
+++ b/Bustle/Translation.hs
@@ -0,0 +1,25 @@
+module Bustle.Translation
+    (
+      initTranslation
+    , __
+    )
+where
+
+import Text.I18N.GetText
+import System.Locale.SetLocale
+import System.IO.Unsafe
+
+import GetText_bustle
+
+initTranslation :: IO ()
+initTranslation = do
+    setLocale LC_ALL (Just "")
+    domain <- getMessageCatalogDomain
+    dir <- getMessageCatalogDir
+    bindTextDomain domain (Just dir)
+    textDomain (Just domain)
+    return ()
+
+-- FIXME: I do not like this unsafePerformIO one little bit.
+__ :: String -> String
+__ = unsafePerformIO . getText
diff --git a/Bustle/UI.hs b/Bustle/UI.hs
index 5c58701..a78797e 100644
--- a/Bustle/UI.hs
+++ b/Bustle/UI.hs
@@ -31,6 +31,7 @@ import qualified Data.Set as Set
 import Data.List (intercalate)
 import Data.Time
 import Data.Monoid (mempty)
+import Text.Printf
 
 import Paths_bustle
 import Bustle.Application.Monad
@@ -46,6 +47,7 @@ import Bustle.UI.OpenTwoDialog (setupOpenTwoDialog)
 import Bustle.UI.Recorder
 import Bustle.UI.Util (displayError)
 import Bustle.StatisticsPane
+import Bustle.Translation (__)
 import Bustle.Loader
 
 import qualified Control.Exception as C
@@ -93,7 +95,6 @@ data WindowInfo =
 
 data BConfig =
     BConfig { debugEnabled :: Bool
-            , bustleIcon :: Maybe Pixbuf
             , methodIcon :: Maybe Pixbuf
             , signalIcon :: Maybe Pixbuf
             }
@@ -118,11 +119,10 @@ uiMain = failOnGError $ do
     -- FIXME: get a real option parser
     let debug = any isDebug args
 
-    [bustle, method, signal] <- mapM loadPixbuf
-        ["bustle.png", "dfeet-method.png", "dfeet-signal.png"]
+    [method, signal] <- mapM loadPixbuf
+        ["dfeet-method.png", "dfeet-signal.png"]
 
     let config = BConfig { debugEnabled = debug
-                         , bustleIcon = bustle
                          , methodIcon = method
                          , signalIcon = signal
                          }
@@ -205,7 +205,7 @@ loadLogWith getWindow logDetails = do
 
     case ret of
       Left (LoadError f e) -> io $
-          displayError Nothing ("Could not read '" ++ f ++ "'") (Just e)
+          displayError Nothing (printf (__ "Could not read '%s'") f) (Just e)
       Right () -> return ()
 
 startRecording :: B ()
@@ -281,15 +281,15 @@ promptToSave wi = io $ do
     case mdetails of
         Just (RecordedLog tempFilePath) -> do
             let tempFileName = takeFileName tempFilePath
-                title = "Save log “" ++ tempFileName ++ "” before closing?"
+                title = printf (__ "Save log '%s' before closing?") tempFileName
             prompt <- messageDialogNew (Just (wiWindow wi))
                                        [DialogModal]
                                        MessageWarning
                                        ButtonsNone
                                        title
             messageDialogSetSecondaryText prompt
-                "If you don’t save, this log will be lost forever."
-            dialogAddButton prompt "Close _without saving" ResponseClose
+                (__ "If you don't save, this log will be lost forever.")
+            dialogAddButton prompt (__ "Close _Without Saving") ResponseClose
             dialogAddButton prompt stockCancel ResponseCancel
             dialogAddButton prompt stockSave ResponseYes
 
@@ -337,10 +337,8 @@ emptyWindow = do
   openTwoDialog <- embedIO $ \r ->
       setupOpenTwoDialog builder window $ \f1 f2 ->
           makeCallback (loadInInitialWindow (TwoLogs f1 f2)) r
-  withProgramIcon (windowSetIcon openTwoDialog)
 
   -- Set up the window itself
-  withProgramIcon (windowSetIcon window)
   embedIO $ onDestroy window . makeCallback maybeQuit
 
   -- File menu and related buttons
@@ -356,8 +354,7 @@ emptyWindow = do
       onActivateLeaf openTwoItem $ widgetShowAll openTwoDialog
 
   -- Help menu
-  withProgramIcon $ \icon -> io $
-      onActivateLeaf aboutItem $ showAboutDialog window icon
+  io $ onActivateLeaf aboutItem $ showAboutDialog window
 
   m <- asks methodIcon
   s <- asks signalIcon
@@ -462,7 +459,7 @@ wiSetLogDetails :: WindowInfo
                 -> IO ()
 wiSetLogDetails wi logDetails = do
     writeIORef (wiLogDetails wi) (Just logDetails)
-    windowSetTitle (wiWindow wi) (logWindowTitle logDetails ++ " — Bustle")
+    windowSetTitle (wiWindow wi) (printf (__ "%s - Bustle") (logWindowTitle logDetails))
 
 setPage :: MonadIO io
         => WindowInfo
@@ -507,9 +504,7 @@ displayLog wi@(WindowInfo { wiWindow = window
     statsPaneSetMessages statsPane sessionMessages systemMessages
 
     widgetSetSensitivity viewStatistics True
-    -- the version of gtk2hs I'm using has a checkMenuItemToggled which is a
-    -- method not a signal.
-    connectGeneric "toggled" False viewStatistics $ do
+    viewStatistics `on` checkMenuItemToggled $ do
         active <- checkMenuItemGetActive viewStatistics
         if active
             then widgetShow statsBook
@@ -526,9 +521,6 @@ displayLog wi@(WindowInfo { wiWindow = window
 
   return ()
 
-withProgramIcon :: (Maybe Pixbuf -> IO a) -> B a
-withProgramIcon f = asks bustleIcon >>= io . f
-
 loadPixbuf :: FilePath -> IO (Maybe Pixbuf)
 loadPixbuf filename = do
   iconName <- getDataFileName $ "data/" ++ filename
diff --git a/Bustle/UI/AboutDialog.hs b/Bustle/UI/AboutDialog.hs
index 44536f6..7ef4ce5 100644
--- a/Bustle/UI/AboutDialog.hs
+++ b/Bustle/UI/AboutDialog.hs
@@ -30,41 +30,42 @@ import Control.Monad (when)
 
 import Graphics.UI.Gtk
 
+import Bustle.Translation (__)
 import Bustle.Util
 import Paths_bustle
 
 
 showAboutDialog :: Window
-                -> Maybe Pixbuf
                 -> IO ()
-showAboutDialog window icon = do
+showAboutDialog window = do
     dialog <- aboutDialogNew
 
     license <- (Just `fmap` (readFile =<< getDataFileName "LICENSE"))
                `catch` (\e -> warn (show (e :: IOException)) >> return Nothing)
 
-    dialog `set` [ aboutDialogName := "Bustle"
+    dialog `set` [ aboutDialogName := __ "Bustle"
                  , aboutDialogVersion := showVersion version
-                 , aboutDialogComments := "Someone's favourite D-Bus profiler"
+                 , aboutDialogComments := __ "Someone's favourite D-Bus profiler"
                  , aboutDialogWebsite := "http://willthompson.co.uk/bustle"
                  , aboutDialogAuthors := authors
-                 , aboutDialogCopyright := "© 2008–2012 Collabora Ltd."
+                 , aboutDialogCopyright := "© 2008–2014 Will Thompson, Collabora Ltd. and contributors"
                  , aboutDialogLicense := license
                  ]
     dialog `afterResponse` \resp ->
         when (resp == ResponseCancel) (widgetDestroy dialog)
     windowSetTransientFor dialog window
     windowSetModal dialog True
-    aboutDialogSetLogo dialog icon
+    aboutDialogSetLogoIconName dialog (Just "bustle")
 
     widgetShowAll dialog
 
 authors :: [String]
-authors = [ "Will Thompson <will.thompson at collabora.co.uk>"
+authors = [ "Will Thompson <will at willthompson.co.uk>"
           , "Dafydd Harries"
           , "Chris Lamb"
           , "Marc Kleine-Budde"
           , "Cosimo Alfarano"
           , "Sergei Trofimovich"
           , "Alex Merry"
+          , "Philip Withnall"
           ]
diff --git a/Bustle/UI/DetailsView.hs b/Bustle/UI/DetailsView.hs
index ebcbcc1..35e80d6 100644
--- a/Bustle/UI/DetailsView.hs
+++ b/Bustle/UI/DetailsView.hs
@@ -29,6 +29,7 @@ import Graphics.UI.Gtk hiding (Signal, Markup)
 
 import qualified DBus as D
 
+import Bustle.Translation (__)
 import Bustle.Types
 import Bustle.Markup
 import Bustle.VariantFormatter
@@ -80,10 +81,10 @@ detailsViewNew = do
     miscSetAlignment title 0 0
     tableAttach table title 0 2 0 1 [Fill] [Fill] 0 0
 
-    pathLabel <- addField table "Path:" 1
-    memberLabel <- addField table "Member:" 2
+    pathLabel <- addField table (__ "Path:") 1
+    memberLabel <- addField table (__ "Member:") 2
 
-    addTitle table "Arguments:" 3
+    addTitle table (__ "Arguments:") 3
 
     view <- textViewNew
     textViewSetWrapMode view WrapWordChar
@@ -100,13 +101,13 @@ detailsViewNew = do
 
 pickTitle :: Detailed Message -> Markup
 pickTitle (Detailed _ m _) = case m of
-    MethodCall {} -> b (escape "Method call")
-    MethodReturn {} -> b (escape "Method return")
-    Error {} -> b (escape "Error")
+    MethodCall {} -> b (escape (__ "Method call"))
+    MethodReturn {} -> b (escape (__ "Method return"))
+    Error {} -> b (escape (__ "Error"))
     Signal { signalDestination = d } ->
         b . escape $ case d of
-            Nothing -> "Signal"
-            Just _  -> "Directed signal"
+            Nothing -> (__ "Signal")
+            Just _  -> (__ "Directed signal")
 
 getMemberMarkup :: Member -> String
 getMemberMarkup m =
@@ -123,8 +124,8 @@ getMember (Detailed _ m _) = case m of
 
 formatMessage :: Detailed Message -> String
 formatMessage (Detailed _ _ Nothing) =
-    "# No message body information is available. Please capture a fresh log\n\
-    \# using bustle-pcap if you need it!"
+    __ "No message body information is available. Please capture a fresh log \
+       \using a recent version of Bustle!"
 formatMessage (Detailed _ _ (Just (_size, rm))) =
     formatArgs $ D.receivedMessageBody rm
   where
@@ -140,6 +141,8 @@ detailsViewUpdate d m = do
     buf <- textViewGetBuffer $ detailsBodyView d
     let member_ = getMember m
     labelSetMarkup (detailsTitle d) (unMarkup $ pickTitle m)
-    labelSetText (detailsPath d) (maybe "Unknown" (D.formatObjectPath . path) member_)
-    labelSetMarkup (detailsMember d) (maybe "Unknown" getMemberMarkup member_)
+    labelSetText (detailsPath d) (maybe unknown (D.formatObjectPath . path) member_)
+    labelSetMarkup (detailsMember d) (maybe unknown getMemberMarkup member_)
     textBufferSetText buf $ formatMessage m
+  where
+    unknown = __ "<unknown>"
diff --git a/Bustle/UI/FilterDialog.hs b/Bustle/UI/FilterDialog.hs
index 5a33462..9560507 100644
--- a/Bustle/UI/FilterDialog.hs
+++ b/Bustle/UI/FilterDialog.hs
@@ -28,6 +28,7 @@ import Data.Set (Set)
 
 import Graphics.UI.Gtk
 
+import Bustle.Translation (__)
 import Bustle.Types
 
 formatNames :: (UniqueName, Set OtherName)
@@ -101,10 +102,10 @@ runFilterDialog parent names currentlyHidden = do
     instructions <- labelNew Nothing
     widgetSetSizeRequest instructions 600 (-1)
     labelSetMarkup instructions
-        "Unticking a service hides its column in the diagram, \
+        (__ "Unticking a service hides its column in the diagram, \
         \and all messages it is involved in. That is, all methods it calls \
         \or are called on it, the corresponding returns, and all signals it \
-        \emits will be hidden."
+        \emits will be hidden.")
     labelSetLineWrap instructions True
     boxPackStart vbox instructions PackNatural 0
 
diff --git a/Bustle/UI/Recorder.hs b/Bustle/UI/Recorder.hs
index c04d817..1e98a68 100644
--- a/Bustle/UI/Recorder.hs
+++ b/Bustle/UI/Recorder.hs
@@ -28,6 +28,7 @@ import Control.Concurrent.MVar
 import qualified Data.Map as Map
 import Data.Monoid
 import Control.Monad.State (runStateT)
+import Text.Printf
 
 import qualified Control.Exception as C
 import System.Glib.GError
@@ -37,6 +38,7 @@ import Bustle.Loader.Pcap (convert)
 import Bustle.Loader (isRelevant)
 import Bustle.Monitor
 import Bustle.Renderer
+import Bustle.Translation (__)
 import Bustle.Types
 import Bustle.UI.Util (displayError)
 import Bustle.Util
@@ -76,7 +78,7 @@ processBatch pendingRef n label incoming = do
                 i <- takeMVar n
                 let j = i + (length pending)
                 labelSetMarkup label $
-                    "Logged <b>" ++ show j ++ "</b> messages…"
+                    printf (__ "Logged <b>%u</b> messages…") j
                 putMVar n j
 
                 incoming rr'
@@ -89,14 +91,14 @@ recorderRun :: FilePath
             -> RecorderFinishedCallback
             -> IO ()
 recorderRun filename mwindow incoming finished = C.handle newFailed $ do
-    monitor <- monitorNew BusTypeSession filename NoDebugOutput
+    monitor <- monitorNew BusTypeSession filename
     dialog <- dialogNew
 
     maybe (return ()) (windowSetTransientFor dialog) mwindow
     dialog `set` [ windowModal := True ]
 
     label <- labelNew Nothing
-    labelSetMarkup label "Logged <b>0</b> messages…"
+    labelSetMarkup label $ printf (__ "Logged <b>%u</b> messages…") (0 :: Int)
     loaderStateRef <- newMVar Map.empty
     pendingRef <- newMVar []
     let updateLabel µs body = do
diff --git a/Bustle/Util.hs b/Bustle/Util.hs
index 490c4c1..5ac76a2 100644
--- a/Bustle/Util.hs
+++ b/Bustle/Util.hs
@@ -41,6 +41,7 @@ import System.IO (hPutStrLn, stderr)
 import Foreign.C.String
 import System.Directory
 import System.FilePath ((</>))
+import Bustle.Translation (__)
 
 -- Escape hatch to log a value from a non-IO monadic context.
 traceM :: (Show a, Monad m) => a -> m ()
@@ -49,7 +50,7 @@ traceM x = trace (show x) $ return ()
 -- Log a warning which isn't worth showing to the user, but which might
 -- interest someone debugging the application.
 warn :: String -> IO ()
-warn = hPutStrLn stderr . ("Warning: " ++)
+warn = hPutStrLn stderr . ((__ "Warning: ") ++)
 
 -- Shorthand for liftIO.
 io :: MonadIO m => IO a -> m a
diff --git a/INSTALL b/INSTALL
index 08e3bc3..2ce67e8 100644
--- a/INSTALL
+++ b/INSTALL
@@ -2,17 +2,31 @@ Building from source
 ====================
 
 First, make sure the Haskell Platform is installed, preferably along with the
-Gtk+ bindings for Haskell. On Debian-flavoured systems:
-
-    sudo apt-get install haskell-platform libghc-gtk-dev
-
-If you can't get the Haskell Platform via your package manager, see
+Gtk+ bindings for Haskell, and some other dependencies. On Debian-flavoured
+systems, well, actually just `apt-get build-dep bustle`, but:
+
+    sudo apt-get install \
+        pkg-config \
+        libdbus-1-dev \
+        libglib2.0-dev \
+        libpcap0.8-dev \
+        haskell-platform \
+        libghc-mtl-dev \
+        libghc-cairo-dev \
+        libghc-gtk-dev \
+        libghc-parsec3-dev \
+        libghc-glade-dev \
+        libghc-dbus-dev \
+        libghc-pcap-dev \
+        help2man
+
+(If you can't get the Haskell Platform via your package manager, see
 <http://hackage.haskell.org/platform/>. If you can't get the Gtk+ binding for
 Haskell via your package manager, you'll need to run:
 
     cabal install gtk2hs-buildtools
 
-and ensure that ~/.cabal/bin is in your PATH before continuing.
+and ensure that ~/.cabal/bin is in your PATH before continuing.)
 
 Got that? Great!
 
@@ -21,13 +35,14 @@ Got that? Great!
     # Build and install Bustle itself.
     cabal install --prefix=$PREFIX
 
-    # Build and install the stand-alone logger binary.
+    # Build and install the stand-alone logger binary, plus the icons, desktop
+    # file, etc. etc.
     make install PREFIX=$PREFIX
 
 If the Haskell Platform is not available on the platform you want to do
 some D-Bus profiling on, that's fine: the logger is written in C, and
 you can view logs generated on your fancy embedded hardware on your more
-pedestrian Linux laptop. The logger depends on a few widely-available
+pedestrian Linux laptop. The logger only depends on a few widely-available
 libraries:
 
     sudo apt-get install libglib2.0-dev libpcap-dev
diff --git a/Makefile b/Makefile
index 16fc353..0b228ed 100644
--- a/Makefile
+++ b/Makefile
@@ -5,15 +5,23 @@ PCAP_FLAGS := $(shell pcap-config --cflags pcap-config --libs)
 DESTDIR =
 PREFIX = /usr/local
 BINDIR = $(DESTDIR)$(PREFIX)/bin
-MAN1DIR = $(DESTDIR)$(PREFIX)/share/man/man1
+DATADIR = $(DESTDIR)$(PREFIX)/share
+MAN1DIR = $(DATADIR)/man/man1
 
 BINARIES = \
 	dist/build/bustle-pcap \
 	$(NULL)
 
 MANPAGE = bustle-pcap.1
+DESKTOP_FILE = bustle.desktop
+APPDATA_FILE = bustle.appdata.xml
+ICON_SIZES = 16x16 22x22 32x32 48x48 256x256
+ICONS = \
+	data/icons/scalable/bustle.svg \
+	$(foreach size,$(ICON_SIZES),data/icons/$(size)/bustle.png) \
+	$(NULL)
 
-all: $(BINARIES) $(MANPAGE)
+all: $(BINARIES) $(MANPAGE) $(DESKTOP_FILE) $(APPDATA_FILE) $(ICONS)
 
 BUSTLE_PCAP_SOURCES = c-sources/pcap-monitor.c c-sources/bustle-pcap.c
 BUSTLE_PCAP_GENERATED_HEADERS = dist/build/autogen/version.h
@@ -22,6 +30,12 @@ BUSTLE_PCAP_HEADERS = c-sources/pcap-monitor.h $(BUSTLE_PCAP_GENERATED_HEADERS)
 bustle-pcap.1: dist/build/bustle-pcap
 	-help2man --output=$@ --no-info --name='Generate D-Bus logs for bustle' $<
 
+bustle.desktop: data/bustle.desktop.in
+	LC_ALL=C intltool-merge -d -u po $< $@
+
+bustle.appdata.xml: data/bustle.appdata.xml.in
+	LC_ALL=C intltool-merge -x -u po $< $@
+
 dist/build/bustle-pcap: $(BUSTLE_PCAP_SOURCES) $(BUSTLE_PCAP_HEADERS)
 	@mkdir -p dist/build
 	$(CC) -Idist/build/autogen $(CFLAGS) $(CPPFLAGS) $(LDFLAGS) \
@@ -37,16 +51,40 @@ install: all
 	mkdir -p $(BINDIR)
 	cp $(BINARIES) $(BINDIR)
 	-mkdir -p $(MAN1DIR)
-	-cp bustle-pcap.1 $(MAN1DIR)
+	-cp $(MANPAGE) $(MAN1DIR)
+	mkdir -p $(DATADIR)/applications
+	cp $(DESKTOP_FILE) $(DATADIR)/applications
+	mkdir -p $(DATADIR)/appdata
+	cp $(APPDATA_FILE) $(DATADIR)/appdata
+	$(foreach size,$(ICON_SIZES),mkdir -p $(DATADIR)/icons/hicolor/$(size)/apps; )
+	$(foreach size,$(ICON_SIZES),cp data/icons/$(size)/bustle.png $(DATADIR)/icons/hicolor/$(size)/apps; )
+	$(MAKE) update-icon-cache
 
 uninstall:
-	rm -f $(notdir $(BINARIES))
+	rm -f $(BINDIR)/$(notdir $(BINARIES))
+	rm -f $(MAN1DIR)/$(MANPAGE)
+	rm -f $(DATADIR)/applications/$(DESKTOP_FILE)
+	rm -f $(DATADIR)/appdata/$(APPDATA_FILE)
+	$(foreach size,$(ICON_SIZES),rm -f $(DATADIR)/icons/hicolor/$(size)/apps/bustle.png)
+	$(MAKE) update-icon-cache
 
 clean:
-	rm -f $(BINARIES) $(MANPAGE) $(BUSTLE_PCAP_GENERATED_HEADERS)
+	rm -f $(BINARIES) $(MANPAGE) $(BUSTLE_PCAP_GENERATED_HEADERS) $(DESKTOP_FILE) $(APPDATA_FILE)
 	if test -d ./$(TARBALL_DIR); then rm -r ./$(TARBALL_DIR); fi
 	rm -f ./$(TARBALL)
 
+# Icon cache stuff
+gtk_update_icon_cache = gtk-update-icon-cache -f -t $(DATADIR)/icons/hicolor
+
+update-icon-cache:
+	@-if test -z "$(DESTDIR)"; then \
+		echo "Updating GTK+ icon cache."; \
+		$(gtk_update_icon_cache); \
+	else \
+		echo "*** Icon cache not updated.  After (un)install, run this:"; \
+		echo "***   $(gtk_update_icon_cache)"; \
+	fi
+
 # Binary tarball stuff. Please ignore this unless you're making a release.
 TOP := $(shell pwd)
 TARBALL_PARENT_DIR := dist
@@ -55,17 +93,18 @@ TARBALL_FULL_DIR := $(TARBALL_PARENT_DIR)/$(TARBALL_DIR)
 TARBALL := $(TARBALL_DIR).tar.bz2
 maintainer-binary-tarball: all
 	mkdir -p $(TARBALL_FULL_DIR)
-	cabal-dev configure --prefix=$(TOP)/$(TARBALL_FULL_DIR) \
+	cabal-dev install --prefix=$(TOP)/$(TARBALL_FULL_DIR) \
 		--datadir=$(TOP)/$(TARBALL_FULL_DIR) --datasubdir=.
-	cabal-dev build
-	cabal-dev copy
 	cp bustle.sh README $(TARBALL_FULL_DIR)
 	perl -pi -e 's{^    bustle-pcap}{    ./bustle-pcap};' \
 		-e  's{^    bustle}     {    ./bustle.sh};' \
 		$(TARBALL_FULL_DIR)/README
-	cp $(BINARIES) $(MANPAGE) $(TARBALL_FULL_DIR)
+	cp $(BINARIES) $(MANPAGE) $(DESKTOP_FILE) $(APPDATA_FILE) $(TARBALL_FULL_DIR)
 	mkdir -p $(TARBALL_FULL_DIR)/lib
 	cp LICENSE.bundled-libraries $(TARBALL_FULL_DIR)/lib
 	./ldd-me-up.sh $(TARBALL_FULL_DIR)/bin/bustle \
 		| xargs -I XXX cp XXX $(TARBALL_FULL_DIR)/lib
 	cd $(TARBALL_PARENT_DIR) && tar cjf $(TARBALL) $(TARBALL_DIR)
+
+maintainer-update-messages-pot:
+	find Bustle -name '*.hs' -print0 | xargs -0 hgettext -k __ -o po/messages.pot
diff --git a/NEWS b/NEWS
index 42f2213..5a38571 100644
--- a/NEWS
+++ b/NEWS
@@ -1,3 +1,49 @@
+Bustle 0.4.7 (2014-07-19)
+-------------------------
+
+* Ship the icons in the tarball! Thanks again, Sergei Trofimovich.
+
+
+Bustle 0.4.6 (2014-07-17)
+-------------------------
+
+* Icons! Thanks to Αποστολίδου Χρυσαφή for redrawing the icon as an SVG, and to
+  Philip Withnall for the build system goop.
+* More appdata! Thanks again, Philip.
+
+Bustle 0.4.5 (2014-02-26)
+-------------------------
+
+* Fix build failure with tests enabled due to translation files.
+* Distribute appdata and desktop files in source tarballs.
+
+Thanks to Sergei Trofimovich for catching and fixing these!
+
+
+Bustle 0.4.4 (2014-01-30)
+-------------------------
+
+Wow, I can't believe the first release was in 2008!
+
+* Bustle's now translatable. It only ships with an English translation,
+  but others are more than welcome! Thanks to Philip Withnall for
+  getting this started.
+* Add an AppData and .desktop file. (Philip Withnall)
+
+
+Bustle 0.4.3 (2013-12-05)
+-------------------------
+
+I think you mean ‘fewer crashy’.
+
+* Don't crash on i386 when opening the stats pane. Thanks to Sujith
+  Sudhi for reporting this issue.
+* [#54237][]: Don't crash if we can't connect to the bus.
+* Don't crash the second time you try to record a log. I swear this
+  didn't happen before.
+
+[#54237]: https://bugs.freedesktop.org/show_bug.cgi?id=54237
+
 Bustle 0.4.2 (2012-11-14)
 -------------------------
 
diff --git a/Setup.hs b/Setup.hs
index 9a994af..9ab758c 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -1,2 +1,113 @@
+{-# OPTIONS_GHC -Wall #-}
+import Data.Maybe (fromMaybe)
+import System.FilePath ( (</>), (<.>) )
+
+import Distribution.PackageDescription
 import Distribution.Simple
-main = defaultMain
+import Distribution.Simple.BuildPaths ( autogenModulesDir )
+import Distribution.Simple.InstallDirs as I
+import Distribution.Simple.LocalBuildInfo
+import Distribution.Simple.Setup as S
+import Distribution.Simple.Utils
+import Distribution.Text ( display )
+
+import Distribution.ModuleName (ModuleName)
+import qualified Distribution.ModuleName as ModuleName
+
+import qualified Distribution.Simple.I18N.GetText as GetText
+
+main :: IO ()
+main = defaultMainWithHooks $ installBustleHooks simpleUserHooks
+
+-- Okay, so we want to use hgettext's install hook, but not the hook that
+-- miraculously runs all our code through CPP just to add a couple of
+-- constants. (cpp doesn't like multi-line Haskell strings, so this is not
+-- purely an academic preference.)
+--
+-- Instead, we generate GetText_bustle.hs which contains the constants, in the
+-- same way as Paths_bustle.hs gets generated by Cabal. Much neater.
+--
+-- TODO: upstream this to hgettext
+installBustleHooks :: UserHooks
+                   -> UserHooks
+installBustleHooks uh = uh
+  { postInst = postInst gtuh
+  , buildHook = \pkg lbi hooks flags -> do
+        writeGetTextConstantsFile pkg lbi flags
+        buildHook uh pkg lbi hooks flags
+  }
+  where
+    gtuh = GetText.installGetTextHooks uh
+
+
+writeGetTextConstantsFile :: PackageDescription -> LocalBuildInfo -> BuildFlags -> IO ()
+writeGetTextConstantsFile pkg lbi flags = do
+    let verbosity = fromFlag (buildVerbosity flags)
+
+    createDirectoryIfMissingVerbose verbosity True (autogenModulesDir lbi)
+
+    let pathsModulePath = autogenModulesDir lbi
+                      </> ModuleName.toFilePath (getTextConstantsModuleName pkg) <.> "hs"
+    rewriteFile pathsModulePath (generateModule pkg lbi)
+
+getTextConstantsModuleName :: PackageDescription -> ModuleName
+getTextConstantsModuleName pkg_descr =
+  ModuleName.fromString $
+    "GetText_" ++ fixedPackageName pkg_descr
+
+-- Cargo-culted from two separate places in Cabal!
+fixedPackageName :: PackageDescription -> String
+fixedPackageName = map fixchar . display . packageName
+  where fixchar '-' = '_'
+        fixchar c   = c
+
+generateModule :: PackageDescription -> LocalBuildInfo -> String
+generateModule pkg lbi =
+    header ++ body
+  where
+    moduleName = getTextConstantsModuleName pkg
+
+    header =
+        "module " ++ display moduleName ++ " (\n"++
+        "    getMessageCatalogDomain,\n" ++
+        "    getMessageCatalogDir\n" ++
+        ") where\n"++
+        "\n" ++
+        "import qualified Control.Exception as Exception\n" ++
+        "import System.Environment (getEnv)\n"
+
+    body =
+        "catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a\n" ++
+        "catchIO = Exception.catch\n" ++
+        "\n" ++
+        "getMessageCatalogDomain :: IO String\n" ++
+        "getMessageCatalogDomain = return " ++ show dom ++ "\n" ++
+        "\n" ++
+        "messageCatalogDir :: String\n" ++
+        "messageCatalogDir = " ++ show tar ++ "\n" ++
+        "\n" ++
+        "getMessageCatalogDir :: IO FilePath\n" ++
+        "getMessageCatalogDir = catchIO (getEnv \"" ++ fixedPackageName pkg ++ "_localedir\") (\\_ -> return messageCatalogDir)\n"
+
+    sMap = customFieldsPD (localPkgDescr lbi)
+    dom = getDomainNameDefault sMap (getPackageName lbi)
+    tar = targetDataDir lbi
+
+-- Cargo-culted from hgettext
+findInParametersDefault :: [(String, String)] -> String -> String -> String
+findInParametersDefault al name def = (fromMaybe def . lookup name) al
+
+getPackageName :: LocalBuildInfo -> String
+getPackageName = fromPackageName . packageName . localPkgDescr
+    where fromPackageName (PackageName s) = s
+
+getDomainNameDefault :: [(String, String)] -> String -> String
+getDomainNameDefault al d = findInParametersDefault al "x-gettext-domain-name" d
+
+targetDataDir :: LocalBuildInfo -> FilePath
+targetDataDir l =
+    let dirTmpls = installDirTemplates l
+        prefix' = prefix dirTmpls
+        data' = datadir dirTmpls
+        dataEx = I.fromPathTemplate $ I.substPathTemplate [(PrefixVar, prefix')] data'
+    in dataEx ++ "/locale"
diff --git a/bustle.cabal b/bustle.cabal
index 33060f9..4ac107c 100644
--- a/bustle.cabal
+++ b/bustle.cabal
@@ -1,19 +1,18 @@
 Name:           bustle
 Category:       Network, Desktop
-Version:        0.4.2
+Version:        0.4.7
 Cabal-Version:  >= 1.8
 Synopsis:       Draw pretty sequence diagrams of D-Bus traffic
 Description:    Draw pretty sequence diagrams of D-Bus traffic
 License:        OtherLicense
 License-file:   LICENSE
-Author:         Will Thompson <will.thompson at collabora.co.uk>
-Maintainer:     Will Thompson <will.thompson at collabora.co.uk>
-Data-files:     data/bustle.png,
-                data/dfeet-method.png,
+Author:         Will Thompson <will at willthompson.co.uk>
+Maintainer:     Will Thompson <will at willthompson.co.uk>
+Data-files:     data/dfeet-method.png,
                 data/dfeet-signal.png,
                 data/bustle.ui,
                 LICENSE
-Build-type:     Simple
+Build-type:     Custom
 Extra-source-files:
                   -- C bits
                     c-sources/bustle-pcap.c,
@@ -34,6 +33,24 @@ Extra-source-files:
                   , ldd-me-up.sh
                   , LICENSE.bundled-libraries
 
+                  -- wow many translate
+                  , po/*.po
+                  , po/*.pot
+
+                  -- intl bits
+                  , data/bustle.appdata.xml.in
+                  , data/bustle.desktop.in
+
+                  -- icons
+                  , data/icons/16x16/bustle.png
+                  , data/icons/22x22/bustle.png
+                  , data/icons/32x32/bustle.png
+                  , data/icons/48x48/bustle.png
+                  , data/icons/256x256/bustle.png
+                  , data/icons/scalable/bustle.svg
+
+x-gettext-po-files:     po/*.po
+x-gettext-domain-name:  bustle
 
 Source-Repository head
   Type:           git
@@ -61,6 +78,7 @@ Executable bustle
                , Bustle.Renderer
                , Bustle.StatisticsPane
                , Bustle.Stats
+               , Bustle.Translation
                , Bustle.Types
                , Bustle.UI
                , Bustle.UI.AboutDialog
@@ -88,12 +106,14 @@ Executable bustle
                , directory
                , filepath
                , glib
-               , gtk >= 0.12.3
+               , gtk >= 0.12.4
+               , hgettext >= 0.1.5
                , mtl
                , pango
                , parsec
                , pcap
                , process
+               , setlocale
                , text
                , time
 
@@ -118,10 +138,12 @@ Executable test-monitor
                , filepath
                , gtk > 0.12
                , glib
+               , hgettext
                , mtl
                , pango
                , parsec
                , pcap
+               , setlocale
                , text
 
 Executable dump-messages
@@ -172,6 +194,8 @@ Test-suite test-renderer
                  , mtl
                  , text
                  , pango
+                 , hgettext
+                 , setlocale
                  , test-framework
                  , test-framework-hunit
                  , HUnit
diff --git a/bustle.sh b/bustle.sh
index 2be1b50..bdf9e51 100755
--- a/bustle.sh
+++ b/bustle.sh
@@ -6,6 +6,9 @@ root="$(dirname $(readlink -f ${0}))"
 bustle_datadir="${root}"
 export bustle_datadir
 
+bustle_localedir="${root}/locale"
+export bustle_localedir
+
 LD_LIBRARY_PATH="${root}/lib:${LD_LIBRARY_PATH}"
 export LD_LIBRARY_PATH
 
diff --git a/c-sources/bustle-pcap.c b/c-sources/bustle-pcap.c
index 1335f75..f68553a 100644
--- a/c-sources/bustle-pcap.c
+++ b/c-sources/bustle-pcap.c
@@ -127,9 +127,9 @@ parse_arguments (
   if (version)
     {
       fprintf (stdout, "bustle-pcap " BUSTLE_VERSION "\n\n");
-      fprintf (stdout, "Copyright 2011 Will Thompson <will.thompson at collabora.co.uk>\n");
+      fprintf (stdout, "Copyright 2011 Will Thompson <will at willthompson.co.uk>\n");
       fprintf (stdout, "This is free software; see the source for copying conditions.  There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.\n\n");
-      fprintf (stdout, "Written by Will Thompson <will.thompson at collabora.co.uk>\n");
+      fprintf (stdout, "Written by Will Thompson <will at willthompson.co.uk>\n");
       exit (0);
     }
   else if (session_specified && system_specified)
diff --git a/c-sources/pcap-monitor.c b/c-sources/pcap-monitor.c
index 9452343..c9623ae 100644
--- a/c-sources/pcap-monitor.c
+++ b/c-sources/pcap-monitor.c
@@ -411,6 +411,7 @@ initable_init (
 {
   BustlePcapMonitor *self = BUSTLE_PCAP_MONITOR (initable);
   BustlePcapMonitorPrivate *priv = self->priv;
+  gchar *address;
   GDBusProxy *bus;
 
   if (priv->bus_type == G_BUS_TYPE_NONE)
@@ -451,7 +452,35 @@ initable_init (
       return FALSE;
     }
 
-  priv->connection = g_bus_get_sync (priv->bus_type, NULL, error);
+  address = g_dbus_address_get_for_bus_sync (priv->bus_type, NULL, error);
+  if (address == NULL)
+    {
+      g_prefix_error (error, "Couldn't get %s bus address: ",
+          priv->bus_type == G_BUS_TYPE_SESSION ? "session" : "system");
+      return FALSE;
+    }
+
+  if (*address == '\0')
+    {
+      g_set_error (error,
+          G_IO_ERROR,
+          G_IO_ERROR_FAILED,
+          "Failed to look up the %s bus address. %s",
+          priv->bus_type == G_BUS_TYPE_SESSION ? "session" : "system",
+          priv->bus_type == G_BUS_TYPE_SESSION
+              ? "Is DBUS_SESSION_BUS_ADDRESS properly set?"
+              : "");
+      g_free (address);
+      return FALSE;
+    }
+
+  priv->connection = g_dbus_connection_new_for_address_sync (address,
+      G_DBUS_CONNECTION_FLAGS_AUTHENTICATION_CLIENT |
+      G_DBUS_CONNECTION_FLAGS_MESSAGE_BUS_CONNECTION,
+      NULL, /* auth observer */
+      NULL, /* cancellable */
+      error);
+  g_free (address);
   if (priv->connection == NULL)
     {
       g_prefix_error (error, "Couldn't connect to %s bus: ",
@@ -459,12 +488,6 @@ initable_init (
       return FALSE;
     }
 
-  /* Work around <https://bugzilla.gnome.org/show_bug.cgi?id=662100>. With glib
-   * 2.30.1, the client closing the connection erroneously triggers the
-   * (implicitly enabled) exit-on-close logic.
-   */
-  g_dbus_connection_set_exit_on_close (priv->connection, FALSE);
-
   priv->caps = g_dbus_connection_get_capabilities (priv->connection);
 
   bus = g_dbus_proxy_new_sync (priv->connection,
diff --git a/data/bustle.appdata.xml.in b/data/bustle.appdata.xml.in
new file mode 100644
index 0000000..ff276cb
--- /dev/null
+++ b/data/bustle.appdata.xml.in
@@ -0,0 +1,24 @@
+<?xml version="1.0" encoding="UTF-8"?>
+<!-- Copyright 2014 Philip Withnall <philip at tecnocode.co.uk> -->
+<application>
+	<id type="desktop">bustle.desktop</id>
+	<metadata_license>CC-BY-SA-3.0</metadata_license>
+	<project_license>LGPL-2.1+ and GPL-2.0+ and GPL-3.0</project_license>
+	<description>
+		<!-- Translators: These are the application description paragraphs in the AppData file. -->
+		<_p>Bustle draws sequence diagrams of D-Bus activity.</_p>
+		<_p>It shows signal emissions, method calls and their
+		    corresponding returns, with time stamps for each individual
+		    event and the duration of each method call. This can help
+		    you check for unwanted D-Bus traffic, and pinpoint why your
+		    D-Bus-based application isn't performing as well as you
+		    like. It also provides statistics like signal frequencies
+		    and average method call times.</_p>
+	</description>
+	<screenshots>
+		<!-- Translators: This should be the URI of a 691×510 pixel screenshot of Bustle in your language. If you can't take a screenshot, leave the string as the English screenshot. -->
+		<_screenshot type="default" width="691" height="510">http://willthompson.co.uk/bustle/bustle-0.3.1.png</_screenshot>
+	</screenshots>
+	<url type="homepage">http://willthompson.co.uk/bustle/</url>
+	<updatecontact>philip_at_tecnocode.co.uk</updatecontact>
+</application>
diff --git a/data/bustle.desktop.in b/data/bustle.desktop.in
new file mode 100644
index 0000000..e239d52
--- /dev/null
+++ b/data/bustle.desktop.in
@@ -0,0 +1,9 @@
+[Desktop Entry]
+_Name=Bustle
+_Comment=Draw sequence diagrams of D-Bus activity
+Exec=bustle
+Icon=bustle
+Terminal=false
+Type=Application
+Categories=GTK;Development;Debugger;Profiling;
+StartupNotify=true
diff --git a/data/bustle.png b/data/bustle.png
deleted file mode 100644
index 779cefa..0000000
Binary files a/data/bustle.png and /dev/null differ
diff --git a/data/bustle.ui b/data/bustle.ui
index 3e2e98d..626feb1 100644
--- a/data/bustle.ui
+++ b/data/bustle.ui
@@ -5,6 +5,8 @@
     <property name="can_focus">False</property>
     <property name="default_width">900</property>
     <property name="default_height">700</property>
+    <property name="icon-name">bustle</property>
+    <property name="title" translatable="yes">Bustle</property>
     <child>
       <object class="GtkVBox" id="box1">
         <property name="visible">True</property>
@@ -52,7 +54,7 @@
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
                         <property name="tooltip_text" translatable="yes">Display two logs—one for the session bus, one for the system bus—side by side.</property>
-                        <property name="label" translatable="yes">O_pen a pair of logs…</property>
+                        <property name="label" translatable="yes">O_pen a Pair of Logs…</property>
                         <property name="use_underline">True</property>
                       </object>
                     </child>
@@ -119,7 +121,7 @@
                         <property name="visible">True</property>
                         <property name="sensitive">False</property>
                         <property name="can_focus">False</property>
-                        <property name="label" translatable="yes">_Filter visible services…</property>
+                        <property name="label" translatable="yes">_Filter Visible Services…</property>
                         <property name="use_underline">True</property>
                         <accelerator key="f" signal="activate" modifiers="GDK_CONTROL_MASK"/>
                       </object>
@@ -224,7 +226,7 @@
                                   <object class="GtkLabel" id="balahah">
                                     <property name="visible">True</property>
                                     <property name="can_focus">False</property>
-                                    <property name="label" translatable="yes">Record a new log</property>
+                                    <property name="label" translatable="yes">Record a New Log</property>
                                   </object>
                                   <packing>
                                     <property name="expand">True</property>
@@ -270,7 +272,7 @@
                                   <object class="GtkLabel" id="balahah1">
                                     <property name="visible">True</property>
                                     <property name="can_focus">False</property>
-                                    <property name="label" translatable="yes">Open an existing log</property>
+                                    <property name="label" translatable="yes">Open an Existing Log</property>
                                   </object>
                                   <packing>
                                     <property name="expand">True</property>
@@ -367,7 +369,7 @@
                       <object class="GtkLabel" id="label6">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="label" translatable="yes">Message frequencies</property>
+                        <property name="label" translatable="yes">Message Frequencies</property>
                       </object>
                       <packing>
                         <property name="tab_fill">False</property>
@@ -392,7 +394,7 @@
                       <object class="GtkLabel" id="label7">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="label" translatable="yes">Method durations</property>
+                        <property name="label" translatable="yes">Method Durations</property>
                       </object>
                       <packing>
                         <property name="position">1</property>
@@ -418,7 +420,7 @@
                       <object class="GtkLabel" id="label8">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="label" translatable="yes">Message sizes</property>
+                        <property name="label" translatable="yes">Message Sizes</property>
                       </object>
                       <packing>
                         <property name="position">2</property>
@@ -492,10 +494,11 @@
   <object class="GtkDialog" id="openTwoDialog">
     <property name="can_focus">False</property>
     <property name="border_width">5</property>
-    <property name="title" translatable="yes">Open a pair of logs</property>
+    <property name="title" translatable="yes">Open a Pair of Logs</property>
     <property name="resizable">False</property>
     <property name="modal">True</property>
     <property name="type_hint">dialog</property>
+    <property name="icon-name">bustle</property>
     <child internal-child="vbox">
       <object class="GtkBox" id="dialog-vbox1">
         <property name="visible">True</property>
diff --git a/data/icons/16x16/bustle.png b/data/icons/16x16/bustle.png
new file mode 100644
index 0000000..a043a68
Binary files /dev/null and b/data/icons/16x16/bustle.png differ
diff --git a/data/icons/22x22/bustle.png b/data/icons/22x22/bustle.png
new file mode 100644
index 0000000..c9aab82
Binary files /dev/null and b/data/icons/22x22/bustle.png differ
diff --git a/data/icons/256x256/bustle.png b/data/icons/256x256/bustle.png
new file mode 100644
index 0000000..669635c
Binary files /dev/null and b/data/icons/256x256/bustle.png differ
diff --git a/data/icons/32x32/bustle.png b/data/icons/32x32/bustle.png
new file mode 100644
index 0000000..70610b7
Binary files /dev/null and b/data/icons/32x32/bustle.png differ
diff --git a/data/icons/48x48/bustle.png b/data/icons/48x48/bustle.png
new file mode 100644
index 0000000..25ae4a5
Binary files /dev/null and b/data/icons/48x48/bustle.png differ
diff --git a/data/icons/scalable/bustle.svg b/data/icons/scalable/bustle.svg
new file mode 100644
index 0000000..66af4b1
--- /dev/null
+++ b/data/icons/scalable/bustle.svg
@@ -0,0 +1,266 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Created with Inkscape (http://www.inkscape.org/) -->
+
+<svg
+   xmlns:dc="http://purl.org/dc/elements/1.1/"
+   xmlns:cc="http://creativecommons.org/ns#"
+   xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+   xmlns:svg="http://www.w3.org/2000/svg"
+   xmlns="http://www.w3.org/2000/svg"
+   xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+   xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+   width="605.06"
+   height="605.06"
+   id="svg2"
+   version="1.1"
+   inkscape:version="0.48.4 r9939"
+   sodipodi:docname="bustle.svg">
+  <defs
+     id="defs4">
+    <inkscape:path-effect
+       is_visible="true"
+       id="path-effect4126"
+       effect="spiro" />
+    <inkscape:path-effect
+       is_visible="true"
+       id="path-effect4123"
+       effect="spiro" />
+    <inkscape:path-effect
+       is_visible="true"
+       id="path-effect4120"
+       effect="spiro" />
+    <inkscape:path-effect
+       is_visible="true"
+       id="path-effect4117"
+       effect="spiro" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3763"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3759"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-1"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-3"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3759-7"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3763-2"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-6"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-3-1"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-6-2"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3763-2-7"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3770-3-1-2"
+       is_visible="true" />
+    <inkscape:path-effect
+       effect="spiro"
+       id="path-effect3759-7-2"
+       is_visible="true" />
+    <filter
+       id="filter4104"
+       inkscape:label="Chalk and sponge"
+       inkscape:menu="Distort"
+       inkscape:menu-tooltip="Low turbulence gives sponge look and high turbulence chalk"
+       width="1.6"
+       height="2"
+       y="-0.5"
+       x="-0.30000001"
+       color-interpolation-filters="sRGB">
+      <feTurbulence
+         id="feTurbulence4106"
+         baseFrequency="0.4"
+         type="fractalNoise"
+         seed="0"
+         numOctaves="5"
+         result="result1" />
+      <feOffset
+         id="feOffset4108"
+         dx="-5"
+         dy="-5"
+         result="result2" />
+      <feDisplacementMap
+         id="feDisplacementMap4110"
+         in2="result1"
+         xChannelSelector="R"
+         yChannelSelector="G"
+         scale="30"
+         in="SourceGraphic" />
+    </filter>
+    <filter
+       id="filter4183"
+       inkscape:label="Chalk and sponge"
+       inkscape:menu="Distort"
+       inkscape:menu-tooltip="Low turbulence gives sponge look and high turbulence chalk"
+       width="1.6"
+       height="2"
+       y="-0.5"
+       x="-0.30000001"
+       color-interpolation-filters="sRGB">
+      <feTurbulence
+         id="feTurbulence4185"
+         baseFrequency="0.4"
+         type="fractalNoise"
+         seed="0"
+         numOctaves="5"
+         result="result1" />
+      <feOffset
+         id="feOffset4187"
+         dx="-5"
+         dy="-5"
+         result="result2" />
+      <feDisplacementMap
+         id="feDisplacementMap4189"
+         in2="result1"
+         xChannelSelector="R"
+         yChannelSelector="G"
+         scale="30"
+         in="SourceGraphic" />
+    </filter>
+    <inkscape:path-effect
+       is_visible="true"
+       id="path-effect4117-2"
+       effect="spiro" />
+  </defs>
+  <sodipodi:namedview
+     id="base"
+     pagecolor="#ffffff"
+     bordercolor="#666666"
+     borderopacity="1.0"
+     inkscape:pageopacity="0.0"
+     inkscape:pageshadow="2"
+     inkscape:zoom="0.59"
+     inkscape:cx="351.05408"
+     inkscape:cy="216.30891"
+     inkscape:document-units="px"
+     inkscape:current-layer="layer1"
+     showgrid="false"
+     inkscape:window-width="1388"
+     inkscape:window-height="833"
+     inkscape:window-x="50"
+     inkscape:window-y="223"
+     inkscape:window-maximized="0"
+     fit-margin-top="0"
+     fit-margin-left="0"
+     fit-margin-right="0"
+     fit-margin-bottom="0">
+    <inkscape:grid
+       type="xygrid"
+       id="grid3834"
+       empspacing="5"
+       visible="true"
+       enabled="true"
+       snapvisiblegridlinesonly="true"
+       originx="-56.941089px"
+       originy="-465.18127px" />
+  </sodipodi:namedview>
+  <metadata
+     id="metadata7">
+    <rdf:RDF>
+      <cc:Work
+         rdf:about="">
+        <dc:format>image/svg+xml</dc:format>
+        <dc:type
+           rdf:resource="http://purl.org/dc/dcmitype/StillImage" />
+        <dc:title />
+      </cc:Work>
+    </rdf:RDF>
+  </metadata>
+  <g
+     inkscape:label="Layer 1"
+     inkscape:groupmode="layer"
+     id="layer1"
+     transform="translate(-56.941089,17.879098)">
+    <path
+       style="fill:none;stroke:#74b674;stroke-width:27.59247017;stroke-miterlimit:4;stroke-opacity:1;stroke-dasharray:82.77741051, 27.59247017;stroke-dashoffset:27.59247017"
+       d="m 70.761814,288.36996 c -0.01207,-1.2669 -0.02449,-2.53589 -0.02449,-3.80671 0,-159.41492 129.271656,-288.6461129 288.736206,-288.6461129 159.46457,0 288.73621,129.2311929 288.73621,288.6461129 l 0,0 0,0 c 0,1.27082 -0.009,2.53969 -0.0245,3.80671"
+       id="path3802-8"
+       inkscape:connector-curvature="0"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+    <path
+       sodipodi:type="arc"
+       style="fill:none;stroke:#000000;stroke-width:34.42315674;stroke-miterlimit:10;stroke-opacity:1;stroke-dasharray:none;stroke-dashoffset:0"
+       id="path2985-7"
+       sodipodi:cx="381.42856"
+       sodipodi:cy="433.79074"
+       sodipodi:rx="130"
+       sodipodi:ry="118.57143"
+       d="m 511.42856,433.79074 a 130,118.57143 0 1 1 -260,0 130,118.57143 0 1 1 260,0 z"
+       transform="matrix(0.50880116,0,0,0.55776489,164.13818,45.848517)"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+    <path
+       style="fill:none;stroke:#000000;stroke-width:18.45480156;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:4;stroke-opacity:1;stroke-dasharray:none"
+       d="m 417.41556,287.80173 211.44171,0"
+       id="path3757-7"
+       inkscape:path-effect="#path-effect3759-7"
+       inkscape:original-d="m 417.41556,287.80173 211.44171,0"
+       inkscape:connector-curvature="0"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+    <path
+       style="fill:none;stroke:#000000;stroke-width:18.17925262;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:4;stroke-opacity:1;stroke-dasharray:none"
+       d="m 294.08479,287.66116 -211.718251,0.2812"
+       id="path3761-7"
+       inkscape:path-effect="#path-effect3763-2"
+       inkscape:original-d="m 294.08479,287.66116 -211.718251,0.2812"
+       inkscape:connector-curvature="0"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+    <path
+       style="fill:none;stroke:#000000;stroke-width:18.33793068;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:4;stroke-opacity:1;stroke-dasharray:none"
+       d="M 200.97285,226.67532 77.897224,289.6408 200.97285,348.92819"
+       id="path3768-2"
+       inkscape:path-effect="#path-effect3770-6"
+       inkscape:original-d="M 200.97285,226.67532 77.897224,289.6408 200.97285,348.92819"
+       inkscape:connector-curvature="0"
+       sodipodi:nodetypes="ccc"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+    <path
+       style="fill:none;stroke:#000000;stroke-width:18.33793068;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:4;stroke-opacity:1;stroke-dasharray:none"
+       d="M 520.66838,225.39683 643.74401,288.36232 520.66838,347.6497"
+       id="path3768-9-7"
+       inkscape:path-effect="#path-effect3770-3-1"
+       inkscape:original-d="M 520.66838,225.39683 643.74401,288.36232 520.66838,347.6497"
+       inkscape:connector-curvature="0"
+       sodipodi:nodetypes="ccc"
+       inkscape:export-filename="/home/ziz-2/Desktop/kkkkkkkk.png"
+       inkscape:export-xdpi="8.2586517"
+       inkscape:export-ydpi="8.2586517" />
+  </g>
+</svg>
diff --git a/po/en.po b/po/en.po
new file mode 100644
index 0000000..a1fa268
--- /dev/null
+++ b/po/en.po
@@ -0,0 +1,164 @@
+# Translation file
+msgid ""
+msgstr ""
+"Project-Id-Version: PACKAGE VERSION\n"
+"Report-Msgid-Bugs-To: \n"
+"POT-Creation-Date: 2009-01-13 06:05-0800\n"
+"PO-Revision-Date: 2014-01-12 14:19+0000\n"
+"Last-Translator: Will Thompson <will at willthompson.co.uk>\n"
+"Language-Team: English\n"
+"Language: en\n"
+"MIME-Version: 1.0\n"
+"Content-Type: text/plain; charset=UTF-8\n"
+"Content-Transfer-Encoding: 8bit\n"
+"Plural-Forms: nplurals=2; plural=(n != 1);\n"
+
+#: Bustle/StatisticsPane.hs:210 Bustle/StatisticsPane.hs:213
+msgid "%.1f ms"
+msgstr "%.1f ms"
+
+#: Bustle/UI.hs:467
+msgid "%s - Bustle"
+msgstr "%s – Bustle"
+
+#: Bustle/Noninteractive.hs:55
+msgid "(no interface)"
+msgstr "(no interface)"
+
+#: Bustle/UI/DetailsView.hs:148
+msgid "<unknown>"
+msgstr "<unknown>"
+
+#: Bustle/UI/DetailsView.hs:87
+msgid "Arguments:"
+msgstr "Arguments:"
+
+#: Bustle/StatisticsPane.hs:228
+msgid "B"
+msgstr "B"
+
+#: Bustle/UI/AboutDialog.hs:47
+msgid "Bustle"
+msgstr "Bustle"
+
+#: Bustle/StatisticsPane.hs:211
+msgid "Calls"
+msgstr "Calls"
+
+#: Bustle/UI.hs:294
+msgid "Close _Without Saving"
+msgstr "Close _Without Saving"
+
+#: Bustle/UI.hs:210
+msgid "Could not read '%s'"
+msgstr "Could not read ‘%s’"
+
+#: Bustle/Noninteractive.hs:48
+msgid "Couldn't parse '%s': %s"
+msgstr "Couldn’t parse ‘%s’: %s"
+
+#: Bustle/UI/DetailsView.hs:110
+msgid "Directed signal"
+msgstr "Directed signal"
+
+#: Bustle/UI/DetailsView.hs:106
+msgid "Error"
+msgstr "Error"
+
+#: Bustle/StatisticsPane.hs:171
+msgid "Frequency"
+msgstr "Frequency"
+
+#: Bustle/UI.hs:293
+msgid "If you don't save, this log will be lost forever."
+msgstr "If you don’t save, this log will be lost forever."
+
+#: Bustle/StatisticsPane.hs:229
+msgid "KB"
+msgstr "KB"
+
+#: Bustle/StatisticsPane.hs:264
+msgid "Largest"
+msgstr "Largest"
+
+#: Bustle/StatisticsPane.hs:230
+msgid "MB"
+msgstr "MB"
+
+#: Bustle/StatisticsPane.hs:212 Bustle/StatisticsPane.hs:263
+msgid "Mean"
+msgstr "Mean"
+
+#: Bustle/StatisticsPane.hs:249
+msgid "Member"
+msgstr "Member"
+
+#: Bustle/UI/DetailsView.hs:85
+msgid "Member:"
+msgstr "Member:"
+
+#: Bustle/StatisticsPane.hs:200
+msgid "Method"
+msgstr "Method"
+
+#: Bustle/UI/DetailsView.hs:104
+msgid "Method call"
+msgstr "Method call"
+
+#: Bustle/UI/DetailsView.hs:105
+msgid "Method return"
+msgstr "Method return"
+
+#: Bustle/StatisticsPane.hs:156
+msgid "Name"
+msgstr "Name"
+
+#: Bustle/UI/DetailsView.hs:127
+msgid ""
+"No message body information is available. Please capture a fresh log using a "
+"recent version of Bustle!"
+msgstr ""
+"No message body information is available. Please capture a fresh log using a "
+"recent version of Bustle!"
+
+#: Bustle/Loader.hs:64
+msgid "Parse error %s"
+msgstr "Parse error %s"
+
+#: Bustle/UI/DetailsView.hs:84
+msgid "Path:"
+msgstr "Path:"
+
+#: Bustle/UI.hs:286
+msgid "Save log '%s' before closing?"
+msgstr "Save log ‘%s’ before closing?"
+
+#: Bustle/UI/DetailsView.hs:109
+msgid "Signal"
+msgstr "Signal"
+
+#: Bustle/StatisticsPane.hs:262
+msgid "Smallest"
+msgstr "Smallest"
+
+#: Bustle/UI/AboutDialog.hs:49
+msgid "Someone's favourite D-Bus profiler"
+msgstr "Someone's favourite D-Bus profiler"
+
+#: Bustle/StatisticsPane.hs:209
+msgid "Total"
+msgstr "Total"
+
+#: Bustle/UI/FilterDialog.hs:105
+msgid ""
+"Unticking a service hides its column in the diagram, and all messages it is "
+"involved in. That is, all methods it calls or are called on it, the "
+"corresponding returns, and all signals it emits will be hidden."
+msgstr ""
+"Unticking a service hides its column in the diagram, and all messages it is "
+"involved in. That is, all methods it calls or are called on it, the "
+"corresponding returns, and all signals it emits will be hidden."
+
+#: Bustle/Util.hs:53
+msgid "Warning: "
+msgstr "Warning: "
diff --git a/po/messages.pot b/po/messages.pot
new file mode 100644
index 0000000..6bda2a0
--- /dev/null
+++ b/po/messages.pot
@@ -0,0 +1,157 @@
+# Translation file
+
+msgid ""
+msgstr ""
+
+"Project-Id-Version: PACKAGE VERSION\n"
+"Report-Msgid-Bugs-To: \n"
+"POT-Creation-Date: 2009-01-13 06:05-0800\n"
+"PO-Revision-Date: YEAR-MO-DA HO:MI+ZONE\n"
+"Last-Translator: FULL NAME <EMAIL at ADDRESS>\n"
+"Language-Team: LANGUAGE <LL at li.org>\n"
+"MIME-Version: 1.0\n"
+"Content-Type: text/plain; charset=UTF-8\n"
+"Content-Transfer-Encoding: 8bit\n"
+
+#: Bustle/StatisticsPane.hs:210
+#: Bustle/StatisticsPane.hs:213
+msgid "%.1f ms"
+msgstr ""
+
+#: Bustle/UI.hs:467
+msgid "%s - Bustle"
+msgstr ""
+
+#: Bustle/Noninteractive.hs:55
+msgid "(no interface)"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:148
+msgid "<unknown>"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:87
+msgid "Arguments:"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:228
+msgid "B"
+msgstr ""
+
+#: Bustle/UI/AboutDialog.hs:47
+msgid "Bustle"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:211
+msgid "Calls"
+msgstr ""
+
+#: Bustle/UI.hs:294
+msgid "Close _Without Saving"
+msgstr ""
+
+#: Bustle/UI.hs:210
+msgid "Could not read '%s'"
+msgstr ""
+
+#: Bustle/Noninteractive.hs:48
+msgid "Couldn't parse '%s': %s"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:110
+msgid "Directed signal"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:106
+msgid "Error"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:171
+msgid "Frequency"
+msgstr ""
+
+#: Bustle/UI.hs:293
+msgid "If you don't save, this log will be lost forever."
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:229
+msgid "KB"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:264
+msgid "Largest"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:230
+msgid "MB"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:212
+#: Bustle/StatisticsPane.hs:263
+msgid "Mean"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:249
+msgid "Member"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:85
+msgid "Member:"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:200
+msgid "Method"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:104
+msgid "Method call"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:105
+msgid "Method return"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:156
+msgid "Name"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:127
+msgid "No message body information is available. Please capture a fresh log using a recent version of Bustle!"
+msgstr ""
+
+#: Bustle/Loader.hs:64
+msgid "Parse error %s"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:84
+msgid "Path:"
+msgstr ""
+
+#: Bustle/UI.hs:286
+msgid "Save log '%s' before closing?"
+msgstr ""
+
+#: Bustle/UI/DetailsView.hs:109
+msgid "Signal"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:262
+msgid "Smallest"
+msgstr ""
+
+#: Bustle/UI/AboutDialog.hs:49
+msgid "Someone's favourite D-Bus profiler"
+msgstr ""
+
+#: Bustle/StatisticsPane.hs:209
+msgid "Total"
+msgstr ""
+
+#: Bustle/UI/FilterDialog.hs:105
+msgid "Unticking a service hides its column in the diagram, and all messages it is involved in. That is, all methods it calls or are called on it, the corresponding returns, and all signals it emits will be hidden."
+msgstr ""
+
+#: Bustle/Util.hs:53
+msgid "Warning: "
+msgstr ""
+

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/pkg-haskell/bustle.git



More information about the Pkg-haskell-commits mailing list