diff --git a/src/QBar/BlockOutput.hs b/src/QBar/BlockOutput.hs
index 1f06099ecfcd89847ae47b73a90e2e0c25b0844b..f5144ea020e2b9b6ec84065840301ce6e6fddc87 100644
--- a/src/QBar/BlockOutput.hs
+++ b/src/QBar/BlockOutput.hs
@@ -3,8 +3,6 @@
 
 module QBar.BlockOutput where
 
-import QBar.Pango
-
 import Control.Lens
 import Data.Aeson.TH
 import Data.Int (Int64)
@@ -37,7 +35,6 @@ data BlockTextSegment = BlockTextSegment {
     importance :: Importance,
     text :: T.Text
   }
-  | PangoTextSegment PangoText
   deriving (Eq, Show)
 
 type PangoText = T.Text
@@ -144,17 +141,12 @@ rawText (BlockText b) = foldMap rawTextFromSegment b
   where
     rawTextFromSegment :: BlockTextSegment -> T.Text
     rawTextFromSegment BlockTextSegment{text} = text
-    rawTextFromSegment (PangoTextSegment text) =
-      case parsePango text of
-        Left _ -> text
-        Right parsed -> removeFormatting parsed
 
 printedLength :: BlockText -> Int64
 printedLength (BlockText b) = sum . map segmentLength $ b
   where
     segmentLength :: BlockTextSegment -> Int64
     segmentLength BlockTextSegment { text } = T.length text
-    segmentLength (PangoTextSegment pango) = either (const $ T.length pango) (T.length . removeFormatting) $ parsePango pango
 
 mkText :: Bool -> Importance -> T.Text -> BlockText
 mkText active importance text = BlockText [BlockTextSegment { text = pangoFriendly text, active, importance }]
@@ -174,8 +166,5 @@ activeText = mkText True normalImportant
 normalText :: T.Text -> BlockText
 normalText = mkText False normalImportant
 
-pangoText :: PangoText -> BlockText
-pangoText pango = BlockText [PangoTextSegment pango]
-
 surroundWith :: (T.Text -> BlockText) -> T.Text -> T.Text -> BlockText -> BlockText
 surroundWith format left right middle = format left <> middle <> format right
\ No newline at end of file
diff --git a/src/QBar/Theme.hs b/src/QBar/Theme.hs
index ff6f294c3d77fa41bf9496505c359d7b3dfd4f36..44c9c8a6405315d0aff2a826d7bd3bbeac319071 100644
--- a/src/QBar/Theme.hs
+++ b/src/QBar/Theme.hs
@@ -2,7 +2,7 @@ module QBar.Theme where
 
 import QBar.BlockOutput
 
-import Control.Lens ((^.), (.~))
+import Control.Lens ((^.))
 import Control.Monad.State.Lazy (State, evalState, get, put)
 import Data.Colour.RGBSpace
 import Data.Colour.RGBSpace.HSV (hsv)
@@ -36,7 +36,6 @@ mkTheme theming' = map themeBlock
     themeBlockText theming (BlockText b) = foldMap (themeSegment theming) b
     themeSegment :: SimplifiedTheme -> BlockTextSegment -> PangoText
     themeSegment theming BlockTextSegment {active, importance, text} = (coloredText' $ theming active importance) text
-    themeSegment _ (PangoTextSegment text) = text
 
 
 invalidColor :: Color
@@ -66,16 +65,16 @@ defaultTheme = mkTheme defaultTheme'
       | otherwise                     = (ColorRGB (RGB (0x96 / 255) (0x98 / 255) (0x96 / 255)), Nothing)
 
 
-rainbowTheme :: Double -> [BlockOutput] -> [BlockOutput]
+rainbowTheme :: Double -> Theme
 rainbowTheme time blocks = reverse $ evalState (mapM rainbowBlock $ reverse blocks) 0
   where
-    rainbowBlock :: BlockOutput -> State Integer BlockOutput
+    rainbowBlock :: BlockOutput -> State Integer (PangoText, Maybe PangoText)
     rainbowBlock block = do
       let text = rawText $ block ^. fullText
       let chars = T.unpack . T.reverse $ text
       coloredChars <- mapM rainbowChar chars
       let rainbowText = T.concat . reverse $ coloredChars
-      return $ fullText .~ pangoText rainbowText $ block
+      return (rainbowText, Nothing)
     rainbowChar :: Char -> State Integer T.Text
     rainbowChar char = do
       color <- nextRainbowColor