Skip to content

Commit dd02eda

Browse files
committed
Some cleanup
1 parent f9022b4 commit dd02eda

File tree

10 files changed

+1914
-1696
lines changed

10 files changed

+1914
-1696
lines changed

Foreign/Matlab/Array.hsc

Lines changed: 1 addition & 0 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

Foreign/Matlab/Config.hs.in

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

Foreign/Matlab/Engine.hsc

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

2726
#include <engine.h>
2827

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

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

Foreign/Matlab/Internal.hsc

Lines changed: 3 additions & 4 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>
@@ -178,18 +177,18 @@ data MAny
178177
type MAnyArray = MXArray MAny
179178

180179
-- |Tag for a NULL array
181-
data MNull deriving (Typeable)
180+
data MNull
182181
instance MType MNull MNull where mxClassOf _ = MXClassNull
183182

184183
mNullArray :: MXArray MNull
185184
mNullArray = MXArray nullPtr
186185

187186
-- |A wrapper for a member of a cell array, which itself simply any other array
188-
newtype MCell = MCell { mCell :: MAnyArray } deriving (Typeable)
187+
newtype MCell = MCell { mCell :: MAnyArray }
189188
instance MType MCell MCell where mxClassOf _ = MXClassCell
190189

191190
-- |A single struct in an array, represented by an (ordered) list of key-value pairs
192-
newtype MStruct = MStruct { mStruct :: [(String,MAnyArray)] } deriving (Typeable)
191+
newtype MStruct = MStruct { mStruct :: [(String,MAnyArray)] }
193192
instance MType MStruct MStruct where mxClassOf _ = MXClassStruct
194193

195194
type MXFun = CInt -> Ptr MXArrayPtr -> CInt -> Ptr MXArrayPtr -> IO ()

Foreign/Matlab/MAT.hsc

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -102,13 +102,14 @@ matLoad file = do
102102
matClose mat
103103
return vars
104104
where
105-
load m =
106-
alloca $ \n -> do
105+
load m = alloca $ \n -> do
107106
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
107+
if a == nullPtr
108+
then return []
109+
else do
110+
a <- mkMXArray a
111+
n <- peek n >>= peekCString
112+
((n,a) :) =.< load m
112113

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

Foreign/Matlab/Runtime.hsc

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,10 @@ import Foreign.C.Types
2222
import System.Posix.DynamicLinker
2323
import Data.List
2424
import qualified Data.Char
25+
import Distribution.Simple.BuildPaths (dllExtension)
2526
import Control.Concurrent.MVar
26-
import System.FilePath
27-
import Foreign.Matlab.Config
27+
import System.FilePath (splitFileName, dropExtensions, extSeparator
28+
, (<.>), (</>))
2829
import Foreign.Matlab.Util
2930
import Foreign.Matlab.Internal
3031

Setup.hs

Lines changed: 21 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,37 +9,49 @@ import Control.Monad
99
import Data.Maybe
1010
import System.Directory
1111
import System.FilePath
12+
1213
defhooks = autoconfUserHooks
13-
programs = [
14-
simpleProgram "matlab",
15-
(simpleProgram "mcr") { programFindLocation =
14+
15+
programs =
16+
[ simpleProgram "matlab"
17+
, (simpleProgram "mcr") { programFindLocation =
1618
\_ -> return (return Nothing) }
1719
]
18-
runtime desc = maybe False (elem ["Foreign","Matlab","Runtime"] . map components . exposedModules) $ library desc
20+
21+
runtime desc = maybe False (elem ["Foreign","Matlab","Runtime"]
22+
. map components . exposedModules) $ library desc
23+
1924
postconf args flags desc build = do
2025
confExists <- doesFileExist "configure"
2126
unless confExists $ rawSystemExit verb "autoconf" []
2227
postConf defhooks args flags{ configConfigureArgs = configConfigureArgs flags ++ confargs } desc build
2328
where
2429
verb = fromFlag $ configVerbosity flags
25-
confargs = ("--" ++ (if runtime desc then "enable" else "disable") ++ "-runtime") : map pconfarg pconf
30+
confargs = ("--" ++ (if runtime desc then "enable" else "disable") ++ "-runtime")
31+
: map pconfarg pconf
2632
pconfarg p = "--with-" ++ programId p ++ "=" ++ programPath p
2733
-- ++ " " ++ unwords (programArgs p)
2834
pconf = mapMaybe (\p -> lookupProgram p (withPrograms build)) programs
35+
2936
build desc binfo hooks flags = do
30-
when (runtime desc) $ rawSystemExit (fromFlag $ buildVerbosity flags) "make" ["-Csrc"]
37+
when (runtime desc) $
38+
rawSystemExit (fromFlag $ buildVerbosity flags) "make" ["-Csrc"]
3139
buildHook defhooks desc binfo hooks flags
40+
3241
clean desc binfo hooks flags = do
3342
makeExists <- doesFileExist "src/Makefile"
34-
when makeExists $ rawSystemExit (fromFlag $ cleanVerbosity flags) "make" ["-Csrc", "clean"]
43+
when makeExists $
44+
rawSystemExit (fromFlag $ cleanVerbosity flags) "make" ["-Csrc", "clean"]
3545
cleanHook defhooks desc binfo hooks flags
46+
3647
install desc binfo hooks flags = do
3748
instHook defhooks desc binfo hooks flags
3849
when (runtime desc) $ mapM_ (\f ->
3950
copyFileVerbose (fromFlag $ installVerbosity flags)
4051
("src" </> f)
4152
(libdir (absoluteInstallDirs desc binfo NoCopyDest) </> f))
4253
["libhsmatlab.so"{-,"libhsmatlab.ctf"-}]
54+
4355
reg desc binfo hooks flags = do
4456
pwd <- getCurrentDirectory
4557
let
@@ -51,6 +63,7 @@ reg desc binfo hooks flags = do
5163
| fromFlag $ regInPlace flags = pwd </> "src"
5264
| otherwise = libdir (absoluteInstallDirs desc binfo NoCopyDest)
5365
regHook defhooks desc' binfo hooks flags
66+
5467
hooks = defhooks {
5568
hookedPrograms = programs,
5669
postConf = postconf,
@@ -59,4 +72,5 @@ hooks = defhooks {
5972
instHook = install,
6073
regHook = reg
6174
}
75+
6276
main = defaultMainWithHooks hooks

0 commit comments

Comments
 (0)