Minor cleanups.

This commit is contained in:
Joe Hendrix 2018-01-29 01:06:59 -08:00
parent ca7ab08124
commit e1e558239e
No known key found for this signature in database
GPG Key ID: 8DFA5FF784098C4F
6 changed files with 49 additions and 37 deletions

View File

@ -67,6 +67,7 @@ library
Data.Macaw.Fold
Data.Macaw.Memory
Data.Macaw.Memory.ElfLoader
Data.Macaw.Memory.LoadCommon
Data.Macaw.Memory.Permissions
Data.Macaw.Types
Data.Macaw.Utils.Pretty

View File

@ -239,11 +239,8 @@ instance TraversableFC App where
prettyPure :: (Applicative m, Pretty v) => v -> m Doc
prettyPure = pure . pretty
ppApp :: (forall u . f u -> Doc)
-> App f tp
-> Doc
ppApp pp a0 = runIdentity $ ppAppA (Identity . pp) a0
-- | Pretty print an 'App' as an expression using the given function
-- for printing arguments.
ppAppA :: Applicative m
=> (forall u . f u -> m Doc)
-> App f tp
@ -286,6 +283,11 @@ ppAppA pp a0 =
Bsf _ x -> sexprA "bsf" [ pp x ]
Bsr _ x -> sexprA "bsr" [ pp x ]
ppApp :: (forall u . f u -> Doc)
-> App f tp
-> Doc
ppApp pp a0 = runIdentity $ ppAppA (Identity . pp) a0
------------------------------------------------------------------------
-- appType

View File

@ -1,5 +1,4 @@
{-|
Module : Data.Macaw.Memory.ElfLoader
Copyright : (c) Galois Inc, 2016
Maintainer : jhendrix@galois.com
@ -18,10 +17,9 @@ Operations for creating a view of memory from an elf file.
{-# LANGUAGE TypeFamilies #-}
module Data.Macaw.Memory.ElfLoader
( SectionIndexMap
, LoadStyle(..)
, LoadOptions(..)
, memoryForElf
, resolveElfFuncSymbols
, module Data.Macaw.Memory.LoadCommon
) where
import Control.Lens
@ -74,6 +72,7 @@ import Data.Maybe
import qualified Data.Vector as V
import Data.Macaw.Memory
import Data.Macaw.Memory.LoadCommon
import qualified Data.Macaw.Memory.Permissions as Perm
-- | Return a subbrange of a bytestring.
@ -118,33 +117,7 @@ flagsForSectionFlags f =
flagIf ef pf = if f `Elf.hasPermissions` ef then pf else Perm.none
------------------------------------------------------------------------
-- LoadOptions
-- | How to load Elf file.
data LoadStyle
= LoadBySection
-- ^ Load loadable sections in Elf file.
| LoadBySegment
-- ^ Load segments in Elf file.
deriving (Eq)
-- | Options used to configure loading
data LoadOptions
= LoadOptions { loadRegionIndex :: !RegionIndex
-- ^ Defines the "region" to load sections and segments into.
--
-- This should be 0 for static libraries since their addresses are
-- absolute. It should likely be non-zero for shared library since their
-- addresses are relative. Different shared libraries loaded into the
-- same memory should have different region indices.
, loadStyle :: !LoadStyle
-- ^ Controls whether to load by section or segment
, includeBSS :: !Bool
-- ^ Include data not backed by file when creating memory segments.
}
------------------------------------------------------------------------
-- MemSegment
-- Loading by segment
-- | Return segments for data
byteSegments :: forall w

View File

@ -0,0 +1,38 @@
{-|
Copyright : (c) Galois Inc, 2016
Maintainer : jhendrix@galois.com
Common datatypes for creating a memory from a binary file.
-}
module Data.Macaw.Memory.LoadCommon
( LoadOptions(..)
, LoadStyle(..)
) where
import Data.Macaw.Memory
------------------------------------------------------------------------
-- LoadOptions
-- | How to load Elf file.
data LoadStyle
= LoadBySection
-- ^ Load loadable sections in Elf file.
| LoadBySegment
-- ^ Load segments in Elf file.
deriving (Eq)
-- | Options used to configure loading
data LoadOptions
= LoadOptions { loadRegionIndex :: !RegionIndex
-- ^ Defines the "region" to load sections and segments into.
--
-- This should be 0 for static libraries since their addresses are
-- absolute. It should likely be non-zero for shared library since their
-- addresses are relative. Different shared libraries loaded into the
-- same memory should have different region indices.
, loadStyle :: !LoadStyle
-- ^ Controls whether to load by section or segment
, includeBSS :: !Bool
-- ^ Include data not backed by file when creating memory segments.
}

View File

@ -54,7 +54,6 @@ import Data.Bits
import qualified Data.Macaw.CFG as M
import qualified Data.Macaw.CFG.Block as M
import qualified Data.Macaw.Discovery.State as M
import qualified Data.Macaw.Memory as M
import qualified Data.Macaw.Types as M
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map

View File

@ -84,7 +84,6 @@ import qualified Data.Macaw.AbsDomain.StridedInterval as SI
import Data.Macaw.Architecture.Info
import Data.Macaw.CFG
import Data.Macaw.CFG.DemandSet
import Data.Macaw.Memory
import qualified Data.Macaw.Memory.Permissions as Perm
import Data.Macaw.Types
( n8