Skip to content

Instantly share code, notes, and snippets.

@KholdStare
Last active August 29, 2015 14:00
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save KholdStare/56d3a1499c2afaeb6c5f to your computer and use it in GitHub Desktop.
Save KholdStare/56d3a1499c2afaeb6c5f to your computer and use it in GitHub Desktop.
Parsing NM files in Haskell
Symbols from lib.a[bye.o]:
Name Value Class Type Size Line Section
bye |0000000000000000| T | FUNC|0000000000000024| |.text
printf | | U | NOTYPE| | |*UND*
Symbols from lib.a[hello.o]:
Name Value Class Type Size Line Section
func |0000000000000000| T | FUNC|0000000000000024| |.text
printf | | U | NOTYPE| | |*UND*
sum |0000000000000024| T | FUNC|0000000000000014| |.text
Symbols from lib.a[bye.o]:
bye |0000000000000000| T | FUNC|0000000000000024| |.text
printf | | U | NOTYPE| | |*UND*
Symbols from lib.a[hello.o]:
func |0000000000000000| T | FUNC|0000000000000024| |.text
printf | | U | NOTYPE| | |*UND*
sum |0000000000000024| T | FUNC|0000000000000014| |.text
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
import Data.Attoparsec.Text
import Control.Applicative
import Control.Monad
import Data.Text
import Data.Text.IO
import Prelude hiding (readFile)
newtype ObjectPath = ObjectPath FilePath
deriving (Show)
newtype LibraryPath = LibraryPath FilePath
deriving (Show)
data ObjectSymbols = ObjectSymbols {
_objectInfo :: (Maybe LibraryPath, ObjectPath),
_symbolTable :: [[Text]]
} deriving (Show)
sysvRow :: Parser [Text]
sysvRow = do
cells <- (strip <$> takeTill pipeOrEol) `sepBy` char '|'
guard $ Prelude.length cells == 7
return cells
where pipeOrEol c = c == '|' || isEndOfLine c
objectPath :: Parser (Maybe LibraryPath, ObjectPath)
objectPath = ((Nothing,) . ObjectPath . unpack) <$> takeTill (== ':')
libraryObjectPath :: Parser (Maybe LibraryPath, ObjectPath)
libraryObjectPath = do
lib <- takeTill (== '[')
obj <- char '[' *> takeTill (== ']') <* char ']'
return (Just $ LibraryPath $ unpack lib, ObjectPath $ unpack obj)
objectFileHeader :: Parser (Maybe LibraryPath, ObjectPath)
objectFileHeader = do
string "Symbols from "
header <- libraryObjectPath <|> objectPath
takeTill isEndOfLine
return header
anyLine :: Parser Text
anyLine = takeTill isEndOfLine <* endOfLine
-- | Skip any occurances of first action until another successful
-- action.
skipTill :: (Alternative f) => f a -> f b -> f b
skipTill skippable nextAction =
nextAction
<|> skippable *> skipTill skippable nextAction
objectSymbols :: Parser ObjectSymbols
objectSymbols = ObjectSymbols
<$> (anyLine `skipTill` objectFileHeader <* endOfLine)
<*> (anyLine `skipTill` many1 (sysvRow <* endOfLine))
sysvSymbolFile :: Parser [ObjectSymbols]
sysvSymbolFile = many objectSymbols
main :: IO ()
main = do
tryParsing "nm-output"
tryParsing "nm-simple-output"
where tryParsing filepath =
print =<< (parseOnly sysvSymbolFile <$> readFile filepath)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment