Skip to content

Commit

Permalink
fix: build error
Browse files Browse the repository at this point in the history
  • Loading branch information
oriollinan committed Jan 9, 2025
1 parent dbbd1b7 commit 69cd5b7
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 7 deletions.
2 changes: 1 addition & 1 deletion lib/Ast/Parser/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ operationTable =
PU.binary "||" (`AT.Op` AT.Or),
PU.binary "or" (`AT.Op` AT.Or)
],
[ PU.postfix ".*" (`AT.UnaryOp` AT.Deref),
[ PU.postfix "." (`AT.UnaryOp` AT.Deref),
PU.postfix "++" (`AT.UnaryOp` AT.PostInc),
PU.postfix "--" (`AT.UnaryOp` AT.PostDec),
parseCall
Expand Down
13 changes: 7 additions & 6 deletions lib/Ast/Parser/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Ast.Parser.Utils where

import qualified Ast.Parser.State as PS
import qualified Ast.Types as AT
import qualified Control.Monad.Combinators.Expr as CE
import qualified Control.Monad.State as S
import qualified Text.Megaparsec as M
import qualified Text.Megaparsec.Char as MC
Expand Down Expand Up @@ -56,12 +57,12 @@ parseSrcLoc = do
(MP.SourcePos {MP.sourceName = _sourceName, MP.sourceLine = _sourceLine, MP.sourceColumn = _sourceColumn}) <- M.getSourcePos
return $ AT.SrcLoc {AT.srcFile = _sourceName, AT.srcLine = MP.unPos _sourceLine, AT.srcCol = MP.unPos _sourceColumn}

prefix :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr) -> CE.Operator PU.Parser AT.Expr
prefix name f = CE.Prefix (f <$> (PU.parseSrcLoc <* PU.symbol name))
prefix :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr) -> CE.Operator Parser AT.Expr
prefix name f = CE.Prefix (f <$> (parseSrcLoc <* symbol name))

postfix :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr) -> CE.Operator PU.Parser AT.Expr
postfix name f = CE.Postfix (f <$> (PU.parseSrcLoc <* PU.symbol name))
postfix :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr) -> CE.Operator Parser AT.Expr
postfix name f = CE.Postfix (f <$> (parseSrcLoc <* symbol name))

-- | Helper functions to define operators
binary :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr -> AT.Expr) -> CE.Operator PU.Parser AT.Expr
binary name f = CE.InfixL (f <$> (PU.parseSrcLoc <* PU.symbol name))
binary :: String -> (AT.SrcLoc -> AT.Expr -> AT.Expr -> AT.Expr) -> CE.Operator Parser AT.Expr
binary name f = CE.InfixL (f <$> (parseSrcLoc <* symbol name))

0 comments on commit 69cd5b7

Please sign in to comment.