Skip to content

Commit 63853c9

Browse files
committed
added Has-classes and a lens for Engine and refactored optics
1 parent 5d62300 commit 63853c9

File tree

4 files changed

+69
-23
lines changed

4 files changed

+69
-23
lines changed

Foreign/Matlab/Engine.hsc

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Foreign.Matlab.Engine (
1414
EngineEvalArg(..),
1515
engineEvalFun,
1616
engineEvalProc,
17+
HasEngine(..), SetEngine(..),
1718
qt
1819
) where
1920

@@ -23,6 +24,7 @@ import Foreign.C.String
2324
import Foreign.C.Types
2425
import Data.List
2526
import Foreign.Matlab.Array (createMXScalar)
27+
import Foreign.Matlab.Optics
2628
import Foreign.Matlab.Util
2729
import Foreign.Matlab.Internal
2830

@@ -31,6 +33,16 @@ import Foreign.Matlab.Internal
3133
data EngineType
3234
type EnginePtr = Ptr EngineType
3335

36+
37+
class HasEngine env where
38+
getEngine :: env -> Engine
39+
40+
class HasEngine env => SetEngine env where
41+
setEngine :: env -> Engine -> env
42+
43+
engine :: Lens' env Engine
44+
engine = lens getEngine setEngine
45+
3446
-- |A Matlab engine instance
3547
newtype Engine = Engine (ForeignPtr EngineType)
3648
deriving Eq

Foreign/Matlab/Internal.hsc

Lines changed: 1 addition & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE Trustworthy #-}
2-
{-# LANGUAGE RankNTypes #-}
32
{-# LANGUAGE ScopedTypeVariables #-}
43

54
module Foreign.Matlab.Internal (
@@ -31,39 +30,19 @@ module Foreign.Matlab.Internal (
3130
MWSize, MWIndex, MWSignedIndex
3231
) where
3332

34-
import Data.Coerce (Coercible, coerce)
3533
import qualified Data.Map.Strict as DM
36-
import Data.Profunctor
37-
import Data.Profunctor.Unsafe
3834

3935

4036
import Foreign
4137
import Foreign.C.Types
4238
import qualified Data.Char
39+
import Foreign.Matlab.Optics
4340
import Foreign.Matlab.Util
4441

4542
#include <matrix.h>
4643

4744
type MIO a = IO a
4845

49-
50-
-- Lens types copied in --
51-
52-
type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
53-
type Iso' s a = Iso s s a a
54-
55-
coerce' :: forall a b. Coercible a b => b -> a
56-
coerce' = coerce (id :: a -> a)
57-
{-# INLINE coerce' #-}
58-
59-
coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
60-
# if __GLASGOW_HASKELL__ >= 710
61-
coerced l = rmap (fmap coerce') l .# coerce
62-
# else
63-
coerced l = case sym Coercion :: Coercion a s of
64-
Coercion -> rmap (fmap coerce') l .# coerce
65-
# endif
66-
6746
boolC :: CBool -> Bool
6847
boolC = (0 /=)
6948

Foreign/Matlab/Optics.hsc

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
3+
4+
-- | A few Optics definitions used by this project. These definitions are either
5+
-- | copied or copmatible with those from the `lens` package.
6+
module Foreign.Matlab.Optics where
7+
8+
import Data.Coerce (Coercible, coerce)
9+
import Data.Profunctor
10+
import Data.Profunctor.Unsafe ((.#))
11+
12+
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
13+
14+
type Lens' s a = Lens s s a a
15+
16+
17+
-- | Build a 'Lens' from a getter and a setter.
18+
--
19+
-- @
20+
-- 'lens' :: 'Functor' f => (s -> a) -> (s -> b -> t) -> (a -> f b) -> s -> f t
21+
-- @
22+
--
23+
-- >>> s ^. lens getter setter
24+
-- getter s
25+
--
26+
-- >>> s & lens getter setter .~ b
27+
-- setter s b
28+
--
29+
-- >>> s & lens getter setter %~ f
30+
-- setter s (f (getter s))
31+
--
32+
-- @
33+
-- 'lens' :: (s -> a) -> (s -> a -> s) -> 'Lens'' s a
34+
-- @
35+
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
36+
lens sa sbt afb s = sbt s <$> afb (sa s)
37+
{-# INLINE lens #-}
38+
39+
type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
40+
type Iso' s a = Iso s s a a
41+
42+
coerce' :: forall a b. Coercible a b => b -> a
43+
coerce' = coerce (id :: a -> a)
44+
{-# INLINE coerce' #-}
45+
46+
coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
47+
# if __GLASGOW_HASKELL__ >= 710
48+
coerced l = rmap (fmap coerce') l .# coerce
49+
# else
50+
coerced l = case sym Coercion :: Coercion a s of
51+
Coercion -> rmap (fmap coerce') l .# coerce
52+
# endif
53+

matlab.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,9 @@ library
5353
Foreign.Matlab.Array.Able,
5454
Foreign.Matlab.Engine.Wrappers,
5555
Foreign.Matlab.MAT
56-
Other-modules: Foreign.Matlab.Util, Foreign.Matlab.Internal
56+
Other-modules: Foreign.Matlab.Optics
57+
Foreign.Matlab.Util,
58+
Foreign.Matlab.Internal
5759
default-extensions: ForeignFunctionInterface,
5860
MultiParamTypeClasses,
5961
FunctionalDependencies,

0 commit comments

Comments
 (0)