Re: [Haskell-cafe] Loading 3D points & normals into OpenGL?

2009-03-11 Thread Artyom Shalkhakov

Hello,

Duane Johnson  писал(а) в своём письме Thu, 12  
Mar 2009 05:23:16 +0600:


Is there something around that will already do the trick?  Or perhaps  
another

format is preferred and already supported?


I'd advise you to restrict yourself to your (specific?) requirements. VRML  
is complex,

and in fact can be an overkill to use in a (simple?) game.

There's another route you can take, though: write an exporter from some  
intermediate
format (like Collada or Blender), that would strip off features you don't  
intend to handle.


--
Cheers,
Artyom Shalkhakov
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get program command line arguments in Unicode-aware way (Unix/Linux)?

2009-03-11 Thread Austin Seipp
Excerpts from Dimitry Golubovsky's message of Wed Mar 11 21:42:14 -0500 2009:
> Hi,
> 
> I am trying to process command line arguments that may contain Unicode
> (cyrillic in this example) characters.
> 
> The standard GHC's getArgs seems to pass whatever was obtained from
> the underlying C library
> without any regard to encoding, e. g the following program (testarg.hs):
> 
> module Main where
> 
> import System.Environment
> 
> main = do
>   x <- getArgs
>   mapM (putStrLn . show) x
> 
> being invoked (ghc 6.10.1)
> 
> runghc testarg -T 'при<в>ет'
> 
> prints the following:
> 
> "-T"
> "\208\191\209\128\208\184<\208\178>\208\181\209\130"
> 
> (not correct, all bytes were passed without proper encoding)
> 
> Is there any way to get program arguments in GHC Unicode-aware? Or at
> least assuming that they are always in UTF-8?
> Something like System.IO.UTF8, but for command line arguments?
> 
> Thanks.
> 
> PS: BTW  runhugs testarg -T 'при<в>ет' prints:
> 
> "-T"
> "\1087\1088\1080<\1074>\1077\1090"
> 
> which is correct.
> 

Hello,

Would this approach work using utf8-string?

import Codec.Binary.UTF8.String
import System.Environment
import Control.Monad

main = do
x <- liftM (map decodeString) getArgs
mapM_ (putStrLn . encodeString) x

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


[Haskell-cafe] Re: Data.Binary patches?

2009-03-11 Thread Denis Bueno
On Wed, Mar 11, 2009 at 20:54, Denis Bueno  wrote:
> I've got a small patch for Data.Binary.  Should I post it here, or is
> there some more appropriate forum?

In case whoever reads this is a Data.Binary maintainer, the patch is
now attached, to save you some work.

The .patch file is the output of darcs send -a --output=.

  Denis


getError.patch
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary patches?

2009-03-11 Thread Paulo Tanimoto
Hi Denis,

On Wed, Mar 11, 2009 at 9:54 PM, Denis Bueno  wrote:
> I've got a small patch for Data.Binary.  Should I post it here, or is
> there some more appropriate forum?
>
> http://code.haskell.org/binary/ doesn't specify.
>
> Thanks,
>                              Denis
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

I've sent one to Don and he was quick to reply.  But in general you
can check the cabal file and send it to the maintainer:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary

Cheers,

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


[Haskell-cafe] Data.Binary patches?

2009-03-11 Thread Denis Bueno
I've got a small patch for Data.Binary.  Should I post it here, or is
there some more appropriate forum?

http://code.haskell.org/binary/ doesn't specify.

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


[Haskell-cafe] How to get program command line arguments in Unicode-aware way (Unix/Linux)?

2009-03-11 Thread Dimitry Golubovsky
Hi,

I am trying to process command line arguments that may contain Unicode
(cyrillic in this example) characters.

The standard GHC's getArgs seems to pass whatever was obtained from
the underlying C library
without any regard to encoding, e. g the following program (testarg.hs):

module Main where

import System.Environment

main = do
  x <- getArgs
  mapM (putStrLn . show) x

being invoked (ghc 6.10.1)

runghc testarg -T 'при<в>ет'

prints the following:

"-T"
"\208\191\209\128\208\184<\208\178>\208\181\209\130"

(not correct, all bytes were passed without proper encoding)

Is there any way to get program arguments in GHC Unicode-aware? Or at
least assuming that they are always in UTF-8?
Something like System.IO.UTF8, but for command line arguments?

Thanks.

PS: BTW  runhugs testarg -T 'при<в>ет' prints:

"-T"
"\1087\1088\1080<\1074>\1077\1090"

which is correct.

-- 
Dimitry Golubovsky

Anywhere on the Web
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Binary Parsing

2009-03-11 Thread Denis Bueno
2009/3/11 Rick R :
> I have basic beginning to a parser for the BSON spec:
> http://www.mongodb.org/display/DOCS/BSON
> It is basically a binary compressed form of JSON.
> The usage model should be general, but I intend to read this data over TCP.
[...]
> I was wondering if there is a tool set that exists for this purpose. For
> instance, should I use Data.Binary and make my Binary instance of get and
> put use the BSON protocol? Or is that not correct?

It sounds like this would work well.  I just used Data.Binary for the
first time yesterday to parse a few several-hundred-megabyte files,
and I have no complaints.  Its interface allows for testing of nice
properties, like that (decode . encode $ x) == x.  Along with
quickCheck and an Arbitrary instance for your unserialised types, this
makes it easy to find problems in your coding.

The Data.Binary authors have also gone to some trouble to make it all
efficient -- you really should try it out.

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


Re: [Haskell-cafe] Loading 3D points & normals into OpenGL?

2009-03-11 Thread Thomas Davie
If you were to strip out all texture loading code, then yes,  
otherwise, no.


Bob

On 12 Mar 2009, at 01:36, Duane Johnson wrote:

The MTL portion of that library depends on an external DevIL  
library ... is there a way to specify just the Obj portion which has  
no such dependency?


Thanks,
Duane

On Mar 11, 2009, at 5:28 PM, Luke Palmer wrote:


You might be interested in the obj library: 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/obj

Luke

On Wed, Mar 11, 2009 at 5:23 PM, Duane Johnson > wrote:

Hi,

I am considering writing a VRML (.wrl) parser so that I can load  
points and normals for a game I'm making in Haskell.  Is there  
something around that will already do the trick?  Or perhaps  
another format is preferred and already supported?


Thanks,
Duane Johnson
(canadaduane)
http://blog.inquirylabs.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



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


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


Re: [Haskell-cafe] Loading 3D points & normals into OpenGL?

2009-03-11 Thread Duane Johnson
The MTL portion of that library depends on an external DevIL  
library ... is there a way to specify just the Obj portion which has  
no such dependency?


Thanks,
Duane

On Mar 11, 2009, at 5:28 PM, Luke Palmer wrote:


You might be interested in the obj library: 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/obj

Luke

On Wed, Mar 11, 2009 at 5:23 PM, Duane Johnson > wrote:

Hi,

I am considering writing a VRML (.wrl) parser so that I can load  
points and normals for a game I'm making in Haskell.  Is there  
something around that will already do the trick?  Or perhaps another  
format is preferred and already supported?


Thanks,
Duane Johnson
(canadaduane)
http://blog.inquirylabs.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



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


Re: [Haskell-cafe] ThreadScope: Request for features for the performance tuning of parallel and concurrent Haskell programs

2009-03-11 Thread Ben Lippmeier


Hi Satnam,

On 12/03/2009, at 12:24 AM, Satnam Singh wrote:
Before making the release I thought it would be an idea to ask  
people what other features people would find useful or performance  
tuning. So if you have any suggestions please do let us know!




Is it available in a branch somewhere to try out?

Ben.


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


[Haskell-cafe] Binary Parsing

2009-03-11 Thread Rick R
I have basic beginning to a parser for the BSON spec:
http://www.mongodb.org/display/DOCS/BSON
It is basically a binary compressed form of JSON.
The usage model should be general, but I intend to read this data over TCP.

Currently my system is quite inefficient, I convert leading bytes to Int
then switch based on that type that that Int represtents.

I was wondering if there is a tool set that exists for this purpose. For
instance, should I use Data.Binary and make my Binary instance of get and
put use the BSON protocol? Or is that not correct?
I also looked at Parsec.ByteString, but that seems to only have a file input
mechanism, and tcp buffers may be out of its scope. Are there any other
tools that I should look at?

I'm sure similar things have been done before. Can anyone point me to some
open, successful implementations that I could mimick?


-- 
We can't solve problems by using the same kind of thinking we used when we
created them.
   - A. Einstein
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Loading 3D points & normals into OpenGL?

2009-03-11 Thread Luke Palmer
You might be interested in the obj library:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/obj

Luke

On Wed, Mar 11, 2009 at 5:23 PM, Duane Johnson wrote:

