
I copy pasted Daniel's code. Changed the code to use Mersenne
genrerator and got 4200% (!) improvement:
import System.Random.Mersenne
import System( getArgs )
inCirc :: Double -> Double -> Int
inCirc x y
| dx*dx + dy*dy < 0.25 = 1
| otherwise = 0
where
dx = x - 0.5
dy = y - 0.5
-- transform a list of coordinates into a list of indicators
-- whether the point is inside the circle (sorry for the
-- stupid name)
inCircles :: [Double] -> [Int]
inCircles (x:y:zs) = inCirc x y : inCircles zs
inCircles _ = []
-- given a count of experiments and an infinite list of coordinates,
-- calculate an approximation to pi
calcPi :: Int -> [Double] -> Double
calcPi n ds = fromIntegral ct / fromIntegral n * 4
where
ct = sum . take n $ inCircles ds
-- now the IO part is only
-- * getting the number of experiments and
-- * getting the StdGen
main :: IO ()
main = do
args <- getArgs
sg <- getStdGen
let n = case args of
(a:_) -> read a
_ -> 10000
rands <- randoms sg :: IO [Double]
print $ calcPi n rands
time ./slow-pi +RTS -K1G -RTS 1000000
3.14222
real 0m6.886s
user 0m6.680s
sys 0m0.200s
time ./improved-pi 1000000
3.14364
real 0m0.163s
user 0m0.160s
sys 0m0.000s
Thanks all for the help !
On Fri, Jan 29, 2010 at 12:31 PM,
Send Beginners mailing list submissions to beginners@haskell.org
To subscribe or unsubscribe via the World Wide Web, visit http://www.haskell.org/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-request@haskell.org
You can reach the person managing the list at beginners-owner@haskell.org
When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..."
Today's Topics:
1. Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) (Lyndon Maydwell) 2. Re: subset - a little add (Daniel Fischer) 3. Re: Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) (Daniel Fischer) 4. Re: Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) (Lyndon Maydwell) 5. subset - a little add (Luca Ciciriello) 6. Re: Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) (Daniel Fischer) 7. PI calculation - Newbie question (Gabi)
----------------------------------------------------------------------
Message: 1 Date: Fri, 29 Jan 2010 16:52:37 +0800 From: Lyndon Maydwell
Subject: [Haskell-beginners] Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) To: beginners@haskell.org Message-ID: Content-Type: text/plain; charset=UTF-8 Hi Beginners.
I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix.
However, when I query the type of an identical implementation to vicinityMatrix in ghci it is successful:
:t \m x y -> fromRows $ vicinityRows m x y \m x y -> fromRows $ vicinityRows m x y :: forall (m :: * -> *) (m1 :: * -> *) a. (Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a)
What might be preventing the class from compiling?
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a]
toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y
row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]]
at = (!!!) (!!!) = at
vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell | x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y
vicinityMatrix m x y = fromRows $ vicinityRows m x y
-- neighbours = catMaybes . toListN . vicinityMatrix
toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y
------------------------------
Message: 2 Date: Fri, 29 Jan 2010 10:06:29 +0100 From: Daniel Fischer
Subject: Re: [Haskell-beginners] subset - a little add To: beginners@haskell.org Message-ID: <201001291006.30011.daniel.is.fischer@web.de> Content-Type: text/plain; charset="utf-8" Am Freitag 29 Januar 2010 08:36:35 schrieb Luca Ciciriello:
Just a little add to may previous mail.
The solution I've found from myself is:
subset :: [String] -> [String] -> Bool subset xs ys = and [elem x ys | x <- xs]
Variant:
subset xs ys = all (`elem` ys) xs
but is that really what you want? That says subset [1,1,1,1] [1] ~> True. If you regard your lists as representatives of sets (as the name suggests), then that's correct, otherwise not.
However, this is O(length xs * length ys). If you need it only for types belonging to Ord, a much better way is
import qualified Data.Set as Set import Data.Set (fromList, isSubsetOf, ...)
subset xs ys = fromList xs `isSubsetOf` fromList ys
or, if you don't want to depend on Data.Set,
subset xs ys = sort xs `isOrderedSublistOf` sort ys
xxs@(x:xs) `isOrderedSublistOf` (y:ys) | x < y = False | x == y = xs `isOrderedSublistOf` ys | otherwise = xxs `isOrderedSublistOf` ys [] `isOrderedSublistOf` _ = True _ `isOrderedSublistOf` [] = False
My question is if exists a more elegant way to do that.
Luca.
------------------------------
Message: 3 Date: Fri, 29 Jan 2010 10:17:10 +0100 From: Daniel Fischer
Subject: Re: [Haskell-beginners] Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) To: beginners@haskell.org Message-ID: <201001291017.10744.daniel.is.fischer@web.de> Content-Type: text/plain; charset="utf-8" Am Freitag 29 Januar 2010 09:52:37 schrieb Lyndon Maydwell:
Hi Beginners.
I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix.
However, when I query the type of an identical implementation to
vicinityMatrix in ghci it is successful: :t \m x y -> fromRows $ vicinityRows m x y
\m x y -> fromRows $ vicinityRows m x y
:: forall (m :: * -> *) (m1 :: * -> *) a.
(Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a)
What might be preventing the class from compiling?
Well, the error says the compiler (the type checker) can't deduce the context (Matrix m (Maybe a)) from the givens. If you supply that information,
vicinityMatrix :: Matrix m (Maybe a) => m a -> Integer -> Integer -> m (Maybe a)
it'll work.
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a]
toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y
row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]]
at = (!!!) (!!!) = at
vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell
| x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y
vicinityMatrix m x y = fromRows $ vicinityRows m x y
-- neighbours = catMaybes . toListN . vicinityMatrix
toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y
------------------------------
Message: 4 Date: Fri, 29 Jan 2010 17:45:32 +0800 From: Lyndon Maydwell
Subject: Re: [Haskell-beginners] Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a) To: Daniel Fischer Cc: beginners@haskell.org Message-ID: Content-Type: text/plain; charset=UTF-8 Thanks Daniel.
It works, but I'm a bit confused as to why the extra type information is needed.
On Fri, Jan 29, 2010 at 5:17 PM, Daniel Fischer
wrote: Am Freitag 29 Januar 2010 09:52:37 schrieb Lyndon Maydwell:
Hi Beginners.
I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix.
However, when I query the type of an identical implementation to
vicinityMatrix in ghci it is successful: :t \m x y -> fromRows $ vicinityRows m x y
\m x y -> fromRows $ vicinityRows m x y
:: forall (m :: * -> *) (m1 :: * -> *) a.
(Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a)
What might be preventing the class from compiling?
Well, the error says the compiler (the type checker) can't deduce the context (Matrix m (Maybe a)) from the givens. If you supply that information,
vicinityMatrix :: Matrix m (Maybe a) => m a -> Integer -> Integer -> m (Maybe a)
it'll work.
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a]
toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y
row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]]
at = (!!!) (!!!) = at
vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell
| x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y
vicinityMatrix m x y = fromRows $ vicinityRows m x y
-- neighbours = catMaybes . toListN . vicinityMatrix
toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y
------------------------------
Message: 5 Date: Fri, 29 Jan 2010 10:01:36 +0000 From: Luca Ciciriello
Subject: [Haskell-beginners] subset - a little add To: Message-ID: Content-Type: text/plain; charset="iso-8859-1" Thanks Daniel.
Yes my function operate only in a set-theory contest and your solution:
subset xs ys = all (`elem` ys) xs
is indeed more elegant than mine.
Thanks again for your help.
Luca.
From: daniel.is.fischer@web.de To: beginners@haskell.org Subject: Re: [Haskell-beginners] subset - a little add Date: Fri, 29 Jan 2010 10:06:29 +0100 CC: luca_ciciriello@hotmail.com
Am Freitag 29 Januar 2010 08:36:35 schrieb Luca Ciciriello:
Just a little add to may previous mail.
The solution I've found from myself is:
subset :: [String] -> [String] -> Bool subset xs ys = and [elem x ys | x <- xs]
Variant:
subset xs ys = all (`elem` ys) xs
but is that really what you want? That says subset [1,1,1,1] [1] ~> True. If you regard your lists as representatives of sets (as the name suggests), then that's correct, otherwise not.
However, this is O(length xs * length ys). If you need it only for types belonging to Ord, a much better way is
import qualified Data.Set as Set import Data.Set (fromList, isSubsetOf, ...)
subset xs ys = fromList xs `isSubsetOf` fromList ys
or, if you don't want to depend on Data.Set,
subset xs ys = sort xs `isOrderedSublistOf` sort ys
xxs@(x:xs) `isOrderedSublistOf` (y:ys) | x < y = False | x == y = xs `isOrderedSublistOf` ys | otherwise = xxs `isOrderedSublistOf` ys [] `isOrderedSublistOf` _ = True _ `isOrderedSublistOf` [] = False
My question is if exists a more elegant way to do that.
Luca.
Not got a Hotmail account? Sign-up now - Free
_________________________________________________________________ Send us your Hotmail stories and be featured in our newsletter http://clk.atdmt.com/UKM/go/195013117/direct/01/