aboutsummaryrefslogtreecommitdiff
path: root/src/CHAD/Compile.hs
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2025-11-10 22:31:56 +0100
committerTom Smeding <tom@tomsmeding.com>2025-11-10 22:31:56 +0100
commitcd135319f65f40a554d864b2a878a4ef44043a98 (patch)
treec51a5100b356ff4bf1a41a9b4b269faac3326850 /src/CHAD/Compile.hs
parent57eb321eaeabc53c8c8b83d0554d8a8cca6eed76 (diff)
hlint cleanup
Diffstat (limited to 'src/CHAD/Compile.hs')
-rw-r--r--src/CHAD/Compile.hs72
1 files changed, 36 insertions, 36 deletions
diff --git a/src/CHAD/Compile.hs b/src/CHAD/Compile.hs
index 38bef8c..44a335c 100644
--- a/src/CHAD/Compile.hs
+++ b/src/CHAD/Compile.hs
@@ -451,10 +451,10 @@ compileToString codeID env expr =
else id
,showString $ " const bool success = typed_kernel(" ++
"\n (" ++ repSTy (typeOf expr) ++ "*)(data + " ++ show result_offset ++ ")" ++
- concat (map (\((arg, typ), off) ->
- ",\n *(" ++ typ ++ "*)(data + " ++ show off ++ ")"
- ++ " /* " ++ arg ++ " */")
- (zip arg_pairs arg_offsets)) ++
+ concat (zipWith (\(arg, typ) off ->
+ ",\n *(" ++ typ ++ "*)(data + " ++ show off ++ ")"
+ ++ " /* " ++ arg ++ " */")
+ arg_pairs arg_offsets) ++
"\n );\n"
,showString $ " *(uint8_t*)(data + " ++ show okres_offset ++ ") = success;\n"
,if debugRefc then showString " fprintf(stderr, PRTAG \"Return\\n\");\n"
@@ -621,7 +621,7 @@ peekShape :: Ptr () -> Int -> SNat n -> IO (Shape n)
peekShape ptr off = \case
SZ -> return ShNil
SS n -> ShCons <$> peekShape ptr off n
- <*> (fromIntegral <$> peekByteOff @Int64 ptr (off + (fromSNat n) * 8))
+ <*> (fromIntegral <$> peekByteOff @Int64 ptr (off + fromSNat n * 8))
compile' :: SList (Const String) env -> Ex env t -> CompM CExpr
compile' env = \case
@@ -852,15 +852,15 @@ compile' env = \case
emit $ SLoop (repSTy tIx) ivar (CELit "0") (CELit shszname) $
pure (SVarDecl False (repSTy t) accvar (CELit x0name))
<> x0incrStmts -- we're copying x0 here
- <> (pure $ SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
- -- The combination function will consume the array element
- -- and the accumulator. The accumulator is replaced by
- -- what comes out of the function anyway, so that's
- -- fine, but we do need to increment the array element.
- arreltIncrStmts
- <> pure (SVarDecl True pairstrname pairvar (CEStruct pairstrname [("a", CELit accvar), ("b", CELit arreltlit)]))
- <> funStmts
- <> pure (SAsg accvar funres))
+ <> pure (SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
+ -- The combination function will consume the array element
+ -- and the accumulator. The accumulator is replaced by
+ -- what comes out of the function anyway, so that's
+ -- fine, but we do need to increment the array element.
+ arreltIncrStmts
+ <> pure (SVarDecl True pairstrname pairvar (CEStruct pairstrname [("a", CELit accvar), ("b", CELit arreltlit)]))
+ <> funStmts
+ <> pure (SAsg accvar funres))
<> pure (SAsg (resname ++ ".buf->xs[" ++ ivar ++ "]") (CELit accvar))
incrementVarAlways "foldx0" Decrement t x0name
@@ -1013,17 +1013,17 @@ compile' env = \case
emit $ SLoop (repSTy tIx) ivar (CELit "0") (CELit shsz1name) $
pure (SVarDecl False (repSTy t) accvar (CELit x0name))
<> x0incrStmts -- we're copying x0 here
- <> (pure $ SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
- -- The combination function will consume the array element
- -- and the accumulator. The accumulator is replaced by
- -- what comes out of the function anyway, so that's
- -- fine, but we do need to increment the array element.
- arreltIncrStmts
- <> pure (SVarDecl True pairstrname pairvar (CEStruct pairstrname [("a", CELit accvar), ("b", CELit arreltlit)]))
- <> funStmts
- <> pure (SVarDecl True (repSTy (typeOf efun)) funresvar funres)
- <> pure (SAsg accvar (CEProj (CELit funresvar) "a"))
- <> pure (SAsg (storesname ++ ".buf->xs[" ++ eltidx ++ "]") (CEProj (CELit funresvar) "b")))
+ <> pure (SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
+ -- The combination function will consume the array element
+ -- and the accumulator. The accumulator is replaced by
+ -- what comes out of the function anyway, so that's
+ -- fine, but we do need to increment the array element.
+ arreltIncrStmts
+ <> pure (SVarDecl True pairstrname pairvar (CEStruct pairstrname [("a", CELit accvar), ("b", CELit arreltlit)]))
+ <> funStmts
+ <> pure (SVarDecl True (repSTy (typeOf efun)) funresvar funres)
+ <> pure (SAsg accvar (CEProj (CELit funresvar) "a"))
+ <> pure (SAsg (storesname ++ ".buf->xs[" ++ eltidx ++ "]") (CEProj (CELit funresvar) "b")))
<> pure (SAsg (resname ++ ".buf->xs[" ++ ivar ++ "]") (CELit accvar))
incrementVarAlways "foldd1x0" Decrement t x0name
@@ -1071,16 +1071,16 @@ compile' env = \case
-- we need to loop in reverse here, but we let jvar run in the
-- forward direction so that we can use SLoop. Note jvar is
-- reversed in eltidx above
- <> (pure $ SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
- -- The combination function will consume the accumulator
- -- and the stores element. The accumulator is replaced by
- -- what comes out of the function anyway, so that's
- -- fine, but we do need to increment the stores element.
- storeseltIncrStmts
- <> funStmts
- <> pure (SVarDecl True (repSTy (typeOf efun)) funresvar funres)
- <> pure (SAsg accvar (CEProj (CELit funresvar) "a"))
- <> pure (SAsg (outctgname ++ ".buf->xs[" ++ eltidx ++ "]") (CEProj (CELit funresvar) "b")))
+ <> pure (SLoop (repSTy tIx) jvar (CELit "0") (CELit lenname) $
+ -- The combination function will consume the accumulator
+ -- and the stores element. The accumulator is replaced by
+ -- what comes out of the function anyway, so that's
+ -- fine, but we do need to increment the stores element.
+ storeseltIncrStmts
+ <> funStmts
+ <> pure (SVarDecl True (repSTy (typeOf efun)) funresvar funres)
+ <> pure (SAsg accvar (CEProj (CELit funresvar) "a"))
+ <> pure (SAsg (outctgname ++ ".buf->xs[" ++ eltidx ++ "]") (CEProj (CELit funresvar) "b")))
<> pure (SAsg (x0ctgname ++ ".buf->xs[" ++ ivar ++ "]") (CELit accvar))
incrementVarAlways "foldd2stores" Decrement (STArr (SS n) bty) storesname
@@ -1170,7 +1170,7 @@ compile' env = \case
accname <- genName' "accum"
emit $ SVarDecl False actyname accname
(CEStruct actyname [("buf", CECall "malloc_instr" [CELit (show (sizeofSTy (fromSMTy t)))])])
- emit $ SAsg (accname++".buf->ac") (maybe (CELit name1) id mcopy)
+ emit $ SAsg (accname++".buf->ac") (fromMaybe (CELit name1) mcopy)
emit $ SVerbatim $ "// initial accumulator constructed (" ++ name1 ++ ")."
e2' <- compile' (Const accname `SCons` env) e2