Skip to content

Commit

Permalink
Merge branch 'main' into 3143-repeated-reformatting-of-multi-line-com…
Browse files Browse the repository at this point in the history
…ments-resulting-in-them-moving-to-the-right
  • Loading branch information
lukaszcz authored Dec 6, 2024
2 parents 4546bc5 + 5029a56 commit 31fce41
Show file tree
Hide file tree
Showing 105 changed files with 1,280 additions and 281 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ env:
RISC0_VM_VERSION: v1.0.1
# This is the top commit hash in the branch lukasz/juvix-integration-tracking
# of the anoma repository.
ANOMA_VERSION: 1213cd83b6b0912c98a12e88a40f93ce9b6da094
ANOMA_VERSION: 81601ab7ee8e7ceade7e7cb00bdcc5b65aef77c9
JUST_ARGS: runtimeCcArg=$CC runtimeLibtoolArg=$LIBTOOL
STACK_BUILD_ARGS: --pedantic -j4 --ghc-options=-j

Expand Down
3 changes: 3 additions & 0 deletions app/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,6 +188,9 @@ getEntryPointStdin' RunAppIOArgs {..} = do
| otherwise -> return Nothing
set entryPointStdin estdin <$> entryPointFromGlobalOptionsNoFile root opts

askPackageDotJuvixPath :: (Members '[App] r) => Sem r (Path Abs File)
askPackageDotJuvixPath = mkPackagePath . (^. rootRootDir) <$> askRoot

fromRightGenericError :: (Members '[App] r, ToGenericError err, Typeable err) => Either err a -> Sem r a
fromRightGenericError = fromRightJuvixError . mapLeft JuvixError

Expand Down
2 changes: 1 addition & 1 deletion app/Commands/Dev/Nockma/Format.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ runCommand opts = do
afile <- fromAppPathFile file
parsedTerm <-
runAppError @JuvixError
. Nockma.ignoreHighlightBuilder
. Nockma.evalHighlightBuilder
$ Nockma.parseTermFile afile
putStrLn (ppPrint parsedTerm)
where
Expand Down
2 changes: 1 addition & 1 deletion app/Commands/Dev/Nockma/Ide/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,6 @@ runCommand opts = do
afile <- fromAppPathFile (opts ^. nockmaCheckFile)
void
. runAppError @JuvixError
. ignoreHighlightBuilder
. evalHighlightBuilder
$ Nockma.parseTermFile afile
renderStdOutLn ("Ok" :: Text)
17 changes: 12 additions & 5 deletions app/Commands/Format.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,15 +49,22 @@ targetFromOptions opts = do
-- | Formats the project on the root
formatProject ::
forall r.
(Members '[App, EmbedIO, TaggedLock, Logger, Files, Output FormattedFileInfo] r) =>
(Members '[App, EmbedIO, TaggedLock, Logger, ScopeEff, Files, Output FormattedFileInfo] r) =>
Sem r FormatResult
formatProject = silenceProgressLog . runPipelineOptions . runPipelineSetup $ do
res :: [(ImportNode, PipelineResult ModuleInfo)] <- processProject
res' :: [(ImportNode, SourceCode)] <- forM res $ \(node, nfo) -> do
pkgId :: PackageId <- (^. entryPointPackageId) <$> ask
src <- runReader pkgId (formatModuleInfo node nfo)
pkgId :: PackageId <- (^. entryPointPackageId) <$> ask
res' :: [(ImportNode, SourceCode)] <- runReader pkgId $ forM res $ \(node, nfo) -> do
src <- formatModuleInfo node nfo
return (node, src)
formatProjectSourceCode res'
formatRes <- formatProjectSourceCode res'
formatPkgRes <- formatPackageDotJuvix
return (formatRes <> formatPkgRes)

formatPackageDotJuvix :: forall r. (Members '[App, Files, Logger, Output FormattedFileInfo, ScopeEff] r) => Sem r FormatResult
formatPackageDotJuvix = do
pkgDotJuvix <- askPackageDotJuvixPath
ifM (fileExists' pkgDotJuvix) (format pkgDotJuvix) (return mempty)

runCommand :: forall r. (Members AppEffects r) => FormatOptions -> Sem r ()
runCommand opts = do
Expand Down
2 changes: 1 addition & 1 deletion examples/demo/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -5,5 +5,5 @@ import PackageDescription.V2 open;
package : Package :=
defaultPackage@{
name := "Demo";
version := mkVersion 0 1 0
version := mkVersion 0 1 0;
};
2 changes: 1 addition & 1 deletion examples/midsquare/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -5,5 +5,5 @@ import PackageDescription.V2 open;
package : Package :=
defaultPackage@{
name := "midsquare";
version := mkVersion 0 1 0
version := mkVersion 0 1 0;
};
2 changes: 1 addition & 1 deletion examples/milestone/Bank/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,5 @@ import PackageDescription.V2 open;

package : Package :=
defaultPackage@{
name := "bank"
name := "bank";
};
2 changes: 1 addition & 1 deletion examples/milestone/Collatz/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "Collatz";
version := mkVersion 0 1 0;
main := just "Collatz.juvix"
main := just "Collatz.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/Fibonacci/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "Fibonacci";
version := mkVersion 0 1 0;
main := just "Fibonacci.juvix"
main := just "Fibonacci.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/Hanoi/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "Hanoi";
version := mkVersion 0 1 0;
main := just "Hanoi.juvix"
main := just "Hanoi.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/HelloWorld/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "HelloWorld";
version := mkVersion 0 1 0;
main := just "HelloWorld.juvix"
main := just "HelloWorld.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/PascalsTriangle/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "PascalsTriangle";
version := mkVersion 0 1 0;
main := just "PascalsTriangle.juvix"
main := just "PascalsTriangle.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/TicTacToe/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ package : Package :=
defaultPackage@{
name := "TicTacToe";
version := mkVersion 0 1 0;
main := just "CLI/TicTacToe.juvix"
main := just "CLI/TicTacToe.juvix";
};
2 changes: 1 addition & 1 deletion examples/milestone/Tutorial/Package.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -5,5 +5,5 @@ import PackageDescription.V2 open;
package : Package :=
defaultPackage@{
name := "Tutorial";
version := mkVersion 0 1 0
version := mkVersion 0 1 0;
};
1 change: 1 addition & 0 deletions include/anoma/start.exs
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,5 @@
Logger.configure(level: :none)
eclient = Anoma.Client.Examples.EClient.create_example_client
IO.puts("#{eclient.client.grpc_port} #{eclient.node.node_id}")
Anoma.Node.Utility.Consensus.start_link(node_id: eclient.node.node_id, interval: 10000)
)
2 changes: 1 addition & 1 deletion runtime/nockma/anomalib.nockma

Large diffs are not rendered by default.

30 changes: 19 additions & 11 deletions src/Juvix/Compiler/Casm/Extra/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,35 +14,43 @@ adjustAp idx mr@MemRef {..} = case _memRefReg of
Ap -> MemRef Ap (_memRefOff - idx)
Fp -> mr

mkAssign :: MemRef -> RValue -> Instruction
mkAssign mr rv =
mkAssign' :: Maybe Text -> MemRef -> RValue -> Instruction
mkAssign' comment mr rv =
Assign
InstrAssign
{ _instrAssignResult = mr,
_instrAssignValue = rv,
_instrAssignIncAp = False
_instrAssignIncAp = False,
_instrAssignComment = comment
}

mkAssignAp :: RValue -> Instruction
mkAssignAp v =
mkAssign :: MemRef -> RValue -> Instruction
mkAssign = mkAssign' Nothing

mkAssignAp' :: Maybe Text -> RValue -> Instruction
mkAssignAp' comment v =
Assign
InstrAssign
{ _instrAssignResult = MemRef Ap 0,
_instrAssignValue = v,
_instrAssignIncAp = True
_instrAssignIncAp = True,
_instrAssignComment = comment
}

mkAssignAp :: RValue -> Instruction
mkAssignAp = mkAssignAp' Nothing

mkCallRel :: Value -> Instruction
mkCallRel tgt = Call (InstrCall tgt True)
mkCallRel tgt = Call (InstrCall tgt True Nothing)

mkCallAbs :: Value -> Instruction
mkCallAbs tgt = Call (InstrCall tgt False)
mkCallAbs tgt = Call (InstrCall tgt False Nothing)

mkJumpAbs :: RValue -> Instruction
mkJumpAbs tgt = Jump (InstrJump tgt False False)
mkJumpAbs tgt = Jump (InstrJump tgt False False Nothing)

mkJumpIf :: Value -> MemRef -> Instruction
mkJumpIf tgt v = JumpIf (InstrJumpIf tgt v False)
mkJumpIf tgt v = JumpIf (InstrJumpIf tgt v False Nothing)

mkJumpRel :: RValue -> Instruction
mkJumpRel tgt = Jump (InstrJump tgt True False)
mkJumpRel tgt = Jump (InstrJump tgt True False Nothing)
15 changes: 10 additions & 5 deletions src/Juvix/Compiler/Casm/Language.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,34 +99,39 @@ data Instruction
data InstrAssign = InstrAssign
{ _instrAssignValue :: RValue,
_instrAssignResult :: MemRef,
_instrAssignIncAp :: Bool
_instrAssignIncAp :: Bool,
_instrAssignComment :: Maybe Text
}

data InstrExtraBinop = InstrExtraBinop
{ _instrExtraBinopArg1 :: MemRef,
_instrExtraBinopArg2 :: Value,
_instrExtraBinopResult :: MemRef,
_instrExtraBinopOpcode :: ExtraOpcode,
_instrExtraBinopIncAp :: Bool
_instrExtraBinopIncAp :: Bool,
_instrExtraBinopComment :: Maybe Text
}

data InstrJump = InstrJump
{ _instrJumpTarget :: RValue,
_instrJumpRel :: Bool,
_instrJumpIncAp :: Bool
_instrJumpIncAp :: Bool,
_instrJumpComment :: Maybe Text
}

-- | Jump if value is nonzero. Boolean true is translated to zero, false to
-- non-zero.
data InstrJumpIf = InstrJumpIf
{ _instrJumpIfTarget :: Value,
_instrJumpIfValue :: MemRef,
_instrJumpIfIncAp :: Bool
_instrJumpIfIncAp :: Bool,
_instrJumpIfComment :: Maybe Text
}

data InstrCall = InstrCall
{ _instrCallTarget :: Value,
_instrCallRel :: Bool
_instrCallRel :: Bool,
_instrCallComment :: Maybe Text
}

newtype InstrAlloc = InstrAlloc
Expand Down
20 changes: 15 additions & 5 deletions src/Juvix/Compiler/Casm/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,11 @@ ppIncAp = \case
True -> return $ Str.semicolon <+> Str.apPlusPlus
False -> mempty

ppComment :: Maybe Text -> Sem r (Doc Ann)
ppComment = \case
Just c -> return $ Str.commentLineStart <+> pretty c <> hardline
Nothing -> return mempty

instance PrettyCode Reg where
ppCode = \case
Ap -> return Str.ap
Expand Down Expand Up @@ -121,19 +126,21 @@ instance PrettyCode Hint where

instance PrettyCode InstrAssign where
ppCode InstrAssign {..} = do
comment <- ppComment _instrAssignComment
v <- ppCode _instrAssignValue
r <- ppCode _instrAssignResult
incAp <- ppIncAp _instrAssignIncAp
return $ r <+> Str.equal <+> v <> incAp
return $ comment <> r <+> Str.equal <+> v <> incAp

instance PrettyCode InstrExtraBinop where
ppCode InstrExtraBinop {..} = do
comment <- ppComment _instrExtraBinopComment
v1 <- ppCode _instrExtraBinopArg1
v2 <- ppCode _instrExtraBinopArg2
op <- ppCode _instrExtraBinopOpcode
r <- ppCode _instrExtraBinopResult
incAp <- ppIncAp _instrExtraBinopIncAp
return $ r <+> Str.equal <+> v1 <+> op <+> v2 <> incAp
return $ comment <> r <+> Str.equal <+> v1 <+> op <+> v2 <> incAp

ppRel :: Bool -> RValue -> Sem r (Doc Ann)
ppRel isRel tgt
Expand All @@ -148,23 +155,26 @@ ppRel isRel tgt

instance PrettyCode InstrJump where
ppCode InstrJump {..} = do
comment <- ppComment _instrJumpComment
tgt <- ppCode _instrJumpTarget
incAp <- ppIncAp _instrJumpIncAp
rel <- ppRel _instrJumpRel _instrJumpTarget
return $ Str.jmp <+> rel <> tgt <> incAp
return $ comment <> Str.jmp <+> rel <> tgt <> incAp

instance PrettyCode InstrJumpIf where
ppCode InstrJumpIf {..} = do
comment <- ppComment _instrJumpIfComment
tgt <- ppCode _instrJumpIfTarget
v <- ppCode _instrJumpIfValue
incAp <- ppIncAp _instrJumpIfIncAp
return $ Str.jmp <+> tgt <+> Str.if_ <+> v <+> Str.notequal <+> annotate AnnLiteralInteger "0" <> incAp
return $ comment <> Str.jmp <+> tgt <+> Str.if_ <+> v <+> Str.notequal <+> annotate AnnLiteralInteger "0" <> incAp

instance PrettyCode InstrCall where
ppCode InstrCall {..} = do
comment <- ppComment _instrCallComment
tgt <- ppCode _instrCallTarget
rel <- ppRel _instrCallRel (Val _instrCallTarget)
return $ Str.call <+> rel <> tgt
return $ comment <> Str.call <+> rel <> tgt

instance PrettyCode InstrAlloc where
ppCode InstrAlloc {..} = do
Expand Down
3 changes: 2 additions & 1 deletion src/Juvix/Compiler/Casm/Transformation/Optimize/Peephole.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@ peephole = mapT go
let call =
InstrCall
{ _instrCallTarget = tgt,
_instrCallRel = _instrJumpRel
_instrCallRel = _instrJumpRel,
_instrCallComment
}
in Call call : Return : is
is -> is
Expand Down
12 changes: 8 additions & 4 deletions src/Juvix/Compiler/Casm/Translation/FromCairo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,8 @@ fromCairo elems0 =
Call
InstrCall
{ _instrCallRel = _instrPcUpdate == Cairo.PcUpdateJumpRel,
_instrCallTarget = val
_instrCallTarget = val,
_instrCallComment = Nothing
}
(rval, delta) = decodeRes i elems
val = case rval of
Expand Down Expand Up @@ -110,7 +111,8 @@ fromCairo elems0 =
InstrAssign
{ _instrAssignResult = dst,
_instrAssignValue = rval,
_instrAssignIncAp = _instrApUpdate == Cairo.ApUpdateInc
_instrAssignIncAp = _instrApUpdate == Cairo.ApUpdateInc,
_instrAssignComment = Nothing
}

goNop :: Cairo.Instruction -> [Cairo.Element] -> (Instruction, Int)
Expand All @@ -136,7 +138,8 @@ fromCairo elems0 =
InstrJump
{ _instrJumpTarget = res,
_instrJumpRel = isRel,
_instrJumpIncAp = _instrApUpdate == Cairo.ApUpdateInc
_instrJumpIncAp = _instrApUpdate == Cairo.ApUpdateInc,
_instrJumpComment = Nothing
}

goJumpIf :: Cairo.Instruction -> [Cairo.Element] -> (Instruction, Int)
Expand All @@ -159,7 +162,8 @@ fromCairo elems0 =
InstrJumpIf
{ _instrJumpIfTarget = tgt,
_instrJumpIfValue = dst,
_instrJumpIfIncAp = _instrApUpdate == Cairo.ApUpdateInc
_instrJumpIfIncAp = _instrApUpdate == Cairo.ApUpdateInc,
_instrJumpIfComment = Nothing
}

goAlloc :: Cairo.Instruction -> [Cairo.Element] -> (Instruction, Int)
Expand Down
Loading

0 comments on commit 31fce41

Please sign in to comment.