> Hi,
>
> I am considering writing a VRML (.wrl) parser so that I can load points and
> normals for a game I'm making in Haskell.  Is there something around that
> will already do the trick?  Or perhaps another format is preferred and
> already supported?
>
> Thanks,
> Duane Johnson
> (canadaduane)
> http://blog.inquirylabs.com/
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Loading 3D points & normals into OpenGL?

2009-03-11 Thread Duane Johnson

Hi,

I am considering writing a VRML (.wrl) parser so that I can load  
points and normals for a game I'm making in Haskell.  Is there  
something around that will already do the trick?  Or perhaps another  
format is preferred and already supported?


Thanks,
Duane Johnson
(canadaduane)
http://blog.inquirylabs.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generic sum for an UArr

2009-03-11 Thread Manlio Perillo

Daniel Fischer ha scritto:

[...]

   genericSumU :: (UA e, Integral e) => UArr e -> Int
   genericSumU = foldU add 0


That would have to be foldlU, the type of foldU is
foldU :: UA a => (a -> a -> a) -> a -> UArr a -> a

while 
foldlU :: UA a => (b -> a -> b) -> b -> UArr a -> b




Damn...

I was reading the source code of uvector, where
foldU = foldlU

and I totally forgot to check types.


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


Re: [Haskell-cafe] generic sum for an UArr

2009-03-11 Thread Daniel Fischer
Am Mittwoch, 11. März 2009 23:13 schrieb Manlio Perillo:
> Hi.
>
> I have an array (Data.Array.Vector.UArr) of Word8 elements.
> Elements are stored as Word8 to keep memory usage down.
>
> Now I need to compute the sum of all the array elements; what is the
> best method?
> The sum must be of type Int.
>
>
> How efficient is to simply convert to an UArr Int, using:
>
>mapU fromIntegral v :: UArr Int
> ?
>
>
> What about, instead, of something like:
>
>genericSumU :: (UA e, Integral e) => UArr e -> Int
>genericSumU = foldU add 0

That would have to be foldlU, the type of foldU is
foldU :: UA a => (a -> a -> a) -> a -> UArr a -> a

while 
foldlU :: UA a => (b -> a -> b) -> b -> UArr a -> b

>where
>  add x y = x + fromIntegral y
> ?
>
>
> Unfortunately the latter does not compile:
>
>   Couldn't match expected type `Int' against inferred type `e'
>`e' is a rigid type variable bound by
>the type signature for `genericSumU' at
> bin/process-data-1.hs:64:19
>  In the expression: foldU add 0
>  In the definition of `genericSumU':
>  genericSumU = foldU add 0
>  where
>  add x y = x + fromIntegral y
>
>
> Moreover, this is not really a generic version.
> I would like to have:
>
>genericSumU :: (Num i, UA e, Num e) => UArr e -> i
>
> is this possible?
>
>
>
> Thanks  Manlio
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] generic sum for an UArr

2009-03-11 Thread Manlio Perillo

Hi.

I have an array (Data.Array.Vector.UArr) of Word8 elements.
Elements are stored as Word8 to keep memory usage down.

Now I need to compute the sum of all the array elements; what is the 
best method?

The sum must be of type Int.


How efficient is to simply convert to an UArr Int, using:

  mapU fromIntegral v :: UArr Int
?


What about, instead, of something like:

  genericSumU :: (UA e, Integral e) => UArr e -> Int
  genericSumU = foldU add 0
  where
add x y = x + fromIntegral y
?


Unfortunately the latter does not compile:

 Couldn't match expected type `Int' against inferred type `e'
  `e' is a rigid type variable bound by
  the type signature for `genericSumU' at 
bin/process-data-1.hs:64:19

In the expression: foldU add 0
In the definition of `genericSumU':
genericSumU = foldU add 0
where
add x y = x + fromIntegral y


Moreover, this is not really a generic version.
I would like to have:

  genericSumU :: (Num i, UA e, Num e) => UArr e -> i

is this possible?



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


Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Ryan Ingram
2009/3/11 R J :
> 3.  Any advice on how, aside from tons of practice, to develop the intuition
> for rapidly seeing solutions to questions like these would be much
> appreciated.  The difficulty a newbie faces in answering seemingly simple
> questions like these is quite discouraging.

Don't be discouraged; this is far from a simple question.  I still
don't have an intuitive understanding of the "use functions"
definition of foldl-in-terms-of-foldr:

> foldl f z xs = foldr magic id xs z where
>magic x k e = k (f e x)

"magic" just looks like a bunch of characters that somehow typechecks.
 This definition of "magic" is slightly more comprehensible to me:

>   magic x k = k . flip f x

The definition with reverse is easier to understand but seems less elegant:

> foldl f z xs = foldr (flip f) z (reverse xs)

But it does follow almost directly from these definitions for foldl
and foldr on finite lists:

foldr f z [x1, x2, x3, ..., xN] = x1 `f` (x2 `f` (x3 `f` ... (xN `f` z)...))
foldl f z [xN, ..., x3, x2, x1] = ((...(z `f` xN)... `f` x3) `f` x2) `f` x1

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


Re: Re[2]: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread Peter Verswyvelen
In Dutch it is "luiaard' and that also means "lazy person".



On Wed, Mar 11, 2009 at 2:52 PM, Deniz Dogan wrote:

> 2009/3/11 minh thu :
> > 2009/3/11 Bulat Ziganshin :
> >> Hello Wolfgang,
> >>
> >> Wednesday, March 11, 2009, 1:06:37 PM, you wrote:
> >>
>  Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
>  they're so freaking cute... :)
> >>
> >>> Same in German: The german “Faultier” means “lazy animal”.
> >>
> >> russian too, if that matter. i was really amazed by this idea.
> >> pure, lazy and fun! :)
> >
> > Same in french : 'paresseux' just means lazy.
> >
> > Thu
>
> In Swedish it translates to "late walker" (?) and in Turkish it's "lazy
> animal".
>
> Deniz
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How to insert character key self in sourceView?

2009-03-11 Thread Andy Stewart
Andy Stewart  writes:

> Hi all,
>
> I use gtk2hs develop editor.
>
> I use below function handle key press event.
>
> keyPressHandler :: Event -> IO Bool
> keyPressHandler (Key {eventKeyName = keyName}) = do
>   case keyName of
> "Escape" -> do
>   mainQuit >> return True
> _ -> do 
>   -- How to insert character self?
>   return True
>
I answer self.

Just modified like below:

keyPressHandler :: Event -> IO Bool
keyPressHandler (Key {eventKeyName = keyName}) = do
  case keyName of
"Escape" -> do
  mainQuit >> return True
_ -> return False

Okay, now fix. :)

  -- Andy



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


Re: [Haskell-cafe] How to insert character key self in sourceView?

2009-03-11 Thread Wolfgang Jeltsch
Maybe you should direct your question to the Gtk2Hs users mailing list 
.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to insert character key self in sourceView?

2009-03-11 Thread Andy Stewart
Hi all,

I use gtk2hs develop editor.

I use below function handle key press event.

keyPressHandler :: Event -> IO Bool
keyPressHandler (Key {eventKeyName = keyName}) = do
  case keyName of
"Escape" -> do
  mainQuit >> return True
_ -> do 
  -- How to insert character self?
  return True

I need handle key press event, and insert itself if key is character
(like: 'a' 'b' 'c').

How to insert character self in sourceView buffer?

Below are complete source code:
--> source code start 
<--
import Graphics.UI.Gtk
import Graphics.UI.Gtk.SourceView
import Graphics.UI.Gtk.Abstract.Widget
import Graphics.UI.Gtk.Gdk.Events
import Text.Printf
import Control.Monad

main :: IO ()
main = do
  -- Init.
  initGUI

  -- Root frame.
  rootFrame <- windowNew
  onDestroy rootFrame mainQuit  -- quit main loop when root frame close

  -- Root frame status.
  -- windowFullscreen rootFrame   -- fullscreen
  windowSetPosition rootFrame WinPosCenter -- set init position
  windowSetDefaultSize rootFrame 400 300   -- set init size

  -- Main box.
  mainBox <- vBoxNew False 0
  containerAdd rootFrame mainBox

  -- Source view box.
  sourceViewBox <- vBoxNew False 0
  containerAdd mainBox sourceViewBox

  -- Source view.
  sourceView <- sourceViewNew
  boxPackStart sourceViewBox sourceView PackNatural 0

  -- Echo area box.
  echoAreaBox <- vBoxNew False 0
  echoAreaAlign <- alignmentNew 0 1 1 1
  containerAdd echoAreaBox echoAreaAlign
  containerAdd mainBox echoAreaBox

  -- Echo area.
  echoArea <- statusbarNew
  boxPackStart echoAreaBox echoArea PackNatural 0
  
  -- Display.
  widgetShowAll rootFrame

  -- Handle keystroke.
  onKeyPress rootFrame $ keyPressHandler

  -- Update echo area.
  updateEchoArea sourceView echoArea

  -- Loop
  mainGUI

