feat(Numeric): move all modules to Numeric

This commit is contained in:
Mahdi Dibaiee 2016-10-17 01:54:35 +03:30
parent 506b180498
commit ed6d2b3021
16 changed files with 20 additions and 65 deletions

View File

@ -1,5 +1,5 @@
module Main where
import Sibe
import Numeric.Sibe
import Numeric.LinearAlgebra
import Data.List
import Debug.Trace

View File

@ -1,8 +1,7 @@
module Main
where
-- import Sibe
import Sibe.NLP
import Sibe.NaiveBayes
import Numeric.Sibe.NLP
import Numeric.Sibe.NaiveBayes
import Text.Printf
import Data.List
import Data.Maybe

View File

@ -3,7 +3,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Sibe
import Numeric.Sibe
import Numeric.LinearAlgebra
import Data.List
import Debug.Trace

View File

@ -3,9 +3,9 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Sibe
import Sibe.Word2Vec
import Sibe.Utils
import Numeric.Sibe
import Numeric.Sibe.Word2Vec
import Numeric.Sibe.Utils
import Data.Default.Class
import qualified Data.Vector.Storable as V
import Data.List (sortBy)

View File

@ -1,5 +1,5 @@
module Main where
import Sibe
import Numeric.Sibe
import Numeric.LinearAlgebra
import Data.List
import Debug.Trace

View File

@ -1,5 +1,5 @@
name: sibe
version: 0.1.0.1
version: 0.2.0.0
synopsis: Machine Learning algorithms
description: Haskell Machine Learning
homepage: https://github.com/mdibaiee/sibe
@ -15,7 +15,7 @@ cabal-version: >=1.10
library
hs-source-dirs: src
exposed-modules: Sibe, Sibe.NaiveBayes, Sibe.NLP, Sibe.Word2Vec, Sibe.Utils
exposed-modules: Numeric.Sibe, Numeric.Sibe.NaiveBayes, Numeric.Sibe.NLP, Numeric.Sibe.Word2Vec, Numeric.Sibe.Utils
build-depends: base >= 4.7 && < 5
, hmatrix
, random

Binary file not shown.

BIN
src/Lib.o

Binary file not shown.

View File

@ -3,7 +3,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Sibe
module Numeric.Sibe
(Network(..),
Layer(..),
Input,

View File

@ -1,4 +1,4 @@
module Sibe.NLP
module Numeric.Sibe.NLP
(Class,
Document(..),
accuracy,
@ -13,7 +13,7 @@ module Sibe.NLP
ngramText,
)
where
import Sibe.Utils
import Numeric.Sibe.Utils
import Data.List
import Debug.Trace
import Data.List.Split

View File

@ -1,4 +1,4 @@
module Sibe.NaiveBayes
module Numeric.Sibe.NaiveBayes
(Document(..),
NB(..),
initialize,
@ -18,8 +18,8 @@ module Sibe.NaiveBayes
removeStopwords,
)
where
import Sibe.Utils
import Sibe.NLP
import Numeric.Sibe.Utils
import Numeric.Sibe.NLP
import Data.List
import Debug.Trace
import qualified Data.Set as Set

View File

@ -1,4 +1,4 @@
module Sibe.Utils
module Numeric.Sibe.Utils
( similarity
, ordNub
, onehot

View File

@ -1,12 +1,12 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Sibe.Word2Vec
module Numeric.Sibe.Word2Vec
( word2vec
, Word2Vec (..)
, W2VMethod (..)
) where
import Sibe
import Sibe.Utils
import Numeric.Sibe
import Numeric.Sibe.Utils
import Debug.Trace
import Data.Char
import Data.Maybe

View File

@ -1,44 +0,0 @@
module Sibe.Word2Vec
(word2vec,
mapTuple
) where
import Sibe
import Sibe.NLP
import Debug.Trace
import Data.Char
import Data.Maybe
import Data.List
import Numeric.LinearAlgebra hiding (find)
import qualified Data.Vector.Storable as V
word2vec docs session = do
let cooccurence = concat $ map co docs
a = (sigmoid, sigmoid')
o = (softmax, crossEntropy')
window = 2
s = session { training = cooccurence
, test = cooccurence
, network = buildNetwork 0 (-1, 1) n [(n, 300, (id, id))] (300, n, (softmax, crossEntropy'))
}
print $ network s
newses <- run gd s
return (newses, cooccurence, vocabulary, vocvec)
where
n = length vocabulary
vocabulary = ordNub . words . map toLower . concatMap (++ " ") $ docs
vocvec = zip vocabulary $ map tovec [0..n]
tovec i = replicate i 0 ++ [1] ++ replicate (n - i - 1) 0
co d =
let p = pairs d
in map (\(a, [b, c]) -> (f a, V.concat [f b, f c])) p
where
f w = vector . snd . fromJust $ find ((== w) . fst) vocvec
pairs d = concatMap iter [0..length ws]
where
ws = words $ map toLower d
iter i
| i > 0 && i < length ws - 1 = [(ws !! i, [ws !! (i - 1), ws !! (i + 1)])]
| otherwise = []
mapTuple :: (a -> b) -> (a, a) -> (b, b)
mapTuple f (a, b) = (f a, f b)