EPICS Controls Argonne National Laboratory

Experimental Physics and
Industrial Control System

1994  1995  1996  1997  1998  1999  2000  2001  2002  2003  2004  2005  2006  <20072008  2009  2010  2011  2012  2013  2014  2015  2016  2017  2018  2019  2020  2021  2022  2023  2024  Index 1994  1995  1996  1997  1998  1999  2000  2001  2002  2003  2004  2005  2006  <20072008  2009  2010  2011  2012  2013  2014  2015  2016  2017  2018  2019  2020  2021  2022  2023  2024 
<== Date ==> <== Thread ==>

Subject: Re: lexical analyzer for .db?
From: Benjamin Franksen <[email protected]>
To: [email protected]
Date: Thu, 1 Nov 2007 13:06:30 +0100
On Thursday 01 November 2007 08:18, Heinrich du Toit wrote:
> Oops.. actually I need like the parser part..
> Ie. what bison does :)
>
> On Thu, 2007-11-01 at 08:31 +0200, Heinrich du Toit wrote:
> > Hi
> >
> > Is there 'n lexical analyzer for .db files?
> >
> > I guess there must be something in epics BASE somewhere?
> > But is it written in something like flex that can easily be
> > extended/used or is it some custom code nightmare?
> >
> > O let me explain.
> > I want to make some sort of .db file pre-processor that can do some
> > modifications. Mainly macro expansion type stuff.
> > And this I want to use so that some rule stuff can be written in
> > Macro's and not in long complex records and hopefully make it easier to
> > maintain and understand and change. And then maybe also handle some
> > other stuff with the pre-processor to keep thing consistently linked
> > ect... making it more reliable and less prone to human error. Plus the
> > person working with it might not fully understand all the internal
> > stuff of 'n db.

FWIW, attached you find a parser for the db file syntax written in Haskell 
using a parser combinator library. Took me about 20 minutes to write and 
worked out of the box.

Cheers
Ben
module ParseEpics where

import Text.ParserCombinators.Parsec

quadruple p q s t = do
  rp <- p
  symbol ","
  rq <- q
  symbol ","
  rs <- s
  symbol ","
  rt <- t
  return (rp,rq,rs,rt)

pair p q = do
  rp <- p
  symbol ","
  rq <- q
  return (rp,rq)

braces p = do
  symbol "{"
  r <- p
  symbol "}"
  return r

parens p = do
  symbol "("
  r <- p
  symbol ")"
  return r

item = lexeme (quoted <|> bareword)

symbol = lexeme . string

lexeme p = do
  r <- p
  skipWhite
  return r

bareword = many1 (alphaNum <|> oneOf "_-:.[]<>;")

quoted = do
  char '"'
  s <- manyTill (try escquote <|> notquote) (char '"')
  return s

notquote = noneOf "\""
escquote = string "\\\"" >> return '"'

skipWhite = skipMany white

white = blank <|> comment

blank = skip (oneOf " \n\t\v")

comment = char '#' >> skipMany (noneOf "\n")

skip p = p >> return ()
{-# LANGUAGE FlexibleContexts #-}
--module ParseDb (parseEpicsDb) where

import Data.Collections
import MonadLib hiding (try)
import Monads (runException)
import Text.ParserCombinators.Parsec

-- import Gadgets (EpicsRecord(..),Attributes)
import ParseEpics

type Attributes = StdMap String String

data EpicsRecord = ER {
    erType :: String,
    erName :: String,
    erFieldDefs :: Attributes
  } deriving Show

type EpicsDb = [EpicsRecord]

parseEpicsDb :: ExceptionM m String => SourceName -> String -> m EpicsDb
parseEpicsDb filename input = case parse epicsDb filename input of
  Right records -> return records
  Left parseErr -> raise (show parseErr)

epicsDb = skipWhite >> many epicsRecord

epicsRecord = do
  symbol "record"
  (rectype,recname) <- parens (pair item item)
  recfields <- braces fields
  return $ ER { erType=rectype, erName=recname, erFieldDefs=recfields }

fields = fmap fromList (many field)
  
field = do
  symbol "field"
  parens (pair item item)

-- test
main = do --getContents >>= parseTest epicsDb
  input <- getContents
  case runException (parseEpicsDb "" input) of
    Left err -> putStrLn err
    Right rs -> putStr . unlines . map show $ rs

References:
lexical analyzer for .db? Heinrich du Toit
Re: lexical analyzer for .db? Heinrich du Toit

Navigate by Date:
Prev: Re: lexical analyzer for .db? Heinrich du Toit
Next: question about iocConsole marco_hair
Index: 1994  1995  1996  1997  1998  1999  2000  2001  2002  2003  2004  2005  2006  <20072008  2009  2010  2011  2012  2013  2014  2015  2016  2017  2018  2019  2020  2021  2022  2023  2024 
Navigate by Thread:
Prev: Re: lexical analyzer for .db? Heinrich du Toit
Next: Re: lexical analyzer for .db? Andrew Johnson
Index: 1994  1995  1996  1997  1998  1999  2000  2001  2002  2003  2004  2005  2006  <20072008  2009  2010  2011  2012  2013  2014  2015  2016  2017  2018  2019  2020  2021  2022  2023  2024 
ANJ, 10 Nov 2011 Valid HTML 4.01! · Home · News · About · Base · Modules · Extensions · Distributions · Download ·
· Search · EPICS V4 · IRMIS · Talk · Bugs · Documents · Links · Licensing ·