Skip to content

Commit

Permalink
Fixed compilation with GHC 9.2
Browse files Browse the repository at this point in the history
  • Loading branch information
mmhat committed Feb 3, 2022
1 parent 0a345cc commit c85dd23
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 8 deletions.
19 changes: 11 additions & 8 deletions effectful-th/src/Effectful/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,8 @@ makeSendFunctionFor tinfo cinfo = do
let replaceEff = map (pure . replaceTV m effMonad)

-- Create the function's type signature.
let bndrs = effectVarBndrs <> constructorVars cinfo <> [esBndr, rBndr]
let bndrs = map (mapTVFlag (const inferredSpec)) $
effectVarBndrs <> constructorVars cinfo <> [esBndr, rBndr]

let effect = appsT $ conT (datatypeName tinfo) : map varT effectVars
effectConstraint = [t| $(effect) :> $(varT es) |]
Expand All @@ -86,7 +87,7 @@ makeSendFunctionFor tinfo cinfo = do
eff = [t| Eff $(varT es) $(varT r) |]
funSig = arrowsT args eff

sig <- sigD fname $ forallT bndrs ctx funSig
sig <- withDoc $ sigD fname $ forallT bndrs ctx funSig

-- Create the function's definition.
ns <- let
Expand All @@ -101,14 +102,16 @@ makeSendFunctionFor tinfo cinfo = do

defn <- funD fname [clause pats body []]

pure [sig, defn]
where
withDoc :: Q Dec -> Q Dec
#if MIN_VERSION_template_haskell(2,18,0)
let doc :: String
doc = "-- | Send the '"
<> show (constructorName cinfo)
<> "' effect to the effect handler."
pure [withDecDoc doc sig, defn]
withDoc = withDecDoc
$ "-- | Send the '"
<> show (constructorName cinfo)
<> "' effect to the effect handler."
#else
pure [sig, defn]
withDoc = id
#endif

toFunctionName :: Name -> Name
Expand Down
2 changes: 2 additions & 0 deletions effectful-th/tests/Fail.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE TemplateHaskell #-}
module Fail where

import Prelude hiding (fail)

import Effectful.Fail (Fail)
import Effectful.TH

Expand Down

0 comments on commit c85dd23

Please sign in to comment.