Skip to content

Commit

Permalink
Re-export some Data.Text modules for the purpose of downstream librar…
Browse files Browse the repository at this point in the history
…ies being able to write code compatible with the fake text module
  • Loading branch information
newhoggy committed Nov 11, 2021
1 parent d155e79 commit 4d3b61f
Show file tree
Hide file tree
Showing 9 changed files with 77 additions and 12 deletions.
14 changes: 8 additions & 6 deletions prettyprinter/bench/LargeOutput.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

Expand All @@ -13,10 +15,10 @@ import Control.Monad.Compat
import Data.Char
import Data.Map (Map)
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as TL
import Prettyprinter.Util.Compat.Text (Text)
import qualified Prettyprinter.Util.Compat.Text as T
import qualified Prettyprinter.Util.Compat.Text.IO as T
import qualified Prettyprinter.Util.Compat.Text.Lazy as TL
import Prettyprinter
import Prettyprinter.Render.Text
import GHC.Generics
Expand Down
4 changes: 4 additions & 0 deletions prettyprinter/prettyprinter.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,10 @@ library
, Prettyprinter.Render.Util.SimpleDocTree
, Prettyprinter.Render.Util.StackMachine
, Prettyprinter.Util
, Prettyprinter.Util.Compat.Text
, Prettyprinter.Util.Compat.Text.IO
, Prettyprinter.Util.Compat.Text.Lazy
, Prettyprinter.Util.Compat.Text.Lazy.Builder

, Prettyprinter.Symbols.Unicode
, Prettyprinter.Symbols.Ascii
Expand Down
2 changes: 2 additions & 0 deletions prettyprinter/src-text/Data/Text/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,5 @@ type Text = T.Text
length = T.length
lines = T.lines
toStrict = id
pack = T.pack
unpack = T.unpack
26 changes: 22 additions & 4 deletions prettyprinter/src-text/Data/Text/Lazy/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,25 @@

module Data.Text.Lazy.Builder where

type Builder = String
fromText = id
singleton = (:[])
toLazyText = id
import Data.String (IsString (..))
import Data.Semigroup

newtype Builder = Builder (String -> String)

instance IsString Builder where
fromString s = Builder (s ++)

instance Semigroup Builder where
Builder a <> Builder b = Builder (a . b)

instance Monoid Builder where
mempty = Builder id

fromText :: String -> Builder
fromText t = Builder (t ++)

singleton :: Char -> Builder
singleton c = Builder ([c] ++)

toLazyText :: Builder -> String
toLazyText (Builder b) = b ""
2 changes: 0 additions & 2 deletions prettyprinter/src/Prettyprinter/Render/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,8 @@

-- | Render an unannotated 'SimpleDocStream' as plain 'Text'.
module Prettyprinter.Render.Text (
#ifdef MIN_VERSION_text
-- * Conversion to plain 'Text'
renderLazy, renderStrict,
#endif

-- * Render to a 'Handle'
renderIO,
Expand Down
11 changes: 11 additions & 0 deletions prettyprinter/src/Prettyprinter/Util/Compat/Text.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
-- | This module is for use by packages that need to be able to use the prettyprinter package
-- without incurring a dependency on the text package.
--
-- Legitimate examples of packages that must have text as an optional dependency, include text (or
-- bytetring).
module Prettyprinter.Util.Compat.Text
( module Data.Text
) where

import Data.Text (Text, cons, dropWhileEnd, head, intercalate, length, lines, map, null, pack, replicate,
singleton, snoc, stripEnd, unlines, unpack, words, uncons, splitOn)
10 changes: 10 additions & 0 deletions prettyprinter/src/Prettyprinter/Util/Compat/Text/IO.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
-- | This module is for use by packages that need to be able to use the prettyprinter package
-- without incurring a dependency on the text package.
--
-- Legitimate examples of packages that must have text as an optional dependency, include text (or
-- bytetring).
module Prettyprinter.Util.Compat.Text.IO
( module Data.Text.IO
) where

import Data.Text.IO (hPutStr, putStrLn)
10 changes: 10 additions & 0 deletions prettyprinter/src/Prettyprinter/Util/Compat/Text/Lazy.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
-- | This module is for use by packages that need to be able to use the prettyprinter package
-- without incurring a dependency on the text package.
--
-- Legitimate examples of packages that must have text as an optional dependency, include text (or
-- bytetring).
module Prettyprinter.Util.Compat.Text.Lazy
( module Data.Text.Lazy
) where

import Data.Text.Lazy (Text, length, lines, toStrict, pack, unpack)
10 changes: 10 additions & 0 deletions prettyprinter/src/Prettyprinter/Util/Compat/Text/Lazy/Builder.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
-- | This module is for use by packages that need to be able to use the prettyprinter package
-- without incurring a dependency on the text package.
--
-- Legitimate examples of packages that must have text as an optional dependency, include text (or
-- bytetring).
module Prettyprinter.Util.Compat.Text.Lazy.Builder
( module Data.Text.Lazy.Builder
) where

import Data.Text.Lazy.Builder (Builder (), fromText, singleton, toLazyText)

0 comments on commit 4d3b61f

Please sign in to comment.