keyPressHandler :: Event -> IO Bool
keyPressHandler (Key {eventKeyName = keyName}) = do
  case keyName of
"Escape" -> do
  mainQuit >> return True
_ -> do 
  return True

updateEchoArea :: SourceView -> Statusbar -> IO ()
updateEchoArea sv sb = do
buf  <- textViewGetBuffer sv
mark <- textBufferGetInsert buf
iter <- textBufferGetIterAtMark buf mark
line <- textIterGetLine iter
col  <- textIterGetLineOffset iter
statusbarPop sb 1
statusbarPush sb 1 $ printf "Line %4d, Column %3d" (line + 1) (col + 1)
return ()
--> source code end   
<--

Any help?

Thanks!

  -- Andy


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


Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Daniel Fischer
Am Mittwoch, 11. März 2009 19:24 schrieb R J:
> foldl and foldr are defined as follows:
>
>   foldr:: (a -> b -> b) -> b -> [a] -> b
>   foldr f e [] =  e
>   foldr f e (x : xs)   =  f x (foldr f e xs)
>
>   foldl:: (b -> a -> b) -> b -> [a] -> b
>   foldl f e [] =  e
>   foldl f e (x : xs)   =  foldl f (f e x) xs
>
> 1.  I understand how these definitions work, and yet I'm unable to
> implement foldl in terms of foldr.  What's a systematic approach to
> identifying such an implementation, and what is the implementation?

Implementation:
myfoldl f e xs = foldr (flip f) e (reverse xs)

Systematic approach:
Assume you have an implementation.
From considering simple cases, derive necessary conditions for the 
implementation.
When the necessary conditions have narrowed the possibilities far enough down, 
check which of the remaining possibilities solve the problem.

Here:
foldl f e === foldr g v . h
where h should be a simple polymorphic function on lists, 
h :: [a] -> [a]

foldl f e [] = e,
foldr g v (h []) = if null (h []) then v else g (h []) v

since h should be generic, h [] can't be anything but [] or _|_, h [] = _|_ 
won't work with strict functions, so h [] = [] and v = e

foldl f e [x] = f e x,
foldr g e (h [x]) = if null (h [x]) then e else g (h [x]) e

h [x] = [] would break for many f, as would h [x] = _|_, so h [x] can only be 
one of [x], [x,x], [x,x,x], ..., repeat x
If h [x] = [x], we have foldr g e (h [x]) = g x e, and we must have
forall x, e. f e x === g x e
, hence g = flip f.
If h [x] = [x,x] or [x,x,x] or ..., we would have to have
f e x == x `g` (x `g` (... e))
pick a few simple examples which don't allow that, 
say f = (+), e = (0 :: Int), x = 1
f = (+), e = (1 :: Int), x = 1

foldl f e [x,y] = (e `f` x) `f` y
foldr (flip f) e (h [x,y]) = ?

foldr g e [u,v] = u `g` (v `g` e)
with g = flip f, that reduces to (e `f` v) `f` u,
so for [u,v] = [y,x] we have what we want, and our candidate is

foldl f e =?= foldr (flip f) e . reverse

The rest is tedious verification.

>
> 2.  I believe that the reverse implementation--namely, implementing foldr
> in terms of foldl--is impossible.  What's the proof of that?

foldr (++) [] (infinite list)

that delivers something (unless all lists inside the infinite list are empty), 
but reverse (infinite list) never returns.

>
> 3.  Any advice on how, aside from tons of practice, to develop the
> intuition for rapidly seeing solutions to questions like these would be
> much appreciated.  The difficulty a newbie faces in answering seemingly
> simple questions like these is quite discouraging.
>

Sorry, can't offer anything but practice.

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


Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Dan Doel
On Wednesday 11 March 2009 2:24:55 pm R J wrote:
> foldl and foldr are defined as follows:
>
>   foldr:: (a -> b -> b) -> b -> [a] -> b
>   foldr f e [] =  e
>   foldr f e (x : xs)   =  f x (foldr f e xs)
>
>   foldl:: (b -> a -> b) -> b -> [a] -> b
>   foldl f e [] =  e
>   foldl f e (x : xs)   =  foldl f (f e x) xs
>
> 1.  I understand how these definitions work, and yet I'm unable to
> implement foldl in terms of foldr.  What's a systematic approach to
> identifying such an implementation, and what is the implementation?

This is a bit tricky, because although the base cases of the two line up, the 
inductive cases do not. When that sort of thing happens, and you can't find a 
tweaking of the function that brings it into line with foldr, what one has to 
do is to start looking for definitions like:

  foldl'aux [] = e'aux
  foldl'aux (x:xs) = g x (foldl'aux xs)

where you can get foldl from foldl'aux by applying some post-processing. In 
this case, you might fool around with foldl a bit:

  foldl f e [] = id e
  foldl f e (x:xs) = (\e -> foldl f (f e x) xs) e

