Skip to content

Commit 6ab5884

Browse files
committed
Move to prettyprinter
1 parent 0d3e1e2 commit 6ab5884

17 files changed

+326
-251
lines changed

library/Neovim.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,6 @@ module Neovim (
7272
Doc,
7373
Pretty(..),
7474
errOnInvalidResult,
75-
text,
7675
NeovimException(..),
7776
-- ** Generated functions for neovim interaction
7877
module Neovim.API.String,
@@ -129,7 +128,7 @@ import Neovim.RPC.FunctionCall (wait, wait', waitErr, waitErr')
129128
import Neovim.Util (unlessM, whenM,
130129
withCustomEnvironment)
131130
import System.Log.Logger (Priority (..))
132-
import Text.PrettyPrint.ANSI.Leijen (Doc, Pretty (..), text)
131+
import Data.Text.Prettyprint.Doc (Doc, Pretty (..))
133132

134133
-- Installation {{{1
135134
{- $installation

library/Neovim/API/Parser.hs

+24-23
Original file line numberDiff line numberDiff line change
@@ -20,19 +20,20 @@ import Neovim.Classes
2020

2121
import Control.Applicative
2222
import Control.Monad.Except
23-
import qualified Data.ByteString as B
24-
import Data.Map (Map)
25-
import qualified Data.Map as Map
23+
import qualified Data.ByteString as B
24+
import Data.Map (Map)
25+
import qualified Data.Map as Map
2626
import Data.MessagePack
2727
import Data.Monoid
2828
import Data.Serialize
29-
import System.IO (hClose)
29+
import Neovim.Compat.Megaparsec as P
30+
import System.IO (hClose)
3031
import System.Process
31-
import Neovim.Compat.Megaparsec as P
32-
import Text.PrettyPrint.ANSI.Leijen (Doc)
33-
import qualified Text.PrettyPrint.ANSI.Leijen as P
34-
import UnliftIO.Exception (SomeException,
35-
bracket, catch)
32+
import UnliftIO.Exception (SomeException,
33+
bracket, catch)
34+
35+
import Data.Text.Prettyprint.Doc (Doc, Pretty(..), (<+>))
36+
import Data.Text.Prettyprint.Doc.Render.Terminal (AnsiStyle)
3637

3738
import Prelude
3839

@@ -80,10 +81,10 @@ data NeovimAPI
8081
deriving (Show)
8182

8283
-- | Run @nvim --api-info@ and parse its output.
83-
parseAPI :: IO (Either Doc NeovimAPI)
84-
parseAPI = either (Left . P.text) extractAPI <$> (decodeAPI `catch` readFromAPIFile)
84+
parseAPI :: IO (Either (Doc AnsiStyle) NeovimAPI)
85+
parseAPI = either (Left . pretty) extractAPI <$> (decodeAPI `catch` readFromAPIFile)
8586

86-
extractAPI :: Object -> Either Doc NeovimAPI
87+
extractAPI :: Object -> Either (Doc AnsiStyle) NeovimAPI
8788
extractAPI apiObj = fromObject apiObj >>= \apiMap -> NeovimAPI
8889
<$> extractErrorTypes apiMap
8990
<*> extractCustomTypes apiMap
@@ -112,43 +113,43 @@ decodeAPI = bracket queryNeovimAPI clean $ \(out, _) ->
112113
terminateProcess ph
113114

114115

115-
oLookup :: (NvimObject o) => String -> Map String Object -> Either Doc o
116+
oLookup :: (NvimObject o) => String -> Map String Object -> Either (Doc AnsiStyle) o
116117
oLookup qry = maybe throwErrorMessage fromObject . Map.lookup qry
117118
where
118-
throwErrorMessage = throwError . P.text $ "No entry for: " <> show qry
119+
throwErrorMessage = throwError $ "No entry for:" <+> pretty qry
119120

120121

121-
oLookupDefault :: (NvimObject o) => o -> String -> Map String Object -> Either Doc o
122+
oLookupDefault :: (NvimObject o) => o -> String -> Map String Object -> Either (Doc AnsiStyle) o
122123
oLookupDefault d qry m = maybe (return d) fromObject $ Map.lookup qry m
123124

124125

125-
extractErrorTypes :: Map String Object -> Either Doc [(String, Int64)]
126+
extractErrorTypes :: Map String Object -> Either (Doc AnsiStyle) [(String, Int64)]
126127
extractErrorTypes objAPI = extractTypeNameAndID =<< oLookup "error_types" objAPI
127128

128129

129-
extractTypeNameAndID :: Object -> Either Doc [(String, Int64)]
130+
extractTypeNameAndID :: Object -> Either (Doc AnsiStyle) [(String, Int64)]
130131
extractTypeNameAndID m = do
131132
types <- Map.toList <$> fromObject m
132133
forM types $ \(errName, idMap) -> do
133134
i <- oLookup "id" idMap
134135
return (errName,i)
135136

136137

137-
extractCustomTypes :: Map String Object -> Either Doc [(String, Int64)]
138+
extractCustomTypes :: Map String Object -> Either (Doc AnsiStyle) [(String, Int64)]
138139
extractCustomTypes objAPI = extractTypeNameAndID =<< oLookup "types" objAPI
139140

140141

141-
extractFunctions :: Map String Object -> Either Doc [NeovimFunction]
142+
extractFunctions :: Map String Object -> Either (Doc AnsiStyle) [NeovimFunction]
142143
extractFunctions objAPI = mapM extractFunction =<< oLookup "functions" objAPI
143144

144145

145-
toParameterlist :: [(String, String)] -> Either Doc [(NeovimType, String)]
146+
toParameterlist :: [(String, String)] -> Either (Doc AnsiStyle) [(NeovimType, String)]
146147
toParameterlist ps = forM ps $ \(t,n) -> do
147148
t' <- parseType t
148149
return (t', n)
149150

150151

151-
extractFunction :: Map String Object -> Either Doc NeovimFunction
152+
extractFunction :: Map String Object -> Either (Doc AnsiStyle) NeovimFunction
152153
extractFunction funDefMap = NeovimFunction
153154
<$> (oLookup "name" funDefMap)
154155
<*> (oLookup "parameters" funDefMap >>= toParameterlist)
@@ -157,8 +158,8 @@ extractFunction funDefMap = NeovimFunction
157158
<*> (oLookup "return_type" funDefMap >>= parseType)
158159

159160

160-
parseType :: String -> Either Doc NeovimType
161-
parseType s = either (throwError . P.text . show) return $ parse (pType <* eof) s s
161+
parseType :: String -> Either (Doc AnsiStyle) NeovimType
162+
parseType s = either (throwError . pretty . show) return $ parse (pType <* eof) s s
162163

163164

164165
pType :: P.Parser NeovimType

library/Neovim/API/TH.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ import Data.MessagePack
5656
import Data.Monoid
5757
import qualified Data.Set as Set
5858
import Data.Text (Text)
59-
import Text.PrettyPrint.ANSI.Leijen (text, (<+>), Doc)
59+
import Data.Text.Prettyprint.Doc ((<+>), Doc, viaShow, Pretty(..))
6060
import UnliftIO.Exception
6161

6262
import Prelude
@@ -252,9 +252,9 @@ customTypeInstance typeName nis =
252252
clause
253253
[ varP o ]
254254
(normalB [|throwError $
255-
text "Object is not convertible to:"
256-
<+> text n
257-
<+> text "Received:" <+> (text . show) $(varE o)|])
255+
pretty "Object is not convertible to:"
256+
<+> viaShow n
257+
<+> pretty "Received:" <+> viaShow $(varE o)|])
258258
[]
259259

260260
toObjectClause :: Name -> Int64 -> Q Clause
@@ -481,7 +481,7 @@ functionImplementation functionName = do
481481
-- _ -> err "Wrong number of arguments"
482482
errorCase :: Q Match
483483
errorCase = match wildP
484-
(normalB [|throw . ErrorMessage . text $ "Wrong number of arguments for function: "
484+
(normalB [|throw . ErrorMessage . pretty $ "Wrong number of arguments for function: "
485485
++ $(litE (StringL (nameBase functionName))) |]) []
486486

487487
-- [x,y] -> case pure add <*> fromObject x <*> fromObject y of ...
@@ -512,6 +512,6 @@ functionImplementation functionName = do
512512
failedEvaluation :: Q Match
513513
failedEvaluation = newName "e" >>= \e ->
514514
match (conP (mkName "Left") [varP e])
515-
(normalB [|err ($(varE e) :: Doc)|])
515+
(normalB [|err ($(varE e) :: Doc AnsiStyle)|])
516516
[]
517517

0 commit comments

Comments
 (0)