Skip to content

Commit

Permalink
made all the changes to restore install
Browse files Browse the repository at this point in the history
  • Loading branch information
adrienhaxaire committed Nov 9, 2011
1 parent 6689d5c commit 5ccc3ee
Show file tree
Hide file tree
Showing 7 changed files with 7 additions and 74 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
*.hi
qc
QC
TAGS

# haddock, hlint
doc/
Expand Down
2 changes: 2 additions & 0 deletions Numeric/Funfem.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Numeric.Funfem (
module Numeric.Funfem.Elements
,module Numeric.Funfem.Vector
,module Numeric.Funfem.Matrix
,module Numeric.Funfem.Input
,module Numeric.Funfem.Solver
,module Numeric.Funfem.BoundaryConditions
Expand All @@ -9,6 +10,7 @@ module Numeric.Funfem (

import Numeric.Funfem.Elements
import Numeric.Funfem.Vector
import Numeric.Funfem.Matrix
import Numeric.Funfem.Input
import Numeric.Funfem.Solver
import Numeric.Funfem.BoundaryConditions
Expand Down
1 change: 0 additions & 1 deletion Numeric/Funfem/Elements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,4 +119,3 @@ matPropertyFromName mat name = propValue $ head property
where property = filter (\n -> (propName n) == name) (matProperties mat)


-- Boundary conditions
1 change: 1 addition & 0 deletions Numeric/Funfem/ShapeFunctions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import Data.List as L hiding (transpose)

import Numeric.Funfem.Elements
import Numeric.Funfem.Vector
import Numeric.Funfem.Matrix

-- | Interpolation function for 3-noded triangle
tri3 :: Element -> Matrix
Expand Down
2 changes: 2 additions & 0 deletions Numeric/Funfem/Solver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@
module Numeric.Funfem.Solver (cg) where

import Numeric.Funfem.Vector
import Numeric.Funfem.Matrix


eps :: Double
eps = 1.0e-3
Expand Down
73 changes: 0 additions & 73 deletions Numeric/Funfem/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,76 +87,3 @@ vmap = Numeric.Funfem.Vector.map
norm :: Vector -> Double
{-# INLINE norm #-}
norm v = sqrt (v .* v)

data Matrix = Matrix [Vector]
deriving (Eq, Ord, Show)

fromVectors :: [Vector] -> Matrix
fromVectors v = Matrix v

fromMatrix :: Matrix -> [Vector]
fromMatrix (Matrix m) = m

fromMatrix' :: Matrix -> [[Double]]
fromMatrix' m = [fromVector v | v <- fromMatrix m]

transpose :: Matrix -> Matrix
transpose m = fromVectors [fromList l | l <- L.transpose $ fromMatrix' m]

tensor_product :: Vector -> Vector -> Matrix
tensor_product vs ws = fromVectors [Numeric.Funfem.Vector.map (*v) ws | v <- fromVector vs]

multMV :: Matrix -> Vector -> Vector
{-# INLINE multMV #-}
multMV m v = fromList $ L.map (.* v) (fromMatrix m)

multMM :: Matrix -> Matrix -> Matrix
{-# INLINE multMM #-}
multMM a b = fromVectors [fromList [a' .* b' | b' <- fromMatrix $ transpose' b] | a' <- fromMatrix a]
where
transpose' = Numeric.Funfem.Vector.transpose


-- | Scalar to Matrix multiplication
multSM :: Double -> Matrix -> Matrix
{-# INLINE multSM #-}
multSM x m = fromVectors [vmap (*x) v | v <- fromMatrix m]

-- | Returns a matrix without row and column numbers
butRowColumn :: Int -> Int -> Matrix -> Matrix
butRowColumn r c m = fromVectors $ butRow r $ butColumn c $ fromMatrix m
where
butColumn c' (v:vs) = [butSlice c' c' v] L.++ butColumn c' vs
butColumn _ [] = []
butRow r' m' = pre L.++ post
where
pre = fst splat
post = L.tail $ (snd splat)
splat = splitAt (r'-1) m'

isSquare :: Matrix -> Bool
isSquare m = L.foldl' (&&) True [(length column) == rows | column <- m']
where
m' = fromMatrix' m
rows = length m'

det :: Matrix -> Double
det (Matrix []) = 0.0
det (Matrix [Vector [a]]) = a
det m = if size fstRow == 2 then det2x2 m else subdets
where
fstRow = L.head $ fromMatrix m
subdets = L.sum $ L.zipWith (*) cofs dets
cofs = [if even i then (fstRow ! i) else -(fstRow ! i) | i <- [0..(n-1)]]
dets = [det (butRowColumn 1 i m) | i <- [1..n]]
n = size fstRow

det2x2 :: Matrix -> Double
det2x2 m = det2x2' (L.head vs) (L.last vs)
where
vs = fromMatrix m
det2x2' v w = head' v * last' w - last' v * head' w
head' = Numeric.Funfem.Vector.head
last' = Numeric.Funfem.Vector.last


1 change: 1 addition & 0 deletions funfem.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ library
Numeric.Funfem,
Numeric.Funfem.Elements,
Numeric.Funfem.Vector,
Numeric.Funfem.Matrix,
Numeric.Funfem.Solver,
Numeric.Funfem.ShapeFunctions,
Numeric.Funfem.BoundaryConditions,
Expand Down

0 comments on commit 5ccc3ee

Please sign in to comment.