Skip to content
Snippets Groups Projects
Commit 7f29dda7 authored by Jens Nolte's avatar Jens Nolte
Browse files

Remove PangoTextSegment

parent 252a5bb8
No related branches found
No related tags found
No related merge requests found
...@@ -3,8 +3,6 @@ ...@@ -3,8 +3,6 @@
module QBar.BlockOutput where module QBar.BlockOutput where
import QBar.Pango
import Control.Lens import Control.Lens
import Data.Aeson.TH import Data.Aeson.TH
import Data.Int (Int64) import Data.Int (Int64)
...@@ -37,7 +35,6 @@ data BlockTextSegment = BlockTextSegment { ...@@ -37,7 +35,6 @@ data BlockTextSegment = BlockTextSegment {
importance :: Importance, importance :: Importance,
text :: T.Text text :: T.Text
} }
| PangoTextSegment PangoText
deriving (Eq, Show) deriving (Eq, Show)
type PangoText = T.Text type PangoText = T.Text
...@@ -144,17 +141,12 @@ rawText (BlockText b) = foldMap rawTextFromSegment b ...@@ -144,17 +141,12 @@ rawText (BlockText b) = foldMap rawTextFromSegment b
where where
rawTextFromSegment :: BlockTextSegment -> T.Text rawTextFromSegment :: BlockTextSegment -> T.Text
rawTextFromSegment BlockTextSegment{text} = text rawTextFromSegment BlockTextSegment{text} = text
rawTextFromSegment (PangoTextSegment text) =
case parsePango text of
Left _ -> text
Right parsed -> removeFormatting parsed
printedLength :: BlockText -> Int64 printedLength :: BlockText -> Int64
printedLength (BlockText b) = sum . map segmentLength $ b printedLength (BlockText b) = sum . map segmentLength $ b
where where
segmentLength :: BlockTextSegment -> Int64 segmentLength :: BlockTextSegment -> Int64
segmentLength BlockTextSegment { text } = T.length text 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 :: Bool -> Importance -> T.Text -> BlockText
mkText active importance text = BlockText [BlockTextSegment { text = pangoFriendly text, active, importance }] mkText active importance text = BlockText [BlockTextSegment { text = pangoFriendly text, active, importance }]
...@@ -174,8 +166,5 @@ activeText = mkText True normalImportant ...@@ -174,8 +166,5 @@ activeText = mkText True normalImportant
normalText :: T.Text -> BlockText normalText :: T.Text -> BlockText
normalText = mkText False normalImportant normalText = mkText False normalImportant
pangoText :: PangoText -> BlockText
pangoText pango = BlockText [PangoTextSegment pango]
surroundWith :: (T.Text -> BlockText) -> T.Text -> T.Text -> BlockText -> BlockText surroundWith :: (T.Text -> BlockText) -> T.Text -> T.Text -> BlockText -> BlockText
surroundWith format left right middle = format left <> middle <> format right surroundWith format left right middle = format left <> middle <> format right
\ No newline at end of file
...@@ -2,7 +2,7 @@ module QBar.Theme where ...@@ -2,7 +2,7 @@ module QBar.Theme where
import QBar.BlockOutput import QBar.BlockOutput
import Control.Lens ((^.), (.~)) import Control.Lens ((^.))
import Control.Monad.State.Lazy (State, evalState, get, put) import Control.Monad.State.Lazy (State, evalState, get, put)
import Data.Colour.RGBSpace import Data.Colour.RGBSpace
import Data.Colour.RGBSpace.HSV (hsv) import Data.Colour.RGBSpace.HSV (hsv)
...@@ -36,7 +36,6 @@ mkTheme theming' = map themeBlock ...@@ -36,7 +36,6 @@ mkTheme theming' = map themeBlock
themeBlockText theming (BlockText b) = foldMap (themeSegment theming) b themeBlockText theming (BlockText b) = foldMap (themeSegment theming) b
themeSegment :: SimplifiedTheme -> BlockTextSegment -> PangoText themeSegment :: SimplifiedTheme -> BlockTextSegment -> PangoText
themeSegment theming BlockTextSegment {active, importance, text} = (coloredText' $ theming active importance) text themeSegment theming BlockTextSegment {active, importance, text} = (coloredText' $ theming active importance) text
themeSegment _ (PangoTextSegment text) = text
invalidColor :: Color invalidColor :: Color
...@@ -66,16 +65,16 @@ defaultTheme = mkTheme defaultTheme' ...@@ -66,16 +65,16 @@ defaultTheme = mkTheme defaultTheme'
| otherwise = (ColorRGB (RGB (0x96 / 255) (0x98 / 255) (0x96 / 255)), Nothing) | 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 rainbowTheme time blocks = reverse $ evalState (mapM rainbowBlock $ reverse blocks) 0
where where
rainbowBlock :: BlockOutput -> State Integer BlockOutput rainbowBlock :: BlockOutput -> State Integer (PangoText, Maybe PangoText)
rainbowBlock block = do rainbowBlock block = do
let text = rawText $ block ^. fullText let text = rawText $ block ^. fullText
let chars = T.unpack . T.reverse $ text let chars = T.unpack . T.reverse $ text
coloredChars <- mapM rainbowChar chars coloredChars <- mapM rainbowChar chars
let rainbowText = T.concat . reverse $ coloredChars let rainbowText = T.concat . reverse $ coloredChars
return $ fullText .~ pangoText rainbowText $ block return (rainbowText, Nothing)
rainbowChar :: Char -> State Integer T.Text rainbowChar :: Char -> State Integer T.Text
rainbowChar char = do rainbowChar char = do
color <- nextRainbowColor color <- nextRainbowColor
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment