diff options
author | Will Thompson <will@willthompson.co.uk> | 2012-08-28 23:51:34 -0400 |
---|---|---|
committer | Will Thompson <will@willthompson.co.uk> | 2012-08-28 23:51:34 -0400 |
commit | dd619eecabdf4d11c14652cabc8577947eb2a294 (patch) | |
tree | 0f04eb77a61fb2af7f38e7edf6fe1a579d711ca8 /Bustle | |
parent | d503486b4d27116ba29bbbe10c911966fa8b2ac6 (diff) |
Build against dbus 0.10.x
This was quite a lot of grunt work because, ironically, the unboxing
functions for BusName et al. changed to return String rather than Text.
But in practice this just removed a lot of T.unpack from the UI code.
Diffstat (limited to 'Bustle')
-rw-r--r-- | Bustle/Loader.hs | 12 | ||||
-rw-r--r-- | Bustle/Loader/OldSkool.hs | 37 | ||||
-rw-r--r-- | Bustle/Loader/Pcap.hs | 72 | ||||
-rw-r--r-- | Bustle/Markup.hs | 8 | ||||
-rw-r--r-- | Bustle/Noninteractive.hs | 8 | ||||
-rw-r--r-- | Bustle/Renderer.hs | 20 | ||||
-rw-r--r-- | Bustle/StatisticsPane.hs | 2 | ||||
-rw-r--r-- | Bustle/Types.hs | 51 | ||||
-rw-r--r-- | Bustle/UI.hs | 2 | ||||
-rw-r--r-- | Bustle/UI/DetailsView.hs | 7 | ||||
-rw-r--r-- | Bustle/UI/FilterDialog.hs | 6 | ||||
-rw-r--r-- | Bustle/Upgrade.hs | 2 | ||||
-rw-r--r-- | Bustle/VariantFormatter.hs | 6 |
13 files changed, 139 insertions, 94 deletions
diff --git a/Bustle/Loader.hs b/Bustle/Loader.hs index 3586dbf..85cf411 100644 --- a/Bustle/Loader.hs +++ b/Bustle/Loader.hs @@ -29,8 +29,6 @@ import Control.Monad.Error import Control.Arrow ((***)) import qualified Data.Text as Text -import DBus.Constants (dbusName) -import DBus.Types (busNameText) import qualified Bustle.Loader.OldSkool as Old import qualified Bustle.Loader.Pcap as Pcap @@ -69,13 +67,13 @@ isRelevant (MessageEvent m) = case m of where -- FIXME: really? Maybe we should allow people to be interested in, -- say, binding to signals? - senderIsBus = sender m == O (OtherName (busNameText dbusName)) - destIsBus = destination m == O (OtherName (busNameText dbusName)) + senderIsBus = sender m == busDriver + destIsBus = destination m == busDriver + busDriver = O (OtherName dbusName) -- When the monitor is forcibly disconnected from the bus, the - -- Disconnected message has no sender, so the logger spits out <none>. - -- This gets turned into OtherName "" - isDisconnected = sender m == O (OtherName Text.empty) + -- Disconnected message has no sender; the old logger spat out <none>. + isDisconnected = sender m == O (OtherName Old.senderWhenDisconnected) none bs = not $ or bs none3 = none [senderIsBus, destIsBus, isDisconnected] diff --git a/Bustle/Loader/OldSkool.hs b/Bustle/Loader/OldSkool.hs index 22e01e8..5bd1587 100644 --- a/Bustle/Loader/OldSkool.hs +++ b/Bustle/Loader/OldSkool.hs @@ -19,11 +19,12 @@ Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA -} module Bustle.Loader.OldSkool ( readLog + , senderWhenDisconnected ) where import Bustle.Types -import qualified DBus.Types as D +import qualified DBus as D import qualified Data.Text as T import Text.ParserCombinators.Parsec hiding (Parser) import Data.Map (Map) @@ -55,12 +56,30 @@ nameChars = many1 (noneOf "\t\n") parseUniqueName :: Parser UniqueName parseUniqueName = do char ':' - fmap (UniqueName . T.pack . (':':)) nameChars + rest <- nameChars + case D.parseBusName (':':rest) of + Just n -> return $ UniqueName n + Nothing -> fail $ "':" ++ rest ++ "' is not a valid unique name" <?> "unique name" +-- FIXME: this shouldn't exist. +senderWhenDisconnected :: D.BusName +senderWhenDisconnected = D.busName_ "org.freedesktop.DBus.Local" + +parseMissingName :: Parser OtherName +parseMissingName = do + none + return $ OtherName senderWhenDisconnected + +parseSpecifiedOtherName :: Parser OtherName +parseSpecifiedOtherName = do + x <- nameChars + case D.parseBusName x of + Just n -> return $ OtherName n + Nothing -> fail $ "'" ++ x ++ "' is not a valid name" + parseOtherName :: Parser OtherName -parseOtherName = - fmap (OtherName . T.pack) ((none >> return "") <|> nameChars) +parseOtherName = parseMissingName <|> parseSpecifiedOtherName <?> "non-unique name" @@ -84,15 +103,15 @@ none = do return Nothing pathify :: String -> D.ObjectPath -pathify s = case D.objectPath (T.pack s) of +pathify s = case D.parseObjectPath s of Just p -> p Nothing -> D.objectPath_ "/unparseable/object/path" interfacify :: String -> Maybe D.InterfaceName -interfacify = D.interfaceName . T.pack +interfacify = D.parseInterfaceName memberNamify :: String -> D.MemberName -memberNamify s = case D.memberName (T.pack s) of +memberNamify s = case D.parseMemberName s of Just m -> m Nothing -> D.memberName_ "UnparseableMemberName" @@ -181,11 +200,11 @@ perhaps act = (noName >> return Nothing) <|> fmap Just act sameUnique :: UniqueName -> UniqueName -> Parser () sameUnique u u' = guard (u == u') - <?> "owner to be " ++ T.unpack (unUniqueName u) ++ ", not " ++ T.unpack (unUniqueName u') + <?> "owner to be " ++ unUniqueName u ++ ", not " ++ unUniqueName u' atLeastOne :: OtherName -> Parser a atLeastOne n = fail "" - <?> T.unpack (unOtherName n) ++ " to gain or lose an owner" + <?> unOtherName n ++ " to gain or lose an owner" nameOwnerChanged :: Parser DetailedEvent nameOwnerChanged = do diff --git a/Bustle/Loader/Pcap.hs b/Bustle/Loader/Pcap.hs index e24d3d0..d900765 100644 --- a/Bustle/Loader/Pcap.hs +++ b/Bustle/Loader/Pcap.hs @@ -34,10 +34,7 @@ import Control.Monad.State import Network.Pcap -import DBus.Constants (dbusName, dbusInterface) -import DBus.Wire -import DBus.Message -import DBus.Types +import DBus import qualified Data.Text as T import Data.Text (Text) @@ -49,16 +46,22 @@ import qualified Bustle.Types as B -- Conversions from dbus-core's types into Bustle's more stupid types. This -- whole section is pretty upsetting. -stupifyBusName :: Text +stupifyBusName :: BusName -> B.TaggedBusName stupifyBusName n - | not (T.null n) && T.head n == ':' = B.U $ B.UniqueName n - | otherwise = B.O $ B.OtherName n + | isUnique n = B.U $ B.UniqueName n + | otherwise = B.O $ B.OtherName n -convertBusName :: Text +isUnique :: BusName -> Bool +isUnique n = head (formatBusName n) == ':' + +convertBusName :: String -> Maybe BusName -> B.TaggedBusName -convertBusName context n = stupifyBusName (maybe context busNameText n) +convertBusName fallback n = + stupifyBusName (fromMaybe fallback_ n) + where + fallback_ = busName_ fallback convertMember :: (a -> ObjectPath) -> (a -> Maybe InterfaceName) @@ -110,9 +113,9 @@ isNOC (Just sender) s | looksLikeNOC = names = map fromVariant $ signalBody s looksLikeNOC = - and [ sender == dbusName - , signalInterface s == dbusInterface - , memberNameText (signalMember s) == "NameOwnerChanged" + and [ sender == B.dbusName + , signalInterface s == B.dbusInterface + , formatMemberName (signalMember s) == "NameOwnerChanged" ] isNOC _ _ = Nothing @@ -132,11 +135,8 @@ bustlifyNOC ns@(name, oldOwner, newOwner) (Nothing, Just new) -> B.Claimed (uniquify new) (Nothing, Nothing) -> error $ "wtf: NOC" ++ show ns where - isUnique :: BusName -> Bool - isUnique n = T.head (busNameText n) == ':' - - uniquify = B.UniqueName . busNameText - otherify = B.OtherName . busNameText + uniquify = B.UniqueName + otherify = B.OtherName tryBustlifyGetNameOwnerReply :: Maybe (MethodCall, a) -> MethodReturn @@ -146,7 +146,7 @@ tryBustlifyGetNameOwnerReply maybeCall mr = do -- • check that the service really is the bus daemon -- • don't crash if the body of the call or reply doesn't contain one bus name. (rawCall, _) <- maybeCall - guard (memberNameText (methodCallMember rawCall) == "GetNameOwner") + guard (formatMemberName (methodCallMember rawCall) == "GetNameOwner") ownedName <- fromVariant $ (methodCallBody rawCall !! 0) return $ bustlifyNOC ( ownedName , Nothing @@ -162,12 +162,16 @@ bustlify µs bytes m = do bm <- buildBustledMessage return $ B.Detailed µs bm (Just (bytes, m)) where + sender = receivedMessageSender m + -- FIXME: can we do away with the un-Maybe-ing and just push that Nothing + -- means 'the monitor' downwards? Or skip the message if sender is Nothing. + wrappedSender = convertBusName "sen.der" sender + buildBustledMessage = case m of - (ReceivedMethodCall serial sender mc) -> do + (ReceivedMethodCall serial mc) -> do let call = B.MethodCall { B.serial = serialValue serial - -- sender may be empty if it's us who sent it - , B.sender = convertBusName "method.call.sender" sender + , B.sender = wrappedSender , B.destination = convertBusName "method.call.destination" $ methodCallDestination mc , B.member = convertMember methodCallPath methodCallInterface methodCallMember mc } @@ -176,44 +180,44 @@ bustlify µs bytes m = do insertPending sender serial mc (B.Detailed µs call (Just (bytes, m))) return $ B.MessageEvent call - (ReceivedMethodReturn _serial sender mr) -> do + (ReceivedMethodReturn _serial mr) -> do call <- popMatchingCall (methodReturnDestination mr) (methodReturnSerial mr) return $ case tryBustlifyGetNameOwnerReply call mr of Just noc -> B.NOCEvent noc Nothing -> B.MessageEvent $ B.MethodReturn { B.inReplyTo = fmap snd call - , B.sender = convertBusName "method.return.sender" sender + , B.sender = wrappedSender , B.destination = convertBusName "method.return.destination" $ methodReturnDestination mr } - (ReceivedError _serial sender e) -> do - call <- popMatchingCall (errorDestination e) (errorSerial e) + (ReceivedMethodError _serial e) -> do + call <- popMatchingCall (methodErrorDestination e) (methodErrorSerial e) return $ B.MessageEvent $ B.Error { B.inReplyTo = fmap snd call - , B.sender = convertBusName "method.error.sender" sender - , B.destination = convertBusName "method.error.destination" $ errorDestination e + , B.sender = wrappedSender + , B.destination = convertBusName "method.error.destination" $ methodErrorDestination e } - (ReceivedSignal _serial sender sig) + (ReceivedSignal _serial sig) | Just names <- isNOC sender sig -> return $ B.NOCEvent $ bustlifyNOC names | otherwise -> return $ B.MessageEvent $ - B.Signal { B.sender = convertBusName "signal.sender" sender + B.Signal { B.sender = wrappedSender , B.member = convertMember signalPath (Just . signalInterface) signalMember sig - , B.signalDestination = fmap (stupifyBusName . busNameText) + , B.signalDestination = fmap stupifyBusName $ signalDestination sig } - (ReceivedUnknown _ _ _) -> error "wtf" + _ -> error "woah there! someone added a new message type." convert :: Monad m => B.Microseconds -> BS.ByteString -> StateT PendingMessages m (Either String B.DetailedEvent) convert µs body = - case unmarshalMessage body of - Left unmarshalError -> return $ Left $ show unmarshalError - Right m -> liftM Right $ bustlify µs (BS.length body) m + case unmarshal body of + Left e -> return $ Left $ unmarshalErrorMessage e + Right m -> liftM Right $ bustlify µs (BS.length body) m data Result e a = EOF diff --git a/Bustle/Markup.hs b/Bustle/Markup.hs index a5e6719..5c31552 100644 --- a/Bustle/Markup.hs +++ b/Bustle/Markup.hs @@ -40,7 +40,7 @@ import Graphics.Rendering.Pango.BasicTypes (Weight(..)) import Graphics.Rendering.Pango.Layout (escapeMarkup) import Graphics.Rendering.Pango.Markup (markSpan, SpanAttribute(..)) -import Bustle.Types (ObjectPath, objectPathText, InterfaceName, interfaceNameText, MemberName, memberNameText) +import Bustle.Types (ObjectPath, formatObjectPath, InterfaceName, formatInterfaceName, MemberName, formatMemberName) newtype Markup = Markup { unMarkup :: String } deriving (Show, Read, Ord, Eq) @@ -93,13 +93,13 @@ instance Unescaped Text where toString = T.unpack instance Unescaped InterfaceName where - toString = toString . interfaceNameText + toString = formatInterfaceName instance Unescaped ObjectPath where - toString = toString . objectPathText + toString = formatObjectPath instance Unescaped MemberName where - toString = toString . memberNameText + toString = formatMemberName escape :: Unescaped s => s -> Markup escape = Markup . escapeMarkup . toString diff --git a/Bustle/Noninteractive.hs b/Bustle/Noninteractive.hs index 2f286c4..a3edbc7 100644 --- a/Bustle/Noninteractive.hs +++ b/Bustle/Noninteractive.hs @@ -29,7 +29,6 @@ import System.Exit (exitFailure) import System.IO (hPutStrLn, stderr) import Data.Maybe (fromMaybe, mapMaybe) import Data.List (nub) -import qualified Data.Text as T import Control.Monad.Error import Text.Printf @@ -56,10 +55,7 @@ process filepath analyze format = do mapM_ (putStrLn . format) $ analyze log formatInterface :: Maybe InterfaceName -> String -formatInterface = maybe "(no interface)" (T.unpack . interfaceNameText) - -formatMemberName :: MemberName -> String -formatMemberName = T.unpack . memberNameText +formatInterface = maybe "(no interface)" formatInterfaceName runCount :: FilePath -> IO () runCount filepath = process filepath frequencies format @@ -85,7 +81,7 @@ runDot filepath = process filepath makeDigraph id makeDigraph log = ["digraph bustle {"] ++ makeDigraph' log ++ ["}"] makeDigraph' log = - [ concat [" \"", T.unpack (unBusName s), "\" -> \"", T.unpack (unBusName d), "\";"] + [ concat [" \"", unBusName s, "\" -> \"", unBusName d, "\";"] | (s, d) <- nub . mapMaybe (methodCall . deEvent) $ log ] diff --git a/Bustle/Renderer.hs b/Bustle/Renderer.hs index bfe60f7..3e80308 100644 --- a/Bustle/Renderer.hs +++ b/Bustle/Renderer.hs @@ -366,13 +366,13 @@ lookupOtherName bus o = do -- No matches indicates a corrupt log, which we try to recover from … [] -> do warn $ concat [ "'" - , Text.unpack $ unOtherName o + , unOtherName o , "' appeared unheralded on the " , describeBus bus , " bus; making something up..." ] let namesInUse = Map.keys as - candidates = map (UniqueName . (Text.append ":fake.") . Text.pack . show) + candidates = map (fakeUniqueName . show) ([1..] :: [Integer]) u = head $ filter (not . (`elem` namesInUse)) candidates addUnique bus u @@ -425,7 +425,7 @@ appCoordinate bus n = do -- FIXME: Does this really live here? currentRow <- gets row - let ns = map Text.unpack $ bestNames u os + let ns = bestNames u os h = headerHeight ns shape $ Header ns x (currentRow - (10 + h)) shape $ ClientLines (x :| []) (currentRow - 5) (currentRow + 15) @@ -455,7 +455,7 @@ addUnique bus n = do case existing of Nothing -> return () Just _ -> warn $ concat [ "Unique name '" - , Text.unpack $ unUniqueName n + , unUniqueName n , "' apparently connected to the bus twice" ] modifyApps bus $ Map.insert n ai @@ -538,7 +538,7 @@ advanceBy d = do when (current' - lastLabelling > 400) $ do xs <- (++) <$> getsApps Map.toList SessionBus <*> getsApps Map.toList SystemBus - let xs' = [ (x, map Text.unpack $ bestNames u os) + let xs' = [ (x, bestNames u os) | (u, ApplicationInfo (CurrentColumn x) os _) <- xs ] let (height, ss) = headers xs' (current' + 20) @@ -562,11 +562,11 @@ advanceBy d = do (x:xs') -> shape $ ClientLines (x :| xs') (current + 15) (next + 15) _ -> return () -bestNames :: UniqueName -> Set OtherName -> [Text] -bestNames (UniqueName u) os - | Set.null os = [u] - | otherwise = reverse . sortBy (comparing Text.length) . map readable $ Set.toList os - where readable = Text.reverse . Text.takeWhile (/= '.') . Text.reverse . unOtherName +bestNames :: UniqueName -> Set OtherName -> [String] +bestNames u os + | Set.null os = [unUniqueName u] + | otherwise = reverse . sortBy (comparing length) . map readable $ Set.toList os + where readable = reverse . takeWhile (/= '.') . reverse . unOtherName edgemostApp :: Bus -> Renderer (Maybe Double) edgemostApp bus = do diff --git a/Bustle/StatisticsPane.hs b/Bustle/StatisticsPane.hs index c0ee816..90d5bb6 100644 --- a/Bustle/StatisticsPane.hs +++ b/Bustle/StatisticsPane.hs @@ -28,7 +28,7 @@ import Control.Monad (forM_) import Text.Printf import Graphics.UI.Gtk hiding (Markup) import Bustle.Stats -import Bustle.Types (Log, interfaceNameText) +import Bustle.Types (Log) import qualified Bustle.Markup as Markup import Bustle.Markup (Markup) import Data.Monoid diff --git a/Bustle/Types.hs b/Bustle/Types.hs index 3fc3259..8a28cfc 100644 --- a/Bustle/Types.hs +++ b/Bustle/Types.hs @@ -19,13 +19,13 @@ Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA -} module Bustle.Types ( ObjectPath - , objectPathText + , formatObjectPath , InterfaceName - , interfaceNameText + , formatInterfaceName , MemberName - , memberNameText + , formatMemberName , Serial @@ -34,8 +34,15 @@ module Bustle.Types , TaggedBusName(..) , isUnique , isOther + , unUniqueName + , unOtherName , unBusName + , dbusName + , dbusInterface + + , fakeUniqueName + , Microseconds(..) , µsFromPair , µsToMs @@ -54,8 +61,12 @@ module Bustle.Types where import Data.Word (Word32) -import DBus.Types (ObjectPath, objectPathText, InterfaceName, interfaceNameText, MemberName, memberNameText) -import DBus.Message (ReceivedMessage) +import DBus ( ObjectPath, formatObjectPath + , InterfaceName, formatInterfaceName, interfaceName_ + , MemberName, formatMemberName + , BusName, formatBusName, busName_ + , ReceivedMessage + ) import qualified Data.Text as Text import Data.Text (Text) import Data.Maybe (maybeToList) @@ -63,9 +74,9 @@ import Data.Either (partitionEithers) type Serial = Word32 -newtype UniqueName = UniqueName { unUniqueName :: Text } +newtype UniqueName = UniqueName BusName deriving (Ord, Show, Eq) -newtype OtherName = OtherName { unOtherName :: Text } +newtype OtherName = OtherName BusName deriving (Ord, Show, Eq) data TaggedBusName = U UniqueName @@ -77,9 +88,29 @@ isUnique (U _) = True isUnique (O _) = False isOther = not . isUnique -unBusName :: TaggedBusName -> Text -unBusName (U (UniqueName x)) = x -unBusName (O (OtherName x)) = x +unUniqueName :: UniqueName -> String +unUniqueName (UniqueName x) = formatBusName x + +unOtherName :: OtherName -> String +unOtherName (OtherName x) = formatBusName x + +unBusName :: TaggedBusName -> String +unBusName (U (UniqueName x)) = formatBusName x +unBusName (O (OtherName x)) = formatBusName x + +-- These useful constants disappeared from dbus in the grand removing of the +-- -core suffix. +dbusName :: BusName +dbusName = busName_ "org.freedesktop.DBus" + +dbusInterface :: InterfaceName +dbusInterface = interfaceName_ "org.freedesktop.DBus" + +-- FIXME: nothing stops someone passing in garbage +-- http://www.youtube.com/watch?v=WorPANO_ANU +fakeUniqueName :: String + -> UniqueName +fakeUniqueName = UniqueName . busName_ . (":fake." ++) newtype Microseconds = Microseconds Integer deriving (Show, Ord, Eq, Num, Real, Enum, Integral) diff --git a/Bustle/UI.hs b/Bustle/UI.hs index 72f4204..1bb36ea 100644 --- a/Bustle/UI.hs +++ b/Bustle/UI.hs @@ -63,8 +63,6 @@ import System.FilePath ( splitFileName, takeFileName, takeDirectory ) import System.Directory (renameFile) -import qualified DBus.Message - type B a = Bustle BConfig BState a data LogDetails = diff --git a/Bustle/UI/DetailsView.hs b/Bustle/UI/DetailsView.hs index c8a27c7..b09c6ed 100644 --- a/Bustle/UI/DetailsView.hs +++ b/Bustle/UI/DetailsView.hs @@ -29,9 +29,8 @@ import Data.Maybe (maybe, fromJust) import Control.Applicative ((<$>)) import Graphics.UI.Gtk hiding (Signal, Markup) import qualified Data.Text as T -import qualified DBus.Message -import qualified DBus.Types as D +import qualified DBus as D import Bustle.Types import Bustle.Markup @@ -130,7 +129,7 @@ formatMessage (Detailed _ _ Nothing) = "# No message body information is available. Please capture a fresh log\n\ \# using bustle-pcap if you need it!" formatMessage (Detailed _ _ (Just (_size, rm))) = - formatArgs $ DBus.Message.receivedBody rm + formatArgs $ D.receivedMessageBody rm where formatArgs = intercalate "\n" . map (format_Variant VariantStyleSignature) @@ -144,6 +143,6 @@ detailsViewUpdate d m = do buf <- textViewGetBuffer $ detailsBodyView d let member_ = getMember m labelSetMarkup (detailsTitle d) (unMarkup $ pickTitle m) - labelSetText (detailsPath d) (maybe "Unknown" (T.unpack . D.objectPathText . path) member_) + 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 db9e9ec..cc798fb 100644 --- a/Bustle/UI/FilterDialog.hs +++ b/Bustle/UI/FilterDialog.hs @@ -37,10 +37,10 @@ import Graphics.UI.Gtk import Bustle.Types formatNames :: (UniqueName, Set OtherName) - -> Text + -> String formatNames (u, os) | Set.null os = unUniqueName u - | otherwise = Text.intercalate "\n" . map unOtherName $ Set.toAscList os + | otherwise = intercalate "\n" . map unOtherName $ Set.toAscList os type NameStore = ListStore (Bool, (UniqueName, Set OtherName)) @@ -82,7 +82,7 @@ makeView nameStore = do treeViewAppendColumn nameView nameColumn cellLayoutSetAttributes nameColumn nameCell nameStore $ \(_, ns) -> - [ cellText := Text.unpack (formatNames ns) ] + [ cellText := formatNames ns ] sw <- scrolledWindowNew Nothing Nothing scrolledWindowSetPolicy sw PolicyAutomatic PolicyAutomatic diff --git a/Bustle/Upgrade.hs b/Bustle/Upgrade.hs index 443123f..1a9454f 100644 --- a/Bustle/Upgrade.hs +++ b/Bustle/Upgrade.hs @@ -59,6 +59,6 @@ synth n = do ] fakeName :: OtherName -> UniqueName -fakeName = UniqueName . Text.append ":fake." . unOtherName +fakeName = fakeUniqueName . unOtherName -- vim: sw=2 sts=2 diff --git a/Bustle/VariantFormatter.hs b/Bustle/VariantFormatter.hs index d4aa489..caaa48c 100644 --- a/Bustle/VariantFormatter.hs +++ b/Bustle/VariantFormatter.hs @@ -30,7 +30,7 @@ import Data.Char (chr, isPrint) import Data.Maybe (fromJust) import qualified Data.Text.Lazy as Text -import DBus.Types +import DBus format_Bool :: Bool -> String format_Bool = show @@ -68,10 +68,10 @@ format_String :: String -> String format_String = show format_Signature :: Signature -> String -format_Signature = show . signatureText +format_Signature = show . formatSignature format_ObjectPath :: ObjectPath -> String -format_ObjectPath = show . objectPathText +format_ObjectPath = show . formatObjectPath format_Array :: Array -> String format_Array a = "[" ++ intercalate ", " items ++ "]" |