Skip to content

Commit

Permalink
Merge pull request #20 from GaloisInc/prettyprinter
Browse files Browse the repository at this point in the history
Switch from `ansi-wl-pprint` to the `prettyprinter` package.
  • Loading branch information
brianhuffman authored Dec 1, 2020
2 parents a24700f + d5df4c2 commit fe018fb
Show file tree
Hide file tree
Showing 7 changed files with 39 additions and 32 deletions.
2 changes: 1 addition & 1 deletion elf-edit.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -22,12 +22,12 @@ source-repository head
library
build-depends:
base >= 4.11 && < 5,
ansi-wl-pprint,
binary,
bytestring,
containers,
lens,
mtl,
prettyprinter >= 1.7.0,
utf8-string,
vector
ghc-options : -Wall
Expand Down
51 changes: 27 additions & 24 deletions src/Data/ElfEdit/HighLevel/Types.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
Expand Down Expand Up @@ -36,15 +37,15 @@ import qualified Data.Foldable as F
import qualified Data.Sequence as Seq
import Data.Word
import GHC.TypeLits
import Text.PrettyPrint.ANSI.Leijen hiding ((<>), (<$>))
import Prettyprinter

import Data.ElfEdit.Prim
import Data.ElfEdit.HighLevel.GOT
import Data.ElfEdit.HighLevel.Sections
import Data.ElfEdit.Utils (ppHex)

ppShow :: Show v => v -> Doc
ppShow = text . show
ppShow :: Show v => v -> Doc ann
ppShow = viaShow

------------------------------------------------------------------------
-- ElfMemSize
Expand Down Expand Up @@ -186,33 +187,35 @@ deriving instance ElfWidthConstraints w => Show (ElfDataRegion w)

$(pure [])

ppSegment :: ElfWidthConstraints w => ElfSegment w -> Doc
ppSegment :: ElfWidthConstraints w => ElfSegment w -> Doc ann
ppSegment s =
text "type: " <+> ppShow (elfSegmentType s) <$$>
text "flags:" <+> ppShow (elfSegmentFlags s) <$$>
text "index:" <+> ppShow (elfSegmentIndex s) <$$>
text "vaddr:" <+> text (ppHex (elfSegmentVirtAddr s)) <$$>
text "paddr:" <+> text (ppHex (elfSegmentPhysAddr s)) <$$>
text "align:" <+> ppShow (elfSegmentAlign s) <$$>
text "msize:" <+> ppShow (elfSegmentMemSize s) <$$>
text "data:" <$$>
indent 2 (vcat . map ppRegion . F.toList $ elfSegmentData s)
vcat
[ "type: " <+> ppShow (elfSegmentType s)
, "flags:" <+> ppShow (elfSegmentFlags s)
, "index:" <+> ppShow (elfSegmentIndex s)
, "vaddr:" <+> pretty (ppHex (elfSegmentVirtAddr s))
, "paddr:" <+> pretty (ppHex (elfSegmentPhysAddr s))
, "align:" <+> ppShow (elfSegmentAlign s)
, "msize:" <+> ppShow (elfSegmentMemSize s)
, "data:"
, indent 2 (vcat . map ppRegion . F.toList $ elfSegmentData s)
]

instance ElfWidthConstraints w => Show (ElfSegment w) where
show s = show (ppSegment s)

ppRegion :: ElfWidthConstraints w => ElfDataRegion w -> Doc
ppRegion :: ElfWidthConstraints w => ElfDataRegion w -> Doc ann
ppRegion r = case r of
ElfDataElfHeader -> text "ELF header"
ElfDataSegmentHeaders -> text "segment header table"
ElfDataSegment s -> hang 2 (text "contained segment" <$$> ppSegment s)
ElfDataSectionHeaders -> text "section header table"
ElfDataSectionNameTable w -> text "section name table" <+> parens (text "section number" <+> ppShow w)
ElfDataGOT got -> text "global offset table:" <+> ppShow got
ElfDataStrtab w -> text "strtab section" <+> parens (text "section number" <+> ppShow w)
ElfDataSymtab _idx symtab -> text "symtab section:" <+> ppShow symtab
ElfDataSection sec -> text "other section:" <+> ppShow sec
ElfDataRaw bs -> text "raw bytes:" <+> ppShow bs
ElfDataElfHeader -> "ELF header"
ElfDataSegmentHeaders -> "segment header table"
ElfDataSegment s -> hang 2 $ vcat ["contained segment", ppSegment s]
ElfDataSectionHeaders -> "section header table"
ElfDataSectionNameTable w -> "section name table" <+> parens ("section number" <+> ppShow w)
ElfDataGOT got -> "global offset table:" <+> ppShow got
ElfDataStrtab w -> "strtab section" <+> parens ("section number" <+> ppShow w)
ElfDataSymtab _idx symtab -> "symtab section:" <+> ppShow symtab
ElfDataSection sec -> "other section:" <+> ppShow sec
ElfDataRaw bs -> "raw bytes:" <+> ppShow bs