Noticing this, we might try factoring out the 'e' parameter, and building a 
function to apply it to...

  foldl' f [] = id
  foldl' f (x:xs) = \e -> foldl' f xs (f e x)
  = (\x e -> foldl' f xs (f e x)) x
  = (\x k e -> k (f e x)) x (foldl' f xs)

And now this is in the correct form for implementation with foldr:

  foldl' f = foldr (\x k e -> k (f e x)) id

And:

  foldl f e l = foldl' f l e = foldr (\x k e -> k (f e x)) id l e

> 2.  I believe that the reverse implementation--namely, implementing foldr
> in terms of foldl--is impossible.  What's the proof of that?

This isn't a proof, but "foldl f z l" is bottom when l is an infinite list, 
regardless of f and z, whereas foldr works fine on infinite lists. This is at 
least a clue that implementing foldr in terms of foldl is a problem.

Note that foldr *can* be implemented with foldl if you restrict yourself to 
finite lists. The definition is similar to the reverse.

> 3.  Any advice on how, aside from tons of practice, to develop the
> intuition for rapidly seeing solutions to questions like these would be
> much appreciated.  The difficulty a newbie faces in answering seemingly
> simple questions like these is quite discouraging.

I recommend the paper Adrian Neumann linked to. :)

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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread Manlio Perillo

Manlio Perillo ha scritto:

minh thu ha scritto:

[...]
The approach I suggested is a bit overkill. You can indeed use L.lines
to split the input into lines then work on that.

But still, avoid the pair (Int, Bytestring). Instead, you can 
basically map

on each line the unsafeReadInt modified to :
- return the id
- return if it is one kind of id or the other kind.

so :
type UserId = Int
type MovieId = Int
unsafeReadInt :: Line -> Either MovieId UserId

Now you have a nice list [Either MovieId UserId] that
you need to transform into (MovieId, [UserId]).



Thanks, this seems a much better solution.



Done:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2309


real1m15.220s
user0m4.816s
sys 0m0.308s


3084 KB memory usage

Previous version required 4956 KB of memory.


Thanks again for the suggestion, Minh.


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


Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Max Rabkin
2009/3/11 R J :
> 2.  I believe that the reverse implementation--namely, implementing foldr in
> terms of foldl--is impossible.  What's the proof of that?

That's correct. Consider their behaviour on infinite lists.

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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread minh thu
2009/3/11 Manlio Perillo :
> Manlio Perillo ha scritto:
>>
>> minh thu ha scritto:
>>>
>>> [...]
>>> The approach I suggested is a bit overkill. You can indeed use L.lines
>>> to split the input into lines then work on that.
>>>
>>> But still, avoid the pair (Int, Bytestring). Instead, you can basically
>>> map
>>> on each line the unsafeReadInt modified to :
>>> - return the id
>>> - return if it is one kind of id or the other kind.
>>>
>>> so :
>>> type UserId = Int
>>> type MovieId = Int
>>> unsafeReadInt :: Line -> Either MovieId UserId
>>>
>>> Now you have a nice list [Either MovieId UserId] that
>>> you need to transform into (MovieId, [UserId]).
>>>
>>
>> Thanks, this seems a much better solution.
>>
>
> Done:
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2309

One improvement you can do :

In the line
  quiz' (Left id : l) = (id, quiz'' l) : quiz' l

notice you use two times the 'l', and the next line of code
pass through the Right case.

Change your code so that quiz'' has a return type ([UserId],Bytestring).
The above line becomes

quiz' (Left id : l) = (id, ids) : quiz' rest
where (ids,rest) = quiz'' l

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


Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Adrian Neumann

Read this excellent paper:

http://www.cs.nott.ac.uk/~gmh/fold.pdf


Am 11.03.2009 um 19:24 schrieb R J:


foldl and foldr are defined as follows:

  foldr:: (a -> b -> b) -> b -> [a] -> b
  foldr f e [] =  e
  foldr f e (x : xs)   =  f x (foldr f e xs)

  foldl:: (b -> a -> b) -> b -> [a] -> b
  foldl f e [] =  e
  foldl f e (x : xs)   =  foldl f (f e x) xs

1.  I understand how these definitions work, and yet I'm unable to  
implement foldl in terms of foldr.  What's a systematic approach to  
identifying such an implementation, and what is the implementation?


2.  I believe that the reverse implementation--namely, implementing  
foldr in terms of foldl--is impossible.  What's the proof of that?


3.  Any advice on how, aside from tons of practice, to develop the  
intuition for rapidly seeing solutions to questions like these  
would be much appreciated.  The difficulty a newbie faces in  
answering seemingly simple questions like these is quite discouraging.


Express your personality in color! Preview and select themes for  
Hotmail®. See how.

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




PGP.sig
Description: Signierter Teil der Nachricht
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread R J

foldl and foldr are defined as follows:

  foldr:: (a -> b -> b) -> b -> [a] -> b
  foldr f e [] =  e
  foldr f e (x : xs)   =  f x (foldr f e xs)

  foldl:: (b -> a -> b) -> b -> [a] -> b
  foldl f e [] =  e
  foldl f e (x : xs)   =  foldl f (f e x) xs

1.  I understand how these definitions work, and yet I'm unable to implement 
foldl in terms of foldr.  What's a systematic approach to identifying such an 
implementation, and what is the implementation?

2.  I believe that the reverse implementation--namely, implementing foldr in 
terms of foldl--is impossible.  What's the proof of that?

3.  Any advice on how, aside from tons of practice, to develop the intuition 
for rapidly seeing solutions to questions like these would be much appreciated. 
 The difficulty a newbie faces in answering seemingly simple questions like 
these is quite discouraging.

_
Express your personality in color! Preview and select themes for Hotmail®. 
http://www.windowslive-hotmail.com/LearnMore/personalize.aspx?ocid=TXT_MSGTX_WL_HM_express_032009#colortheme___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-11 Thread Peter Verswyvelen
Okay, I submitted it as a GHC feature request. Thanks for the feedback.
On Wed, Mar 11, 2009 at 5:16 PM, Creighton Hogg  wrote:

> 2009/3/11 Peter Verswyvelen :
> > When I put
> > {-# OPTIONS_GHC -Wall -Werror #-}
> > in my source file, I don't get compiler (GHC) warnings about redundant
> > language extensions that I enabled.
> > It would be nice if the compiler gave warnings about this, since after
> > refactoring, some language extensions might not be needed anymore, and
> hence
> > should be removed since fewer language extensions mean more stable and
> > portable code no?
> > What do you think?
>
> So you mean something like if you put {-# LANGUAGE
> GeneralizedNewtypeDeriving #-} in a file, but never do newtype
> deriving, it would warn you?
>
> I have no idea how hard that'd be to implement, but that sounds kind
> of cool.  Useful for both refactoring and when you've inherited old
> code.
>
> Cheers,
> C
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ByteString in patterns

2009-03-11 Thread Manlio Perillo

Don Stewart ha scritto:

[...]

Then there is something I'm missing.
Your code does not compile.


Sure it does:



As Daniel suggested, I'm using an old bytestring version that came with 
Debian Etch (GHC 6.8.2).




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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread Manlio Perillo

minh thu ha scritto:

[...]
The approach I suggested is a bit overkill. You can indeed use L.lines
to split the input into lines then work on that.

But still, avoid the pair (Int, Bytestring). Instead, you can basically map
on each line the unsafeReadInt modified to :
- return the id
- return if it is one kind of id or the other kind.

so :
type UserId = Int
type MovieId = Int
unsafeReadInt :: Line -> Either MovieId UserId

Now you have a nice list [Either MovieId UserId] that
you need to transform into (MovieId, [UserId]).



Thanks, this seems a much better solution.


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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread minh thu
2009/3/11 minh thu :
> 2009/3/11 Manlio Perillo :
>> minh thu ha scritto:
>>>
>>> [...]
>>> I suggest you try an alternative strategy.
>>> That altenrative strategy is twofold, just like you have
>>> quiz' and quiz'.
>>> This alternate strategy avoid pattern matching on strings
>>> (which would be cumbersome for a bit more complex syntax).
>>>
>>
>> But for this specific case it is very compact and elegant (IMHO).
>
> I would say it is difficult to see what you're doing in the code without
> the desciption you gave in the mail. But you're right, it's not the string
> pattern matching which is the problem.
>
> It is more the pair (Int, rest of the bytestring which can begin or
> not with ':')...
>
> Why not have quiz' accepting just the bytestring (and not the id value),
> and returning the (Int,[Int]) ?
>
>>> [...]
>>> Now, given those two functions, try to apply them
>>> on your input string, feeding the next function application
>>> with the resulting string of the current application.
>>>
>>
>> So, I should not split the string into lines?
>
> See below.
>
>> An useful feature of my program is that it parses both an input like:
>>
>> 1:
>> 1046323,2005-12-19
>>
>> and
>> 1:
>> 1046323
>>
>>
>> If I write a parser from scratch I need to implement two separate functions.
>
> I didn't think to that but nothing prevent you to write the second function I
> suggested to account for that case, or for an end of line (if can 'eat' the 
> ':'
> from the input, you can also eat a newline).
>
> Thu

Ok,

The approach I suggested is a bit overkill. You can indeed use L.lines
to split the input into lines then work on that.

But still, avoid the pair (Int, Bytestring). Instead, you can basically map
on each line the unsafeReadInt modified to :
- return the id
- return if it is one kind of id or the other kind.

so :
type UserId = Int
type MovieId = Int
unsafeReadInt :: Line -> Either MovieId UserId

Now you have a nice list [Either MovieId UserId] that
you need to transform into (MovieId, [UserId]).

Sorry, for the previous response.

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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread minh thu
2009/3/11 Manlio Perillo :
> minh thu ha scritto:
>>
>> [...]
>> I suggest you try an alternative strategy.
>> That altenrative strategy is twofold, just like you have
>> quiz' and quiz'.
>> This alternate strategy avoid pattern matching on strings
>> (which would be cumbersome for a bit more complex syntax).
>>
>
> But for this specific case it is very compact and elegant (IMHO).

I would say it is difficult to see what you're doing in the code without
the desciption you gave in the mail. But you're right, it's not the string
pattern matching which is the problem.

It is more the pair (Int, rest of the bytestring which can begin or
not with ':')...

Why not have quiz' accepting just the bytestring (and not the id value),
and returning the (Int,[Int]) ?

>> [...]
>> Now, given those two functions, try to apply them
>> on your input string, feeding the next function application
>> with the resulting string of the current application.
>>
>
> So, I should not split the string into lines?

See below.

> An useful feature of my program is that it parses both an input like:
>
> 1:
> 1046323,2005-12-19
>
> and
> 1:
> 1046323
>
>
> If I write a parser from scratch I need to implement two separate functions.

I didn't think to that but nothing prevent you to write the second function I
suggested to account for that case, or for an end of line (if can 'eat' the ':'
from the input, you can also eat a newline).

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


Re: [Haskell-cafe] View patterns and warnings about overlapping or non-exhaustive patterns

2009-03-11 Thread Stephan Friedrichs
Svein Ove Aas wrote:
> [...]
> 
> For the time being, it will *work*, you just won't get useful
> warnings. Hopefully it's going to be fixed for 10.2.
> 

Hmm I don't find #2395 anywhere on
http://hackage.haskell.org/trac/ghc/milestone/6.10.2 :(

//Stephan


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread Manlio Perillo

minh thu ha scritto:

[...]
I suggest you try an alternative strategy.
That altenrative strategy is twofold, just like you have
quiz' and quiz'.
This alternate strategy avoid pattern matching on strings
(which would be cumbersome for a bit more complex syntax).



But for this specific case it is very compact and elegant (IMHO).


[...]
Now, given those two functions, try to apply them
on your input string, feeding the next function application
with the resulting string of the current application.



So, I should not split the string into lines?

An useful feature of my program is that it parses both an input like:

1:
1046323,2005-12-19

and
1:
1046323


If I write a parser from scratch I need to implement two separate functions.

I will give it a try, just to check if it has better performances.


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


Re: [Haskell-cafe] ByteString in patterns

2009-03-11 Thread Daniel Fischer
Am Mittwoch, 11. März 2009 17:09 schrieb Manlio Perillo:
> Don Stewart ha scritto:
> > manlio_perillo:
> >> Don Stewart ha scritto:
> >>> [...]
> >>> {-# LANGUAGE OverloadedStrings #-}
> >>>
> >>> import qualified Data.ByteString.Char8 as C
> >>>
> >>> isMatch :: C.ByteString -> Bool
> >>> isMatch "match" = True
> >>> isMatch _   = False
> >>>
> >>> main = print . map isMatch . C.lines =<< C.getContents
> >>
> >> What is the reason why instance declarations for IsString class are not
> >> defined for available ByteStrings?
> >>
> >> I need to define it by myself.
> >
> > They're exported from Data.ByteString.Char8
>
> Then there is something I'm missing.

A recent enough bytestring package.
Compiles and works with 0.9.1.4

> Your code does not compile.
>
>
>
> Thanks  Manlio Perillo
>

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


Re: [Haskell-cafe] View patterns and warnings about overlapping or non-exhaustive patterns

2009-03-11 Thread Neil Mitchell
Hi Stephan,

> I'm working on a data structure that uses Data.Sequence a lot, so views
> are important and I tried to simplify my code using view patterns.
>
> The problem is, that I keep getting warnings about both overlapping and
> non-exhaustive pattern matches. A simple test case:

http://hackage.haskell.org/trac/ghc/ticket/2395

Add yourself to the CC list if it matters to you!

Thanks

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


Re: [Haskell-cafe] ByteString in patterns

2009-03-11 Thread Don Stewart
manlio_perillo:
> Don Stewart ha scritto:
>> manlio_perillo:
>>> Don Stewart ha scritto:
 [...]
 {-# LANGUAGE OverloadedStrings #-}

 import qualified Data.ByteString.Char8 as C

 isMatch :: C.ByteString -> Bool
 isMatch "match" = True
 isMatch _   = False

 main = print . map isMatch . C.lines =<< C.getContents

>>> What is the reason why instance declarations for IsString class are 
>>> not  defined for available ByteStrings?
>>>
>>> I need to define it by myself.
>>
>> They're exported from Data.ByteString.Char8
>>
>
> Then there is something I'm missing.
> Your code does not compile.

Sure it does:

$ ghci A.hs  
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( A.hs, interpreted )
Ok, modules loaded: Main.

*Main> :t main
main :: IO ()

You should give any error message, and the steps you took that lead to
the error when making a bug report.

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


Re: [Haskell-cafe] View patterns and warnings about overlapping or non-exhaustive patterns

2009-03-11 Thread Svein Ove Aas
On Wed, Mar 11, 2009 at 5:22 PM, Stephan Friedrichs
 wrote:
> Hi,
>
> I'm working on a data structure that uses Data.Sequence a lot, so views
> are important and I tried to simplify my code using view patterns.
>
> The problem is, that I keep getting warnings about both overlapping and
> non-exhaustive pattern matches. A simple test case:
>
The view pattern implementation is currently incomplete, specifically
in that it is unable to decide whether a pattern match using them is
overlapping or non-exhaustive. Arguably the warnings should be
suppressed instead..

For the time being, it will *work*, you just won't get useful
warnings. Hopefully it's going to be fixed for 10.2.

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


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-11 Thread Peter Verswyvelen
Yes, exactly. Indeed I should have given an example, thanks for doing so, I
was too hasty being lazy :)
On Wed, Mar 11, 2009 at 5:16 PM, Creighton Hogg  wrote:

> 2009/3/11 Peter Verswyvelen :
> > When I put
> > {-# OPTIONS_GHC -Wall -Werror #-}
> > in my source file, I don't get compiler (GHC) warnings about redundant
> > language extensions that I enabled.
> > It would be nice if the compiler gave warnings about this, since after
> > refactoring, some language extensions might not be needed anymore, and
> hence
> > should be removed since fewer language extensions mean more stable and
> > portable code no?
> > What do you think?
>
> So you mean something like if you put {-# LANGUAGE
> GeneralizedNewtypeDeriving #-} in a file, but never do newtype
> deriving, it would warn you?
>
> I have no idea how hard that'd be to implement, but that sounds kind
> of cool.  Useful for both refactoring and when you've inherited old
> code.
>
> Cheers,
> C
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] View patterns and warnings about overlapping or non-exhaustive patterns

2009-03-11 Thread Stephan Friedrichs
Hi,

I'm working on a data structure that uses Data.Sequence a lot, so views
are important and I tried to simplify my code using view patterns.

The problem is, that I keep getting warnings about both overlapping and
non-exhaustive pattern matches. A simple test case:

===T.hs===
{-# LANGUAGE ViewPatterns #-}

import Data.Sequence

test :: Seq a -> Seq b -> String
test (viewl -> EmptyL) (viewl -> EmptyL) = "empty, empty"
test (viewl -> EmptyL) (viewl -> _ :< _) = "empty, non-empty"
test (viewl -> _ :< _) (viewl -> EmptyL) = "non-empty, empty"
test _ _ = "non-empty, non-empty"
==

> ghci -Wall T.hs
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( T.hs, interpreted )

T.hs:6:0:
Warning: Pattern match(es) are overlapped
 In the definition of `test':
 test ((viewl -> EmptyL)) ((viewl -> EmptyL)) = ...
 test ((viewl -> EmptyL)) ((viewl -> _ :< _)) = ...
 test ((viewl -> _ :< _)) ((viewl -> EmptyL)) = ...
 test _ _ = ...

T.hs:6:0:
Warning: Pattern match(es) are non-exhaustive
 In the definition of `test': Patterns not matched:
Ok, modules loaded: Main.

*Main> test empty (singleton 'a')
"empty, non-empty"
*Main> test (singleton 'b') (singleton 'a')
"non-empty, non-empty"
*Main> test (singleton 'b') empty
"non-empty, empty"
*Main> test empty empty
"empty, empty"

There are warnings about non-exhaustive and overlapping pattern matches,
but the tests show that this isn't the case. So what's the problem? I
don't want to turn off or ignore warnings.

//Stephan


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] advice on a parsing function

2009-03-11 Thread minh thu
2009/3/11 Manlio Perillo :
> Hi.
>
> I'm still working on the Netflix Prize; now I have managed to implement a
> parsing function for the qualifying data set (or quiz set).
>
> The quiz set is in the format:
>
> 1:
> 10
> 20
> 30
> 2:
> 100
> 200
> 3:
> 1000
> 2000
> 3000
> 4000
> 5000
>
>
> Where 1, 2, 3 are movie ids, and the others are user ids.
>
> The parsing program is at:
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2300
>
>
> The program reads the file using lazy IO.
> One of the feature I want is, for the quiz function, to be a *good
> producer*.
>
> I'm quite satisfied with the result (this is the first "complex" parsing
> function I have written in Haskell), and I have also managed to avoid the
> use of an accumulator.
>
> However I'm interested to know it there is a more efficient solution.
>
>
> The qualifying.txt file is 51MB, 2834601 lines.
>
> On my laptop, the function performance are:
>
> real1m14.117s
> user0m2.496s
> sys 0m0.136s
>
> CPU usage is about 3%,
> system load is about 0.20,
> memory usage is 4956 KB.
>
>
> What I'm worried about is:
>
> quiz' ((id, ":") : l) = (id, quiz'' l) : quiz' l
> quiz' ((id, _) : l) = quiz' l
>
>
> the problem here is that the same elements in the list are processed
> multiple times.
>
>
> I have written alternate versions.
> The first using foldl
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2303
> (that, however, builds the entire data structure in memory, and in reverse
> order)
>
> The latter using foldr
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2304
> (that, however, is incorrect and I'm unable to fix).

Hi,

I suggest you try an alternative strategy.
That altenrative strategy is twofold, just like you have
quiz' and quiz'.
This alternate strategy avoid pattern matching on strings
(which would be cumbersome for a bit more complex syntax).

So you have to write two functions :
one try to parse an 'id:' from the string.
It either succeed and returns the Int value of
the id, or it fails. You can use Either to encode
success and failure. Furthermore that function has
to return the remaining string (which is the same
as received upon failure).

The second function do a similar thing, this time
failing on 'id:'. (And it still returns alos the remainstring).

If you're familiar with the State monad, you can
write the above two functions by using the string
as the state.

Now, given those two functions, try to apply them
on your input string, feeding the next function application
with the resulting string of the current application.

What I proposed here is the very basics of a natural and
very used parsing technique (google for parser combinators).
That technic will scale well for more complex inputs, and,
I believe, should provide you with sufficient performance.

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


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-11 Thread Martijn van Steenbergen
I'd love that. I've been wanting this for a while, at least 
subconsciously. Thanks for making it explicit. :-)



Peter Verswyvelen wrote:

When I put

{-# OPTIONS_GHC -Wall -Werror #-}

in my source file, I don't get compiler (GHC) warnings about redundant 
language extensions that I enabled.


It would be nice if the compiler gave warnings about this, since after 
refactoring, some language extensions might not be needed anymore, and 
hence should be removed since fewer language extensions mean more stable 
and portable code no?


What do you think?




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


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


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-11 Thread Creighton Hogg
2009/3/11 Peter Verswyvelen :
> When I put
> {-# OPTIONS_GHC -Wall -Werror #-}
> in my source file, I don't get compiler (GHC) warnings about redundant
> language extensions that I enabled.
> It would be nice if the compiler gave warnings about this, since after
> refactoring, some language extensions might not be needed anymore, and hence
> should be removed since fewer language extensions mean more stable and
> portable code no?
> What do you think?

So you mean something like if you put {-# LANGUAGE
GeneralizedNewtypeDeriving #-} in a file, but never do newtype
deriving, it would warn you?

I have no idea how hard that'd be to implement, but that sounds kind
of cool.  Useful for both refactoring and when you've inherited old
code.

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


Re: [Haskell-cafe] ByteString in patterns

2009-03-11 Thread Manlio Perillo

Don Stewart ha scritto:

manlio_perillo:

Don Stewart ha scritto:

[...]
{-# LANGUAGE OverloadedStrings #-}

import qualified Data.ByteString.Char8 as C

isMatch :: C.ByteString -> Bool
isMatch "match" = True
isMatch _   = False

main = print . map isMatch . C.lines =<< C.getContents

What is the reason why instance declarations for IsString class are not  
defined for available ByteStrings?


I need to define it by myself.


They're exported from Data.ByteString.Char8



Then there is something I'm missing.
Your code does not compile.



Thanks  Manlio Perillo

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


[Haskell-cafe] Request: warn about language extensions that are not used

2009-03-11 Thread Peter Verswyvelen
When I put

{-# OPTIONS_GHC -Wall -Werror #-}

in my source file, I don't get compiler (GHC) warnings about redundant
language extensions that I enabled.

It would be nice if the compiler gave warnings about this, since after
refactoring, some language extensions might not be needed anymore, and hence
should be removed since fewer language extensions mean more stable and
portable code no?

What do you think?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] advice on a parsing function

2009-03-11 Thread Manlio Perillo

Hi.

I'm still working on the Netflix Prize; now I have managed to implement 
a parsing function for the qualifying data set (or quiz set).


The quiz set is in the format:

1:
10
20
30
2:
100
200
3:
1000
2000
3000
4000
5000


Where 1, 2, 3 are movie ids, and the others are user ids.

The parsing program is at:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2300


The program reads the file using lazy IO.
One of the feature I want is, for the quiz function, to be a *good 
producer*.


I'm quite satisfied with the result (this is the first "complex" parsing 
function I have written in Haskell), and I have also managed to avoid 
the use of an accumulator.


However I'm interested to know it there is a more efficient solution.


The qualifying.txt file is 51MB, 2834601 lines.

On my laptop, the function performance are:

real1m14.117s
user0m2.496s
sys 0m0.136s

CPU usage is about 3%,
system load is about 0.20,
memory usage is 4956 KB.


What I'm worried about is:

quiz' ((id, ":") : l) = (id, quiz'' l) : quiz' l
quiz' ((id, _) : l) = quiz' l


the problem here is that the same elements in the list are processed 
multiple times.



I have written alternate versions.
The first using foldl
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2303
(that, however, builds the entire data structure in memory, and in 
reverse order)


The latter using foldr
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2304
(that, however, is incorrect and I'm unable to fix).


The performances of the foldr version are very similar to the 
performances of the first implementation (it make use, however, of 3704 
KB, and it is about 3 seconds faster).




P.S:
the expected result for the sample quiz set I have posted is:
[(1,[10,20,30]),(2,[100,200]),(3,[1000,2000,3000,4000,5000])]

The foldl version produces:
[(3,[5000,4000,3000,2000,1000]),(2,[200,100]),(1,[30,20,10])]

The foldr version produces:
[(1,[]),(2,[10,20,30]),(3,[100,200]),(5000,[1000,2000,3000,4000])]




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


Re: [Haskell-cafe] QC 2.0 missing some stuff I need

2009-03-11 Thread Max Bolingbroke
Hi John,

I also had this problem when adding a QuickCheck 2 provider to
test-framework 
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/test-framework-quickcheck2).
In the end I had to copy considerable portions of the QuickCheck2 code
into the provider because there seems to be no pure interface at all
:-(. This is especially important for test-framework because it may
use threading to run several tests simultaneously, and you don't
really want output from multiple tests interleaved on the console.

Actually, despite copying a large chunk of QC2 into the provider I
/still/ didn't entirely stop it from writing to the console, so failed
QC2 properties running under test-framework write the arguments to the
properties that demonstrate failure BEFORE the message telling you the
property has failed! Upsetting, but I had to draw the line at copying
code somewhere.

Cheers,
Max

2009/3/11 John Goerzen :
> Hi,
>
> QuickCheck 1.x had this function:
>
> evaluate :: Testable a => a -> Gen Result
>
> which I used in TestPack to help wrap a QuickCheck test as a HUnit
> test case.  QuickCheck 2.x seems to have no pure evaluate-like
> function at all; all of its functions are in the IO monad and also
> write their result to stdout, according to the docs.  Am I missing
> something?
>
> Thanks,
>
> -- John
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Using FosSyDe to translate haskell to VHDL.

2009-03-11 Thread wanghanyi

Hey Matthijs
 Thanks for replying, and that might help. I will try with it to see if it 
works, and I am still looking for the answer myself. If there is anyone has 
worked with the Haskell to VHDL translater, plz let me know cause I have many 
to discuss.

Thanks

 

Hanyi  
 
> Date: Tue, 10 Mar 2009 20:23:57 +0100
> From: matth...@stdin.nl
> To: wanghany...@hotmail.com
> CC: haskell-cafe@haskell.org
> Subject: Re: [Haskell-cafe] Using FosSyDe to translate haskell to VHDL.
> 
> Hi Hany,
> 
> > *Plus2> writeVHDL plus2SysDef
> > *** Exception: VHDL Compilation Error: Untranslatable function: where 
> > constructs are not supported in functions:
> > where addOnef_0 = n_1 GHC.Num.+ 1
> > in process function `addTwof' (created in Plus2) used by process 
> > `plus2Proc' belonging to system definition `plus2' (created in )
> I don't know much about ForSyDe, but it seems that where clauses simply aren't
> supported. Perhaps let expressions are?
> 
> The would mean something like the following:
> 
> addTwof :: ProcFun (Int32 -> Int32)
> addTwof = $(newProcFun [d|addTwof :: Int32 -> Int32
> let addOnef = n +1 in
> addTwof n = addOnef+1
> |])
> 
> (Not sure if this is completely valid code, I'm not too familiar with TH..).
> 
> Gr.
> 
> Matthijs


_
MSN安全保护中心,免费修复系统漏洞,保护MSN安全!
http://im.live.cn/safe/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread Hugo Pacheco
I have previously thought of something like this, when the initial
idea for a sloth was suggested:

> I like the ideia, and could imagine something like this:
> http://i41.tinypic.com/se65ux.jpg
>
> Sorry for the bad drawing and scanning quality. If someone likes the ideia, 
> I'm sure
> they can do much better than me :)
>
> hugo

On Wed, Mar 11, 2009 at 1:52 PM, Deniz Dogan  wrote:
> 2009/3/11 minh thu :
>> 2009/3/11 Bulat Ziganshin :
>>> Hello Wolfgang,
>>>
>>> Wednesday, March 11, 2009, 1:06:37 PM, you wrote:
>>>
> Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
> they're so freaking cute... :)
>>>
 Same in German: The german “Faultier” means “lazy animal”.
>>>
>>> russian too, if that matter. i was really amazed by this idea.
>>> pure, lazy and fun! :)
>>
>> Same in french : 'paresseux' just means lazy.
>>
>> Thu
>
> In Swedish it translates to "late walker" (?) and in Turkish it's "lazy 
> animal".
>
> Deniz
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
www.di.uminho.pt/~hpacheco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QC 2.0 missing some stuff I need

2009-03-11 Thread John Goerzen
Hi,

QuickCheck 1.x had this function:

evaluate :: Testable a => a -> Gen Result

which I used in TestPack to help wrap a QuickCheck test as a HUnit
test case.  QuickCheck 2.x seems to have no pure evaluate-like
function at all; all of its functions are in the IO monad and also
write their result to stdout, according to the docs.  Am I missing
something?

Thanks,

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


Re: Re[2]: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread Deniz Dogan
2009/3/11 minh thu :
> 2009/3/11 Bulat Ziganshin :
>> Hello Wolfgang,
>>
>> Wednesday, March 11, 2009, 1:06:37 PM, you wrote:
>>
 Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
 they're so freaking cute... :)
>>
>>> Same in German: The german “Faultier” means “lazy animal”.
>>
>> russian too, if that matter. i was really amazed by this idea.
>> pure, lazy and fun! :)
>
> Same in french : 'paresseux' just means lazy.
>
> Thu

In Swedish it translates to "late walker" (?) and in Turkish it's "lazy animal".

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


[Haskell-cafe] ThreadScope: Request for features for the performance tuning of parallel and concurrent Haskell programs

2009-03-11 Thread Satnam Singh
Donnie Jones, Simon Marlow and I have been working on infrastructure for 
logging run-time events and a graphical viewer program called ThreadScope. 
Hopefully these features will make it into the next release of GHC. We hope the 
event-log viewer ThreadScope will be useful for the performance tuning of 
parallel and concurrent Haskell programs. You can see a few screen shots at the 
program's website http://raintown.org/threadscope

Before making the release I thought it would be an idea to ask people what 
other features people would find useful or performance tuning. So if you have 
any suggestions please do let us know!

Cheers,

Satnam Singh


Satnam Singh
Microsoft
7 JJ Thomson Avenue
Cambridge
CB3 0FB
United Kingdom

Email: satn...@microsoft.com
UK tel: +44 1223 479905
Fax: +44 1223 479 999
UK mobile: +44 7979 648412
USA cell: 206 330 1580
USA tel: 206 219 9024
URL: http://research.microsoft.com/~satnams
Live Messenger: sat...@raintown.org

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


Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-11 Thread Sean Leather
Hi Mark,

Because Haskell is not OO, it is functional, I was wondering if there is
> some kind of analogous “design pattern”/”template” type concept that
> describe commonly used functions that can be “factored out” in a general
> sense to provide the same kind of usefulness that Design Patterns do for
> OOP. Basically I’m asking if there are any kinds of “common denominator”
>  function compositions that are used again and again to solve problems. If
> so, what are they called?
>

Look at Jeremy Gibbons' publications. All of the ones that have "pattern" or
"origami" in the title describe design patterns in Haskell. Some of them
relate to the translation of Gang-of-Four patterns.

  http://www.comlab.ox.ac.uk/people/publications/date/Jeremy.Gibbons.html

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


[Haskell-cafe] Re: Design Patterns by Gamma or equivalent

2009-03-11 Thread Achim Schneider
"Mark Spezzano"  wrote:

> Basically I___m asking if there are any kinds of ___common denominator___
> function compositions that are used again and again to solve
> problems. If so, what are they called?
>
Haskellers tend to cast their design patterns into functions and
libraries. What they're supposed to be called is a zealously heated
discussion, there's, for example, 

return == pure == point 

and 

fmap == map == (.) == liftM [1]

OTOH, we're said to not care at all:

| Don't underrate Haskell programmers. The ones I know have the kind of
| minds where if you switched the names to pig latin, they wouldn't skip
| a beat.
-- [2]


If you're looking for a text that could be named "The N most
(use|success)ful Haskell Design Patterns", I recommend having a look at
the Typeclassopedia[3].



[1]well, at least there _could_ be. 
[2]http://www.mail-archive.com/bo...@lists.boost.org/msg08898.html
[3]http://byorgey.wordpress.com/2009/02/16/the-typeclassopedia-request-for-feedback/

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-11 Thread Robin Green
The concept of "design pattern" tends not to be used by Haskell
programmers - it brings a lot of baggage with it (like being formally
documented in a particular way, being "proven" by being used in
production several times, etc.) and it doesn't seem to be particularly
useful for us in this heavyweight form.

However, we do have a more lightweight concept of an "idiom" and
"idiomatic Haskell". See
http://www.haskell.org/haskellwiki/Category:Idioms (Not all of these
pages should probably be in this category, but it gives you an idea.)
-- 
Robin

On Wed, 11 Mar 2009 21:28:52 +1030
"Mark Spezzano"  wrote:

> Hi,
> 
>  
> 
> I’m very familiar with the concept of Design Patterns for OOP in Java
> and C++. They’re basically a way of fitting components of a program
> so that objects/classes fit together nicely like Lego blocks and it’s
> useful because it also provides a common “language” to talk about
> concepts, like Abstract Factory, or an Observer to other programmers.
> In this way one programmer can instantly get a feel what another
> programmer is talking about even though the concepts are
> fundamentally abstract.
> 
>  
> 
> Because Haskell is not OO, it is functional, I was wondering if there
> is some kind of analogous “design pattern”/”template” type concept
> that describe commonly used functions that can be “factored out” in a
> general sense to provide the same kind of usefulness that Design
> Patterns do for OOP. Basically I’m asking if there are any kinds of
> “common denominator” function compositions that are used again and
> again to solve problems. If so, what are they called?
> 
>  
> 
> Cheers,
> 
>  
> 
> Mark Spezzano
> 
>  
> 
>  
> 
> 
> No virus found in this outgoing message.
> Checked by AVG. 
> Version: 7.5.557 / Virus Database: 270.11.9/1993 - Release Date:
> 10/03/2009 7:19 AM
>  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread minh thu
2009/3/11 Bulat Ziganshin :
> Hello Wolfgang,
>
> Wednesday, March 11, 2009, 1:06:37 PM, you wrote:
>
>>> Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
>>> they're so freaking cute... :)
>
>> Same in German: The german “Faultier” means “lazy animal”.
>
> russian too, if that matter. i was really amazed by this idea.
> pure, lazy and fun! :)

Same in french : 'paresseux' just means lazy.

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


Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-11 Thread minh thu
2009/3/11 Mark Spezzano :
> Hi,
>
>
>
> I’m very familiar with the concept of Design Patterns for OOP in Java and
> C++. They’re basically a way of fitting components of a program so that
> objects/classes fit together nicely like Lego blocks and it’s useful because
> it also provides a common “language” to talk about concepts, like Abstract
> Factory, or an Observer to other programmers. In this way one programmer can
> instantly get a feel what another programmer is talking about even though
> the concepts are fundamentally abstract.
>
>
>
> Because Haskell is not OO, it is functional, I was wondering if there is
> some kind of analogous “design pattern”/”template” type concept that
> describe commonly used functions that can be “factored out” in a general
> sense to provide the same kind of usefulness that Design Patterns do for
> OOP. Basically I’m asking if there are any kinds of “common denominator”
>  function compositions that are used again and again to solve problems. If
> so, what are they called?

Hi,

A particular instance of what can replace the idea of design pattern is given
by this now famous post :
http://blog.sigfpe.com/2009/01/haskell-monoids-and-their-uses.html

You'll see that what 'speaks' to the haskell programmers, maybe in the
same way you
say design patterns speak to another oo programmer, is much more fitted to the
language in haskell. At a lower scale, the reusability of some simple
functions like fold or map
is reflected at a higher scale by the reusability of concepts like
monoids (whih 'exist' in
the language, as type classes, while a pattern doesn't).

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


Re: [Haskell-cafe] Against cuteness

2009-03-11 Thread minh thu
2009/3/11 Gregg Reynolds :
> On Wed, Mar 11, 2009 at 5:25 AM, Bulat Ziganshin 
> wrote:
>>
>> Hello Gregg,
>>
>> Wednesday, March 11, 2009, 1:17:41 PM, you wrote:
>>
>> > are not O'Reilly.  Of all the billions of images from all the
>> > cultures in the world available to us we can surely find something
>> > that is witty or charming without being cute.
>>
>> it will not be fun :)
>
> Perhaps not, but it also won't be torture.  I can't take any more cuteness.
> ;)
>

Let's use the tool of TMR cover on the sloth; laziness hammered !

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


[Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-11 Thread Mark Spezzano
Hi,

 

I’m very familiar with the concept of Design Patterns for OOP in Java and
C++. They’re basically a way of fitting components of a program so that
objects/classes fit together nicely like Lego blocks and it’s useful because
it also provides a common “language” to talk about concepts, like Abstract
Factory, or an Observer to other programmers. In this way one programmer can
instantly get a feel what another programmer is talking about even though
the concepts are fundamentally abstract.

 

Because Haskell is not OO, it is functional, I was wondering if there is
some kind of analogous “design pattern”/”template” type concept that
describe commonly used functions that can be “factored out” in a general
sense to provide the same kind of usefulness that Design Patterns do for
OOP. Basically I’m asking if there are any kinds of “common denominator”
function compositions that are used again and again to solve problems. If
so, what are they called?

 

Cheers,

 

Mark Spezzano

 

 


No virus found in this outgoing message.
Checked by AVG. 
Version: 7.5.557 / Virus Database: 270.11.9/1993 - Release Date: 10/03/2009
7:19 AM
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Against cuteness

2009-03-11 Thread Gregg Reynolds
On Wed, Mar 11, 2009 at 5:25 AM, Bulat Ziganshin
wrote:

> Hello Gregg,
>
> Wednesday, March 11, 2009, 1:17:41 PM, you wrote:
>
> > are not O'Reilly.  Of all the billions of images from all the
> > cultures in the world available to us we can surely find something
> > that is witty or charming without being cute.
>
> it will not be fun :)
>

Perhaps not, but it also won't be torture.  I can't take any more cuteness.
;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread Bulat Ziganshin
Hello Wolfgang,

Wednesday, March 11, 2009, 1:06:37 PM, you wrote:

>> Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
>> they're so freaking cute... :) 

> Same in German: The german “Faultier” means “lazy animal”.

russian too, if that matter. i was really amazed by this idea.
pure, lazy and fun! :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Against cuteness

2009-03-11 Thread Bulat Ziganshin
Hello Gregg,

Wednesday, March 11, 2009, 1:17:41 PM, you wrote:

> are not O'Reilly.  Of all the billions of images from all the
> cultures in the world available to us we can surely find something
> that is witty or charming without being cute.

it will not be fun :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-11 Thread Wolfgang Jeltsch
Am Dienstag, 10. März 2009 00:59 schrieb Joe Fredette:
> Hehe, I love it. Sloth is a synonym for Lazyness in English too, and
> they're so freaking cute... :) 

Same in German: The german “Faultier” means “lazy animal”.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FRP + physics / status of hpysics

2009-03-11 Thread Wolfgang Jeltsch
Am Samstag, 7. März 2009 18:49 schrieb Roman Cheplyaka:
> Great! I'll have more free time after March 15, and we can arrange an
> IRC meeting to discuss this.

I’d be happy if you would also invite me to this IRC meeting when it will 
finally happen.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [grapefruit] [reactive] FRP + physics / status of hpysics

2009-03-11 Thread Wolfgang Jeltsch
Am Freitag, 6. März 2009 17:57 schrieb Wolfgang Jeltsch:
> Am Freitag, 6. März 2009 17:51 schrieb Wolfgang Jeltsch:
> > By the way, the adress of the Grapefruit mailing list is
> > grapefr...@projects.haskell.org, not grapefr...@haskell.org.
>
> Oh, this is really strange: I addressed my e-mail to
> grapefr...@projects.haskell.org but the version arriving at the Reactive
> mailing list has grapefr...@haskell.org in its To: header. However, my
> e-mail also reached the Grapefruit mailing list (but Daniel Bünzli’s
> didn’t) and the version there has the correct address in its To: headers.
>
> Does anyone know who is responsible for the Haskell mail server?
>
> Best wishes,
> Wolfgang

It was a misconfiguration of the mailserver which is believed to be fixed now.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Generics Versus Parametric Polymorphism

2009-03-11 Thread Bulat Ziganshin
Hello porges,

Wednesday, March 11, 2009, 12:35:18 PM, you wrote:

> Most importantly (or awesomely?), every time Haskell infers the
> type of a function you've written, you get *the most generic possible* 
> version, for free :)

and using generics, you can get function polymorphic on *any* type
just for few pennies more :)))


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Against cuteness

