-
Notifications
You must be signed in to change notification settings - Fork 14
/
Copy pathHelper.hs
88 lines (75 loc) · 2.59 KB
/
Helper.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
{-|
Module : SDL.Raw.Helper
Copyright : (c) 2015 Siniša Biđin
License : MIT
Maintainer : sinisa@bidin.eu
Stability : experimental
Exposes a way to automatically generate a foreign import alongside its lifted,
inlined MonadIO variant. Use this to simplify the package's SDL.Raw.* modules.
-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
module SDL.Raw.Helper (liftF) where
import Control.Monad (replicateM)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Language.Haskell.TH
import Language.Haskell.TH.Datatype.TyVarBndr (plainTVSpecified)
-- | Given a name @fname@, a name of a C function @cname@ and the desired
-- Haskell type @ftype@, this function generates:
--
-- * A foreign import of @cname@, named as @fname'@.
-- * An always-inline MonadIO version of @fname'@, named @fname@.
liftF :: String -> String -> Q Type -> Q [Dec]
liftF fname cname ftype = do
let f' = mkName $ fname ++ "'" -- Direct binding.
let f = mkName fname -- Lifted.
t' <- ftype -- Type of direct binding.
-- The generated function accepts n arguments.
args <- replicateM (countArgs t') $ newName "x"
-- If the function has no arguments, then we just liftIO it directly.
-- However, this fails to typecheck without an explicit type signature.
-- Therefore, we include one. TODO: Can we get rid of this?
sigd <- case args of
[] -> ((:[]) . SigD f) `fmap` liftType t'
_ -> return []
return $ concat
[
[ ForeignD $ ImportF CCall Safe cname f' t'
, PragmaD $ InlineP f Inline FunLike AllPhases
]
, sigd
, [ FunD f
[ Clause
(map VarP args)
(NormalB $ 'liftIO `applyTo` [f' `applyTo` map VarE args])
[]
]
]
]
-- | How many arguments does a function of a given type take?
countArgs :: Type -> Int
countArgs = count 0
where
count !n = \case
(AppT (AppT ArrowT _) t) -> count (n+1) t
(ForallT _ _ t) -> count n t
(SigT t _) -> count n t
_ -> n
-- | An expression where f is applied to n arguments.
applyTo :: Name -> [Exp] -> Exp
applyTo f [] = VarE f
applyTo f es = loop (tail es) . AppE (VarE f) $ head es
where
loop as e = foldl AppE e as
-- | Fuzzily speaking, converts a given IO type into a MonadIO m one.
liftType :: Type -> Q Type
liftType = \case
AppT _ t -> do
m <- newName "m"
return $
ForallT
[plainTVSpecified m]
[AppT (ConT ''MonadIO) $ VarT m]
(AppT (VarT m) t)
t -> return t