1- {-# LANGUAGE BangPatterns #-}
2- {-# LANGUAGE CPP #-}
3- {-# LANGUAGE DefaultSignatures #-}
4- {-# LANGUAGE DeriveDataTypeable #-}
5- {-# LANGUAGE DeriveGeneric #-}
6- {-# LANGUAGE GADTs #-}
7- {-# LANGUAGE OverloadedStrings #-}
8- {-# LANGUAGE ScopedTypeVariables #-}
1+ {-# LANGUAGE BangPatterns #-}
2+ {-# LANGUAGE CPP #-}
3+ {-# LANGUAGE DefaultSignatures #-}
4+ {-# LANGUAGE DeriveDataTypeable #-}
5+ {-# LANGUAGE DeriveGeneric #-}
6+ {-# LANGUAGE FlexibleInstances #-}
7+ {-# LANGUAGE GADTs #-}
8+ {-# LANGUAGE MultiParamTypeClasses #-}
9+ {-# LANGUAGE OverloadedStrings #-}
10+ {-# LANGUAGE ScopedTypeVariables #-}
11+ {-# LANGUAGE TypeOperators #-}
912
1013{-# OPTIONS_HADDOCK not-home #-}
1114
@@ -23,7 +26,7 @@ module Prettyprinter.Internal (
2326 Doc (.. ),
2427
2528 -- * Basic functionality
26- Pretty (.. ),
29+ Pretty (.. ), PrettyAnn ( .. ),
2730 viaShow , unsafeViaShow , unsafeTextWithoutNewlines ,
2831 emptyDoc , nest , line , line' , softline , softline' , hardline ,
2932
@@ -347,6 +350,54 @@ instance Pretty Char where
347350 prettyList = vsep . map unsafeTextWithoutNewlines . T. splitOn " \n "
348351#endif
349352
353+ -- | This class is similar to 'Pretty', but allows you to embed annotations in
354+ -- the 'Doc'.
355+ --
356+ -- @since 1.7.1
357+ class PrettyAnn a ann where
358+
359+ prettyAnn :: a -> Doc ann
360+
361+ default prettyAnn :: Show a => a -> Doc ann
362+ prettyAnn = viaShow
363+
364+ prettyAnnList :: [a ] -> Doc ann
365+ prettyAnnList = align . list . map prettyAnn
366+
367+ instance PrettyAnn (Doc ann ) ann where
368+ prettyAnn = id
369+
370+ instance PrettyAnn a ann => PrettyAnn (Const a b ) ann where
371+ prettyAnn = prettyAnn . getConst
372+
373+ #if FUNCTOR_IDENTITY_IN_BASE
374+ instance PrettyAnn a ann => PrettyAnn (Identity a ) ann where
375+ prettyAnn = prettyAnn . runIdentity
376+ #endif
377+
378+ instance PrettyAnn a ann => PrettyAnn [a ] ann where
379+ prettyAnn = prettyAnnList
380+
381+ instance PrettyAnn a ann => PrettyAnn (NonEmpty a ) ann where
382+ prettyAnn (x:| xs) = prettyAnnList (x: xs)
383+
384+ instance PrettyAnn () ann where
385+ prettyAnn _ = " ()"
386+
387+ instance PrettyAnn Bool ann where
388+ prettyAnn True = " True"
389+ prettyAnn False = " False"
390+
391+ instance PrettyAnn Char ann where
392+ prettyAnn ' \n ' = line
393+ prettyAnn c = Char c
394+
395+ #ifdef MIN_VERSION_text
396+ prettyAnnList = pretty . (id :: Text -> Text ) . fromString
397+ #else
398+ prettyAnnList = vsep . map unsafeTextWithoutNewlines . T. splitOn " \n "
399+ #endif
400+
350401-- | Convenience function to convert a 'Show'able value to a 'Doc'. If the
351402-- 'String' does not contain newlines, consider using the more performant
352403-- 'unsafeViaShow'.
@@ -467,6 +518,46 @@ instance Pretty Lazy.Text where pretty = pretty . Lazy.toStrict
467518-- []
468519instance Pretty Void where pretty = absurd
469520
521+ instance PrettyAnn Int ann where prettyAnn = unsafeViaShow
522+ instance PrettyAnn Int8 ann where prettyAnn = unsafeViaShow
523+ instance PrettyAnn Int16 ann where prettyAnn = unsafeViaShow
524+ instance PrettyAnn Int32 ann where prettyAnn = unsafeViaShow
525+ instance PrettyAnn Int64 ann where prettyAnn = unsafeViaShow
526+ instance PrettyAnn Word ann where prettyAnn = unsafeViaShow
527+ instance PrettyAnn Word8 ann where prettyAnn = unsafeViaShow
528+ instance PrettyAnn Word16 ann where prettyAnn = unsafeViaShow
529+ instance PrettyAnn Word32 ann where prettyAnn = unsafeViaShow
530+ instance PrettyAnn Word64 ann where prettyAnn = unsafeViaShow
531+
532+ instance PrettyAnn Integer ann where prettyAnn = unsafeViaShow
533+
534+ #if NATURAL_IN_BASE
535+ instance PrettyAnn Natural ann where prettyAnn = unsafeViaShow
536+ #endif
537+
538+ instance PrettyAnn Float ann where prettyAnn = unsafeViaShow
539+
540+ instance PrettyAnn Double ann where prettyAnn = unsafeViaShow
541+
542+ instance (PrettyAnn a1 ann , PrettyAnn a2 ann ) => PrettyAnn (a1 ,a2 ) ann where
543+ prettyAnn (x1,x2) = tupled [prettyAnn x1, prettyAnn x2]
544+
545+ instance (PrettyAnn a1 ann , PrettyAnn a2 ann , PrettyAnn a3 ann ) => PrettyAnn (a1 ,a2 ,a3 ) ann where
546+ prettyAnn (x1,x2,x3) = tupled [prettyAnn x1, prettyAnn x2, prettyAnn x3]
547+
548+ instance PrettyAnn a ann => PrettyAnn (Maybe a ) ann where
549+ prettyAnn = maybe mempty prettyAnn
550+ prettyAnnList = prettyAnnList . catMaybes
551+
552+ #ifdef MIN_VERSION_text
553+ instance PrettyAnn Text ann where prettyAnn = vsep . map unsafeTextWithoutNewlines . T. splitOn " \n "
554+
555+ instance PrettyAnn Lazy. Text ann where prettyAnn = prettyAnn . Lazy. toStrict
556+ #endif
557+
558+ instance PrettyAnn Void ann where prettyAnn = absurd
559+
560+
470561
471562
472563-- | @(unsafeTextWithoutNewlines s)@ contains the literal string @s@.
@@ -1810,8 +1901,8 @@ defaultLayoutOptions = LayoutOptions { layoutPageWidth = defaultPageWidth }
18101901-- | This is the default layout algorithm, and it is used by 'show', 'putDoc'
18111902-- and 'hPutDoc'.
18121903--
1813- -- @'layoutPretty'@ commits to rendering something in a certain way if the
1814- -- remainder of the current line fits the layout constraints; in other words,
1904+ -- @'layoutPretty'@ commits to rendering something in a certain way if the
1905+ -- remainder of the current line fits the layout constraints; in other words,
18151906-- it has up to one line of lookahead when rendering. Consider using the
18161907-- smarter, but a bit less performant, @'layoutSmart'@ algorithm if the results
18171908-- seem to run off to the right before having lots of line breaks.
0 commit comments