2009-03-11 Thread Gregg Reynolds
Regarding logos/mascots:  nothing personal folks, but I would like to cast a
loud firm vote against all forms of cuteness, especially small furry animal
cuteness.  It's been done half to death, and we are not O'Reilly.  Of all
the billions of images from all the cultures in the world available to us we
can surely find something that is witty or charming without being cute.

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


Re: [Haskell-cafe] Generics Versus Parametric Polymorphism

2009-03-11 Thread Sean Leather
Hi Mark,

> Just wondering if Generics and Parametric polymorphism are one and the same
> in Haskell.
>
> I read (somewhere!) an article stating that generics might be included in
> Haskell Prime but I thought that they’re already included as parametric
> polymorphism.
>
To see the current status of Haskell Prime, visit the Trac page:

  http://hackage.haskell.org/trac/haskell-prime/

> Did I misread something? Or is generics in Haskell referring to something
> completely different.
>
I'm not sure which article you read, but there is a lot of ambiguity in the
term "generics." Depending on whom you talk to, it means a different thing.
But I can give you some pointers to where you can learn about many of the
possible interpretations.

The following paper gives a useful vocabulary for describing the different
types of "generics." Just by reading section 2 you can see how confusing it
is when so many techniques are referred to as generic programming. For
example, parametric polymorphism is an example of genericity by type here.
In the Haskell world, (as Don said) it's not considered generics, but in
Java (as Alp remarked), it's called generics.

  http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/dgp.pdf

