Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-01 Thread Pekka Karjalainen
On Sat, Aug 1, 2009 at 4:44 PM, Paul Moorep.f.mo...@gmail.com wrote:
 PS I know my code is probably fairly clumsy - I'd appreciate style
 suggestions, but my main interest here is whether a beginner, with a
 broad programming background, a basic understanding of Haskell, and
 access to Google, put together a clear, efficient, program (ie, the
 case where my usual scripting language is too slow and I want to knock
 something up quickly in a high-level, high-performance language).

Here is one way to rewrite your program. It improved the speed
somewhat for me. I timed both programs on my computer. I suppose one
could try using an array for calculating the histogram as well, but I
only tried the simples thing here. I hope someone can weigh in with a
more thorough analysis.

Please note how I've avoided including the IO Monad in some type
signatures by extracting the data from it locally (with -). It is
quite possible to apply the histogram function to the data before
going through the IO Monad as well, but it doesn't appear to change
the execution speed much here.

Caveat: My testing wasn't extensive. I just compiled with -O and timed
the programs a couple of times.

import System.Random
import qualified Data.Map as Map
import Data.Map (Map)
import Data.List

diceRolls :: Int - IO [Int]
diceRolls highVal = do
generator - getStdGen
return (randomRs (1, highVal) generator)

groupDice :: Int - [Int] - [[Int]]
groupDice chunk rolls = map (take chunk) $ iterate (drop chunk) rolls

simulate :: Int - Int - Int - IO [Int]
simulate count m n = do
rolls - diceRolls n
let sums = map sum $ groupDice m rolls
return (take count sums)

histogram :: Ord a = [a] - [(a,Int)]
histogram = Map.assocs . foldl f Map.empty
 where
   f m k = Map.insertWith (+) k 1 m

simulation = do
 lst - simulate 10 3 6
 return (histogram $ lst)

main = do
 s - simulation
 putStrLn (show s)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell haikus

2008-12-07 Thread Pekka Karjalainen
On Sat, Dec 6, 2008 at 1:18 AM, Gwern Branwen [EMAIL PROTECTED] wrote:
 So: does anybody have a haiku I missed? Or even better, is anyone
 feeling poetically inspired tonight? :)

There's one by shapr in HaskellQuotes at the Wiki.

 shapr the snow falls slowly, the lambdas are lifting, weak head normal form

Here's one by me:

Without a kigo / or requisite syllables / haiku don't typecheck

Pekka Karjalainen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] GHC 6.10 and OpenGL

2008-12-02 Thread Pekka Karjalainen
On Tue, Dec 2, 2008 at 6:55 PM, Claus Reinke [EMAIL PROTECTED] wrote:
 I finally got round to trying cabal-install with OpenGL/GLUT,
 using a freshly built ghc head, a cygwin bash, and
[...]

   C:\Program
 Files\Haskell\GLUT-2.1.1.2\ghc-6.11.20081202/libHSGLUT-2.1.1.2.a(Window.o):fake:
 (.text+0x15): undefined reference to `glutWarpPointer'
[...]

I believe these errors are caused by the wrong calling convention
being used in the Haskell bindings. This part in the configure script
tests the build (host) platform:

case $host in
*-mingw32) CALLCONV=stdcall ;;
*)  CALLCONV=ccall ;;
esac

Since it doesn't test for Cygwin, you end up with the calling
convention being ccall, which leads to the linker errors because of
associated name mangling (you would also see run-time crashes if you
managed to somehow link your program).

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (OT) Has GHC stopped being the Glorious Glasgow Haskell Compiler?

2008-11-20 Thread Pekka Karjalainen
On Thu, Nov 20, 2008 at 6:26 AM, Benjamin L.Russell
[EMAIL PROTECTED] wrote:
 Am I missing something, or has the nickname been changed?

Well, 'ghc --version' tells me that I am using The Glorious Glasgow
Haskell Compilation System, version 6.10.1...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linker errors to OpenGL with GHC 6.10.1

2008-11-12 Thread Pekka Karjalainen
2008/11/13 Greg Fitzgerald [EMAIL PROTECTED]:
 Do you know how I can fix these linker errors?

 C:\projects\funcat HelloWorld.hs

 import Graphics.Rendering.OpenGL
 import Graphics.UI.GLUT
 main = do
   (progname, _) - getArgsAndInitialize
   createWindow Hello World
   displayCallback $= clear [ColorBuffer]
   mainLoop

 C:\projects\funls lib
 GlU32.Lib
 glut32.lib
 OpenGL32.Lib
 glut.def
 glut32.dll

 C:\projects\funghc -Llib -lglut32 -lglu32 -lopengl32 HelloWorld.hs --make
 Linking HelloWorld.exe ...
 C:\Program
 Files\Haskell\GLUT-2.1.1.2\ghc-6.10.1/libHSGLUT-2.1.1.2.a(Begin.o):fake:(.text+0x1cb):
 undefined reference to `glutGet'
[...]

 Thanks,
 Greg

I'm assuming this is on Windows because of C:\...

These kinds of linker errors happened to me when I built libHSGLUT
with a wrong type of calling convention (by accident). There are two
callconvs, and they are called stdcall and ccall on the Haskell side.
The 'runhaskell setup configure' step is supposed to detect the
correct one to use, so you should run it and then grep for lines with
CALLCONV. They should say stdcall on Windows. If you find them saying
ccall, that's likely the cause of all the linker errors. (Most Windows
dynamic libraries use stdcall, but for extra configuration fun OpenAL
uses ccall.)

