Skip to content

Commit 8f781d4

Browse files
committed
adding Iso optic for MStruct
1 parent 395c2bd commit 8f781d4

File tree

3 files changed

+34
-5
lines changed

3 files changed

+34
-5
lines changed

Foreign/Matlab/Array/IMX.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -154,8 +154,8 @@ imxData a = do
154154
imxc MXClassStruct False = do
155155
s <- mxArraySize a'
156156
fv <- mxArrayGetAll a'
157-
f <- if null fv then mStructFields a' else return (map fst (DM.toList $ mStruct (head fv)))
158-
listIMXStruct f s =.< mapM imxData (concatMap (map snd . DM.toList . mStruct) fv)
157+
f <- if null fv then mStructFields a' else return (map fst (DM.toList $ _mStruct (head fv)))
158+
listIMXStruct f s =.< mapM imxData (concatMap (map snd . DM.toList . _mStruct) fv)
159159
imxc MXClassLogical False = IMXLogical =.< imxa return
160160
imxc MXClassChar False = IMXChar =.< imxa return
161161
imxc MXClassDouble False = IMXDouble =.< imxa return

Foreign/Matlab/Internal.hsc

Lines changed: 31 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,7 @@
1+
{-# LANGUAGE Trustworthy #-}
2+
{-# LANGUAGE RankNTypes #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
15
module Foreign.Matlab.Internal (
26
CBool, boolC, cBool,
37
MIO,
@@ -22,12 +26,17 @@ module Foreign.Matlab.Internal (
2226
MAny, MAnyArray,
2327
MNull, mNullArray, isMNull,
2428
MCell(..),
25-
MStruct(..),
29+
MStruct(..), mStruct,
2630
MXFun, MFun,
2731
MWSize, MWIndex, MWSignedIndex
2832
) where
2933

34+
import Data.Coerce (Coercible, coerce)
3035
import qualified Data.Map.Strict as DM
36+
import Data.Profunctor
37+
import Data.Profunctor.Unsafe
38+
39+
3140
import Foreign
3241
import Foreign.C.Types
3342
import qualified Data.Char
@@ -37,7 +46,23 @@ import Foreign.Matlab.Util
3746

3847
type MIO a = IO a
3948

40-
-- type CBool = #type bool
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
4166

4267
boolC :: CBool -> Bool
4368
boolC = (0 /=)
@@ -194,12 +219,15 @@ instance MType MCell MCell where
194219
mxClassOf _ = MXClassCell
195220
196221
-- |A single struct in an array, represented by an (ordered) list of key-value pairs
197-
newtype MStruct = MStruct { mStruct :: DM.Map String MAnyArray }
222+
newtype MStruct = MStruct { _mStruct :: DM.Map String MAnyArray }
198223
instance MType MStruct MStruct where
199224
hs2mx = id
200225
mx2hs = id
201226
mxClassOf _ = MXClassStruct
202227
228+
mStruct :: Iso' MStruct (DM.Map String MAnyArray)
229+
mStruct = coerced
230+
203231
type MXFun = CInt -> Ptr MXArrayPtr -> CInt -> Ptr MXArrayPtr -> IO ()
204232
-- |A Matlab function
205233
type MFun =

matlab.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ library
4242
array,
4343
filepath,
4444
path,
45+
profunctors >= 5.3,
4546
Cabal < 3.0
4647
Exposed-modules: Foreign.Matlab,
4748
Foreign.Matlab.Types,

0 commit comments

Comments
 (0)