{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Copyright   :  (C) 2011-2019 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-- Utility functions to augment the prettyprinter library's interface.
----------------------------------------------------------------------------

module Text.Trifecta.Util.Pretty
  ( AnsiStyle
  , renderIO
  -- * Rendering
  , char
  -- * Styles
  , bold
  , debold
  , underlined
  , deunderline
  -- * Compatibility shims
  , renderPretty
  , columns
  ) where


#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif

import Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc.Render.Terminal
import Data.Text.Prettyprint.Doc.Render.Terminal.Internal (ansiBold, ansiUnderlining)

char :: Char -> Doc a
char :: Char -> Doc a
char = Char -> Doc a
forall a ann. Pretty a => a -> Doc ann
pretty

renderPretty :: Double -> Int -> Doc AnsiStyle -> SimpleDocStream AnsiStyle
renderPretty :: Double -> Int -> Doc AnsiStyle -> SimpleDocStream AnsiStyle
renderPretty Double
ribbonFraction Int
page
  = LayoutOptions -> Doc AnsiStyle -> SimpleDocStream AnsiStyle
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
layoutSmart LayoutOptions :: PageWidth -> LayoutOptions
LayoutOptions { layoutPageWidth :: PageWidth
layoutPageWidth = Int -> Double -> PageWidth
AvailablePerLine Int
page Double
ribbonFraction }

debold, deunderline :: AnsiStyle
debold :: AnsiStyle
debold = AnsiStyle
forall a. Monoid a => a
mempty { ansiBold :: Maybe Bold
ansiBold = Maybe Bold
forall a. Maybe a
Nothing }
deunderline :: AnsiStyle
deunderline = AnsiStyle
forall a. Monoid a => a
mempty { ansiUnderlining :: Maybe Underlined
ansiUnderlining = Maybe Underlined
forall a. Maybe a
Nothing}

columns :: (Maybe Int -> Doc AnsiStyle) -> Doc AnsiStyle
columns :: (Maybe Int -> Doc AnsiStyle) -> Doc AnsiStyle
columns Maybe Int -> Doc AnsiStyle
f = (PageWidth -> Doc AnsiStyle) -> Doc AnsiStyle
forall ann. (PageWidth -> Doc ann) -> Doc ann
pageWidth (Maybe Int -> Doc AnsiStyle
f (Maybe Int -> Doc AnsiStyle)
-> (PageWidth -> Maybe Int) -> PageWidth -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageWidth -> Maybe Int
toMaybeInt) where
  toMaybeInt :: PageWidth -> Maybe Int
toMaybeInt (AvailablePerLine Int
cpl Double
_) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
cpl
  toMaybeInt PageWidth
Unbounded = Maybe Int
forall a. Maybe a
Nothing