$(pure [])

Expand Down
4 changes: 2 additions & 2 deletions src/Data/ElfEdit/Prim/SymbolTable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ import qualified Data.ByteString.Char8 as BSC
import Data.ElfEdit.Prim.Shdr
import qualified Data.Vector as V
import Data.Word
import Text.PrettyPrint.ANSI.Leijen hiding ((<>), (<$>))
import Prettyprinter

import Data.ElfEdit.Prim.Ehdr
import Data.ElfEdit.Prim.File
Expand Down Expand Up @@ -273,7 +273,7 @@ ppSymbolTableEntry i e =
]

-- | Pretty print symbol table entries in format used by readelf.
ppSymbolTableEntries :: (Integral w, Bits w, Show w) => [SymtabEntry B.ByteString w] -> Doc
ppSymbolTableEntries :: (Integral w, Bits w, Show w) => [SymtabEntry B.ByteString w] -> Doc ann
ppSymbolTableEntries l = fixTableColumns (snd <$> cols) (fmap fst cols : entries)
where entries = zipWith ppSymbolTableEntry [0..] l
cols = [ ("Num:", alignRight 6)
Expand Down
4 changes: 2 additions & 2 deletions src/Data/ElfEdit/Relocations/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Data.Bits
import qualified Data.ByteString as B
import Data.Word
import GHC.TypeLits (Nat)
import Text.PrettyPrint.ANSI.Leijen hiding ((<>), (<$>))
import Prettyprinter

import Data.ElfEdit.Prim.Ehdr
import Data.ElfEdit.Utils
Expand Down Expand Up @@ -258,7 +258,7 @@ decodeRelaEntries d bs = do
_ -> Left $ "Rela buffer must be a multiple of rela entry size."

-- | Pretty-print a table of relocation entries.
ppRelaEntries :: IsRelocationType tp => [RelaEntry tp] -> Doc
ppRelaEntries :: IsRelocationType tp => [RelaEntry tp] -> Doc ann
ppRelaEntries l = fixTableColumns (snd <$> cols) (fmap fst cols : entries)
where entries = zipWith ppRelaEntry [0..] l
cols = [ ("Num", alignRight 0)
Expand Down
6 changes: 3 additions & 3 deletions src/Data/ElfEdit/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import qualified Data.ByteString as B
import Data.List (intercalate, transpose)
import qualified Data.Vector as V
import Numeric (showHex)
import Text.PrettyPrint.ANSI.Leijen hiding ((<>), (<$>))
import Prettyprinter

-- | @enumCnt b c@ returns a list with @c@ enum values starting from @b@.
enumCnt :: (Enum e, Real r) => e -> r -> [e]
Expand Down Expand Up @@ -70,8 +70,8 @@ alignRight minw l = ar <$> l
fixTableColumns :: [ColumnAlignmentFn]
-- ^ Functions for modifying each column
-> [[String]]
-> Doc
fixTableColumns colFns rows = vcat (hsep . fmap text <$> fixed_rows)
-> Doc ann
fixTableColumns colFns rows = vcat (hsep . fmap pretty <$> fixed_rows)
where cols = transpose rows
fixed_cols = zipWith ($) colFns cols
fixed_rows = transpose fixed_cols
Expand Down
2 changes: 2 additions & 0 deletions stack-8.4.yaml
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
resolver: lts-12.26
packages:
- '.'
extra-deps:
- prettyprinter-1.7.0
2 changes: 2 additions & 0 deletions stack-8.6.yaml
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
resolver: lts-13.13
packages:
- '.'
extra-deps:
- prettyprinter-1.7.0

0 comments on commit fe018fb

Please sign in to comment.