If this is the problem, you can change the offending ccall in the
configuration files to stdcall and rebuild the library. Grepping for
CALLCONV will also show the places you need to change this way.

In my case the wrong configuration came from using the sh program from
Cygwin. With the MSYS variety there was no problem. To be exact, it
came down to the $host variable checked by the configuration script.

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extract source code from literate Haskell (LHS) files

2007-10-01 Thread Pekka Karjalainen
On 9/30/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:

  This is of course very easy to do manually, but does a command line tool
 exist for extracting source code from literate Haskell files?

There are a lot of good answers already. You can also use some GHC
command line options.

Please see: http://haskell.org/haddock/haddock-html-0.8/invoking.html#cpp

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-15 Thread Pekka Karjalainen
On 8/15/07, Mathias Biilmann Christensen [EMAIL PROTECTED] wrote:
 Spotted this thread as I was working on a Haskell solution for this
 one myself - here's the solution I came up with:
 [ ... ]
 raw_matrix =
  08 02 22 97 38 15 00 40 00 75 04 05 07 78 52 12 50 77 91 08  ++
  49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48 04 56 62 00  ++
  81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65  ++
[ ... ]

A little style issue here on the side, if I may. You don't need to use
(++) to join multiline string literals.

text = If you want to have multiline string literals \
   \in your source code, you can break them up with \
   \backslashes. Any whitespace characters between \
   \two backslashes will be ignored.

(The Haskell 98 Report calls them backslants.)

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A few questions on primes generating.

2007-08-13 Thread Pekka Karjalainen
On 8/13/07, L.Guo [EMAIL PROTECTED] wrote:
 Hi All:

Hello,


 I am reading http://www.haskell.org/haskellwiki/Prime_numbers

 The code in sector 1 Bitwise prime sieve.

 I have 3 questions about it.

 1) In function go, what does the number 46340 mean ? Is it sqrt(MAX_LONG) ?

Yes, it appears so. In a 32 bit implementation I get:

Prelude sqrt $ fromIntegral (maxBound :: Int)
46340.950001051984

 2) We have this type definition :
 pureSieve :: Int - Int
Why there is no error (type mismatch) of this call in func main :
 pureSieve 1000

If you have integer literals in your program, the compiler sees a
fromInteger in front of them. So the value is just converted to type
Int automatically, because that is expected here.

You can give different numeric default declarations in your own
modules. Please see sections 10.3 (for overloaded literals) and 10.4
(for defaults) here:
http://www.haskell.org/tutorial/numbers.html

Sometimes you can get an overflow like this:

Prelude 1000 :: Int
-159383552

 3) In main again, what does expression [| x |] mean ? Why this cannot be 
 execute in
 GHCi ?

It's Template Haskell, and is used there for some kind of optimisation
(I think). Template Haskell needs to be enabled with a command line
switch for it to work. Please see the documentation for more
information. It's section 7.6 in your User's Guide.

Though in this case you can probably just remove it to try out the
program. Perhaps someone else can explain what actual effect it has
here.

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Pekka Karjalainen
On 7/31/07, Chris Eidhof [EMAIL PROTECTED] wrote:
 Hey Haskell-Cafe,

 I was trying out the code in Dons's article [1], and I noticed a
 weird thing when doing it in GHCi. When binding the function
 composition to a variable, the type suddenly changes. I'm not
 completely sure why this happens. Is this because GHCi is in a monad
 and wants to find an instance for the type variable? Here's my GHCi
 session: [ ... ]

Apfelmus already explained why it happens. I'd like to add one thing.
If you are experimenting with GHCi, you can turn the restriction off
with the option -fno-monomorphism-restriction. In GHCi itself this is
given as follows:

Prelude :set -fno-monomorphism-restriction

After giving this and entering the same things as in your original
message, the type of encode came out to be as follows:

Prelude Control.Arrow Data.List let encode = map (length  head) . group
Prelude Control.Arrow Data.List :t encode
encode :: (Eq a) = [a] - [(Int, a)]

This option also saves some typing (of the variety you do on the
keyboard!) when you just want to use GHCi as a calculator:

Prelude Control.Arrow Data.List let x = 5
Prelude Control.Arrow Data.List let y = 6.3
Prelude Control.Arrow Data.List x*y
31.5

Instead of Integer, the type of x is now x :: (Num t) = t without the
restriction, and I don't need to add fromInteger to the
multiplication.

I don't recommend you to use this option all the time, of course. It's
just a convenience.

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: partitions of a multiset

2007-07-24 Thread Pekka Karjalainen

On 7/24/07, Brent Yorgey [EMAIL PROTECTED] wrote:

I'm not sure what a formal
mathematical definition would be off the top of my head; but in Haskell,
given a list L :: [a], I'm looking for all partitions P :: [[a]] where (sort
. concat $ P) == (sort L).


Here is quick attempt that requires Ord [a] and expects a sorted list.
It may very well not be correct, but it seemed to get all the simple
cases I tried right. Can you find a counterexample where it doesn't
work?

import Data.List (nub, (\\))

subsets [] = [[]]
subsets xs = []:[ a:b | a - nub xs,
 let (_:tl) = dropWhile (/=a) xs, b - subsets tl ]

multiPart [] = [[]]
multiPart xs = [ a:b | a - takeWhile ((head xs ==) . head) $ tail $
 subsets xs, b - multiPart $ xs \\ a, null b || a = head b ]

It would be nice if one could get rid of the (=) and hence Ord
without allowing duplicates. Furthermore, I haven't worried at all
about space or time efficiency while writing this. I'd want to get it
right first.

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe