Skip to content

Commit

Permalink
Fix formatting
Browse files Browse the repository at this point in the history
  • Loading branch information
paulcadman committed Apr 6, 2023
1 parent 510939b commit d80bd27
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 24 deletions.
38 changes: 19 additions & 19 deletions src/Juvix/Compiler/Core/Transformation/IntToInt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,6 @@ convertNode tab = rmap go
(BuiltinIntCtorOfNat, BuiltinIntCtorNegSuc) -> makeIf br1 br2
(BuiltinIntCtorNegSuc, BuiltinIntCtorOfNat) -> makeIf br2 br1
_ -> impossible

[] -> recur [] $ fromJust _caseDefault
_ -> impossible
_ -> recur [] node
Expand All @@ -69,20 +68,21 @@ convertNode tab = rmap go
binder = fromJust (headMay (caseBranch ^. caseBranchBinders))
binder' = over binderType (go recur) binder
mkBody n = go (recur . (BCKeep binder :)) n
in
case builtinCtor caseBranch of
in case builtinCtor caseBranch of
BuiltinIntCtorOfNat ->
mkIf _caseInfo
boolSym
(mkBuiltinApp' OpIntLe [mkConstant' (ConstInteger 0), cv])
(mkLet mempty binder' cv (mkBody (caseBranch ^. caseBranchBody)))
(go recur defaultNode)
mkIf
_caseInfo
boolSym
(mkBuiltinApp' OpIntLe [mkConstant' (ConstInteger 0), cv])
(mkLet mempty binder' cv (mkBody (caseBranch ^. caseBranchBody)))
(go recur defaultNode)
BuiltinIntCtorNegSuc ->
mkIf _caseInfo
boolSym
(mkBuiltinApp' OpIntLt [cv, mkConstant' (ConstInteger 0)])
(mkLet mempty binder' (negSucConv cv) (mkBody (caseBranch ^. caseBranchBody)))
(go recur defaultNode)
mkIf
_caseInfo
boolSym
(mkBuiltinApp' OpIntLt [cv, mkConstant' (ConstInteger 0)])
(mkLet mempty binder' (negSucConv cv) (mkBody (caseBranch ^. caseBranchBody)))
(go recur defaultNode)

makeIf :: CaseBranch -> CaseBranch -> Node
makeIf ofNatBranch negSucBranch =
Expand All @@ -92,12 +92,12 @@ convertNode tab = rmap go
binder br = fromJust (headMay (br ^. caseBranchBinders))
binder' br = over binderType (go recur) (binder br)
mkBody br = go (recur . (BCKeep (binder br) :)) (br ^. caseBranchBody)
in
mkIf _caseInfo
boolSym
(mkBuiltinApp' OpIntLe [mkConstant' (ConstInteger 0), cv])
(mkLet mempty (binder' ofNatBranch) cv (mkBody ofNatBranch))
(mkLet mempty (binder' negSucBranch) (negSucConv cv) (mkBody negSucBranch))
in mkIf
_caseInfo
boolSym
(mkBuiltinApp' OpIntLe [mkConstant' (ConstInteger 0), cv])
(mkLet mempty (binder' ofNatBranch) cv (mkBody ofNatBranch))
(mkLet mempty (binder' negSucBranch) (negSucConv cv) (mkBody negSucBranch))

builtinCtor :: CaseBranch -> BuiltinIntCtor
builtinCtor CaseBranch {..} =
Expand Down
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
module Juvix.Compiler.Core.Translation.FromInternal.Builtins.Nat where

import Data.HashMap.Strict qualified as HashMap
import Juvix.Compiler.Core.Language
import Juvix.Compiler.Core.Data
import Juvix.Compiler.Core.Extra
import Juvix.Compiler.Core.Info.NameInfo
import Juvix.Compiler.Core.Language

setupIntToNat :: Symbol -> InfoTable -> InfoTable
setupIntToNat sym tab =
Expand Down
9 changes: 5 additions & 4 deletions src/Juvix/Compiler/Internal/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -107,10 +107,11 @@ instance PrettyCode LetClause where
return (kwMutual <+> braces (line <> indent' b' <> line))

instance PrettyCode Literal where
ppCode = return . \case
LitNatural n -> pretty n
LitInteger n -> pretty n
LitString s -> ppStringLit s
ppCode =
return . \case
LitNatural n -> pretty n
LitInteger n -> pretty n
LitString s -> ppStringLit s

ppPipeBlock :: (PrettyCode a, Members '[Reader Options] r, Traversable t) => t a -> Sem r (Doc Ann)
ppPipeBlock items = vsep <$> mapM (fmap (kwPipe <+>) . ppCode) items
Expand Down

0 comments on commit d80bd27

Please sign in to comment.