Skip to content

Commit

Permalink
Fix werrors
Browse files Browse the repository at this point in the history
  • Loading branch information
rnjtranjan committed Jun 30, 2023
1 parent 84d6623 commit c181410
Showing 1 changed file with 5 additions and 6 deletions.
11 changes: 5 additions & 6 deletions src/Streamly/Internal/Data/Unbox/TH.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-implicit-lift #-}

module Streamly.Internal.Data.Unbox.TH
( makeUnbox
Expand All @@ -10,8 +11,6 @@ module Streamly.Internal.Data.Unbox.TH
-- Imports
--------------------------------------------------------------------------------

import Data.Maybe (fromMaybe)
import Data.List (find)
import Data.Word (Word16, Word32, Word64, Word8)
import Data.Proxy (Proxy(..))
import TH.Utilities (appsT, plainInstanceD)
Expand Down Expand Up @@ -204,10 +203,10 @@ mkPokeExprFields tagSize fields = do
$(varE (mkFieldName i))|]

mkPokeMatch :: Name -> Int -> Q Exp -> Q Match
mkPokeMatch cname numFields exp =
mkPokeMatch cname numFields exp0 =
match
(conP cname (map varP (map mkFieldName [0 .. (numFields - 1)])))
(normalB exp)
(normalB exp0)
[]

mkPokeExpr :: Type -> [DataCon] -> Q Exp
Expand All @@ -217,14 +216,14 @@ mkPokeExpr headTy cons =
[|error
("Attempting to poke type with no constructors (" ++
$(lift (pprint headTy)) ++ ")")|]
[con@(DataCon cname _ _ fields)] ->
[(DataCon cname _ _ fields)] ->
caseE
(varE _val)
[mkPokeMatch cname (length fields) (mkPokeExprFields 0 fields)]
_ ->
caseE
(varE _val)
(map (\(tagVal, con@(DataCon cname _ _ fields)) ->
(map (\(tagVal, (DataCon cname _ _ fields)) ->
mkPokeMatch
cname
(length fields)
Expand Down

0 comments on commit c181410

Please sign in to comment.