There's a comparison paper from 2003 that presents language support for
generics in C++, ML, Haskell, Eiffel, Java, and C#. Things have changed a
bit since then, but it's an interesting read.

  http://ece-www.colorado.edu/~siek/pubs/comparing_generic_programming03.pdf

"Generics" in Haskell has come to be known as datatype-generic programming.
In the past, it has been labeled polytypism, structural polymorphism, or
typecase. This refers to the technique of writing functions or programs that
work for many types and have knowledge about the structure of the type
(mentioned by Bulat).

Generic Haskell is a (non-standard) language extension to Haskell. It was
used to explore the possibilities of datatype-generic programming (DGP) with
Haskell. The following paper compares varying approaches of DGP to Generic
Haskell.

  http://people.cs.uu.nl/johanj/publications/ComparingGP.pdf

In the last few years, people have seen the power of Haskell's type system,
and GHC has developed some interesting extensions to that type system. As a
result of this and the difficulty with maintaining language extensions
external to a compiler (e.g. Generic Haskell), libraries for DGP in Haskell
have become much more common and powerful. The following article compares a
large number of these libraries.


http://www.cs.uu.nl/wiki/Alexey/ComparingLibrariesForGenericProgrammingInHaskell

Lastly, since I started working in this area over a year ago, I've been
collecting references to published research. My citations are on CiteULike:

  http://www.citeulike.org/user/spl

