Skip to content

Commit d823003

Browse files
committed
Merge branch 'master' into unify
2 parents a6adb16 + 5c4ca0a commit d823003

25 files changed

+541
-4126
lines changed

Foreign/Matlab.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# OPTIONS_GHC -fno-implicit-prelude #-}
1+
{-# LANGUAGE NoImplicitPrelude #-}
22

33
{-|
44
Bundles Matlab data structure and general-purpose routines.

Foreign/Matlab/Array.hsc

Lines changed: 14 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ScopedTypeVariables, UndecidableInstances #-}
12
{-|
23
Array access, including cell arrays and structures.
34
@@ -19,19 +20,16 @@ module Foreign.Matlab.Array (
1920
mIndexOffset,
2021

2122
-- * Array element access
22-
MXArrayComponent,
23+
MXArrayComponent (mxArrayGetOffset, mxArraySetOffset
24+
, mxArrayGetOffsetList, mxArraySetOffsetList
25+
, mxScalarGet, isMXScalar
26+
, createMXArray, createMXScalar
27+
, createColVector, createRowVector),
2328
castMXArray,
24-
-- |raw array element access
25-
mxArrayGetOffset, mxArraySetOffset,
26-
-- |raw array list access
27-
mxArrayGetOffsetList, mxArraySetOffsetList,
28-
-- |array element access
29+
-- | array element access
2930
mxArrayGet, mxArraySet,
30-
-- |array list access
31+
-- | array list access
3132
mxArrayGetList, mxArraySetList,
32-
mxScalarGet, isMXScalar,
33-
createMXArray, createMXScalar,
34-
createColVector, createRowVector,
3533
mxArrayGetAll, mxArraySetAll,
3634

3735
-- * Struct access
@@ -273,19 +271,18 @@ createNumericArray :: MXClass -> Bool -> MWSize -> Ptr MWSize -> IO MXArrayPtr
273271
createNumericArray t c n s = mxCreateNumericArray n s (hs2mx t) (if c then (#const mxCOMPLEX) else (#const mxREAL))
274272

275273
#let numarray t = "\
276-
foreign import ccall unsafe mxIs%1$s :: MXArrayPtr -> IO CBool\n\
277-
instance MXArrayComponent M%1$s where\n\
278-
isMXArray a = boolC =.< withMXArray a mxIs%1$s\n\
279-
createMXArray s = withNDims s (uncurry $ createNumericArray (mxClassOf (undefined :: M%1$s)) False) >>= mkMXArray\n\
274+
foreign import ccall unsafe mxIs%s :: MXArrayPtr -> IO CBool\n\
275+
instance MXArrayComponent M%s where\n\
276+
isMXArray a = boolC =.< withMXArray a mxIs%s\n\
277+
createMXArray s = withNDims s (uncurry $ createNumericArray (mxClassOf (undefined :: M%s)) False) >>= mkMXArray\n\
280278
\
281279
mxArrayGetOffset = arrayDataGet ;\
282280
mxArraySetOffset = arrayDataSet ;\
283281
mxArrayGetOffsetList = arrayDataGetList ;\
284282
mxArraySetOffsetList = arrayDataSetList\
285283
\n\
286-
instance MXArrayData MX%1$s M%1$s\
287-
", #t
288-
--"
284+
instance MXArrayData MX%s M%s\
285+
", #t, #t, #t, #t, #t, #t
289286
290287
foreign import ccall unsafe mxIsDouble :: MXArrayPtr -> IO CBool
291288
foreign import ccall unsafe mxCreateDoubleScalar :: MXDouble -> IO MXArrayPtr

Foreign/Matlab/Array/Able.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,7 @@
44
In general, scalars convert to the obvious, and lists to row vectors.
55
-}
66
module Foreign.Matlab.Array.Able (
7-
Matlabable,
8-
toMatlab, fromMatlab,
7+
Matlabable (toMatlab, fromMatlab),
98
withMatlabArray, fromMatlabArray
109
) where
1110

Foreign/Matlab/Array/Auto.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@ module Foreign.Matlab.Array.Auto (
1313
import Foreign
1414
import Foreign.Matlab.Util
1515
import Foreign.Matlab.Internal
16-
import Foreign.Matlab.Types
1716

1817
-- |A 'MXArray' that is automatically freed with 'Foreign.Matlab.Array.freeMXArray'
1918
newtype MXAuto a = MXAuto (ForeignPtr MXArrayType)

Foreign/Matlab/Array/IMX.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,8 @@
66
-}
77
module Foreign.Matlab.Array.IMX (
88
IMXData(..),
9-
IMXArrayElem,
9+
IMXArray,
10+
IMXArrayElem (imxConstr, imxArray),
1011

1112
-- * Interface with "Foreign.Matlab.Array"
1213
imxData, iMXData,
@@ -16,7 +17,6 @@ module Foreign.Matlab.Array.IMX (
1617

1718
-- * Construction and access
1819
imxSize,
19-
imxConstr, imxArray,
2020
listIMX, scalarIMX,
2121
imxList, imxScalar,
2222
listIMXStruct,
@@ -27,7 +27,6 @@ import Control.Monad
2727
import Data.Array.IArray
2828
import Data.Complex
2929
import Data.List
30-
import Text.Show
3130
import Foreign.Matlab.Util
3231
import Foreign.Matlab.Internal
3332
import Foreign.Matlab.Types
@@ -191,7 +190,7 @@ iMXData = imxd where
191190
imxd (IMXStruct f a) = do
192191
let ((r0,_),(r1,_)) = bounds a
193192
m <- createStruct (mRangeSize (r0,r1)) f
194-
zipWithM (\i -> mStructSetFields m (mOffset i) <=< mapM iMXData) [0..] (segment (length f) (elems a))
193+
zipWithM_ (\i -> mStructSetFields m (mOffset i) <=< mapM iMXData) [0..] (segment (length f) (elems a))
195194
return $ anyMXArray m
196195
imxd (IMXLogical a) = imxa a return
197196
imxd (IMXChar a) = imxa a return

Foreign/Matlab/Config.hs

Lines changed: 0 additions & 1 deletion
This file was deleted.

Foreign/Matlab/Config.hs.in

Lines changed: 0 additions & 11 deletions
This file was deleted.

Foreign/Matlab/Engine.hsc

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,6 @@ import Foreign.C.Types
2222
import Data.List
2323
import Foreign.Matlab.Util
2424
import Foreign.Matlab.Internal
25-
import Foreign.Matlab.Types
26-
import Foreign.Matlab.Config
2725

2826
#include <engine.h>
2927

@@ -37,9 +35,8 @@ foreign import ccall unsafe engOpen :: CString -> IO EnginePtr
3735
foreign import ccall unsafe "&" engClose :: FunPtr (EnginePtr -> IO ()) -- CInt
3836

3937
-- |Start Matlab server process. It will automatically be closed down when no longer in use.
40-
newEngine :: Maybe FilePath -> IO Engine
41-
newEngine Nothing = newEngine (Just matlabBin)
42-
newEngine (Just bin) = do
38+
newEngine :: FilePath -> IO Engine
39+
newEngine bin = do
4340
eng <- withCString bin engOpen
4441
if eng == nullPtr
4542
then fail "engOpen"

Foreign/Matlab/Internal.hsc

Lines changed: 35 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ module Foreign.Matlab.Internal (
3030
import Foreign
3131
import Foreign.C.Types
3232
import qualified Data.Char
33-
import Data.Typeable
3433
import Foreign.Matlab.Util
3534

3635
#include <matrix.h>
@@ -137,21 +136,20 @@ instance MType MXSingle MSingle where
137136
mx2hs = id
138137
mxClassOf _ = MXClassSingle
139138

140-
#let inttype u, n = "\
141-
type MX%2$s%1$u = %3$s%1$u\n\
142-
type M%2$s%1$u = %3$s%1$u\n\
143-
instance MType MX%2$s%1$u M%2$s%1$u where { hs2mx = id ; mx2hs = id ; mxClassOf _ = MXClass%2$s%1$u }\
144-
", n, u ? "Uint" : "Int", u ? "Word" : "Int"
145-
--"
146-
147-
#inttype 0, 8
148-
#inttype 0, 16
149-
#inttype 0, 32
150-
#inttype 0, 64
151-
#inttype 1, 8
152-
#inttype 1, 16
153-
#inttype 1, 32
154-
#inttype 1, 64
139+
#let inttype u, v, n = "\
140+
type MX%s%u = %s%u\r\n\
141+
type M%s%u = %s%u\r\n\
142+
instance MType MX%s%u M%s%u where { hs2mx = id ; mx2hs = id ; mxClassOf _ = MXClass%s%u }\
143+
", u, n, v, n, u, n, v, n, u, n, u, n, u, n
144+
145+
#inttype "Int", "Int", 8
146+
#inttype "Int", "Int", 16
147+
#inttype "Int", "Int", 32
148+
#inttype "Int", "Int", 64
149+
#inttype "Uint", "Word", 8
150+
#inttype "Uint", "Word", 16
151+
#inttype "Uint", "Word", 32
152+
#inttype "Uint", "Word", 64
155153
156154
data MXArrayType
157155
type MXArrayPtr = Ptr MXArrayType
@@ -178,19 +176,28 @@ data MAny
178176
type MAnyArray = MXArray MAny
179177
180178
-- |Tag for a NULL array
181-
data MNull deriving (Typeable)
182-
instance MType MNull MNull where mxClassOf _ = MXClassNull
179+
data MNull
180+
instance MType MNull MNull where
181+
hs2mx = id
182+
mx2hs = id
183+
mxClassOf _ = MXClassNull
183184
184185
mNullArray :: MXArray MNull
185186
mNullArray = MXArray nullPtr
186187
187188
-- |A wrapper for a member of a cell array, which itself simply any other array
188-
newtype MCell = MCell { mCell :: MAnyArray } deriving (Typeable)
189-
instance MType MCell MCell where mxClassOf _ = MXClassCell
189+
newtype MCell = MCell { mCell :: MAnyArray }
190+
instance MType MCell MCell where
191+
hs2mx = id
192+
mx2hs = id
193+
mxClassOf _ = MXClassCell
190194
191195
-- |A single struct in an array, represented by an (ordered) list of key-value pairs
192-
newtype MStruct = MStruct { mStruct :: [(String,MAnyArray)] } deriving (Typeable)
193-
instance MType MStruct MStruct where mxClassOf _ = MXClassStruct
196+
newtype MStruct = MStruct { mStruct :: [(String,MAnyArray)] }
197+
instance MType MStruct MStruct where
198+
hs2mx = id
199+
mx2hs = id
200+
mxClassOf _ = MXClassStruct
194201
195202
type MXFun = CInt -> Ptr MXArrayPtr -> CInt -> Ptr MXArrayPtr -> IO ()
196203
-- |A Matlab function
@@ -210,6 +217,12 @@ instance MType MXFun MFun where
210217
map MXArray =.< peekArray no outp
211218
mxClassOf _ = MXClassFun
212219
220+
#ifdef mingw32_HOST_OS
221+
type MWSize = Word32
222+
type MWIndex = Word32
223+
type MWSignedIndex = Int32
224+
#else
213225
type MWSize = #type mwSize
214226
type MWIndex = #type mwIndex
215227
type MWSignedIndex = #type mwSignedIndex
228+
#endif

Foreign/Matlab/MAT.hsc

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ import Foreign.C.String
2121
import Foreign.C.Error
2222
import Foreign.Matlab.Util
2323
import Foreign.Matlab.Internal
24-
import Foreign.Matlab.Types
2524

2625
#include <mat.h>
2726

@@ -102,13 +101,14 @@ matLoad file = do
102101
matClose mat
103102
return vars
104103
where
105-
load m =
106-
alloca $ \n -> do
104+
load m = alloca $ \n -> do
107105
a <- matGetNextVariable m n
108-
if a == nullPtr then return [] else do
109-
a <- mkMXArray a
110-
n <- peek n >>= peekCString
111-
((n,a) :) =.< load m
106+
if a == nullPtr
107+
then return []
108+
else do
109+
a <- mkMXArray a
110+
n <- peek n >>= peekCString
111+
((n,a) :) =.< load m
112112

113113
-- |Write all the variables to a new MAT file
114114
matSave :: FilePath -> [(String,MXArray a)] -> IO ()

0 commit comments

Comments
 (0)