From 6b767df2fc47a77a4f856e040346ce49c0e7bf00 Mon Sep 17 00:00:00 2001 From: tv Date: Fri, 25 Jan 2019 04:15:45 +0100 Subject: Add support for Text --- src/Blessings.hs | 130 ++++++++++++++++++++++++++++++------------------------- 1 file changed, 71 insertions(+), 59 deletions(-) (limited to 'src/Blessings.hs') diff --git a/src/Blessings.hs b/src/Blessings.hs index 56c1af0..21cbabd 100644 --- a/src/Blessings.hs +++ b/src/Blessings.hs @@ -1,10 +1,17 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} -module Blessings where +module Blessings + ( module Export + , module Blessings + ) where +import qualified Prelude +import Blessings.Internal as Export (Blessable) +import qualified Blessings.Internal as Bless +import Prelude hiding (length,drop,take) import Control.Applicative -import Data.List import Data.String import Data.Ix (inRange) @@ -181,7 +188,7 @@ filterPm :: (Pm -> Maybe Int) -> Pm -> Pm filterPm f = rec [] where rec ys xs@(xhead:xtail) = maybe (rec (ys ++ [xhead]) xtail) - (rec ys . flip drop xs) + (rec ys . flip Prelude.drop xs) (f xs) rec ys _ = ys @@ -204,13 +211,14 @@ type RenderState = [(FColor, BColor, Blink, Bold, Underline)] emptyRenderState :: RenderState emptyRenderState = [(ECMA48FColor 39, ECMA48BColor 49, NoBlink, NoBold, NoUnderline)] -renderString :: RenderState -> Blessings String -> String -> String -renderString _ (Plain s) y = s ++ y +render :: (Blessable a) => RenderState -> Blessings a -> a -> a + +render _ (Plain s) y = s <> y -- TODO merge successive sequences: \ESC[32m\ESC[1m -> \ESC[31;1m -renderString rs@((fc, bc, bl, b, u):_) (SGR c t) y = - renderSGR bra ++ renderString rs' t (renderSGR ket ++ y) +render rs@((fc, bc, bl, b, u):_) (SGR c t) y = + renderSGR bra <> render rs' t (renderSGR ket <> y) where fc' = maybe fc id $ fromPm c bc' = maybe bc id $ fromPm c @@ -227,57 +235,61 @@ renderString rs@((fc, bc, bl, b, u):_) (SGR c t) y = (if b' /= b then (toPm b', toPm b) else ([],[])) : (if u' /= u then (toPm u', toPm u) else ([],[])) : [] -renderString _ (SGR _ _) _ = - error "renderString called w/o proper initial state" +render _ (SGR _ _) _ = + error "render called w/o proper initial state" -- where a proper initial state is s.th. like emptyRenderState -renderString r (Append t1 t2) y = - renderString r t1 $ renderString r t2 y - -renderString _ Empty y = y - - -len :: Blessings String -> Int -len (Plain x) = length x -len (SGR _ x) = len x -len (Append t1 t2) = len t1 + len t2 -len Empty = 0 - - -pp :: Blessings String -> String -pp t = renderString emptyRenderState t "" - - -renderSGR :: Pm -> String -renderSGR [] = [] -renderSGR xs = ("\ESC["++) . (++"m") . intercalate ";" $ map show xs - - -blessingsDrop :: Int -> Blessings String -> Blessings String -blessingsDrop n = \case - Append t1 t2 -> - case compare n (len t1) of - LT -> Append (blessingsDrop n t1) t2 - EQ -> t2 - GT -> blessingsDrop (n - len t1) t2 - Plain s -> - Plain (drop n s) - SGR pm t -> - SGR pm (blessingsDrop n t) - Empty -> - Empty - - -blessingsTake :: Int -> Blessings String -> Blessings String -blessingsTake n = \case - Append t1 t2 -> - case compare n (len t1) of - LT -> blessingsTake n t1 - EQ -> t1 - GT -> Append t1 (blessingsTake (n - len t1) t2) - Plain s -> - Plain (take n s) - SGR pm t -> - SGR pm (blessingsTake n t) - Empty -> - Empty +render r (Append t1 t2) y = + render r t1 $ render r t2 y + +render _ Empty y = y + + +renderSGR :: (Blessable a) => Pm -> a +renderSGR [] = mempty +renderSGR pm = + ("\ESC["<>) . (<>"m") . Bless.intercalate ";" . map Bless.fromInt $ pm + + +pp :: (Blessable a) => Blessings a -> a +pp t = render emptyRenderState t "" + + +instance Blessable a => Blessable (Blessings a) where + length (Plain x) = Bless.length x + length (SGR _ t) = Bless.length t + length (Append t1 t2) = Bless.length t1 + Bless.length t2 + length Empty = 0 + + drop n = \case + Append t1 t2 -> + case compare n (Bless.length t1) of + LT -> Bless.drop n t1 <> t2 + EQ -> t2 + GT -> Bless.drop (n - Bless.length t1) t2 + Plain s -> + Plain (Bless.drop n s) + SGR pm t -> + SGR pm (Bless.drop n t) + Empty -> + Empty + + take n = \case + Append t1 t2 -> + case compare n (Bless.length t1) of + LT -> Bless.take n t1 + EQ -> t1 + GT -> t1 <> Bless.take (n - Bless.length t1) t2 + Plain s -> + Plain (Bless.take n s) + SGR pm t -> + SGR pm (Bless.take n t) + Empty -> + Empty + + intercalate i = \case + [] -> mempty + [t] -> t + (t:ts) -> t <> i <> Bless.intercalate i ts + + fromInt = Plain . Bless.fromInt -- cgit v1.2.3