[Haskell-cafe] possible bug in latest hackage Elf (Elf-0.27)

Baojun Wang wangbj at gmail.com
Thu May 15 06:18:31 UTC 2014


Hi list,

with below test program:

--
​/* test1.c: build with -g -O0 */
include <stdio.h>

static const char appmsg[] = "hello, world";

int main(int argc, char* argv[])
{
        fputs(appmsg, stdout);

        return 0;
}


--- elf-test1.hs
module Main where

import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C

import Control.Monad

import Data.Elf

testelf = "/tmp/test1"
testelfsym = C.pack "appmsg"

lookupSymbol1 _ [] = Nothing
lookupSymbol1 sym (t:ts) =
   case (snd (steName t)) of
     Nothing -> lookupSymbol1 sym ts
     Just sname -> if sname == sym then Just t
                   else lookupSymbol1 sym ts

lookupSymbol _ [] = Nothing
lookupSymbol sym (t:ts) =
  case (lookupSymbol1 sym t) of
    Nothing -> lookupSymbol sym ts
    t1 -> t1

test1 elf symtab symbol = mapM_ (print) (elfSections elf)

test2 elf symtab symbol =
  lookupSymbol symbol symtab

test3 elf symtab symbol =
  lookupSymbol symbol symtab >>= \et ->
  findSymbolDefinition et

mainloop elf symtab symbol =
--  (test1 elf symtab symbol) >>
  print (test2 elf symtab symbol) >>
  print (test3 elf symtab symbol) >>
  return ()

main = do
  contents <- B.readFile testelf
  let elf = parseElf contents
      symtab = parseSymbolTables elf
  mainloop elf symtab testelfsym
---

the latest Data.Elf doesn't geive correct output as expected:

output will be:

Just (EST {steName = (9,Just "appmsg"), steEnclosingSection = Just
(ElfSection {elfSectionName = ".fini", elfSectionType = SHT_PROGBITS,
elfSectionFlags = [SHF_EXECINSTR,SHF_ALLOC], elfSectionAddr = 4195908,
elfSectionSize = 9, elfSectionLink = 0, elfSectionInfo = 0,
elfSectionAddrAlign = 4, elfSectionEntSize = 0, elfSectionData =
"H\131\236\bH\131\196\b\195"}), steType = STTObject, steBind = STBLocal,
steOther = 0, steIndex = SHNIndex 14, steValue = 4195924, steSize = 13})

>From above, you can see the steEnclosingSection is wrong and offset by 1.

The *correct* output should be:
Just (EST {steName = (9,Just "appmsg"), steEnclosingSection = Just
(ElfSection {elfSectionName = ".rodata", elfSectionType = SHT_PROGBITS,
elfSectionFlags = [SHF_ALLOC], elfSectionAddr = 4195920, elfSectionSize =
17, elfSectionLink = 0, elfSectionInfo = 0, elfSectionAddrAlign = 4,
elfSectionEntSize = 0, elfSectionData = "\SOH\NUL\STX\NULhello,
world\NUL"}), steType = STTObject, steBind = STBLocal, steOther = 0,
steIndex = SHNIndex 14, steValue = 4195924, steSize = 13})
Just "hello, world\NUL"

After check Elf.hs, I found there could be two issues:
1) in sectionByIndex, (SHNIndex) should start from 0, not 1; this cause the
steEnclosingSection from my exmaple offset by 1;
2) in findSymbolDefinition, start should substract the sectionAddr (base
address).

please see below diff for details:

--

--- a/Elf.hs   2012-12-04 19:27:51.000000000 -0800
+++ b/Elf.hs      2014-05-14 22:57:01.014498515 -0700
@@ -1,5 +1,5 @@
 -- | Data.Elf  is a module for parsing a ByteString of an ELF file into an
Elf record.
-module Data.Elf ( parseElf
+module Elf ( parseElf
                 , parseSymbolTables
                 , findSymbolDefinition
                 , Elf(..)
@@ -666,12 +666,12 @@ getSymbolTableEntries e s =
 -- If the size is zero, or the offset larger than the 'elfSectionData',
 -- then 'Nothing' is returned.
 findSymbolDefinition :: ElfSymbolTableEntry -> Maybe B.ByteString
-findSymbolDefinition e =
-    let enclosingData = fmap elfSectionData (steEnclosingSection e)
-        start = fromIntegral (steValue e)
+findSymbolDefinition e = steEnclosingSection e >>= \enclosingSection ->
+    let enclosingData = elfSectionData enclosingSection
+        start = ( (fromIntegral (steValue e)) - (fromIntegral
(elfSectionAddr enclosingSection) ) )
         len = fromIntegral (steSize e)
-        def = fmap (B.take len . B.drop start) enclosingData
-    in if def == Just B.empty then Nothing else def
+        def = (B.take len . B.drop start) enclosingData
+    in if def == B.empty then Nothing else Just def

 runGetMany :: Get a -> L.ByteString -> [a]
 runGetMany g bs
@@ -712,7 +712,7 @@ getSymbolTableEntry e strtlb =
     return $ EST (nameIdx,name) sec typ bind other sTlbIdx symVal size

 sectionByIndex :: Elf -> ElfSectionIndex -> Maybe ElfSection
-sectionByIndex e (SHNIndex i) = lookup i . zip [1..] $ (elfSections e)
+sectionByIndex e (SHNIndex i) = lookup i . zip [0..] $ (elfSections e)
 sectionByIndex _ _ = Nothing

 infoToTypeAndBind :: Word8 -> (ElfSymbolType,ElfSymbolBinding)

--

Would you please check above change and update Data.Elf hackage? I cannot
find the author from http://hackage.haskell.org/package/elf-0.27

Thanks
baojun
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140514/f28a706c/attachment.html>


More information about the Haskell-Cafe mailing list