mirror of
https://github.com/anoma/juvix.git
synced 2024-12-03 09:41:10 +03:00
Rename Const
constructor in Tree and Reg languages (#2695)
This is to avoid potential conflicts with Haskell's [Data.Functor.Const](https://hackage.haskell.org/package/base-4.19.1.0/docs/Data-Functor-Const.html#t:Const)
This commit is contained in:
parent
0f713c7c84
commit
5daa0e7520
@ -38,7 +38,7 @@ genCode fi =
|
||||
go isTail node = case node of
|
||||
Tree.Binop x -> goBinop isTail x
|
||||
Tree.Unop x -> goUnop isTail x
|
||||
Tree.Const x -> goConstant isTail x
|
||||
Tree.Constant x -> goConstant isTail x
|
||||
Tree.MemRef x -> goMemRef isTail x
|
||||
Tree.AllocConstr x -> goAllocConstr isTail x
|
||||
Tree.AllocClosure x -> goAllocClosure isTail x
|
||||
|
@ -313,7 +313,7 @@ fromRegInstr bNoStack info = \case
|
||||
|
||||
fromValue :: Reg.Value -> Expression
|
||||
fromValue = \case
|
||||
Reg.Const c -> fromConst c
|
||||
Reg.ValConst c -> fromConst c
|
||||
Reg.CRef Reg.ConstrField {..} ->
|
||||
case _constrFieldMemRep of
|
||||
Reg.MemRepConstr ->
|
||||
|
@ -110,13 +110,13 @@ fromReg tab = uncurry Result $ run $ runLabelInfoBuilderWithNextId (Reg.getNextS
|
||||
|
||||
goValue :: Reg.Value -> ([Instruction], Value)
|
||||
goValue = \case
|
||||
Reg.Const c -> ([], Imm $ goConst c)
|
||||
Reg.ValConst c -> ([], Imm $ goConst c)
|
||||
Reg.CRef x -> ([mkAssignAp (goConstrField x)], Ref $ MemRef Ap (-1))
|
||||
Reg.VRef x -> ([], Ref $ goVarRef x)
|
||||
|
||||
goRValue :: Reg.Value -> RValue
|
||||
goRValue = \case
|
||||
Reg.Const c -> Val $ Imm $ goConst c
|
||||
Reg.ValConst c -> Val $ Imm $ goConst c
|
||||
Reg.CRef x -> goConstrField x
|
||||
Reg.VRef x -> Val $ Ref $ goVarRef x
|
||||
|
||||
@ -162,8 +162,8 @@ fromReg tab = uncurry Result $ run $ runLabelInfoBuilderWithNextId (Reg.getNextS
|
||||
|
||||
goBinop :: Address -> Reg.InstrBinop -> Sem r [Instruction]
|
||||
goBinop addr x@Reg.InstrBinop {..} = case _instrBinopArg1 of
|
||||
Reg.Const c1 -> case _instrBinopArg2 of
|
||||
Reg.Const c2 -> case Reg.evalBinop' _instrBinopOpcode c1 c2 of
|
||||
Reg.ValConst c1 -> case _instrBinopArg2 of
|
||||
Reg.ValConst c2 -> case Reg.evalBinop' _instrBinopOpcode c1 c2 of
|
||||
Left err -> error err
|
||||
Right c ->
|
||||
return [mkAssign res (Val $ Imm $ goConst c)]
|
||||
|
@ -12,7 +12,7 @@ import GHC.Show qualified as Show
|
||||
import Juvix.Compiler.Core.Info (Info, IsInfo, Key)
|
||||
import Juvix.Compiler.Core.Language.Builtins (BuiltinDataTag (..), builtinConstrArgsNum)
|
||||
import Juvix.Extra.Serialize
|
||||
import Juvix.Prelude hiding (Const)
|
||||
import Juvix.Prelude
|
||||
import Prettyprinter
|
||||
|
||||
type Location = Interval
|
||||
|
@ -270,7 +270,7 @@ compile :: forall r. (Members '[Reader CompilerCtx] r) => Tree.Node -> Sem r (Te
|
||||
compile = \case
|
||||
Tree.Binop b -> goBinop b
|
||||
Tree.Unop b -> goUnop b
|
||||
Tree.Const c -> return (goConst (c ^. Tree.nodeConstant))
|
||||
Tree.Constant c -> return (goConstant (c ^. Tree.nodeConstant))
|
||||
Tree.MemRef c -> goMemRef (c ^. Tree.nodeMemRef)
|
||||
Tree.AllocConstr c -> goAllocConstr c
|
||||
Tree.AllocClosure c -> goAllocClosure c
|
||||
@ -312,8 +312,8 @@ compile = \case
|
||||
goDirectRef :: Tree.DirectRef -> Term Natural
|
||||
goDirectRef dr = OpAddress # directRefPath dr
|
||||
|
||||
goConst :: Tree.Constant -> Term Natural
|
||||
goConst = \case
|
||||
goConstant :: Tree.Constant -> Term Natural
|
||||
goConstant = \case
|
||||
Tree.ConstInt i
|
||||
| i < 0 -> error "negative integer"
|
||||
| otherwise -> nockIntegralLiteral i
|
||||
|
@ -53,7 +53,7 @@ overValueRefs f = \case
|
||||
|
||||
goValue :: Value -> Value
|
||||
goValue = \case
|
||||
Const c -> Const c
|
||||
ValConst c -> ValConst c
|
||||
CRef x -> CRef $ goConstrField x
|
||||
VRef x -> VRef $ f x
|
||||
|
||||
|
@ -144,7 +144,7 @@ computeStringMap strs = snd . run . execState (HashMap.size strs, strs) . mapM g
|
||||
|
||||
goVal :: (Member (State (Int, HashMap Text Int)) r) => Value -> Sem r ()
|
||||
goVal = \case
|
||||
Const (ConstString str) ->
|
||||
ValConst (ConstString str) ->
|
||||
modify'
|
||||
( \(sid :: Int, sstrs) ->
|
||||
if
|
||||
|
@ -88,7 +88,7 @@ runFunction hout infoTable args0 info0 = do
|
||||
|
||||
readValue :: Args -> Vars s -> Value -> ST s Val
|
||||
readValue args tmps = \case
|
||||
Const c -> return $ constantToValue c
|
||||
ValConst c -> return $ constantToValue c
|
||||
CRef r -> readConstrRef args tmps r
|
||||
VRef r -> readVarRef args tmps r
|
||||
|
||||
|
@ -7,7 +7,7 @@ where
|
||||
import Juvix.Compiler.Reg.Language.Base
|
||||
|
||||
data Value
|
||||
= Const Constant
|
||||
= ValConst Constant
|
||||
| CRef ConstrField
|
||||
| VRef VarRef
|
||||
|
||||
|
@ -43,7 +43,7 @@ instance PrettyCode ConstrField where
|
||||
|
||||
instance PrettyCode Value where
|
||||
ppCode = \case
|
||||
Const x -> Tree.ppCode x
|
||||
ValConst x -> Tree.ppCode x
|
||||
CRef x -> ppCode x
|
||||
VRef x -> ppCode x
|
||||
|
||||
|
@ -73,7 +73,7 @@ initBranchVars = mapT (const goFun)
|
||||
Assign
|
||||
InstrAssign
|
||||
{ _instrAssignResult = vref,
|
||||
_instrAssignValue = Const ConstVoid
|
||||
_instrAssignValue = ValConst ConstVoid
|
||||
}
|
||||
|
||||
checkInitialized :: InfoTable -> Bool
|
||||
|
@ -131,7 +131,7 @@ fromAsmInstr funInfo tab si Asm.CmdInstr {..} =
|
||||
|
||||
mkValue :: Asm.Value -> Value
|
||||
mkValue = \case
|
||||
Asm.Constant c -> Const c
|
||||
Asm.Constant c -> ValConst c
|
||||
Asm.Ref mv -> case mv of
|
||||
Asm.DRef dref -> VRef $ mkVar dref
|
||||
Asm.ConstrRef Asm.Field {..} ->
|
||||
|
@ -463,7 +463,7 @@ varTmp = do
|
||||
value ::
|
||||
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
|
||||
ParsecS r Value
|
||||
value = (Const <$> constant) <|> varOrConstrRef
|
||||
value = (ValConst <$> constant) <|> varOrConstrRef
|
||||
|
||||
varOrConstrRef ::
|
||||
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
|
||||
|
@ -37,7 +37,7 @@ hEval hout tab = eval' [] mempty
|
||||
eval' args temps node = case node of
|
||||
Binop x -> goBinop x
|
||||
Unop x -> goUnop x
|
||||
Const c -> goConstant c
|
||||
Constant c -> goConstant c
|
||||
MemRef x -> goMemRef x
|
||||
AllocConstr x -> goAllocConstr x
|
||||
AllocClosure x -> goAllocClosure x
|
||||
|
@ -34,7 +34,7 @@ eval tab = E.runReader emptyEvalCtx . eval'
|
||||
eval' node = case node of
|
||||
Binop x -> goBinop x
|
||||
Unop x -> goUnop x
|
||||
Const c -> return (goConstant c)
|
||||
Constant c -> return (goConstant c)
|
||||
MemRef x -> goMemRef x
|
||||
AllocConstr x -> goAllocConstr x
|
||||
AllocClosure x -> goAllocClosure x
|
||||
|
@ -32,7 +32,7 @@ eval tab = runReader emptyEvalCtx . eval'
|
||||
eval' node = case node of
|
||||
Binop x -> goBinop x
|
||||
Unop x -> goUnop x
|
||||
Const c -> return (goConstant c)
|
||||
Constant c -> return (goConstant c)
|
||||
MemRef x -> goMemRef x
|
||||
AllocConstr x -> goAllocConstr x
|
||||
AllocClosure x -> goAllocClosure x
|
||||
|
@ -9,16 +9,16 @@ mkUnop :: UnaryOpcode -> Node -> Node
|
||||
mkUnop op arg = Unop (NodeUnop mempty op arg)
|
||||
|
||||
mkConst :: Constant -> Node
|
||||
mkConst c = Const $ NodeConstant mempty c
|
||||
mkConst c = Constant (NodeConstant mempty c)
|
||||
|
||||
mkMemRef :: MemRef -> Node
|
||||
mkMemRef r = MemRef $ NodeMemRef mempty r
|
||||
mkMemRef r = MemRef (NodeMemRef mempty r)
|
||||
|
||||
getNodeInfo :: Node -> NodeInfo
|
||||
getNodeInfo = \case
|
||||
Binop NodeBinop {..} -> _nodeBinopInfo
|
||||
Unop NodeUnop {..} -> _nodeUnopInfo
|
||||
Const NodeConstant {..} -> _nodeConstantInfo
|
||||
Constant NodeConstant {..} -> _nodeConstantInfo
|
||||
MemRef NodeMemRef {..} -> _nodeMemRefInfo
|
||||
AllocConstr NodeAllocConstr {..} -> _nodeAllocConstrInfo
|
||||
AllocClosure NodeAllocClosure {..} -> _nodeAllocClosureInfo
|
||||
@ -140,10 +140,10 @@ destruct = \case
|
||||
_nodeUnopInfo
|
||||
}
|
||||
}
|
||||
Const c ->
|
||||
Constant c ->
|
||||
NodeDetails
|
||||
{ _nodeChildren = [],
|
||||
_nodeReassemble = noChildren (Const c)
|
||||
_nodeReassemble = noChildren (Constant c)
|
||||
}
|
||||
MemRef r ->
|
||||
NodeDetails
|
||||
|
@ -17,7 +17,7 @@ data Node
|
||||
= Binop NodeBinop
|
||||
| Unop NodeUnop
|
||||
| -- | A constant value.
|
||||
Const NodeConstant
|
||||
Constant NodeConstant
|
||||
| -- | A memory reference.
|
||||
MemRef NodeMemRef
|
||||
| -- | Allocate constructor data. JVT code: 'alloc[<tag>](x1, .., xn)'.
|
||||
|
@ -338,7 +338,7 @@ instance PrettyCode Node where
|
||||
ppCode = \case
|
||||
Binop x -> ppCode x
|
||||
Unop x -> ppCode x
|
||||
Const x -> ppCode x
|
||||
Constant x -> ppCode x
|
||||
MemRef x -> ppCode x
|
||||
AllocConstr x -> ppCode x
|
||||
AllocClosure x -> ppCode x
|
||||
|
@ -15,7 +15,7 @@ inferType tab funInfo = goInfer mempty
|
||||
goInfer bl = \case
|
||||
Binop x -> goBinop bl x
|
||||
Unop x -> goUnop bl x
|
||||
Const x -> goConst bl x
|
||||
Constant x -> goConst bl x
|
||||
MemRef x -> goMemRef bl x
|
||||
AllocConstr x -> goAllocConstr bl x
|
||||
AllocClosure x -> goAllocClosure bl x
|
||||
|
@ -53,7 +53,7 @@ parseNode ::
|
||||
parseNode =
|
||||
(Binop <$> parseBinop)
|
||||
<|> (Unop <$> parseUnop)
|
||||
<|> (Const <$> parseConst)
|
||||
<|> (Constant <$> parseConst)
|
||||
<|> (AllocConstr <$> parseAlloc)
|
||||
<|> (AllocClosure <$> parseCAlloc)
|
||||
<|> (ExtendClosure <$> parseCExtend)
|
||||
|
Loading…
Reference in New Issue
Block a user