There are tags for "generics" and "datatype-generic" that give you a
narrower view on the collection.

  http://www.citeulike.org/user/spl/tag/generics
  http://www.citeulike.org/user/spl/tag/datatype-generic

Hope this helps to answer your questions.

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


Re: [Haskell-cafe] Generics Versus Parametric Polymorphism

2009-03-11 Thread porges
2009/3/11 Bulat Ziganshin Hello Mark,

Wednesday, March 11, 2009, 9:11:42 AM, you wrote:

> Just wondering if Generics and Parametric polymorphism are one and the same in Haskell.

haskell Parametric polymorphism is the same type of thing as Java Generics :)
Most importantly (or awesomely?), every time Haskell infers the type of
a function you've written, you get *the most generic possible* version,
for free :)


signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: do nmergeIO or mergeIO preserve order?

2009-03-11 Thread ChrisK

Anatoly Yakovenko wrote:

do nmergeIO or mergeIO preserve order? or not preserve order?


If you have a list of operations "[IO a]" then the future package at

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/future

can do this.  It's 'forkPromises' function returns a "Chan a" which can be used 
to get the non-order preserving results (actually "Either SomeExcption a").  If 
you are feeling lucky you can use "getChanContents" and "filter" to get a lazy 
"[a]" which is the results as they are completed.


