Skip to content

Commit 1c455b6

Browse files
Add specs for Data.Vector.SEXP.Mutable
1 parent 621d6a1 commit 1c455b6

File tree

6 files changed

+265
-125
lines changed

6 files changed

+265
-125
lines changed

inline-r/inline-r.cabal

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -48,8 +48,8 @@ library
4848
exposed-modules:
4949
Control.Memory.Region
5050
-- Data.Vector.SEXP
51-
-- Data.Vector.SEXP.Base
52-
-- Data.Vector.SEXP.Mutable
51+
Data.Vector.SEXP.Base
52+
Data.Vector.SEXP.Mutable
5353
Foreign.R
5454
Foreign.R.Constraints
5555
Foreign.R.Context
@@ -79,8 +79,8 @@ library
7979
-- Language.R.Event
8080
other-modules:
8181
Control.Monad.R.Class
82-
-- Control.Monad.R.Internal
83-
-- Data.Vector.SEXP.Mutable.Internal
82+
Control.Monad.R.Internal
83+
Data.Vector.SEXP.Mutable.Internal
8484
Internal.Error
8585
build-depends:
8686
base >=4.7 && <5,

inline-r/src/Control/Memory/Region.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,11 @@
66
-- of an object. That is, regions have scopes, and objects within a region are
77
-- guaranteed to remain live within the scope of that region.
88

9+
{-# LANGUAGE FlexibleInstances #-}
10+
{-# LANGUAGE MultiParamTypeClasses #-}
911
{-# LANGUAGE TypeFamilies #-}
1012
{-# LANGUAGE TypeOperators #-}
13+
{-# LANGUAGE UndecidableInstances #-}
1114

1215
module Control.Memory.Region where
1316

@@ -35,3 +38,9 @@ type family a <= b :: Constraint
3538
type instance a <= a = ()
3639
type instance a <= G = ()
3740
type instance V <= b = ()
41+
42+
-- | An alias for (<=).
43+
--
44+
-- XXX: LH complains when using (<=) in type signatures
45+
class SubRegion s' s where
46+
instance s' <= s => SubRegion s' s where

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

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,14 +12,13 @@ import Control.Memory.Region
1212
import Control.Monad.R.Class
1313
import Data.Proxy (Proxy(..))
1414
import Data.Reflection (Reifies, reify)
15-
import Foreign.R (SEXP)
1615
import Foreign.R.Context -- XXX: Needed to help LH name resolution
1716
import Foreign.R.Internal -- XXX: Needed to help LH name resolution
1817

1918
{-@ type AcquireIO s = forall <p :: SEXP s -> Bool > . (SEXP V)<p> -> IO ((SEXP s)<p>) @-}
2019
type AcquireIO s = SEXP V -> IO (SEXP s)
2120

22-
-- XXX: It is not possible to give a specification to withAcquire.
21+
-- XXX: It is not possible to give a specification in LH to withAcquire.
2322
-- Apparently the constraints of the nested function can't be expressed in
2423
-- specs.
2524
withAcquire
@@ -30,3 +29,9 @@ withAcquire
3029
withAcquire f = do
3130
cxt <- getExecContext
3231
reify (\sx -> unsafeRunWithExecContext (acquire sx) cxt) f
32+
33+
getAcquireIO
34+
:: MonadR m => m (AcquireIO (Region m))
35+
getAcquireIO = do
36+
cxt <- getExecContext
37+
return (\sx -> unsafeRunWithExecContext (acquire sx) cxt)

inline-r/src/Data/Vector/SEXP/Base.hs

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
-- Copyright: (C) 2013 Amgen, Inc.
33
--
44

5+
{-# OPTIONS_GHC -fplugin-opt=LiquidHaskell:--skip-module=False #-}
56
{-# LANGUAGE ConstraintKinds #-}
67
{-# LANGUAGE DataKinds #-}
78
{-# LANGUAGE TypeFamilies #-}
@@ -11,7 +12,9 @@ module Data.Vector.SEXP.Base where
1112
import Control.Memory.Region
1213

1314
import Foreign.R.Type
14-
import Foreign.R (SEXP, SomeSEXP)
15+
import Foreign.R.Context -- XXX: needed to help LH name resolution
16+
import Foreign.R.Internal -- XXX: needed to help LH name resolution
17+
import Foreign.R (SEXP)
1518

1619
import Data.Singletons (SingI)
1720

@@ -28,16 +31,16 @@ type family ElemRep s (a :: SEXPTYPE) where
2831
ElemRep s 'Int = Int32
2932
ElemRep s 'Real = Double
3033
ElemRep s 'Complex = Complex Double
31-
ElemRep s 'String = SEXP s 'Char
32-
ElemRep s 'Vector = SomeSEXP s
33-
ElemRep s 'Expr = SomeSEXP s
34+
ElemRep s 'String = SEXP s -- SEXP s 'Char
35+
ElemRep s 'Vector = SEXP s
36+
ElemRep s 'Expr = SEXP s
3437
ElemRep s 'Raw = Word8
3538

3639
-- | 'ElemRep' in the form of a relation, for convenience.
3740
type E s a b = ElemRep s a ~ b
3841

39-
-- | Constraint synonym for all operations on vectors.
40-
type VECTOR s ty a = (Storable a, IsVector ty, SingI ty)
42+
-- Constraint synonym for all operations on vectors.
43+
-- type VECTOR s ty a = (Storable a, IsVector ty, SingI ty)
4144

4245
-- | Constraint synonym for all operations on vectors.
4346
type SVECTOR ty a = (Storable a, IsVector ty, SingI ty, ElemRep V ty ~ a)

0 commit comments

Comments
 (0)