{-# OPTIONS_HADDOCK hide #-}
module Byline.Internal.Stylized
  ( Stylized (..),
    ToStylizedText (..),
    text,
    fg,
    bg,
    bold,
    underline,
    swapFgBg,
    RenderMode (..),
    render,
    renderText,
  )
where
import Byline.Internal.Color (Color)
import qualified Byline.Internal.Color as Color
import Byline.Internal.Types (Modifier (..), OnlyOne (..), Status (..))
import qualified Data.Text.IO as Text
import qualified System.Console.ANSI as ANSI
data Stylized a
  = 
    Stylized Modifier a
  | 
    StylizedMod Modifier
  | 
    StylizedList [Stylized a]
  deriving (Show, Eq, Functor, Foldable, Traversable)
instance Semigroup (Stylized a) where
  
  (<>) a@(Stylized _ _) b@(Stylized _ _) = StylizedList [a, b]
  (<>) (Stylized m t) (StylizedMod m') = Stylized (m <> m') t
  (<>) a@(Stylized _ _) (StylizedList b) = StylizedList (a : b)
  
  (<>) (StylizedMod m) (Stylized m' t) = Stylized (m <> m') t
  (<>) (StylizedMod m) (StylizedMod m') = StylizedMod (m <> m')
  (<>) m@(StylizedMod _) (StylizedList l) = StylizedList (map (m <>) l)
  
  (<>) (StylizedList l) t@(Stylized _ _) = StylizedList (l <> [t])
  (<>) (StylizedList l) m@(StylizedMod _) = StylizedList (map (<> m) l)
  (<>) (StylizedList l) (StylizedList l') = StylizedList (l <> l')
instance Monoid (Stylized a) where
  mempty = StylizedList []
instance IsString (Stylized Text) where
  fromString = text . toText
class ToStylizedText a where
  toStylizedText :: a -> Stylized Text
instance ToStylizedText (Stylized Text) where
  toStylizedText = id
text :: Text -> Stylized Text
text = Stylized mempty
fg :: Color -> Stylized Text
fg c = StylizedMod (mempty {modColorFG = OnlyOne (Just c)})
bg :: Color -> Stylized Text
bg c = StylizedMod (mempty {modColorBG = OnlyOne (Just c)})
bold :: Stylized Text
bold = StylizedMod (mempty {modBold = On})
underline :: Stylized Text
underline = StylizedMod (mempty {modUnderline = On})
swapFgBg :: Stylized Text
swapFgBg = StylizedMod (mempty {modSwapFgBg = On})
data RenderMode
  = 
    Plain
  | 
    Simple
  | 
    Term256
  | 
    TermRGB
data RenderInstruction
  = RenderText Text
  | RenderSGR [ANSI.SGR]
render :: RenderMode -> Handle -> Stylized Text -> IO ()
render mode h stylized = mapM_ go (renderInstructions mode stylized)
  where
    go :: RenderInstruction -> IO ()
    go (RenderText t) = Text.hPutStr h t
    go (RenderSGR s) = ANSI.hSetSGR h s
renderText :: RenderMode -> Stylized Text -> Text
renderText mode stylized = foldMap go (renderInstructions mode stylized)
  where
    go :: RenderInstruction -> Text
    go = \case
      RenderText t -> t
      RenderSGR s ->
        
        
        
        toText (ANSI.setSGRCode s) <> "\STX"
renderInstructions :: RenderMode -> Stylized Text -> [RenderInstruction]
renderInstructions mode = \case
  Stylized m t -> renderMod mode (t, m)
  StylizedMod _ -> []
  StylizedList xs -> concatMap (renderInstructions mode) xs
  where
    renderMod :: RenderMode -> (Text, Modifier) -> [RenderInstruction]
    renderMod mode (t, m) =
      case mode of
        Plain ->
          
          [RenderText t]
        Simple ->
          
          let color l = ANSI.SetColor l ANSI.Dull . Color.colorAsANSI
           in renderToSGR t m color
        Term256 ->
          
          let color l = ANSI.SetPaletteColor l . Color.colorAsIndex256
           in renderToSGR t m color
        TermRGB ->
          
          let color l c = case Color.colorAsRGB c of
                Left ac -> ANSI.SetColor l ANSI.Dull ac
                Right rgb -> ANSI.SetRGBColor l rgb
           in renderToSGR t m color
    renderToSGR ::
      Text ->
      Modifier ->
      (ANSI.ConsoleLayer -> Color -> ANSI.SGR) ->
      [RenderInstruction]
    renderToSGR t m f =
      [ RenderSGR (modToSGR m f),
        RenderText t,
        RenderSGR [ANSI.Reset]
      ]
modToSGR ::
  
  Modifier ->
  
  (ANSI.ConsoleLayer -> Color -> ANSI.SGR) ->
  
  [ANSI.SGR]
modToSGR mod colorF =
  catMaybes
    [ colorF ANSI.Foreground <$> getColor modColorFG,
      colorF ANSI.Background <$> getColor modColorBG,
      ANSI.SetConsoleIntensity <$> getIntensity,
      ANSI.SetUnderlining <$> getUnderlining,
      ANSI.SetSwapForegroundBackground <$> getSwapForegroundBackground
    ]
  where
    getColor :: (Modifier -> OnlyOne Color) -> Maybe Color
    getColor f = unOne (f mod)
    getIntensity :: Maybe ANSI.ConsoleIntensity
    getIntensity = case modBold mod of
      Off -> Nothing
      On -> Just ANSI.BoldIntensity
    getUnderlining :: Maybe ANSI.Underlining
    getUnderlining = case modUnderline mod of
      Off -> Nothing
      On -> Just ANSI.SingleUnderline
    getSwapForegroundBackground :: Maybe Bool
    getSwapForegroundBackground = case modSwapFgBg mod of
      Off -> Nothing
      On -> Just True