{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module GHC.Hs.Doc
( HsDocString
, LHsDocString
, mkHsDocString
, mkHsDocStringUtf8ByteString
, unpackHDS
, hsDocStringToByteString
, ppr_mbDoc
, appendDocs
, concatDocs
, DeclDocMap(..)
, emptyDeclDocMap
, ArgDocMap(..)
, emptyArgDocMap
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Utils.Binary
import GHC.Utils.Encoding
import GHC.Utils.IO.Unsafe
import GHC.Types.Name
import GHC.Utils.Outputable as Outputable
import GHC.Types.SrcLoc
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C8
import qualified Data.ByteString.Internal as BS
import Data.Data
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Foreign
newtype HsDocString = HsDocString ByteString
deriving (HsDocString -> HsDocString -> Bool
(HsDocString -> HsDocString -> Bool)
-> (HsDocString -> HsDocString -> Bool) -> Eq HsDocString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HsDocString -> HsDocString -> Bool
$c/= :: HsDocString -> HsDocString -> Bool
== :: HsDocString -> HsDocString -> Bool
$c== :: HsDocString -> HsDocString -> Bool
External instance of the constraint type Eq ByteString
Eq, Int -> HsDocString -> ShowS
[HsDocString] -> ShowS
HsDocString -> String
(Int -> HsDocString -> ShowS)
-> (HsDocString -> String)
-> ([HsDocString] -> ShowS)
-> Show HsDocString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HsDocString] -> ShowS
$cshowList :: [HsDocString] -> ShowS
show :: HsDocString -> String
$cshow :: HsDocString -> String
showsPrec :: Int -> HsDocString -> ShowS
$cshowsPrec :: Int -> HsDocString -> ShowS
External instance of the constraint type Show ByteString
External instance of the constraint type Ord Int
Show, Typeable HsDocString
DataType
Constr
Typeable HsDocString
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsDocString -> c HsDocString)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsDocString)
-> (HsDocString -> Constr)
-> (HsDocString -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsDocString))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsDocString))
-> ((forall b. Data b => b -> b) -> HsDocString -> HsDocString)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r)
-> (forall u. (forall d. Data d => d -> u) -> HsDocString -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HsDocString -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString)
-> Data HsDocString
HsDocString -> DataType
HsDocString -> Constr
(forall b. Data b => b -> b) -> HsDocString -> HsDocString
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsDocString -> c HsDocString
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsDocString
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> HsDocString -> u
forall u. (forall d. Data d => d -> u) -> HsDocString -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsDocString
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsDocString -> c HsDocString
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsDocString)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsDocString)
$cHsDocString :: Constr
$tHsDocString :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
gmapMp :: (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
gmapM :: (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsDocString -> m HsDocString
gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDocString -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HsDocString -> u
gmapQ :: (forall d. Data d => d -> u) -> HsDocString -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HsDocString -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsDocString -> r
gmapT :: (forall b. Data b => b -> b) -> HsDocString -> HsDocString
$cgmapT :: (forall b. Data b => b -> b) -> HsDocString -> HsDocString
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsDocString)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsDocString)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HsDocString)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsDocString)
dataTypeOf :: HsDocString -> DataType
$cdataTypeOf :: HsDocString -> DataType
toConstr :: HsDocString -> Constr
$ctoConstr :: HsDocString -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsDocString
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsDocString
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsDocString -> c HsDocString
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsDocString -> c HsDocString
External instance of the constraint type Data ByteString
Data)
type LHsDocString = Located HsDocString
instance Binary HsDocString where
put_ :: BinHandle -> HsDocString -> IO ()
put_ BinHandle
bh (HsDocString ByteString
bs) = BinHandle -> ByteString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary ByteString
put_ BinHandle
bh ByteString
bs
get :: BinHandle -> IO HsDocString
get BinHandle
bh = ByteString -> HsDocString
HsDocString (ByteString -> HsDocString) -> IO ByteString -> IO HsDocString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO ByteString
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary ByteString
get BinHandle
bh
instance Outputable HsDocString where
ppr :: HsDocString -> SDoc
ppr = SDoc -> SDoc
doubleQuotes (SDoc -> SDoc) -> (HsDocString -> SDoc) -> HsDocString -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SDoc
text (String -> SDoc) -> (HsDocString -> String) -> HsDocString -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsDocString -> String
unpackHDS
mkHsDocString :: String -> HsDocString
mkHsDocString :: String -> HsDocString
mkHsDocString String
s =
IO HsDocString -> HsDocString
forall a. IO a -> a
inlinePerformIO (IO HsDocString -> HsDocString) -> IO HsDocString -> HsDocString
forall a b. (a -> b) -> a -> b
$ do
let len :: Int
len = String -> Int
utf8EncodedLength String
s
ForeignPtr Word8
buf <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
len
ForeignPtr Word8 -> (Ptr Word8 -> IO HsDocString) -> IO HsDocString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
buf ((Ptr Word8 -> IO HsDocString) -> IO HsDocString)
-> (Ptr Word8 -> IO HsDocString) -> IO HsDocString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr -> do
Ptr Word8 -> String -> IO ()
utf8EncodeString Ptr Word8
ptr String
s
HsDocString -> IO HsDocString
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (ByteString -> HsDocString
HsDocString (ForeignPtr Word8 -> Int -> Int -> ByteString
BS.fromForeignPtr ForeignPtr Word8
buf Int
0 Int
len))
mkHsDocStringUtf8ByteString :: ByteString -> HsDocString
mkHsDocStringUtf8ByteString :: ByteString -> HsDocString
mkHsDocStringUtf8ByteString = ByteString -> HsDocString
HsDocString
unpackHDS :: HsDocString -> String
unpackHDS :: HsDocString -> String
unpackHDS = ByteString -> String
utf8DecodeByteString (ByteString -> String)
-> (HsDocString -> ByteString) -> HsDocString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsDocString -> ByteString
hsDocStringToByteString
hsDocStringToByteString :: HsDocString -> ByteString
hsDocStringToByteString :: HsDocString -> ByteString
hsDocStringToByteString (HsDocString ByteString
bs) = ByteString
bs
ppr_mbDoc :: Maybe LHsDocString -> SDoc
ppr_mbDoc :: Maybe LHsDocString -> SDoc
ppr_mbDoc (Just LHsDocString
doc) = LHsDocString -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
Instance of class: Outputable of the constraint type Outputable HsDocString
ppr LHsDocString
doc
ppr_mbDoc Maybe LHsDocString
Nothing = SDoc
empty
appendDocs :: HsDocString -> HsDocString -> HsDocString
appendDocs :: HsDocString -> HsDocString -> HsDocString
appendDocs HsDocString
x HsDocString
y =
HsDocString -> Maybe HsDocString -> HsDocString
forall a. a -> Maybe a -> a
fromMaybe
(ByteString -> HsDocString
HsDocString ByteString
BS.empty)
([HsDocString] -> Maybe HsDocString
concatDocs [HsDocString
x, HsDocString
y])
concatDocs :: [HsDocString] -> Maybe HsDocString
concatDocs :: [HsDocString] -> Maybe HsDocString
concatDocs [HsDocString]
xs =
if ByteString -> Bool
BS.null ByteString
b
then Maybe HsDocString
forall a. Maybe a
Nothing
else HsDocString -> Maybe HsDocString
forall a. a -> Maybe a
Just (ByteString -> HsDocString
HsDocString ByteString
b)
where
b :: ByteString
b = ByteString -> [ByteString] -> ByteString
BS.intercalate (String -> ByteString
C8.pack String
"\n\n")
([ByteString] -> ByteString)
-> ([HsDocString] -> [ByteString]) -> [HsDocString] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Bool) -> [ByteString] -> [ByteString]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (ByteString -> Bool) -> ByteString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Bool
BS.null)
([ByteString] -> [ByteString])
-> ([HsDocString] -> [ByteString]) -> [HsDocString] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HsDocString -> ByteString) -> [HsDocString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map HsDocString -> ByteString
hsDocStringToByteString
([HsDocString] -> ByteString) -> [HsDocString] -> ByteString
forall a b. (a -> b) -> a -> b
$ [HsDocString]
xs
newtype DeclDocMap = DeclDocMap (Map Name HsDocString)
instance Binary DeclDocMap where
put_ :: BinHandle -> DeclDocMap -> IO ()
put_ BinHandle
bh (DeclDocMap Map Name HsDocString
m) = BinHandle -> [(Name, HsDocString)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
Instance of class: Binary of the constraint type Binary HsDocString
put_ BinHandle
bh (Map Name HsDocString -> [(Name, HsDocString)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Name HsDocString
m)
get :: BinHandle -> IO DeclDocMap
get BinHandle
bh = Map Name HsDocString -> DeclDocMap
DeclDocMap (Map Name HsDocString -> DeclDocMap)
-> ([(Name, HsDocString)] -> Map Name HsDocString)
-> [(Name, HsDocString)]
-> DeclDocMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Name, HsDocString)] -> Map Name HsDocString
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type Ord Name
Map.fromList ([(Name, HsDocString)] -> DeclDocMap)
-> IO [(Name, HsDocString)] -> IO DeclDocMap
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [(Name, HsDocString)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
Instance of class: Binary of the constraint type Binary HsDocString
get BinHandle
bh
instance Outputable DeclDocMap where
ppr :: DeclDocMap -> SDoc
ppr (DeclDocMap Map Name HsDocString
m) = [SDoc] -> SDoc
vcat (((Name, HsDocString) -> SDoc) -> [(Name, HsDocString)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Name, HsDocString) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
Instance of class: Outputable of the constraint type Outputable HsDocString
External instance of the constraint type Outputable Name
pprPair (Map Name HsDocString -> [(Name, HsDocString)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map Name HsDocString
m))
where
pprPair :: (a, a) -> SDoc
pprPair (a
name, a
doc) = a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
name SDoc -> SDoc -> SDoc
Outputable.<> SDoc
colon SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
2 (a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
doc)
emptyDeclDocMap :: DeclDocMap
emptyDeclDocMap :: DeclDocMap
emptyDeclDocMap = Map Name HsDocString -> DeclDocMap
DeclDocMap Map Name HsDocString
forall k a. Map k a
Map.empty
newtype ArgDocMap = ArgDocMap (Map Name (Map Int HsDocString))
instance Binary ArgDocMap where
put_ :: BinHandle -> ArgDocMap -> IO ()
put_ BinHandle
bh (ArgDocMap Map Name (Map Int HsDocString)
m) = BinHandle -> [(Name, [(Int, HsDocString)])] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Int
Instance of class: Binary of the constraint type Binary HsDocString
put_ BinHandle
bh (Map Name [(Int, HsDocString)] -> [(Name, [(Int, HsDocString)])]
forall k a. Map k a -> [(k, a)]
Map.toList (Map Int HsDocString -> [(Int, HsDocString)]
forall k a. Map k a -> [(k, a)]
Map.toAscList (Map Int HsDocString -> [(Int, HsDocString)])
-> Map Name (Map Int HsDocString) -> Map Name [(Int, HsDocString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall k. Functor (Map k)
<$> Map Name (Map Int HsDocString)
m))
get :: BinHandle -> IO ArgDocMap
get BinHandle
bh = Map Name (Map Int HsDocString) -> ArgDocMap
ArgDocMap (Map Name (Map Int HsDocString) -> ArgDocMap)
-> ([(Name, [(Int, HsDocString)])]
-> Map Name (Map Int HsDocString))
-> [(Name, [(Int, HsDocString)])]
-> ArgDocMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(Int, HsDocString)] -> Map Int HsDocString)
-> Map Name [(Int, HsDocString)] -> Map Name (Map Int HsDocString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall k. Functor (Map k)
fmap [(Int, HsDocString)] -> Map Int HsDocString
forall k a. [(k, a)] -> Map k a
Map.fromDistinctAscList (Map Name [(Int, HsDocString)] -> Map Name (Map Int HsDocString))
-> ([(Name, [(Int, HsDocString)])]
-> Map Name [(Int, HsDocString)])
-> [(Name, [(Int, HsDocString)])]
-> Map Name (Map Int HsDocString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Name, [(Int, HsDocString)])] -> Map Name [(Int, HsDocString)]
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type Ord Name
Map.fromList ([(Name, [(Int, HsDocString)])] -> ArgDocMap)
-> IO [(Name, [(Int, HsDocString)])] -> IO ArgDocMap
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [(Name, [(Int, HsDocString)])]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Int
Instance of class: Binary of the constraint type Binary HsDocString
get BinHandle
bh
instance Outputable ArgDocMap where
ppr :: ArgDocMap -> SDoc
ppr (ArgDocMap Map Name (Map Int HsDocString)
m) = [SDoc] -> SDoc
vcat (((Name, Map Int HsDocString) -> SDoc)
-> [(Name, Map Int HsDocString)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Name, Map Int HsDocString) -> SDoc
forall {a} {a} {a}.
(Outputable a, Outputable a, Outputable a) =>
(a, Map a a) -> SDoc
Instance of class: Outputable of the constraint type Outputable HsDocString
External instance of the constraint type Outputable Int
External instance of the constraint type Outputable Name
pprPair (Map Name (Map Int HsDocString) -> [(Name, Map Int HsDocString)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map Name (Map Int HsDocString)
m))
where
pprPair :: (a, Map a a) -> SDoc
pprPair (a
name, Map a a
int_map) =
a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
name SDoc -> SDoc -> SDoc
Outputable.<> SDoc
colon SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
2 (Map a a -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => Map a a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
Evidence bound by a type signature of the constraint type Outputable a
pprIntMap Map a a
int_map)
pprIntMap :: Map a a -> SDoc
pprIntMap Map a a
im = [SDoc] -> SDoc
vcat (((a, a) -> SDoc) -> [(a, a)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (a, a) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
Evidence bound by a type signature of the constraint type Outputable a
pprIPair (Map a a -> [(a, a)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map a a
im))
pprIPair :: (a, a) -> SDoc
pprIPair (a
i, a
doc) = a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
i SDoc -> SDoc -> SDoc
Outputable.<> SDoc
colon SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
2 (a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
doc)
emptyArgDocMap :: ArgDocMap
emptyArgDocMap :: ArgDocMap
emptyArgDocMap = Map Name (Map Int HsDocString) -> ArgDocMap
ArgDocMap Map Name (Map Int HsDocString)
forall k a. Map k a
Map.empty