summaryrefslogtreecommitdiff
path: root/packages/base
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-06-06 18:42:42 +0200
committerAlberto Ruiz <aruiz@um.es>2015-06-06 18:42:42 +0200
commitc680fbb7a743b2fc519987a4d5f24bb9b675655f (patch)
treedfe7ad57aa6fe8c0a8427884db1b7a0ca85f73ba /packages/base
parent66db67b299bd91f3cf35f93500e05eaf6c8085d3 (diff)
support for Int64 elements
Diffstat (limited to 'packages/base')
-rw-r--r--packages/base/src/Internal/C/vector-aux.c2
-rw-r--r--packages/base/src/Internal/Container.hs1
-rw-r--r--packages/base/src/Internal/Conversion.hs5
-rw-r--r--packages/base/src/Internal/LAPACK.hs9
-rw-r--r--packages/base/src/Internal/Matrix.hs22
-rw-r--r--packages/base/src/Internal/Numeric.hs49
-rw-r--r--packages/base/src/Internal/Vectorized.hs44
-rw-r--r--packages/base/src/Numeric/Vector.hs8
8 files changed, 137 insertions, 3 deletions
diff --git a/packages/base/src/Internal/C/vector-aux.c b/packages/base/src/Internal/C/vector-aux.c
index 0921c18..70e46bc 100644
--- a/packages/base/src/Internal/C/vector-aux.c
+++ b/packages/base/src/Internal/C/vector-aux.c
@@ -1365,7 +1365,7 @@ int int2double(KIVEC(x),DVEC(y)) CONVERT_IMP
1365 1365
1366int int2long(KIVEC(x),LVEC(y)) CONVERT_IMP 1366int int2long(KIVEC(x),LVEC(y)) CONVERT_IMP
1367 1367
1368int lont2int(KLVEC(x),IVEC(y)) CONVERT_IMP 1368int long2int(KLVEC(x),IVEC(y)) CONVERT_IMP
1369 1369
1370int long2double(KLVEC(x),DVEC(y)) CONVERT_IMP 1370int long2double(KLVEC(x),DVEC(y)) CONVERT_IMP
1371 1371
diff --git a/packages/base/src/Internal/Container.hs b/packages/base/src/Internal/Container.hs
index f6355b2..7fe5758 100644
--- a/packages/base/src/Internal/Container.hs
+++ b/packages/base/src/Internal/Container.hs
@@ -257,6 +257,7 @@ instance Numeric (Complex Double)
257instance Numeric Float 257instance Numeric Float
258instance Numeric (Complex Float) 258instance Numeric (Complex Float)
259instance Numeric I 259instance Numeric I
260instance Numeric Z
260 261
261-------------------------------------------------------------------------------- 262--------------------------------------------------------------------------------
262 263
diff --git a/packages/base/src/Internal/Conversion.hs b/packages/base/src/Internal/Conversion.hs
index 2f4a9c7..4541ec4 100644
--- a/packages/base/src/Internal/Conversion.hs
+++ b/packages/base/src/Internal/Conversion.hs
@@ -44,6 +44,11 @@ instance Precision (Complex Float) (Complex Double) where
44 double2FloatG = asComplex . double2FloatV . asReal 44 double2FloatG = asComplex . double2FloatV . asReal
45 float2DoubleG = asComplex . float2DoubleV . asReal 45 float2DoubleG = asComplex . float2DoubleV . asReal
46 46
47instance Precision I Z where
48 double2FloatG = long2intV
49 float2DoubleG = int2longV
50
51
47-- | Supported real types 52-- | Supported real types
48class (Element t, Element (Complex t), RealFloat t) 53class (Element t, Element (Complex t), RealFloat t)
49 => RealElement t 54 => RealElement t
diff --git a/packages/base/src/Internal/LAPACK.hs b/packages/base/src/Internal/LAPACK.hs
index d6a2e6e..469b0d5 100644
--- a/packages/base/src/Internal/LAPACK.hs
+++ b/packages/base/src/Internal/LAPACK.hs
@@ -37,6 +37,7 @@ foreign import ccall unsafe "multiplyC" zgemmc :: CInt -> CInt -> TMMM C
37foreign import ccall unsafe "multiplyF" sgemmc :: CInt -> CInt -> TMMM F 37foreign import ccall unsafe "multiplyF" sgemmc :: CInt -> CInt -> TMMM F
38foreign import ccall unsafe "multiplyQ" cgemmc :: CInt -> CInt -> TMMM Q 38foreign import ccall unsafe "multiplyQ" cgemmc :: CInt -> CInt -> TMMM Q
39foreign import ccall unsafe "multiplyI" c_multiplyI :: CInt ::> CInt ::> CInt ::> Ok 39foreign import ccall unsafe "multiplyI" c_multiplyI :: CInt ::> CInt ::> CInt ::> Ok
40foreign import ccall unsafe "multiplyL" c_multiplyL :: Z ::> Z ::> Z ::> Ok
40 41
41isT Matrix{order = ColumnMajor} = 0 42isT Matrix{order = ColumnMajor} = 0
42isT Matrix{order = RowMajor} = 1 43isT Matrix{order = RowMajor} = 1
@@ -75,6 +76,14 @@ multiplyI a b = unsafePerformIO $ do
75 app3 c_multiplyI omat a omat b omat s "c_multiplyI" 76 app3 c_multiplyI omat a omat b omat s "c_multiplyI"
76 return s 77 return s
77 78
79multiplyL :: Matrix Z -> Matrix Z -> Matrix Z
80multiplyL a b = unsafePerformIO $ do
81 when (cols a /= rows b) $ error $
82 "inconsistent dimensions in matrix product "++ shSize a ++ " x " ++ shSize b
83 s <- createMatrix ColumnMajor (rows a) (cols b)
84 app3 c_multiplyL omat a omat b omat s "c_multiplyL"
85 return s
86
78----------------------------------------------------------------------------- 87-----------------------------------------------------------------------------
79 88
80type TSVD t = t ..> t ..> R :> t ..> Ok 89type TSVD t = t ..> t ..> R :> t ..> Ok
diff --git a/packages/base/src/Internal/Matrix.hs b/packages/base/src/Internal/Matrix.hs
index d715cbf..8de06ce 100644
--- a/packages/base/src/Internal/Matrix.hs
+++ b/packages/base/src/Internal/Matrix.hs
@@ -333,6 +333,16 @@ instance Element (CInt) where
333 selectV = selectI 333 selectV = selectI
334 remapM = remapI 334 remapM = remapI
335 335
336instance Element Z where
337 transdata = transdataAux ctransL
338 constantD = constantAux cconstantL
339 extractR = extractAux c_extractL
340 sortI = sortIdxL
341 sortV = sortValL
342 compareV = compareL
343 selectV = selectL
344 remapM = remapL
345
336------------------------------------------------------------------- 346-------------------------------------------------------------------
337 347
338transdataAux fun c1 d c2 = 348transdataAux fun c1 d c2 =
@@ -357,6 +367,7 @@ foreign import ccall unsafe "transR" ctransR :: TMM Double
357foreign import ccall unsafe "transQ" ctransQ :: TMM (Complex Float) 367foreign import ccall unsafe "transQ" ctransQ :: TMM (Complex Float)
358foreign import ccall unsafe "transC" ctransC :: TMM (Complex Double) 368foreign import ccall unsafe "transC" ctransC :: TMM (Complex Double)
359foreign import ccall unsafe "transI" ctransI :: TMM CInt 369foreign import ccall unsafe "transI" ctransI :: TMM CInt
370foreign import ccall unsafe "transL" ctransL :: TMM Z
360 371
361---------------------------------------------------------------------- 372----------------------------------------------------------------------
362 373
@@ -433,6 +444,7 @@ foreign import ccall unsafe "extractF" c_extractF :: Extr Float
433foreign import ccall unsafe "extractC" c_extractC :: Extr (Complex Double) 444foreign import ccall unsafe "extractC" c_extractC :: Extr (Complex Double)
434foreign import ccall unsafe "extractQ" c_extractQ :: Extr (Complex Float) 445foreign import ccall unsafe "extractQ" c_extractQ :: Extr (Complex Float)
435foreign import ccall unsafe "extractI" c_extractI :: Extr CInt 446foreign import ccall unsafe "extractI" c_extractI :: Extr CInt
447foreign import ccall unsafe "extractL" c_extractL :: Extr Z
436 448
437-------------------------------------------------------------------------------- 449--------------------------------------------------------------------------------
438 450
@@ -444,18 +456,22 @@ sortG f v = unsafePerformIO $ do
444sortIdxD = sortG c_sort_indexD 456sortIdxD = sortG c_sort_indexD
445sortIdxF = sortG c_sort_indexF 457sortIdxF = sortG c_sort_indexF
446sortIdxI = sortG c_sort_indexI 458sortIdxI = sortG c_sort_indexI
459sortIdxL = sortG c_sort_indexL
447 460
448sortValD = sortG c_sort_valD 461sortValD = sortG c_sort_valD
449sortValF = sortG c_sort_valF 462sortValF = sortG c_sort_valF
450sortValI = sortG c_sort_valI 463sortValI = sortG c_sort_valI
464sortValL = sortG c_sort_valL
451 465
452foreign import ccall unsafe "sort_indexD" c_sort_indexD :: CV Double (CV CInt (IO CInt)) 466foreign import ccall unsafe "sort_indexD" c_sort_indexD :: CV Double (CV CInt (IO CInt))
453foreign import ccall unsafe "sort_indexF" c_sort_indexF :: CV Float (CV CInt (IO CInt)) 467foreign import ccall unsafe "sort_indexF" c_sort_indexF :: CV Float (CV CInt (IO CInt))
454foreign import ccall unsafe "sort_indexI" c_sort_indexI :: CV CInt (CV CInt (IO CInt)) 468foreign import ccall unsafe "sort_indexI" c_sort_indexI :: CV CInt (CV CInt (IO CInt))
469foreign import ccall unsafe "sort_indexL" c_sort_indexL :: Z :> I :> Ok
455 470
456foreign import ccall unsafe "sort_valuesD" c_sort_valD :: CV Double (CV Double (IO CInt)) 471foreign import ccall unsafe "sort_valuesD" c_sort_valD :: CV Double (CV Double (IO CInt))
457foreign import ccall unsafe "sort_valuesF" c_sort_valF :: CV Float (CV Float (IO CInt)) 472foreign import ccall unsafe "sort_valuesF" c_sort_valF :: CV Float (CV Float (IO CInt))
458foreign import ccall unsafe "sort_valuesI" c_sort_valI :: CV CInt (CV CInt (IO CInt)) 473foreign import ccall unsafe "sort_valuesI" c_sort_valI :: CV CInt (CV CInt (IO CInt))
474foreign import ccall unsafe "sort_valuesL" c_sort_valL :: Z :> Z :> Ok
459 475
460-------------------------------------------------------------------------------- 476--------------------------------------------------------------------------------
461 477
@@ -467,10 +483,12 @@ compareG f u v = unsafePerformIO $ do
467compareD = compareG c_compareD 483compareD = compareG c_compareD
468compareF = compareG c_compareF 484compareF = compareG c_compareF
469compareI = compareG c_compareI 485compareI = compareG c_compareI
486compareL = compareG c_compareL
470 487
471foreign import ccall unsafe "compareD" c_compareD :: CV Double (CV Double (CV CInt (IO CInt))) 488foreign import ccall unsafe "compareD" c_compareD :: CV Double (CV Double (CV CInt (IO CInt)))
472foreign import ccall unsafe "compareF" c_compareF :: CV Float (CV Float (CV CInt (IO CInt))) 489foreign import ccall unsafe "compareF" c_compareF :: CV Float (CV Float (CV CInt (IO CInt)))
473foreign import ccall unsafe "compareI" c_compareI :: CV CInt (CV CInt (CV CInt (IO CInt))) 490foreign import ccall unsafe "compareI" c_compareI :: CV CInt (CV CInt (CV CInt (IO CInt)))
491foreign import ccall unsafe "compareL" c_compareL :: Z :> Z :> I :> Ok
474 492
475-------------------------------------------------------------------------------- 493--------------------------------------------------------------------------------
476 494
@@ -482,6 +500,7 @@ selectG f c u v w = unsafePerformIO $ do
482selectD = selectG c_selectD 500selectD = selectG c_selectD
483selectF = selectG c_selectF 501selectF = selectG c_selectF
484selectI = selectG c_selectI 502selectI = selectG c_selectI
503selectL = selectG c_selectL
485selectC = selectG c_selectC 504selectC = selectG c_selectC
486selectQ = selectG c_selectQ 505selectQ = selectG c_selectQ
487 506
@@ -492,6 +511,7 @@ foreign import ccall unsafe "chooseF" c_selectF :: Sel Float
492foreign import ccall unsafe "chooseI" c_selectI :: Sel CInt 511foreign import ccall unsafe "chooseI" c_selectI :: Sel CInt
493foreign import ccall unsafe "chooseC" c_selectC :: Sel (Complex Double) 512foreign import ccall unsafe "chooseC" c_selectC :: Sel (Complex Double)
494foreign import ccall unsafe "chooseQ" c_selectQ :: Sel (Complex Float) 513foreign import ccall unsafe "chooseQ" c_selectQ :: Sel (Complex Float)
514foreign import ccall unsafe "chooseL" c_selectL :: Sel Z
495 515
496--------------------------------------------------------------------------- 516---------------------------------------------------------------------------
497 517
@@ -503,6 +523,7 @@ remapG f i j m = unsafePerformIO $ do
503remapD = remapG c_remapD 523remapD = remapG c_remapD
504remapF = remapG c_remapF 524remapF = remapG c_remapF
505remapI = remapG c_remapI 525remapI = remapG c_remapI
526remapL = remapG c_remapL
506remapC = remapG c_remapC 527remapC = remapG c_remapC
507remapQ = remapG c_remapQ 528remapQ = remapG c_remapQ
508 529
@@ -513,6 +534,7 @@ foreign import ccall unsafe "remapF" c_remapF :: Rem Float
513foreign import ccall unsafe "remapI" c_remapI :: Rem CInt 534foreign import ccall unsafe "remapI" c_remapI :: Rem CInt
514foreign import ccall unsafe "remapC" c_remapC :: Rem (Complex Double) 535foreign import ccall unsafe "remapC" c_remapC :: Rem (Complex Double)
515foreign import ccall unsafe "remapQ" c_remapQ :: Rem (Complex Float) 536foreign import ccall unsafe "remapQ" c_remapQ :: Rem (Complex Float)
537foreign import ccall unsafe "remapL" c_remapL :: Rem Z
516 538
517-------------------------------------------------------------------------------- 539--------------------------------------------------------------------------------
518 540
diff --git a/packages/base/src/Internal/Numeric.hs b/packages/base/src/Internal/Numeric.hs
index 879daf8..85594cc 100644
--- a/packages/base/src/Internal/Numeric.hs
+++ b/packages/base/src/Internal/Numeric.hs
@@ -24,7 +24,7 @@ import Internal.Element
24import Internal.ST as ST 24import Internal.ST as ST
25import Internal.Conversion 25import Internal.Conversion
26import Internal.Vectorized 26import Internal.Vectorized
27import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI) 27import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI,multiplyL)
28import Data.List.Split(chunksOf) 28import Data.List.Split(chunksOf)
29 29
30-------------------------------------------------------------------------------- 30--------------------------------------------------------------------------------
@@ -129,6 +129,45 @@ instance Container Vector I
129 fromInt' = id 129 fromInt' = id
130 toInt' = id 130 toInt' = id
131 131
132
133instance Container Vector Z
134 where
135 conj' = id
136 size' = dim
137 scale' = vectorMapValL Scale
138 addConstant = vectorMapValL AddConstant
139 add = vectorZipL Add
140 sub = vectorZipL Sub
141 mul = vectorZipL Mul
142 equal u v = dim u == dim v && maxElement' (vectorMapL Abs (sub u v)) == 0
143 scalar' x = fromList [x]
144 konst' = constantD
145 build' = buildV
146 cmap' = mapVector
147 atIndex' = (@>)
148 minIndex' = emptyErrorV "minIndex" (fromIntegral . toScalarL MinIdx)
149 maxIndex' = emptyErrorV "maxIndex" (fromIntegral . toScalarL MaxIdx)
150 minElement' = emptyErrorV "minElement" (toScalarL Min)
151 maxElement' = emptyErrorV "maxElement" (toScalarL Max)
152 sumElements' = sumL
153 prodElements' = prodL
154 step' = stepL
155 find' = findV
156 assoc' = assocV
157 accum' = accumV
158 ccompare' = compareCV compareV
159 cselect' = selectCV selectV
160 scaleRecip = undefined -- cannot match
161 divide = undefined
162 arctan2' = undefined
163 cmod' m x
164 | m /= 0 = vectorMapValL ModVS m x
165 | otherwise = error $ "cmod 0 on vector of size "++(show $ dim x)
166 fromInt' = int2longV
167 toInt' = long2intV
168
169
170
132instance Container Vector Float 171instance Container Vector Float
133 where 172 where
134 conj' = id 173 conj' = id
@@ -540,6 +579,13 @@ instance Product I where
540 normInf = emptyVal (maxElement . vectorMapI Abs) 579 normInf = emptyVal (maxElement . vectorMapI Abs)
541 multiply = emptyMul multiplyI 580 multiply = emptyMul multiplyI
542 581
582instance Product Z where
583 norm2 = undefined
584 absSum = emptyVal (sumElements . vectorMapL Abs)
585 norm1 = absSum
586 normInf = emptyVal (maxElement . vectorMapL Abs)
587 multiply = emptyMul multiplyL
588
543 589
544emptyMul m a b 590emptyMul m a b
545 | x1 == 0 && x2 == 0 || r == 0 || c == 0 = konst' 0 (r,c) 591 | x1 == 0 && x2 == 0 || r == 0 || c == 0 = konst' 0 (r,c)
@@ -676,6 +722,7 @@ type instance RealOf Float = Float
676type instance RealOf (Complex Float) = Float 722type instance RealOf (Complex Float) = Float
677 723
678type instance RealOf I = I 724type instance RealOf I = I
725type instance RealOf Z = Z
679 726
680type family ComplexOf x 727type family ComplexOf x
681 728
diff --git a/packages/base/src/Internal/Vectorized.hs b/packages/base/src/Internal/Vectorized.hs
index b9b8239..b1ad424 100644
--- a/packages/base/src/Internal/Vectorized.hs
+++ b/packages/base/src/Internal/Vectorized.hs
@@ -98,6 +98,8 @@ sumC = sumg c_sumC
98sumI :: Vector CInt -> CInt 98sumI :: Vector CInt -> CInt
99sumI = sumg c_sumI 99sumI = sumg c_sumI
100 100
101sumL = sumg c_sumL
102
101sumg f x = unsafePerformIO $ do 103sumg f x = unsafePerformIO $ do
102 r <- createVector 1 104 r <- createVector 1
103 app2 f vec x vec r "sum" 105 app2 f vec x vec r "sum"
@@ -110,6 +112,7 @@ foreign import ccall unsafe "sumR" c_sumR :: TVV Double
110foreign import ccall unsafe "sumQ" c_sumQ :: TVV (Complex Float) 112foreign import ccall unsafe "sumQ" c_sumQ :: TVV (Complex Float)
111foreign import ccall unsafe "sumC" c_sumC :: TVV (Complex Double) 113foreign import ccall unsafe "sumC" c_sumC :: TVV (Complex Double)
112foreign import ccall unsafe "sumI" c_sumI :: TVV CInt 114foreign import ccall unsafe "sumI" c_sumI :: TVV CInt
115foreign import ccall unsafe "sumL" c_sumL :: TVV Z
113 116
114-- | product of elements 117-- | product of elements
115prodF :: Vector Float -> Float 118prodF :: Vector Float -> Float
@@ -131,6 +134,7 @@ prodC = prodg c_prodC
131prodI :: Vector CInt -> CInt 134prodI :: Vector CInt -> CInt
132prodI = prodg c_prodI 135prodI = prodg c_prodI
133 136
137prodL = prodg c_prodL
134 138
135prodg f x = unsafePerformIO $ do 139prodg f x = unsafePerformIO $ do
136 r <- createVector 1 140 r <- createVector 1
@@ -143,6 +147,7 @@ foreign import ccall unsafe "prodR" c_prodR :: TVV Double
143foreign import ccall unsafe "prodQ" c_prodQ :: TVV (Complex Float) 147foreign import ccall unsafe "prodQ" c_prodQ :: TVV (Complex Float)
144foreign import ccall unsafe "prodC" c_prodC :: TVV (Complex Double) 148foreign import ccall unsafe "prodC" c_prodC :: TVV (Complex Double)
145foreign import ccall unsafe "prodI" c_prodI :: TVV (CInt) 149foreign import ccall unsafe "prodI" c_prodI :: TVV (CInt)
150foreign import ccall unsafe "prodL" c_prodL :: TVV Z
146 151
147------------------------------------------------------------------ 152------------------------------------------------------------------
148 153
@@ -200,6 +205,13 @@ toScalarI oper = toScalarAux c_toScalarI (fromei oper)
200 205
201foreign import ccall unsafe "toScalarI" c_toScalarI :: CInt -> TVV CInt 206foreign import ccall unsafe "toScalarI" c_toScalarI :: CInt -> TVV CInt
202 207
208-- | obtains different functions of a vector: norm1, norm2, max, min, posmax, posmin, etc.
209toScalarL :: FunCodeS -> Vector Z -> Z
210toScalarL oper = toScalarAux c_toScalarL (fromei oper)
211
212foreign import ccall unsafe "toScalarL" c_toScalarL :: CInt -> TVV Z
213
214
203------------------------------------------------------------------ 215------------------------------------------------------------------
204 216
205-- | map of real vectors with given function 217-- | map of real vectors with given function
@@ -232,6 +244,12 @@ vectorMapI = vectorMapAux c_vectorMapI
232 244
233foreign import ccall unsafe "mapI" c_vectorMapI :: CInt -> TVV CInt 245foreign import ccall unsafe "mapI" c_vectorMapI :: CInt -> TVV CInt
234 246
247-- | map of real vectors with given function
248vectorMapL :: FunCodeV -> Vector Z -> Vector Z
249vectorMapL = vectorMapAux c_vectorMapL
250
251foreign import ccall unsafe "mapL" c_vectorMapL :: CInt -> TVV Z
252
235------------------------------------------------------------------- 253-------------------------------------------------------------------
236 254
237-- | map of real vectors with given function 255-- | map of real vectors with given function
@@ -264,6 +282,12 @@ vectorMapValI oper = vectorMapValAux c_vectorMapValI (fromei oper)
264 282
265foreign import ccall unsafe "mapValI" c_vectorMapValI :: CInt -> Ptr CInt -> TVV CInt 283foreign import ccall unsafe "mapValI" c_vectorMapValI :: CInt -> Ptr CInt -> TVV CInt
266 284
285-- | map of real vectors with given function
286vectorMapValL :: FunCodeSV -> Z -> Vector Z -> Vector Z
287vectorMapValL oper = vectorMapValAux c_vectorMapValL (fromei oper)
288
289foreign import ccall unsafe "mapValL" c_vectorMapValL :: CInt -> Ptr Z -> TVV Z
290
267 291
268------------------------------------------------------------------- 292-------------------------------------------------------------------
269 293
@@ -299,6 +323,11 @@ vectorZipI = vectorZipAux c_vectorZipI
299 323
300foreign import ccall unsafe "zipI" c_vectorZipI :: CInt -> TVVV CInt 324foreign import ccall unsafe "zipI" c_vectorZipI :: CInt -> TVVV CInt
301 325
326-- | elementwise operation on CInt vectors
327vectorZipL :: FunCodeVV -> Vector Z -> Vector Z -> Vector Z
328vectorZipL = vectorZipAux c_vectorZipL
329
330foreign import ccall unsafe "zipL" c_vectorZipL :: CInt -> TVVV Z
302 331
303-------------------------------------------------------------------------------- 332--------------------------------------------------------------------------------
304 333
@@ -385,6 +414,12 @@ float2IntV = tog c_float2int
385int2floatV :: Vector CInt -> Vector Float 414int2floatV :: Vector CInt -> Vector Float
386int2floatV = tog c_int2float 415int2floatV = tog c_int2float
387 416
417int2longV :: Vector I -> Vector Z
418int2longV = tog c_int2long
419
420long2intV :: Vector Z -> Vector I
421long2intV = tog c_long2int
422
388 423
389tog f v = unsafePerformIO $ do 424tog f v = unsafePerformIO $ do
390 r <- createVector (dim v) 425 r <- createVector (dim v)
@@ -397,6 +432,8 @@ foreign import ccall unsafe "int2double" c_int2double :: CInt :> Double :> O
397foreign import ccall unsafe "double2int" c_double2int :: Double :> CInt :> Ok 432foreign import ccall unsafe "double2int" c_double2int :: Double :> CInt :> Ok
398foreign import ccall unsafe "int2float" c_int2float :: CInt :> Float :> Ok 433foreign import ccall unsafe "int2float" c_int2float :: CInt :> Float :> Ok
399foreign import ccall unsafe "float2int" c_float2int :: Float :> CInt :> Ok 434foreign import ccall unsafe "float2int" c_float2int :: Float :> CInt :> Ok
435foreign import ccall unsafe "int2long" c_int2long :: I :> Z :> Ok
436foreign import ccall unsafe "long2int" c_long2int :: Z :> I :> Ok
400 437
401 438
402--------------------------------------------------------------- 439---------------------------------------------------------------
@@ -415,10 +452,14 @@ stepF = stepg c_stepF
415stepI :: Vector CInt -> Vector CInt 452stepI :: Vector CInt -> Vector CInt
416stepI = stepg c_stepI 453stepI = stepg c_stepI
417 454
455stepL :: Vector Z -> Vector Z
456stepL = stepg c_stepL
457
458
418foreign import ccall unsafe "stepF" c_stepF :: TVV Float 459foreign import ccall unsafe "stepF" c_stepF :: TVV Float
419foreign import ccall unsafe "stepD" c_stepD :: TVV Double 460foreign import ccall unsafe "stepD" c_stepD :: TVV Double
420foreign import ccall unsafe "stepI" c_stepI :: TVV CInt 461foreign import ccall unsafe "stepI" c_stepI :: TVV CInt
421 462foreign import ccall unsafe "stepL" c_stepL :: TVV Z
422 463
423-------------------------------------------------------------------------------- 464--------------------------------------------------------------------------------
424 465
@@ -461,6 +502,7 @@ foreign import ccall unsafe "constantR" cconstantR :: TConst Double
461foreign import ccall unsafe "constantQ" cconstantQ :: TConst (Complex Float) 502foreign import ccall unsafe "constantQ" cconstantQ :: TConst (Complex Float)
462foreign import ccall unsafe "constantC" cconstantC :: TConst (Complex Double) 503foreign import ccall unsafe "constantC" cconstantC :: TConst (Complex Double)
463foreign import ccall unsafe "constantI" cconstantI :: TConst CInt 504foreign import ccall unsafe "constantI" cconstantI :: TConst CInt
505foreign import ccall unsafe "constantL" cconstantL :: TConst Z
464 506
465---------------------------------------------------------------------- 507----------------------------------------------------------------------
466 508
diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs
index 076f485..017196c 100644
--- a/packages/base/src/Numeric/Vector.hs
+++ b/packages/base/src/Numeric/Vector.hs
@@ -41,6 +41,14 @@ instance Num (Vector I) where
41 abs = vectorMapI Abs 41 abs = vectorMapI Abs
42 fromInteger = fromList . return . fromInteger 42 fromInteger = fromList . return . fromInteger
43 43
44instance Num (Vector Z) where
45 (+) = adaptScalar addConstant add (flip addConstant)
46 negate = scale (-1)
47 (*) = adaptScalar scale mul (flip scale)
48 signum = vectorMapL Sign
49 abs = vectorMapL Abs
50 fromInteger = fromList . return . fromInteger
51
44instance Num (Vector Float) where 52instance Num (Vector Float) where
45 (+) = adaptScalar addConstant add (flip addConstant) 53 (+) = adaptScalar addConstant add (flip addConstant)
46 negate = scale (-1) 54 negate = scale (-1)