--
Chris

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


Re: [Haskell-cafe] Distributing Linux binaries

2009-03-11 Thread Ketil Malde
Lyle Kopnicky  writes:

> I tried to make a Debian package and couldn't figure it out,

Me too.  I don't know why .debs are so hard to get right, most if not
all the necessary information should be in the .cabal file.  Maybe I'm
overly naive here.

> but maybe that's overkill. 

I don't think so.  Don S. has more or less singlehandedly ported
all of Hackage to Arch Linux.  We really should have a central .deb
repository for Hackage that could serve as a basis for Debian-based
distributions as well as a more cutting-edge alternative for stuff
that is not yet in your favorite distro.

> GHC itself has some kind of tarball for the
> binary distributions, one for Debian and one for Red Hat. How would
> I make such a package and what would go into it? 

> There's only one executable, so it shouldn't be too complicated.

> I figure the main issue on Linux is that when you compile it, it's linked to
> specific shared libraries.

I often distribute binaries simply by distributing the executable
file. 

Usually, it will work on most contemporary Linuxes, and if it doesn't,
you often have compat packages of libraries that fixes it.  If you
in addition pass -optl-static to GHC, it will link - with some caveats
- statically, improving the chances of your binary working in
uncharted territories. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generics Versus Parametric Polymorphism

2009-03-11 Thread Bulat Ziganshin
Hello Mark,

Wednesday, March 11, 2009, 9:11:42 AM, you wrote:

> Just wondering if Generics and Parametric polymorphism are one and the same 
> in Haskell.

haskell Parametric polymorphism is the same type of thing as Java Generics :)

haskell Generics provides ability to define procedures polymorphic by
*any* data type with just a fixed number of definitions

there are at least dozen of various tools/libraries supporting
Generics in some way in haskell, so indeed we are interested to have
at least one with guaranteed availability

google for "scrap your boilerplate" paper for a description of one of
the most popular Generics implementation


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Generics Versus Parametric Polymorphism

2009-03-11 Thread Alp Mestan
>
> Parametric polymorphism is kinda boring in Haskell -- since it's been
> there since the beginning.
>
> We tend to reserve the term "generics" for higher order, and fancier,
> polymorphism. These kinds of things:
>
>http://hackage.haskell.org/packages/archive/pkg-list.html#cat:generics
>
> -- Don
>

I think he was refering to "Java Generics", this kind of things.
Java's generics are much less powerful than parametric polymorphism in
Haskell.

-- 
Alp Mestan
In charge of the C++ section on Developpez.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe