Skip to content

Commit 2a878bd

Browse files
Add specs for Language.R.GC
1 parent 0664030 commit 2a878bd

File tree

2 files changed

+11
-13
lines changed

2 files changed

+11
-13
lines changed

inline-r/inline-r.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ library
6363
-- H.Prelude.Interactive
6464
-- Language.R
6565
-- Language.R.Debug
66-
-- Language.R.GC
66+
Language.R.GC
6767
Language.R.Globals
6868
-- Language.R.HExp
6969
-- Language.R.Instance

inline-r/src/Language/R/GC.hs

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -17,18 +17,25 @@
1717
-- discipline, at a performance cost. In particular, collections of many small,
1818
-- short-lived objects are best managed using regions.
1919

20+
{-# LANGUAGE GADTs #-}
21+
{-# OPTIONS_GHC -fplugin-opt=LiquidHaskell:--skip-module=False #-}
2022
module Language.R.GC
2123
( automatic
22-
, automaticSome
2324
) where
2425

26+
import Foreign.C -- only needed to help name resolution in LH
27+
import Control.Monad.Primitive -- only needed to help name resolution in LH
2528
import Control.Memory.Region
2629
import Control.Monad.R.Class
2730
import Control.Exception
28-
import Foreign.R (SomeSEXP(..))
2931
import qualified Foreign.R as R
3032
import System.Mem.Weak (addFinalizer)
3133

34+
-- Helps LH name resolution. Otherwise ~ isn't found.
35+
_f :: a ~ b => a -> b -> CString -> m (PrimState m)
36+
_f = undefined
37+
38+
{-@ automatic :: MonadR m => a:SEXP s -> m (TSEXP G (typeOf a)) @-}
3239
-- | Declare memory management for this value to be automatic. That is, the
3340
-- memory associated with it may be freed as soon as the garbage collector
3441
-- notices that it is safe to do so.
@@ -38,19 +45,10 @@ import System.Mem.Weak (addFinalizer)
3845
-- value can never be observed. Indeed, it is a mere "optimization" to
3946
-- deallocate the value sooner - it would still be semantically correct to never
4047
-- deallocate it at all.
41-
automatic :: MonadR m => R.SEXP s a -> m (R.SEXP G a)
48+
automatic :: MonadR m => R.SEXP s -> m (R.SEXP G)
4249
automatic s = io $ mask_ $ do
4350
R.preserveObject s'
4451
s' `addFinalizer` (R.releaseObject (R.unsafeRelease s'))
4552
return s'
4653
where
4754
s' = R.unsafeRelease s
48-
49-
-- | 'automatic' for 'SomeSEXP'.
50-
automaticSome :: MonadR m => R.SomeSEXP s -> m (R.SomeSEXP G)
51-
automaticSome (SomeSEXP s) = io $ mask_ $ do
52-
R.preserveObject s'
53-
s' `addFinalizer` (R.releaseObject s')
54-
return $ SomeSEXP s'
55-
where
56-
s' = R.unsafeRelease s

0 commit comments

Comments
 (0)