Skip to content

Commit d51fc06

Browse files
committed
first
1 parent e93904a commit d51fc06

File tree

11 files changed

+316
-0
lines changed

11 files changed

+316
-0
lines changed
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
# statistics-dense-linear-algebra
2+
3+
[![Build Status](https://travis-ci.org/githubuser/statistics-dense-linear-algebra.png)](https://travis-ci.org/githubuser/statistics-dense-linear-algebra)
4+
5+
TODO Description.
+2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import Distribution.Simple
2+
main = defaultMain
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,145 @@
1+
{-# LANGUAGE BangPatterns, CPP, FlexibleContexts, Rank2Types #-}
2+
{-# OPTIONS_GHC -fsimpl-tick-factor=200 #-}
3+
-- |
4+
-- Module : Statistics.Function
5+
-- Copyright : (c) 2009, 2010, 2011 Bryan O'Sullivan
6+
-- License : BSD3
7+
--
8+
-- Maintainer : [email protected]
9+
-- Stability : experimental
10+
-- Portability : portable
11+
--
12+
-- Useful functions.
13+
14+
module Statistics.Function
15+
(
16+
-- * Scanning
17+
minMax
18+
-- * Sorting
19+
, sort
20+
, gsort
21+
, sortBy
22+
, partialSort
23+
-- * Indexing
24+
, indexed
25+
, indices
26+
-- * Bit twiddling
27+
, nextHighestPowerOfTwo
28+
-- * Comparison
29+
, within
30+
-- * Arithmetic
31+
, square
32+
-- * Vectors
33+
, unsafeModify
34+
-- * Combinators
35+
, for
36+
, rfor
37+
) where
38+
39+
#include "MachDeps.h"
40+
41+
import Control.Monad.ST (ST)
42+
import Data.Bits ((.|.), shiftR)
43+
import qualified Data.Vector.Algorithms.Intro as I
44+
import qualified Data.Vector.Generic as G
45+
import qualified Data.Vector.Unboxed as U
46+
import qualified Data.Vector.Unboxed.Mutable as M
47+
import Numeric.MathFunctions.Comparison (within)
48+
49+
-- | Sort a vector.
50+
sort :: U.Vector Double -> U.Vector Double
51+
sort = G.modify I.sort
52+
{-# NOINLINE sort #-}
53+
54+
-- | Sort a vector.
55+
gsort :: (Ord e, G.Vector v e) => v e -> v e
56+
gsort = G.modify I.sort
57+
{-# INLINE gsort #-}
58+
59+
-- | Sort a vector using a custom ordering.
60+
sortBy :: (G.Vector v e) => I.Comparison e -> v e -> v e
61+
sortBy f = G.modify $ I.sortBy f
62+
{-# INLINE sortBy #-}
63+
64+
-- | Partially sort a vector, such that the least /k/ elements will be
65+
-- at the front.
66+
partialSort :: (G.Vector v e, Ord e) =>
67+
Int -- ^ The number /k/ of least elements.
68+
-> v e
69+
-> v e
70+
partialSort k = G.modify (`I.partialSort` k)
71+
{-# SPECIALIZE partialSort :: Int -> U.Vector Double -> U.Vector Double #-}
72+
73+
-- | Return the indices of a vector.
74+
indices :: (G.Vector v a, G.Vector v Int) => v a -> v Int
75+
indices a = G.enumFromTo 0 (G.length a - 1)
76+
{-# INLINE indices #-}
77+
78+
-- | Zip a vector with its indices.
79+
indexed :: (G.Vector v e, G.Vector v Int, G.Vector v (Int,e)) => v e -> v (Int,e)
80+
indexed a = G.zip (indices a) a
81+
{-# INLINE indexed #-}
82+
83+
data MM = MM {-# UNPACK #-} !Double {-# UNPACK #-} !Double
84+
85+
-- | Compute the minimum and maximum of a vector in one pass.
86+
minMax :: (G.Vector v Double) => v Double -> (Double, Double)
87+
minMax = fini . G.foldl' go (MM (1/0) (-1/0))
88+
where
89+
go (MM lo hi) k = MM (min lo k) (max hi k)
90+
fini (MM lo hi) = (lo, hi)
91+
{-# INLINE minMax #-}
92+
93+
-- | Efficiently compute the next highest power of two for a
94+
-- non-negative integer. If the given value is already a power of
95+
-- two, it is returned unchanged. If negative, zero is returned.
96+
nextHighestPowerOfTwo :: Int -> Int
97+
nextHighestPowerOfTwo n
98+
#if WORD_SIZE_IN_BITS == 64
99+
= 1 + _i32
100+
#else
101+
= 1 + i16
102+
#endif
103+
where
104+
i0 = n - 1
105+
i1 = i0 .|. i0 `shiftR` 1
106+
i2 = i1 .|. i1 `shiftR` 2
107+
i4 = i2 .|. i2 `shiftR` 4
108+
i8 = i4 .|. i4 `shiftR` 8
109+
i16 = i8 .|. i8 `shiftR` 16
110+
_i32 = i16 .|. i16 `shiftR` 32
111+
-- It could be implemented as
112+
--
113+
-- > nextHighestPowerOfTwo n = 1 + foldl' go (n-1) [1, 2, 4, 8, 16, 32]
114+
-- where go m i = m .|. m `shiftR` i
115+
--
116+
-- But GHC do not inline foldl (probably because it's recursive) and
117+
-- as result function walks list of boxed ints. Hand rolled version
118+
-- uses unboxed arithmetic.
119+
120+
-- | Multiply a number by itself.
121+
square :: Double -> Double
122+
square x = x * x
123+
124+
-- | Simple for loop. Counts from /start/ to /end/-1.
125+
for :: Monad m => Int -> Int -> (Int -> m ()) -> m ()
126+
for n0 !n f = loop n0
127+
where
128+
loop i | i == n = return ()
129+
| otherwise = f i >> loop (i+1)
130+
{-# INLINE for #-}
131+
132+
-- | Simple reverse-for loop. Counts from /start/-1 to /end/ (which
133+
-- must be less than /start/).
134+
rfor :: Monad m => Int -> Int -> (Int -> m ()) -> m ()
135+
rfor n0 !n f = loop n0
136+
where
137+
loop i | i == n = return ()
138+
| otherwise = let i' = i-1 in f i' >> loop i'
139+
{-# INLINE rfor #-}
140+
141+
unsafeModify :: M.MVector s Double -> Int -> (Double -> Double) -> ST s ()
142+
unsafeModify v i f = do
143+
k <- M.unsafeRead v i
144+
M.unsafeWrite v i (f k)
145+
{-# INLINE unsafeModify #-}
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
-- |
2+
-- Module : Statistics.Function.Comparison
3+
-- Copyright : (c) 2011 Bryan O'Sullivan
4+
-- License : BSD3
5+
--
6+
-- Maintainer : [email protected]
7+
-- Stability : experimental
8+
-- Portability : portable
9+
--
10+
-- Approximate floating point comparison, based on Bruce Dawson's
11+
-- \"Comparing floating point numbers\":
12+
-- <http://www.cygnus-software.com/papers/comparingfloats/comparingfloats.htm>
13+
module Statistics.Function.Comparison
14+
{-# DEPRECATED "Use Numeric.MathFunctions.Comparison from math-functions" #-}
15+
(
16+
within
17+
) where
18+
import Numeric.MathFunctions.Comparison (within)
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
3+
-- |
4+
-- Module : Statistics.Sample.Internal
5+
-- Copyright : (c) 2013 Bryan O'Sullivan
6+
-- License : BSD3
7+
--
8+
-- Maintainer : [email protected]
9+
-- Stability : experimental
10+
-- Portability : portable
11+
--
12+
-- Internal functions for computing over samples.
13+
module Statistics.Sample.Internal
14+
(
15+
robustSumVar
16+
, sum
17+
) where
18+
19+
import Numeric.Sum (kbn, sumVector)
20+
import Prelude hiding (sum)
21+
import Statistics.Function (square)
22+
import qualified Data.Vector.Generic as G
23+
24+
robustSumVar :: (G.Vector v Double) => Double -> v Double -> Double
25+
robustSumVar m = sum . G.map (square . subtract m)
26+
{-# INLINE robustSumVar #-}
27+
28+
sum :: (G.Vector v Double) => v Double -> Double
29+
sum = sumVector kbn
30+
{-# INLINE sum #-}
+66
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
# This file was automatically generated by 'stack init'
2+
#
3+
# Some commonly used options have been documented as comments in this file.
4+
# For advanced use and comprehensive documentation of the format, please see:
5+
# https://docs.haskellstack.org/en/stable/yaml_configuration/
6+
7+
# Resolver to choose a 'specific' stackage snapshot or a compiler version.
8+
# A snapshot resolver dictates the compiler version and the set of packages
9+
# to be used for project dependencies. For example:
10+
#
11+
# resolver: lts-3.5
12+
# resolver: nightly-2015-09-21
13+
# resolver: ghc-7.10.2
14+
# resolver: ghcjs-0.1.0_ghc-7.10.2
15+
# resolver:
16+
# name: custom-snapshot
17+
# location: "./custom-snapshot.yaml"
18+
resolver: lts-11.2
19+
20+
# User packages to be built.
21+
# Various formats can be used as shown in the example below.
22+
#
23+
# packages:
24+
# - some-directory
25+
# - https://example.com/foo/bar/baz-0.0.2.tar.gz
26+
# - location:
27+
# git: https://github.com/commercialhaskell/stack.git
28+
# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
29+
# - location: https://github.com/commercialhaskell/stack/commit/e7b331f14bcffb8367cd58fbfc8b40ec7642100a
30+
# extra-dep: true
31+
# subdirs:
32+
# - auto-update
33+
# - wai
34+
#
35+
# A package marked 'extra-dep: true' will only be built if demanded by a
36+
# non-dependency (i.e. a user package), and its test suites and benchmarks
37+
# will not be run. This is useful for tweaking upstream packages.
38+
packages:
39+
- .
40+
# Dependency packages to be pulled from upstream that are not in the resolver
41+
# (e.g., acme-missiles-0.3)
42+
# extra-deps: []
43+
44+
# Override default flag values for local packages and extra-deps
45+
# flags: {}
46+
47+
# Extra package databases containing global packages
48+
# extra-package-dbs: []
49+
50+
# Control whether we use the GHC we find on the path
51+
# system-ghc: true
52+
#
53+
# Require a specific version of stack, using version ranges
54+
# require-stack-version: -any # Default
55+
# require-stack-version: ">=1.6"
56+
#
57+
# Override the architecture used by stack, especially useful on Windows
58+
# arch: i386
59+
# arch: x86_64
60+
#
61+
# Extra directories used by stack for building
62+
# extra-include-dirs: [/path/to/dir]
63+
# extra-lib-dirs: [/path/to/dir]
64+
#
65+
# Allow a newer minor version of GHC than the snapshot specifies
66+
# compiler-check: newer-minor
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
name: statistics-dense-linear-algebra
2+
version: 0.1.0.0
3+
-- synopsis:
4+
-- description:
5+
homepage: https://github.com/githubuser/statistics-dense-linear-algebra
6+
license: BSD3
7+
license-file: LICENSE
8+
author: Author name here
9+
maintainer: [email protected]
10+
copyright: 2018 Author name here
11+
category: Math, Statistics, Numeric
12+
build-type: Simple
13+
extra-source-files: README.md
14+
cabal-version: >=1.10
15+
tested-with: GHC==7.6.3, GHC==7.8.3, GHC==7.10.3, GHC==8.0.1
16+
17+
library
18+
default-language: Haskell2010
19+
ghc-options: -Wall
20+
hs-source-dirs: src
21+
exposed-modules: Statistics.Function
22+
Statistics.Function.Comparison
23+
Statistics.Matrix
24+
Statistics.Matrix.Algorithms
25+
Statistics.Matrix.Mutable
26+
Statistics.Matrix.Types
27+
Statistics.Sample.Internal
28+
build-depends: base >= 4.5 && < 5
29+
, deepseq >= 1.1.0.2
30+
, math-functions >= 0.1.7
31+
, primitive >= 0.3
32+
, vector >= 0.10
33+
, vector-algorithms >= 0.4
34+
, vector-th-unbox
35+
, vector-binary-instances >= 0.2.1
36+
37+
test-suite spec
38+
default-language: Haskell2010
39+
ghc-options: -Wall
40+
type: exitcode-stdio-1.0
41+
hs-source-dirs: test
42+
main-is: Spec.hs
43+
build-depends: base
44+
, statistics-dense-linear-algebra
45+
, hspec
46+
, QuickCheck
47+
48+
source-repository head
49+
type: git
50+
location: https://github.com/githubuser/statistics-dense-linear-algebra

0 commit comments

Comments
 (0)