Skip to content

Commit 621d6a1

Browse files
Add specs for Control.Monad.R.Internal
1 parent 2bc4202 commit 621d6a1

File tree

1 file changed

+9
-2
lines changed

1 file changed

+9
-2
lines changed

inline-r/src/Control/Monad/R/Internal.hs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
-- |
22
-- Copyright: (C) 2016 Tweag I/O Limited.
33

4+
{-# OPTIONS_GHC -fplugin-opt=LiquidHaskell:--skip-module=False #-}
45
{-# LANGUAGE FlexibleContexts #-}
56
{-# LANGUAGE RankNTypes #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
@@ -12,14 +13,20 @@ import Control.Monad.R.Class
1213
import Data.Proxy (Proxy(..))
1314
import Data.Reflection (Reifies, reify)
1415
import Foreign.R (SEXP)
16+
import Foreign.R.Context -- XXX: Needed to help LH name resolution
17+
import Foreign.R.Internal -- XXX: Needed to help LH name resolution
1518

16-
newtype AcquireIO s = AcquireIO (forall ty. SEXP V ty -> IO (SEXP s ty))
19+
{-@ type AcquireIO s = forall <p :: SEXP s -> Bool > . (SEXP V)<p> -> IO ((SEXP s)<p>) @-}
20+
type AcquireIO s = SEXP V -> IO (SEXP s)
1721

22+
-- XXX: It is not possible to give a specification to withAcquire.
23+
-- Apparently the constraints of the nested function can't be expressed in
24+
-- specs.
1825
withAcquire
1926
:: forall m r.
2027
(MonadR m)
2128
=> (forall s. Reifies s (AcquireIO (Region m)) => Proxy s -> m r)
2229
-> m r
2330
withAcquire f = do
2431
cxt <- getExecContext
25-
reify (AcquireIO (\sx -> unsafeRunWithExecContext (acquire sx) cxt)) f
32+
reify (\sx -> unsafeRunWithExecContext (acquire sx) cxt) f

0 commit comments

Comments
 (0)