Make Meta a simple structure

This commit is contained in:
Adam Sampson 2007-04-21 02:54:08 +00:00
parent f701e4bf8a
commit f38d548c33
7 changed files with 29 additions and 54 deletions

View File

@ -1,32 +1,15 @@
-- | Error handling and reporting.
module Errors where
import Data.Generics
import Control.Monad.Error
import qualified AST as A
import Metadata
data OccError = OccError {
errorText :: String,
errorPos :: Maybe OccSourcePos
}
deriving (Show, Eq, Typeable, Data)
type OccErrorT m a = ErrorT OccError m a
die :: String -> a
die s = error $ "\n\nError:\n" ++ s
dieInternal :: Monad m => String -> m a
dieInternal s = die $ "Internal error: " ++ s
formatPos :: Meta -> String
formatPos m
= case findSourcePos m of
Just o -> show o
Nothing -> "?"
dieP :: Monad m => Meta -> String -> m a
dieP m s = die $ formatPos m ++ ": " ++ s
dieP m s = die $ show m ++ ": " ++ s

View File

@ -62,7 +62,7 @@ overArray :: A.Variable -> (SubscripterFunction -> Maybe (CGen ())) -> CGen ()
overArray var func
= do ps <- get
let A.Array ds _ = fromJust $ typeOfVariable ps var
let m = []
let m = emptyMeta
specs <- sequence [makeNonceVariable "i" m A.Int A.VariableName A.Original | _ <- ds]
let indices = [A.Variable m n | A.Specification _ n _ <- specs]
@ -668,7 +668,7 @@ declareInit (A.Chan _) var
declareInit t@(A.Array ds t') var
= Just $ do init <- case t' of
A.Chan _ ->
do let m = []
do let m = emptyMeta
A.Specification _ store _ <- makeNonceVariable "storage" m (A.Array ds A.Int) A.VariableName A.Original
let storeV = A.Variable m store
tell ["Channel "]

View File

@ -1,29 +1,24 @@
-- | Metadata.
-- | Metadata -- i.e. source position.
module Metadata where
import Data.Generics
import Data.List
type Meta = [Metadatum]
data OccSourcePos = OccSourcePos String Int Int
data Meta = Meta {
metaFile :: Maybe String,
metaLine :: Int,
metaColumn :: Int
}
deriving (Eq, Typeable, Data)
instance Show OccSourcePos where
show (OccSourcePos file line col) = file ++ ":" ++ show line ++ ":" ++ show col
data Metadatum =
MdSourcePos OccSourcePos
deriving (Show, Eq, Typeable, Data)
findSourcePos :: Meta -> Maybe OccSourcePos
findSourcePos ms
= do sps <- find (\x -> case x of MdSourcePos _ -> True
otherwise -> False) ms
return $ case sps of MdSourcePos sp -> sp
formatSourcePos :: Meta -> String
formatSourcePos m = case findSourcePos m of
Just (OccSourcePos f l c) -> "<@" ++ show l ++ ":" ++ show c ++ ">"
Nothing -> "<?>"
emptyMeta :: Meta
emptyMeta = Meta {
metaFile = Nothing,
metaLine = 0,
metaColumn = 0
}
instance Show Meta where
show m =
case metaFile m of
Just s -> s ++ ":" ++ show (metaLine m) ++ ":" ++ show (metaColumn m)
Nothing -> "no source position"

View File

@ -234,15 +234,14 @@ eol = do { whiteSpace; reserved eolMarker } <?> "end of line"
--}}}
--{{{ helper functions
getSourcePos :: OccParser OccSourcePos
getSourcePos
= do pos <- getPosition
return $ OccSourcePos (sourceName pos) (sourceLine pos) (sourceColumn pos)
md :: OccParser Meta
md
= do pos <- getSourcePos
return [MdSourcePos pos]
= do pos <- getPosition
return Meta {
metaFile = Just $ sourceName pos,
metaLine = sourceLine pos,
metaColumn = sourceColumn pos
}
tryVX :: OccParser a -> OccParser b -> OccParser a
tryVX p q = try (do { v <- p; q; return v })
@ -1474,6 +1473,6 @@ parseFile file ps
parseProgram :: Monad m => String -> ParseState -> m (A.Process, ParseState)
parseProgram file ps
= do (f, ps') <- parseFile file ps
return (f $ A.Main [], ps')
return (f $ A.Main emptyMeta, ps')
--}}}

View File

@ -38,7 +38,7 @@ doString :: String -> Doc
doString s = text $ show s
doMeta :: Meta -> Doc
doMeta m = text $ formatSourcePos m
doMeta m = text $ show m
doAny :: Data a => a -> Doc
doAny = doGeneral `ext1Q` doList `extQ` doString `extQ` doMeta

View File

@ -12,8 +12,6 @@ that takes several expressions.
The show instance for types should produce occam-looking types.
Redo Meta as a structure rather than a list.
ParseState should be called something more sensible, since most of it has
nothing to do with parsing.

View File

@ -154,7 +154,7 @@ makeConstant m n = A.ExprLiteral m $ A.Literal m A.Int $ A.IntLiteral m (show n)
-- | Find the Meta value in an expression.
metaOfExpression :: A.Expression -> Meta
metaOfExpression e = concat $ gmapQ (mkQ [] findMeta) e
metaOfExpression e = head $ gmapQ (mkQ emptyMeta findMeta) e
where
findMeta :: Meta -> Meta
findMeta m = m