[bustle] patch to build with glib/pango 0.13

Jens Petersen petersen at fedoraproject.org
Sat Feb 14 03:37:02 UTC 2015


commit 0d963334186ce853c5c928fdbc133df86da3869e
Author: Jens Petersen <petersen at redhat.com>
Date:   Sat Feb 14 12:36:21 2015 +0900

    patch to build with glib/pango 0.13

 bustle-0.4.7-gtk2hs-0.13.patch |  624 ++++++++++++++++++++++++++++++++++++++++
 bustle.spec                    |    6 +-
 2 files changed, 628 insertions(+), 2 deletions(-)
---
diff --git a/bustle-0.4.7-gtk2hs-0.13.patch b/bustle-0.4.7-gtk2hs-0.13.patch
new file mode 100644
index 0000000..6dd730d
--- /dev/null
+++ b/bustle-0.4.7-gtk2hs-0.13.patch
@@ -0,0 +1,624 @@
+diff --git a/Bustle/Diagram.hs b/Bustle/Diagram.hs
+index d558beb..f9a96b7 100644
+--- a/Bustle/Diagram.hs
++++ b/Bustle/Diagram.hs
+@@ -53,13 +53,13 @@ import Control.Applicative ((<$>), (<*>))
+ 
+ import Control.Monad.Reader
+ 
+-import Graphics.Rendering.Cairo
++import Graphics.Rendering.Cairo (Operator(..), Render, arc, curveTo, fill, getCurrentPoint, lineTo, moveTo, newPath, paint, rectangle, restore, save, setDash, setLineWidth, setOperator, setSourceRGB, stroke)
+ import Graphics.UI.Gtk.Cairo (cairoCreateContext, showLayout)
+ import Graphics.Rendering.Pango.Layout
+ import Graphics.Rendering.Pango.Font
+ 
+-import qualified Bustle.Markup as Markup
+-import Bustle.Markup (Markup)
++import qualified Bustle.Marquee as Marquee
++import Bustle.Marquee (Marquee)
+ import Bustle.Util
+ import Bustle.Types (ObjectPath, InterfaceName, MemberName)
+ 
+@@ -430,7 +430,7 @@ drawArc cx cy dx dy x1 y1 x2 y2 cap = saved $ do
+     stroke
+ 
+     setSourceRGB 0 0 0
+-    l <- mkLayout (Markup.escape cap) EllipsizeNone AlignLeft
++    l <- mkLayout (Marquee.escape cap) EllipsizeNone AlignLeft
+     (PangoRectangle _ _ textWidth _, _) <- liftIO $ layoutGetExtents l
+     let tx = min x2 dx + abs (x2 - dx) / 2
+     moveTo (if x1 > cx then tx - textWidth else tx) (y2 - 5)
+@@ -445,12 +445,18 @@ font = unsafePerformIO $ do
+ {-# NOINLINE font #-}
+ 
+ mkLayout :: (MonadIO m)
+-         => Markup -> EllipsizeMode -> LayoutAlignment
++         => Marquee -> EllipsizeMode -> LayoutAlignment
+          -> m PangoLayout
+ mkLayout s e a = liftIO $ do
+     ctx <- cairoCreateContext Nothing
+     layout <- layoutEmpty ctx
+-    layoutSetMarkup layout (Markup.unMarkup s)
++    -- layoutSetMarkup returns the un-marked-up text. We don't care about it,
++    -- but recent versions of Pango give it the type
++    --    GlibString string => ... -> IO string
++    -- which we need to disambiguate between Text and String. Old versions were
++    --    .. -> IO String
++    -- so go with that.
++    layoutSetMarkup layout (Marquee.toPangoMarkup s) :: IO String
+     layoutSetFontDescription layout (Just font)
+     layoutSetEllipsize layout e
+     layoutSetAlignment layout a
+@@ -464,7 +470,7 @@ withWidth m w = do
+ 
+ drawHeader :: [String] -> Double -> Double -> Render ()
+ drawHeader names x y = forM_ (zip [0..] names) $ \(i, name) -> do
+-    l <- mkLayout (Markup.escape name) EllipsizeEnd AlignCenter `withWidth` columnWidth
++    l <- mkLayout (Marquee.escape name) EllipsizeEnd AlignCenter `withWidth` columnWidth
+     moveTo (x - (columnWidth / 2)) (y + i * h)
+     showLayout l
+   where h = 10
+@@ -485,14 +491,14 @@ drawMember p i m isReturn x y = do
+       moveTo (x - memberWidth / 2) y'
+       showLayout l
+ 
+-    path = (if isReturn then id else Markup.b) $ Markup.escape p
++    path = (if isReturn then id else Marquee.b) $ Marquee.escape p
+     fullMethod =
+-        (if isReturn then Markup.i else id) $ Markup.formatMember i m
++        (if isReturn then Marquee.i else id) $ Marquee.formatMember i m
+ 
+ drawTimestamp :: String -> Double -> Double -> Render ()
+ drawTimestamp ts x y = do
+     moveTo (x - timestampWidth / 2) (y - 10)
+-    showLayout =<< mkLayout (Markup.escape ts) EllipsizeNone AlignLeft `withWidth` timestampWidth
++    showLayout =<< mkLayout (Marquee.escape ts) EllipsizeNone AlignLeft `withWidth` timestampWidth
+ 
+ drawClientLines :: NonEmpty Double -> Double -> Double -> Render ()
+ drawClientLines xs y1 y2 = saved $ do
+diff --git a/Bustle/Markup.hs b/Bustle/Markup.hs
+deleted file mode 100644
+index 5c31552..0000000
+--- a/Bustle/Markup.hs
++++ /dev/null
+@@ -1,112 +0,0 @@
+-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
+-{-
+-Bustle.Diagram: My First Type-Safe Markup Library
+-Copyright © 2011 Will Thompson
+-
+-This library is free software; you can redistribute it and/or
+-modify it under the terms of the GNU Lesser General Public
+-License as published by the Free Software Foundation; either
+-version 2.1 of the License, or (at your option) any later version.
+-
+-This library 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
+-Lesser General Public License for more details.
+-
+-You should have received a copy of the GNU Lesser General Public
+-License along with this library; if not, write to the Free Software
+-Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
+--}
+-module Bustle.Markup
+-  ( Markup
+-  , unMarkup
+-  , tag
+-  , b
+-  , i
+-  , light
+-  , red
+-  , a
+-  , escape
+-
+-  , formatMember
+-  )
+-where
+-
+-import Data.Monoid
+-import Data.Text (Text)
+-import qualified Data.Text as T
+-
+-import Graphics.Rendering.Pango.BasicTypes (Weight(..))
+-import Graphics.Rendering.Pango.Layout (escapeMarkup)
+-import Graphics.Rendering.Pango.Markup (markSpan, SpanAttribute(..))
+-
+-import Bustle.Types (ObjectPath, formatObjectPath, InterfaceName, formatInterfaceName, MemberName, formatMemberName)
+-
+-newtype Markup = Markup { unMarkup :: String }
+-    deriving (Show, Read, Ord, Eq)
+-
+-instance Monoid Markup where
+-    mempty = Markup ""
+-    mappend x y = Markup (unMarkup x `mappend` unMarkup y)
+-    mconcat = Markup . mconcat . map unMarkup
+-
+---raw :: String -> Markup
+---raw = Markup
+-
+-tag :: String -> Markup -> Markup
+-tag name contents =
+-    Markup $ concat [ "<", name, ">"
+-                    , unMarkup contents
+-                    , "</", name, ">"
+-                    ]
+-
+-b, i :: Markup -> Markup
+-b = tag "b"
+-i = tag "i"
+-
+-a :: String
+-  -> String
+-  -> Markup
+-a href contents =
+-  Markup $ concat [ "<a href=\"", escapeMarkup href, "\">"
+-                  , escapeMarkup contents
+-                  , "</a>"
+-                  ]
+-
+-span_ :: [SpanAttribute] -> Markup -> Markup
+-span_ attrs = Markup . markSpan attrs . unMarkup
+-
+-light :: Markup -> Markup
+-light = span_ [FontWeight WeightLight]
+-
+-red :: Markup -> Markup
+-red = span_ [FontForeground "#ff0000"]
+-
+--- Kind of a transitional measure because some strings are Strings, and some are Text.
+-class Unescaped s where
+-    toString :: s -> String
+-
+-instance Unescaped String where
+-    toString = id
+-
+-instance Unescaped Text where
+-    toString = T.unpack
+-
+-instance Unescaped InterfaceName where
+-    toString = formatInterfaceName
+-
+-instance Unescaped ObjectPath where
+-    toString = formatObjectPath
+-
+-instance Unescaped MemberName where
+-    toString = formatMemberName
+-
+-escape :: Unescaped s => s -> Markup
+-escape = Markup . escapeMarkup . toString
+-
+-formatMember :: Maybe InterfaceName -> MemberName -> Markup
+-formatMember iface member = iface' `mappend` b (escape member)
+-  where
+-    iface' = case iface of
+-        Just ifaceName -> escape ifaceName `mappend` Markup "."
+-        Nothing        -> light (escape "(no interface) ")
+diff --git a/Bustle/Marquee.hs b/Bustle/Marquee.hs
+new file mode 100644
+index 0000000..46c2b4c
+--- /dev/null
++++ b/Bustle/Marquee.hs
+@@ -0,0 +1,114 @@
++{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
++{-
++Bustle.Marquee: My First Type-Safe Markup Library With A Cutesy Name To Not Collide With Pango's 'Markup' Which Is A Synonym For String
++Copyright © 2011 Will Thompson
++
++This library is free software; you can redistribute it and/or
++modify it under the terms of the GNU Lesser General Public
++License as published by the Free Software Foundation; either
++version 2.1 of the License, or (at your option) any later version.
++
++This library 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
++Lesser General Public License for more details.
++
++You should have received a copy of the GNU Lesser General Public
++License along with this library; if not, write to the Free Software
++Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
++-}
++module Bustle.Marquee
++  ( Marquee
++  , toPangoMarkup
++  , tag
++  , b
++  , i
++  , light
++  , red
++  , a
++  , escape
++
++  , formatMember
++
++  , toString
++  )
++where
++
++import Data.Monoid
++import Data.Text (Text)
++import qualified Data.Text as T
++
++import Graphics.Rendering.Pango.BasicTypes (Weight(..))
++import Graphics.Rendering.Pango.Layout (escapeMarkup)
++import Graphics.Rendering.Pango.Markup (markSpan, SpanAttribute(..))
++
++import Bustle.Types (ObjectPath, formatObjectPath, InterfaceName, formatInterfaceName, MemberName, formatMemberName)
++
++newtype Marquee = Marquee { unMarquee :: String }
++    deriving (Show, Read, Ord, Eq)
++
++toPangoMarkup :: Marquee -> String
++toPangoMarkup = unMarquee
++
++instance Monoid Marquee where
++    mempty = Marquee ""
++    mappend x y = Marquee (unMarquee x `mappend` unMarquee y)
++    mconcat = Marquee . mconcat . map unMarquee
++
++tag :: String -> Marquee -> Marquee
++tag name contents =
++    Marquee $ concat [ "<", name, ">"
++                    , unMarquee contents
++                    , "</", name, ">"
++                    ]
++
++b, i :: Marquee -> Marquee
++b = tag "b"
++i = tag "i"
++
++a :: String
++  -> String
++  -> Marquee
++a href contents =
++  Marquee $ concat [ "<a href=\"", escapeMarkup href, "\">"
++                  , escapeMarkup contents
++                  , "</a>"
++                  ]
++
++span_ :: [SpanAttribute] -> Marquee -> Marquee
++span_ attrs = Marquee . markSpan attrs . unMarquee
++
++light :: Marquee -> Marquee
++light = span_ [FontWeight WeightLight]
++
++red :: Marquee -> Marquee
++red = span_ [FontForeground "#ff0000"]
++
++-- Kind of a transitional measure because some strings are Strings, and some are Text.
++class Unescaped s where
++    toString :: s -> String
++
++instance Unescaped String where
++    toString = id
++
++instance Unescaped Text where
++    toString = T.unpack
++
++instance Unescaped InterfaceName where
++    toString = formatInterfaceName
++
++instance Unescaped ObjectPath where
++    toString = formatObjectPath
++
++instance Unescaped MemberName where
++    toString = formatMemberName
++
++escape :: Unescaped s => s -> Marquee
++escape = Marquee . escapeMarkup . toString
++
++formatMember :: Maybe InterfaceName -> MemberName -> Marquee
++formatMember iface member = iface' `mappend` b (escape member)
++  where
++    iface' = case iface of
++        Just ifaceName -> escape ifaceName `mappend` Marquee "."
++        Nothing        -> light (escape "(no interface) ")
+diff --git a/Bustle/StatisticsPane.hs b/Bustle/StatisticsPane.hs
+index 8e895a8..1faead4 100644
+--- a/Bustle/StatisticsPane.hs
++++ b/Bustle/StatisticsPane.hs
+@@ -26,12 +26,12 @@ where
+ import Control.Applicative ((<$>))
+ import Control.Monad (forM_)
+ import Text.Printf
+-import Graphics.UI.Gtk hiding (Markup)
++import Graphics.UI.Gtk
+ import Bustle.Stats
+ import Bustle.Translation (__)
+ import Bustle.Types (Log)
+-import qualified Bustle.Markup as Markup
+-import Bustle.Markup (Markup)
++import qualified Bustle.Marquee as Marquee
++import Bustle.Marquee (Marquee)
+ import Data.Monoid
+ 
+ data StatsPane =
+@@ -83,20 +83,20 @@ statsPaneSetMessages sp sessionMessages systemMessages = do
+ addTextRenderer :: TreeViewColumn
+                 -> ListStore a
+                 -> Bool
+-                -> (a -> Markup)
++                -> (a -> Marquee)
+                 -> IO CellRendererText
+ addTextRenderer col store expand f = do
+     renderer <- cellRendererTextNew
+     cellLayoutPackStart col renderer expand
+     set renderer [ cellTextSizePoints := 7 ]
+     cellLayoutSetAttributes col renderer store $ \x ->
+-        [ cellTextMarkup := (Just . Markup.unMarkup) $ f x ]
++        [ cellTextMarkup := (Just . Marquee.toPangoMarkup) $ f x ]
+     return renderer
+ 
+ addMemberRenderer :: TreeViewColumn
+                   -> ListStore a
+                   -> Bool
+-                  -> (a -> Markup)
++                  -> (a -> Marquee)
+                   -> IO CellRendererText
+ addMemberRenderer col store expand f = do
+     renderer <- addTextRenderer col store expand f
+@@ -110,7 +110,7 @@ addMemberRenderer col store expand f = do
+ addStatColumn :: TreeView
+               -> ListStore a
+               -> String
+-              -> (a -> Markup)
++              -> (a -> Marquee)
+               -> IO ()
+ addStatColumn view store title f = do
+     col <- treeViewColumnNew
+@@ -126,7 +126,7 @@ addTextStatColumn :: TreeView
+                   -> (a -> String)
+                   -> IO ()
+ addTextStatColumn view store title f =
+-    addStatColumn view store title (Markup.escape . f)
++    addStatColumn view store title (Marquee.escape . f)
+ 
+ -- If we managed to load the method and signal icons...
+ maybeAddTypeIconColumn :: CellLayoutClass layout
+@@ -164,7 +164,7 @@ newCountView method signal = do
+           TallySignal -> False
+ 
+   addMemberRenderer nameColumn countStore True $ \fi ->
+-      Markup.formatMember (fiInterface fi) (fiMember fi)
++      Marquee.formatMember (fiInterface fi) (fiMember fi)
+   treeViewAppendColumn countView nameColumn
+ 
+   countColumn <- treeViewColumnNew
+@@ -203,7 +203,7 @@ newTimeView = do
+                  ]
+ 
+   addMemberRenderer nameColumn timeStore True $ \ti ->
+-      Markup.formatMember (tiInterface ti) (tiMethodName ti)
++      Marquee.formatMember (tiInterface ti) (tiMethodName ti)
+   treeViewAppendColumn timeView nameColumn
+ 
+   addTextStatColumn timeView timeStore (__ "Total")
+@@ -214,16 +214,16 @@ newTimeView = do
+ 
+   return (timeStore, timeView)
+ 
+-formatSizeInfoMember :: SizeInfo -> Markup
++formatSizeInfoMember :: SizeInfo -> Marquee
+ formatSizeInfoMember si =
+-    f (Markup.formatMember (siInterface si) (siName si))
++    f (Marquee.formatMember (siInterface si) (siName si))
+   where
+     f = case siType si of
+-            SizeReturn -> Markup.i
+-            SizeError  -> Markup.red
++            SizeReturn -> Marquee.i
++            SizeError  -> Marquee.red
+             _          -> id
+ 
+-formatSize :: Int -> Markup
++formatSize :: Int -> Marquee
+ formatSize s
+     | s < maxB = value 1 `mappend` units (__ "B")
+     | s < maxKB = value 1024 `mappend` units (__ "KB")
+@@ -232,9 +232,9 @@ formatSize s
+     maxB = 10000
+     maxKB = 10000 * 1024
+ 
+-    units = Markup.escape . (' ':)
++    units = Marquee.escape . (' ':)
+ 
+-    value factor = Markup.escape (show (s `div` factor))
++    value factor = Marquee.escape (show (s `div` factor))
+ 
+ newSizeView :: Maybe Pixbuf
+             -> Maybe Pixbuf
+diff --git a/Bustle/UI.hs b/Bustle/UI.hs
+index a78797e..733dd08 100644
+--- a/Bustle/UI.hs
++++ b/Bustle/UI.hs
+@@ -38,6 +38,7 @@ import Bustle.Application.Monad
+ import Bustle.Renderer
+ import Bustle.Types
+ import Bustle.Diagram
++import Bustle.Marquee (toString)
+ import Bustle.Util
+ import Bustle.UI.AboutDialog
+ import Bustle.UI.Canvas
+@@ -281,7 +282,7 @@ promptToSave wi = io $ do
+     case mdetails of
+         Just (RecordedLog tempFilePath) -> do
+             let tempFileName = takeFileName tempFilePath
+-                title = printf (__ "Save log '%s' before closing?") tempFileName
++                title = printf (__ "Save log '%s' before closing?") tempFileName :: String
+             prompt <- messageDialogNew (Just (wiWindow wi))
+                                        [DialogModal]
+                                        MessageWarning
+@@ -459,7 +460,8 @@ wiSetLogDetails :: WindowInfo
+                 -> IO ()
+ wiSetLogDetails wi logDetails = do
+     writeIORef (wiLogDetails wi) (Just logDetails)
+-    windowSetTitle (wiWindow wi) (printf (__ "%s - Bustle") (logWindowTitle logDetails))
++    windowSetTitle (wiWindow wi)
++        (printf (__ "%s - Bustle") (logWindowTitle logDetails) :: String)
+ 
+ setPage :: MonadIO io
+         => WindowInfo
+@@ -525,7 +527,7 @@ loadPixbuf :: FilePath -> IO (Maybe Pixbuf)
+ loadPixbuf filename = do
+   iconName <- getDataFileName $ "data/" ++ filename
+   C.catch (fmap Just (pixbufNewFromFile iconName))
+-          (\(GError _ _ msg) -> warn msg >> return Nothing)
++          (\(GError _ _ msg) -> warn (toString msg) >> return Nothing)
+ 
+ openDialogue :: Window -> B ()
+ openDialogue window = embedIO $ \r -> do
+diff --git a/Bustle/UI/Canvas.hs b/Bustle/UI/Canvas.hs
+index 46c1582..13ec44e 100644
+--- a/Bustle/UI/Canvas.hs
++++ b/Bustle/UI/Canvas.hs
+@@ -16,6 +16,7 @@ You should have received a copy of the GNU Lesser General Public
+ License along with this library; if not, write to the Free Software
+ Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
+ -}
++{-# LANGUAGE OverloadedStrings #-}
+ module Bustle.UI.Canvas
+   (
+     Canvas
+@@ -58,7 +59,7 @@ canvasNew :: Eq a
+           -> (Maybe a -> IO ())
+           -> IO (Canvas a)
+ canvasNew builder showBounds selectionChangedCb = do
+-    layout <- builderGetObject builder castToLayout "diagramLayout"
++    layout <- builderGetObject builder castToLayout ("diagramLayout" :: String)
+     idRef <- newIORef Nothing
+     shapesRef <- newIORef []
+     widthRef <- newIORef 0
+diff --git a/Bustle/UI/DetailsView.hs b/Bustle/UI/DetailsView.hs
+index 35e80d6..c347bbd 100644
+--- a/Bustle/UI/DetailsView.hs
++++ b/Bustle/UI/DetailsView.hs
+@@ -25,13 +25,13 @@ module Bustle.UI.DetailsView
+ where
+ 
+ import Data.List (intercalate)
+-import Graphics.UI.Gtk hiding (Signal, Markup)
++import Graphics.UI.Gtk hiding (Signal)
+ 
+ import qualified DBus as D
+ 
+ import Bustle.Translation (__)
+ import Bustle.Types
+-import Bustle.Markup
++import Bustle.Marquee
+ import Bustle.VariantFormatter
+ 
+ data DetailsView =
+@@ -55,7 +55,7 @@ addValue :: Table
+          -> Int
+          -> IO Label
+ addValue table row = do
+-    label <- labelNew Nothing
++    label <- labelNew (Nothing :: Maybe String)
+     miscSetAlignment label 0 0
+     labelSetEllipsize label EllipsizeStart
+     labelSetSelectable label True
+@@ -77,7 +77,7 @@ detailsViewNew = do
+                 , tableColumnSpacing := 6
+                 ]
+ 
+-    title <- labelNew Nothing
++    title <- labelNew (Nothing :: Maybe String)
+     miscSetAlignment title 0 0
+     tableAttach table title 0 2 0 1 [Fill] [Fill] 0 0
+ 
+@@ -99,7 +99,7 @@ detailsViewNew = do
+     widgetShowAll table
+     return $ DetailsView table title pathLabel memberLabel view
+ 
+-pickTitle :: Detailed Message -> Markup
++pickTitle :: Detailed Message -> Marquee
+ pickTitle (Detailed _ m _) = case m of
+     MethodCall {} -> b (escape (__ "Method call"))
+     MethodReturn {} -> b (escape (__ "Method return"))
+@@ -111,7 +111,7 @@ pickTitle (Detailed _ m _) = case m of
+ 
+ getMemberMarkup :: Member -> String
+ getMemberMarkup m =
+-    unMarkup $ formatMember (iface m) (membername m)
++    toPangoMarkup $ formatMember (iface m) (membername m)
+ 
+ getMember :: Detailed Message -> Maybe Member
+ getMember (Detailed _ m _) = case m of
+@@ -140,7 +140,7 @@ detailsViewUpdate :: DetailsView
+ detailsViewUpdate d m = do
+     buf <- textViewGetBuffer $ detailsBodyView d
+     let member_ = getMember m
+-    labelSetMarkup (detailsTitle d) (unMarkup $ pickTitle m)
++    labelSetMarkup (detailsTitle d) (toPangoMarkup $ pickTitle m)
+     labelSetText (detailsPath d) (maybe unknown (D.formatObjectPath . path) member_)
+     labelSetMarkup (detailsMember d) (maybe unknown getMemberMarkup member_)
+     textBufferSetText buf $ formatMessage m
+diff --git a/Bustle/UI/FilterDialog.hs b/Bustle/UI/FilterDialog.hs
+index 9560507..152931e 100644
+--- a/Bustle/UI/FilterDialog.hs
++++ b/Bustle/UI/FilterDialog.hs
+@@ -99,7 +99,7 @@ runFilterDialog parent names currentlyHidden = do
+     nameStore <- makeStore names currentlyHidden
+     sw <- makeView nameStore
+ 
+-    instructions <- labelNew Nothing
++    instructions <- labelNew (Nothing :: Maybe String)
+     widgetSetSizeRequest instructions 600 (-1)
+     labelSetMarkup instructions
+         (__ "Unticking a service hides its column in the diagram, \
+diff --git a/Bustle/UI/Recorder.hs b/Bustle/UI/Recorder.hs
+index 1e98a68..d0546bd 100644
+--- a/Bustle/UI/Recorder.hs
++++ b/Bustle/UI/Recorder.hs
+@@ -36,6 +36,7 @@ import Graphics.UI.Gtk
+ 
+ import Bustle.Loader.Pcap (convert)
+ import Bustle.Loader (isRelevant)
++import Bustle.Marquee (toString)
+ import Bustle.Monitor
+ import Bustle.Renderer
+ import Bustle.Translation (__)
+@@ -78,7 +79,7 @@ processBatch pendingRef n label incoming = do
+                 i <- takeMVar n
+                 let j = i + (length pending)
+                 labelSetMarkup label $
+-                    printf (__ "Logged <b>%u</b> messages…") j
++                    (printf (__ "Logged <b>%u</b> messages…") j :: String)
+                 putMVar n j
+ 
+                 incoming rr'
+@@ -97,8 +98,9 @@ recorderRun filename mwindow incoming finished = C.handle newFailed $ do
+     maybe (return ()) (windowSetTransientFor dialog) mwindow
+     dialog `set` [ windowModal := True ]
+ 
+-    label <- labelNew Nothing
+-    labelSetMarkup label $ printf (__ "Logged <b>%u</b> messages…") (0 :: Int)
++    label <- labelNew (Nothing :: Maybe String)
++    labelSetMarkup label $
++        (printf (__ "Logged <b>%u</b> messages…") (0 :: Int) :: String)
+     loaderStateRef <- newMVar Map.empty
+     pendingRef <- newMVar []
+     let updateLabel µs body = do
+@@ -142,7 +144,7 @@ recorderRun filename mwindow incoming finished = C.handle newFailed $ do
+     widgetShowAll dialog
+   where
+     newFailed (GError _ _ message) = do
+-        displayError mwindow message Nothing
++        displayError mwindow (toString message) Nothing
+ 
+ recorderChooseFile :: FilePath
+                    -> Maybe Window
+diff --git a/bustle.cabal b/bustle.cabal
+index 4ac107c..d416fa2 100644
+--- a/bustle.cabal
++++ b/bustle.cabal
+@@ -71,7 +71,7 @@ Executable bustle
+                , Bustle.Loader
+                , Bustle.Loader.OldSkool
+                , Bustle.Loader.Pcap
+-               , Bustle.Markup
++               , Bustle.Marquee
+                , Bustle.Monitor
+                , Bustle.Noninteractive
+                , Bustle.Regions
diff --git a/bustle.spec b/bustle.spec
index 5a1d613..95df273 100644
--- a/bustle.spec
+++ b/bustle.spec
@@ -10,6 +10,7 @@ Summary:        Draw pretty sequence diagrams of D-Bus traffic
 License:        LGPLv2+
 Url:            https://hackage.haskell.org/package/%{name}
 Source0:        https://hackage.haskell.org/package/%{name}-%{version}/%{name}-%{version}.tar.gz
+Patch0:         bustle-0.4.7-gtk2hs-0.13.patch
 
 Requires:       gnome-icon-theme
 BuildRequires:  intltool
@@ -58,6 +59,7 @@ call times.
 
 %prep
 %setup -q
+%patch0 -p1 -b .orig
 
 
 %build
@@ -105,8 +107,8 @@ desktop-file-validate %{buildroot}/%{_datadir}/applications/%{name}.desktop
 
 
 %changelog
-* Wed Jan 28 2015 Jens Petersen <petersen at redhat.com> - 0.4.7-6
-- update urls for rebuild
+* Sat Feb 14 2015 Jens Petersen <petersen at redhat.com> - 0.4.7-6
+- patch from git to build with pango/glib 0.13
 
 * Fri Dec 12 2014 Philip Withnall <philip at tecnocode.co.uk> - 0.4.7-5
 - Rebuilt for libHSbase changes


More information about the scm-commits mailing list