diff --git a/prettyprinter/src/Prettyprinter.hs b/prettyprinter/src/Prettyprinter.hs index bf44528e..1b24209f 100644 --- a/prettyprinter/src/Prettyprinter.hs +++ b/prettyprinter/src/Prettyprinter.hs @@ -198,7 +198,7 @@ module Prettyprinter ( Doc, -- * Basic functionality - Pretty(..), + Pretty(..), PrettyAnn(..), viaShow, unsafeViaShow, emptyDoc, nest, line, line', softline, softline', hardline, diff --git a/prettyprinter/src/Prettyprinter/Internal.hs b/prettyprinter/src/Prettyprinter/Internal.hs index 63e4ab43..cf5e8c8e 100755 --- a/prettyprinter/src/Prettyprinter/Internal.hs +++ b/prettyprinter/src/Prettyprinter/Internal.hs @@ -1,11 +1,14 @@ -{-# LANGUAGE BangPatterns #-} -{-# LANGUAGE CPP #-} -{-# LANGUAGE DefaultSignatures #-} -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE DefaultSignatures #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeOperators #-} {-# OPTIONS_HADDOCK not-home #-} @@ -23,7 +26,7 @@ module Prettyprinter.Internal ( Doc(..), -- * Basic functionality - Pretty(..), + Pretty(..), PrettyAnn(..), viaShow, unsafeViaShow, unsafeTextWithoutNewlines, emptyDoc, nest, line, line', softline, softline', hardline, @@ -347,6 +350,54 @@ instance Pretty Char where prettyList = vsep . map unsafeTextWithoutNewlines . T.splitOn "\n" #endif +-- | This class is similar to 'Pretty', but allows you to embed annotations in +-- the 'Doc'. +-- +-- @since 1.7.1 +class PrettyAnn ann a where + + prettyAnn :: a -> Doc ann + + default prettyAnn :: Show a => a -> Doc ann + prettyAnn = viaShow + + prettyAnnList :: [a] -> Doc ann + prettyAnnList = align . list . map prettyAnn + +instance PrettyAnn ann (Doc ann) where + prettyAnn = id + +instance PrettyAnn ann a => PrettyAnn ann (Const a b) where + prettyAnn = prettyAnn . getConst + +#if FUNCTOR_IDENTITY_IN_BASE +instance PrettyAnn ann a => PrettyAnn ann (Identity a) where + prettyAnn = prettyAnn . runIdentity +#endif + +instance PrettyAnn ann a => PrettyAnn ann [a] where + prettyAnn = prettyAnnList + +instance PrettyAnn ann a => PrettyAnn ann (NonEmpty a) where + prettyAnn (x:|xs) = prettyAnnList (x:xs) + +instance PrettyAnn ann () where + prettyAnn _ = "()" + +instance PrettyAnn ann Bool where + prettyAnn True = "True" + prettyAnn False = "False" + +instance PrettyAnn ann Char where + prettyAnn '\n' = line + prettyAnn c = Char c + +#ifdef MIN_VERSION_text + prettyAnnList = pretty . (id :: Text -> Text) . fromString +#else + prettyAnnList = vsep . map unsafeTextWithoutNewlines . T.splitOn "\n" +#endif + -- | Convenience function to convert a 'Show'able value to a 'Doc'. If the -- 'String' does not contain newlines, consider using the more performant -- 'unsafeViaShow'. @@ -467,6 +518,45 @@ instance Pretty Lazy.Text where pretty = pretty . Lazy.toStrict -- [] instance Pretty Void where pretty = absurd +instance PrettyAnn ann Int where prettyAnn = unsafeViaShow +instance PrettyAnn ann Int8 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Int16 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Int32 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Int64 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Word where prettyAnn = unsafeViaShow +instance PrettyAnn ann Word8 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Word16 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Word32 where prettyAnn = unsafeViaShow +instance PrettyAnn ann Word64 where prettyAnn = unsafeViaShow + +instance PrettyAnn ann Integer where prettyAnn = unsafeViaShow + +#if NATURAL_IN_BASE +instance PrettyAnn ann Natural where prettyAnn = unsafeViaShow +#endif + +instance PrettyAnn ann Float where prettyAnn = unsafeViaShow + +instance PrettyAnn ann Double where prettyAnn = unsafeViaShow + +instance (PrettyAnn ann a1, PrettyAnn ann a2) => PrettyAnn ann (a1,a2) where + prettyAnn (x1,x2) = tupled [prettyAnn x1, prettyAnn x2] + +instance (PrettyAnn ann a1, PrettyAnn ann a2, PrettyAnn ann a3) => PrettyAnn ann (a1,a2,a3) where + prettyAnn (x1,x2,x3) = tupled [prettyAnn x1, prettyAnn x2, prettyAnn x3] + +instance PrettyAnn ann a => PrettyAnn ann (Maybe a) where + prettyAnn = maybe mempty prettyAnn + prettyAnnList = prettyAnnList . catMaybes + +#ifdef MIN_VERSION_text +instance PrettyAnn ann Text where prettyAnn = vsep . map unsafeTextWithoutNewlines . T.splitOn "\n" + +instance PrettyAnn ann Lazy.Text where prettyAnn = prettyAnn . Lazy.toStrict +#endif + +instance PrettyAnn ann Void where prettyAnn = absurd + -- | @(unsafeTextWithoutNewlines s)@ contains the literal string @s@. @@ -1810,8 +1900,8 @@ defaultLayoutOptions = LayoutOptions { layoutPageWidth = defaultPageWidth } -- | This is the default layout algorithm, and it is used by 'show', 'putDoc' -- and 'hPutDoc'. -- --- @'layoutPretty'@ commits to rendering something in a certain way if the --- remainder of the current line fits the layout constraints; in other words, +-- @'layoutPretty'@ commits to rendering something in a certain way if the +-- remainder of the current line fits the layout constraints; in other words, -- it has up to one line of lookahead when rendering. Consider using the -- smarter, but a bit less performant, @'layoutSmart'@ algorithm if the results -- seem to run off to the right before having lots of line breaks.