Fixed the occam and Rain parsers to work with the new system for array literals

This commit is contained in:
Neil Brown 2009-02-01 21:54:02 +00:00
parent 3458a9197a
commit 46394b8c34
2 changed files with 24 additions and 17 deletions

View File

@ -632,7 +632,7 @@ tableElems
= stringLiteral = stringLiteral
<|> do m <- md <|> do m <- md
es <- tryXVX sLeft (sepBy1 expression sComma) sRight es <- tryXVX sLeft (sepBy1 expression sComma) sRight
return (A.Infer, A.ArrayLiteral m (map A.ArrayElemExpr es)) return (A.Infer, A.ArrayListLiteral m $ A.Several m (map (A.Only m) es))
<?> "table elements" <?> "table elements"
-- String literals are implicitly typed []BYTE unless otherwise specified, so -- String literals are implicitly typed []BYTE unless otherwise specified, so
@ -641,9 +641,9 @@ stringLiteral :: OccParser (A.Type, A.LiteralRepr)
stringLiteral stringLiteral
= do m <- md = do m <- md
cs <- stringCont <|> stringLit cs <- stringCont <|> stringLit
let aes = [A.ArrayElemExpr $ A.Literal m' A.Infer c let aes = A.Several m [A.Only m $ A.Literal m' A.Infer c
| c@(A.ByteLiteral m' _) <- cs] | c@(A.ByteLiteral m' _) <- cs]
return (A.Array [A.UnknownDimension] A.Byte, A.ArrayLiteral m aes) return (A.Array [A.UnknownDimension] A.Byte, A.ArrayListLiteral m aes)
<?> "string literal" <?> "string literal"
where where
stringCont :: OccParser [A.LiteralRepr] stringCont :: OccParser [A.LiteralRepr]
@ -718,7 +718,8 @@ arrayConstructor
e <- expression e <- expression
scopeOutRep n' scopeOutRep n'
sRight sRight
return $ A.ExprConstr m $ A.RepConstr m A.Infer n' r e return $ A.Literal m A.Infer $ A.ArrayListLiteral m $ A.Spec m
(A.Specification m n' (A.Rep m r)) $ A.Only m e
<?> "array constructor expression" <?> "array constructor expression"
associativeOpExpression :: OccParser A.Expression associativeOpExpression :: OccParser A.Expression

View File

@ -35,6 +35,7 @@ import qualified LexRain as L
import Metadata import Metadata
import ParseUtils import ParseUtils
import Pass import Pass
import Types
import Utils import Utils
type RainState = CompState type RainState = CompState
@ -187,8 +188,8 @@ stringLiteral :: RainParser A.LiteralRepr
stringLiteral stringLiteral
= do (m,str) <- getToken testToken = do (m,str) <- getToken testToken
let processed = replaceEscapes str let processed = replaceEscapes str
let aes = [A.Literal m A.Byte $ A.ByteLiteral m [c] | c <- processed] aes = A.Several m [A.Only m $ A.Literal m A.Byte $ A.ByteLiteral m [c] | c <- processed]
return (A.ListLiteral m aes) return (A.ArrayListLiteral m aes)
<?> "string literal" <?> "string literal"
where where
testToken (L.TokStringLiteral str) = Just str testToken (L.TokStringLiteral str) = Just str
@ -227,11 +228,11 @@ listLiteral
u <- getUniqueIdentifer u <- getUniqueIdentifer
let t = A.List $ A.UnknownVarType (A.TypeRequirements False) (Right (m,u)) let t = A.List $ A.UnknownVarType (A.TypeRequirements False) (Right (m,u))
(do try sRightQ (do try sRightQ
return $ A.Literal m t $ A.ListLiteral m [] return $ A.Literal m t $ A.ArrayListLiteral m (A.Several m [])
<|> do e0 <- try expression <|> do e0 <- try expression
(do try sRightQ (do try sRightQ
return $ A.Literal m t $ return $ A.Literal m t $ A.ArrayListLiteral m $
A.ListLiteral m [e0] A.Several m [A.Only m e0]
-- Up until the first comma, this may be a type declaration -- Up until the first comma, this may be a type declaration
-- in a cast expression, so we "try" all the way -- in a cast expression, so we "try" all the way
-- up until that comma -- up until that comma
@ -239,7 +240,8 @@ listLiteral
es <- sepBy1 expression sComma es <- sepBy1 expression sComma
sRightQ sRightQ
return $ A.Literal m t $ return $ A.Literal m t $
A.ListLiteral m (e0 : es) A.ArrayListLiteral m $ A.Several m $
map (A.Only m) (e0 : es)
) )
) )
@ -264,16 +266,20 @@ range = try $ do m <- sLeftQ
sDots sDots
end <- literal end <- literal
sRightQ sRightQ
case optTy of (t, rep) <- case optTy of
Just (t, mc) -> return $ A.ExprConstr m $ A.RangeConstr m Just (t, mc) ->
(A.List t) let begin' = A.Conversion mc A.DefaultConversion t begin
(A.Conversion mc A.DefaultConversion t begin) end' = A.Conversion mc A.DefaultConversion t end
(A.Conversion mc A.DefaultConversion t end) in return (t, A.For m begin' (subOne $ addExprs begin' end') (makeConstant m 1))
Nothing -> do u <- getUniqueIdentifer Nothing -> do u <- getUniqueIdentifer
let t = A.List $ A.UnknownVarType (A.TypeRequirements let t = A.List $ A.UnknownVarType (A.TypeRequirements
False) (Right (m,u)) False) (Right (m,u))
return $ A.ExprConstr m $ A.RangeConstr m return (t, A.For m begin
t begin end (subOne $ addExprs begin end) (makeConstant m 1))
repSpec@(A.Specification _ repN _) <- defineNonce m "range_rep" (A.Rep m rep) A.ValAbbrev
return $ A.Literal m t $ A.ArrayListLiteral m $
A.Spec m repSpec $ A.Only m $
A.ExprVariable m $ A.Variable m repN
expression :: RainParser A.Expression expression :: RainParser A.Expression
expression expression