[Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-03 Thread Kevin Jardine
I had a situation where I had some related types that all had toString
functions.

Of course in Haskell, lists all have to be composed of values of
exactly the same type, so instead of passing around lists of values
with these related types, I created a polyvariadic function
polyToString so that I could write:

(polyToString value1 value2 value3 ... valueN)

which would then become a list of strings:

[toString value1, toString value2, ... , toString valueN]

I finally figured out how to do this, but it was a bit harder to
figure this out than I expected, and I was wondering if it might be
possible to create a small utility library to help other developers do
this.

It seems to me that in the general case, we would be dealing with a
Monoid rather than a list of strings. We could have a toMonoid
function and then return

polyToMonoid value1 value2 ... valueN =

(toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid
valueN)

So anyone who wanted to convert a bunch of values of different types
to a Monoid  could easily pass them around using polyToMonoid so long
as they defined the appropriate toMonoid function.

Basically, a generalised list.

So I tried writing the following code but GHC said it had undecidable
instances.

Has this ever been done successfully?

class Monoidable a where
toMonoid :: Monoid r = a - r

polyToMonoid :: (Monoidable a, Monoid r) = a - r
polyToMonoid k = polyToMonoid' k mempty

class PolyVariadic p where
polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

instance Monoid r = PolyVariadic r where
polyToMonoid' k ss = (toMonoid k) `mappend` ss

instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
ss)

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


Re: [Haskell-cafe] A parsec question

2010-10-03 Thread Stephen Tetley
Does this one give the expected error message for Parsec3.1 -
unfortunately I can't test as I'm still using Parsec 2.1.0.1.

 parser = block (many digit ? digit)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Non-existing types in existential quantification?

2010-10-03 Thread Henning Thielemann


On Sun, 3 Oct 2010, Ben Franksen wrote:


Christopher Done wrote:


Consider the following program:

main = putStrLn $ show $ length [undefined :: a,undefined :: b]

A concrete type of the element in list doesn't need to be determined
at runtime, or any time. a unifies with b, and that unifies with x in
length :: [x] - Int.


A simpler example is

 main = print Nothing


This seems to be a different example, because GHCi -Wall says that the 
type variable defaults to (). Thus 'Nothing' has monomorphic type at 
runtime. The difference is certainly that 'print' requires a Show 
instance, whereas Christopher's example does not require a type 
constraint.

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


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
On 3 October 2010 06:51, Michael Snoyman mich...@snoyman.com wrote:
 * Does pass.net still exist anywhere? Same for parallel web.

 I couldn't find any references to pass.net.

 http://www.haskell.org/haskellwiki/Web/Existing_software

I meant that I remember adding it, but I couldn't find any references
for it. I.e. it's dead. Maybe we can split that page by
active/inactive too.

 I would recommend *not* qualifying the active/recommended stuff. Maybe
 Frameworks and Frameworks/Inactive. I personally wouldn't want to
 group new, unevaluated code with inactive: I think we should give the
 new players the same publicity as the established products on the main
 page, but perhaps with a little label explaining how new/untested it
 is.

Trouble is most on the Web/Frameworks page are still /available/ but
it's hard to see if they're active i.e. people are still using them,
or whether they're still build-able. Perhaps it would be best to
create the Frameworks/Inactive page and then at the top of the
Frameworks page say Inactive frameworks are listed here. and then
when someone is definitely sure something is defunct they can move it.
Or what do we do?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Michael Snoyman
On Sun, Oct 3, 2010 at 11:59 AM, Christopher Done
chrisd...@googlemail.com wrote:
 On 3 October 2010 06:51, Michael Snoyman mich...@snoyman.com wrote:
 * Does pass.net still exist anywhere? Same for parallel web.

 I couldn't find any references to pass.net.

 http://www.haskell.org/haskellwiki/Web/Existing_software

 I meant that I remember adding it, but I couldn't find any references
 for it. I.e. it's dead. Maybe we can split that page by
 active/inactive too.

 I would recommend *not* qualifying the active/recommended stuff. Maybe
 Frameworks and Frameworks/Inactive. I personally wouldn't want to
 group new, unevaluated code with inactive: I think we should give the
 new players the same publicity as the established products on the main
 page, but perhaps with a little label explaining how new/untested it
 is.

 Trouble is most on the Web/Frameworks page are still /available/ but
 it's hard to see if they're active i.e. people are still using them,
 or whether they're still build-able. Perhaps it would be best to
 create the Frameworks/Inactive page and then at the top of the
 Frameworks page say Inactive frameworks are listed here. and then
 when someone is definitely sure something is defunct they can move it.
 Or what do we do?

I would actually do the opposite: we can put the libraries/frameworks
that we are sure *are* active into the Active section and put
everything else into Inactive. I have a feeling we'll be pretty close
on the mark with our guesses; a quick look at the last upload date on
Hackage should be sufficient. People are *much* more likely to move
stuff from Inactive to Active than the other way around.

We can also send out an email to the cafe/web-devel with a list of
packages we plan to mark as inactive and see if anyone objects. If no
one is willing to stand up for a package, odds are it's dead.

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


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
On 3 October 2010 12:10, Michael Snoyman mich...@snoyman.com wrote:
 I would actually do the opposite: we can put the libraries/frameworks
 that we are sure *are* active into the Active section and put
 everything else into Inactive. I have a feeling we'll be pretty close
 on the mark with our guesses; a quick look at the last upload date on
 Hackage should be sufficient. People are *much* more likely to move
 stuff from Inactive to Active than the other way around.

 We can also send out an email to the cafe/web-devel with a list of
 packages we plan to mark as inactive and see if anyone objects. If no
 one is willing to stand up for a package, odds are it's dead.

That sounds like a good approach. Anyway, it's not the end of the
world if a package gets put in inactive. Ones I know are definitely
active are:

Happstack
Haskell on a Horse
loli
Salvia
Snap
Yesod
Turbinado -- is this still active? Alson Kemp basically ditched Haskell, so...
Yesod

The others... I don't know.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Michael Snoyman
On Sun, Oct 3, 2010 at 12:20 PM, Christopher Done
chrisd...@googlemail.com wrote:
 On 3 October 2010 12:10, Michael Snoyman mich...@snoyman.com wrote:
 I would actually do the opposite: we can put the libraries/frameworks
 that we are sure *are* active into the Active section and put
 everything else into Inactive. I have a feeling we'll be pretty close
 on the mark with our guesses; a quick look at the last upload date on
 Hackage should be sufficient. People are *much* more likely to move
 stuff from Inactive to Active than the other way around.

 We can also send out an email to the cafe/web-devel with a list of
 packages we plan to mark as inactive and see if anyone objects. If no
 one is willing to stand up for a package, odds are it's dead.

 That sounds like a good approach. Anyway, it's not the end of the
 world if a package gets put in inactive. Ones I know are definitely
 active are:

 Happstack
 Haskell on a Horse
 loli
 Salvia
 Snap
 Yesod
 Turbinado -- is this still active? Alson Kemp basically ditched Haskell, so...
 Yesod

 The others... I don't know.


I think it's fair to say that turbinado is inactive. But keep in mind
that we should probably look at more than just the frameworks:
servers, templating, etc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
On 3 October 2010 12:31, Michael Snoyman mich...@snoyman.com wrote:
 I think it's fair to say that turbinado is inactive. But keep in mind
 that we should probably look at more than just the frameworks:
 servers, templating, etc.

Sure, it should be a general rule across the board.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: EDSL for Makefile

2010-10-03 Thread steffen
If you don't want to mention r1 explicitly, but want to refer to
target, sources and such only a monadic approach (e.g. Reader
Monad) might be what you want.

On Oct 3, 6:14 am, C K Kashyap ckkash...@gmail.com wrote:
  Thanks Emil ... yeah, that works...I was wondering what I could do to
  not have to mention r1 explicitly.
  I'll check out Neil's pdf and video now - perhaps I'll find answers there.

 I checked out the video - nice - but I think, understandably, since
 its not open source yet, not much of implementations details were
 mentioned.

 So, I have this unanswered question nagging in my head. In the
 example below, how can I let the makefile writer refer to the target
 name and dependencies. Likr Emil mentioned, I could use target r1
 but I want to avoid having to mention r1.

 http://hpaste.org/40233/haskell_makefile_edsl

 --
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: Non-existing types in existential quantification?

2010-10-03 Thread Daniel Fischer
On Sunday 03 October 2010 10:43:24, Henning Thielemann wrote:
 On Sun, 3 Oct 2010, Ben Franksen wrote:
  Christopher Done wrote:
  Consider the following program:
 
  main = putStrLn $ show $ length [undefined :: a,undefined :: b]
 
  A concrete type of the element in list doesn't need to be determined
  at runtime, or any time. a unifies with b, and that unifies with x in
  length :: [x] - Int.
 
  A simpler example is
 
   main = print Nothing

 This seems to be a different example, because GHCi -Wall says that the
 type variable defaults to (). Thus 'Nothing' has monomorphic type at
 runtime. The difference is certainly that 'print' requires a Show
 instance, whereas Christopher's example does not require a type
 constraint.

Yup.

Prelude print $ length [undefined :: a, undefined :: b]
2
Prelude print $ length [undefined :: a, undefined :: Num b = b]

interactive:1:32:
Warning: Defaulting the following constraint(s) to type `Integer'
 `Num a'
   arising from an expression type signature at 
interactive:1:32-54
In the expression: undefined :: (Num b) = b
In the first argument of `length', namely
`[undefined :: a, undefined :: (Num b) = b]'
In the second argument of `($)', namely
`length [undefined :: a, undefined :: (Num b) = b]'
2
Prelude print $ length [undefined :: a, undefined :: Num b = c - b]

interactive:1:32:
Warning: Defaulting the following constraint(s) to type `Integer'
 `Num b'
   arising from an expression type signature at 
interactive:1:32-59
In the expression: undefined :: (Num b) = c - b
In the first argument of `length', namely
`[undefined :: a, undefined :: (Num b) = c - b]'
In the second argument of `($)', namely
`length [undefined :: a, undefined :: (Num b) = c - b]'
2

At runtime, a type variable has to be either unconstrained or instantiated 
with a concrete type?

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


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-10-03 Thread Henning Thielemann
Andrew Coppin schrieb:

  On 30/09/2010 02:56 PM, Henning Thielemann wrote:

 In Cabal you can write one module per line and need no separator or
 terminator at all.
 
 Really? As far as I can tell, that doesn't work at all...

See e.g.

http://hackage.haskell.org/packages/archive/utility-ht/0.0.5.1/utility-ht.cabal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
I just discovered this:
http://www.haskell.org/haskellwiki/Performance/Strictness

See the Haskell Performance Resource box? That's great! I'm going to
make one for our Web articles.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] EDSL for Makefile

2010-10-03 Thread Neil Mitchell
 I checked out the video - nice - but I think, understandably, since
 its not open source yet, not much of implementations details were
 mentioned.

Yes, it's unfortunate.

 So, I have this unanswered question nagging in my head. In the
 example below, how can I let the makefile writer refer to the target
 name and dependencies. Likr Emil mentioned, I could use target r1
 but I want to avoid having to mention r1.

If it helps, written in Shake, this would be:

main = do
  want [file1]
  file1 * \x - do
need [file2]
putStrLn Hello
putStrLn World

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


Re: [Haskell-cafe] Re: Non-existing types in existential quantification?

2010-10-03 Thread Erik Hesselink
On Sun, Oct 3, 2010 at 14:10, Daniel Fischer daniel.is.fisc...@web.de wrote:
 On Sunday 03 October 2010 10:43:24, Henning Thielemann wrote:
 On Sun, 3 Oct 2010, Ben Franksen wrote:
  Christopher Done wrote:
  Consider the following program:
 
  main = putStrLn $ show $ length [undefined :: a,undefined :: b]
 
  A concrete type of the element in list doesn't need to be determined
  at runtime, or any time. a unifies with b, and that unifies with x in
  length :: [x] - Int.
 
  A simpler example is
 
   main = print Nothing

 This seems to be a different example, because GHCi -Wall says that the
 type variable defaults to (). Thus 'Nothing' has monomorphic type at
 runtime. The difference is certainly that 'print' requires a Show
 instance, whereas Christopher's example does not require a type
 constraint.

 Yup.

 Prelude print $ length [undefined :: a, undefined :: b]
 2
 Prelude print $ length [undefined :: a, undefined :: Num b = b]

 interactive:1:32:
    Warning: Defaulting the following constraint(s) to type `Integer'
             `Num a'
               arising from an expression type signature at
 interactive:1:32-54
    In the expression: undefined :: (Num b) = b
    In the first argument of `length', namely
        `[undefined :: a, undefined :: (Num b) = b]'
    In the second argument of `($)', namely
        `length [undefined :: a, undefined :: (Num b) = b]'
 2
 Prelude print $ length [undefined :: a, undefined :: Num b = c - b]

 interactive:1:32:
    Warning: Defaulting the following constraint(s) to type `Integer'
             `Num b'
               arising from an expression type signature at
 interactive:1:32-59
    In the expression: undefined :: (Num b) = c - b
    In the first argument of `length', namely
        `[undefined :: a, undefined :: (Num b) = c - b]'
    In the second argument of `($)', namely
        `length [undefined :: a, undefined :: (Num b) = c - b]'
 2

 At runtime, a type variable has to be either unconstrained or instantiated
 with a concrete type?

GHC has the 'Any' type, and the docs state:

It's also used to instantiate un-constrained type variables after
type checking. [1]

So I guess at least for GHC, all type variables are instantiated after
type checking?

Regards,

Erik

[1] 
http://www.haskell.org/ghc/docs/6.12.2/html/libraries/ghc-prim-0.2.0.0/GHC-Prim.html#t%3AAny
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: EDSL for Makefile

2010-10-03 Thread C K Kashyap
On Sun, Oct 3, 2010 at 5:22 PM, steffen steffen.sier...@googlemail.com wrote:
 If you don't want to mention r1 explicitly, but want to refer to
 target, sources and such only a monadic approach (e.g. Reader
 Monad) might be what you want.


Thanks Steffen ... would you be able to give me an example?

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


Re: [Haskell-cafe] EDSL for Makefile

2010-10-03 Thread C K Kashyap
Thanks Neil,

 main = do
  want [file1]
  file1 * \x - do
    need [file2]
    putStrLn Hello
    putStrLn World

What if I want to mention file1 only once?

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


Re[2]: [Haskell-cafe] EDSL for Makefile

2010-10-03 Thread Bulat Ziganshin
Hello C,

Sunday, October 3, 2010, 6:59:25 PM, you wrote:

 Thanks Neil,

 main = do
  want [file1]
  file1 * \x - do
    need [file2]
    putStrLn Hello
    putStrLn World

 What if I want to mention file1 only once?

mention_only_once file action = do
  want [file]
  file * action

main = mention_only_once file1 $ \x - do need [file2]
    putStrLn Hello
    putStrLn World




-- 
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] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
So I went through the Applications_and_libraries/Web_programming page
and pulled out any remaining goodness from it into pages under the
Web/ umbrella and then set it up as a redirect to Web/

I made an infobox which I put on every Web/ page, which makes it very
nice for navigating between the sections.

I also added a tiny introduction to the main page.
http://www.haskell.org/haskellwiki/Web

I also updated the Practical Web Programming in Haskell tutorial to
remove irrelevant/out-dated references and links, updated some bits,
and generally improved the formatting so that it's not just a huge
chunk of headings and whitespace:
http://www.haskell.org/haskellwiki/Web/Literature/Practical_web_programming_in_Haskell

I think on the Web/ page we should have a hot frameworks or
something like that, listing Happstack, Yesod and Snap, preferably
with their logos. Do you have a logo for Yesod? I'm thinking of just
tastefully taking the cube.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Michael Snoyman
On Sun, Oct 3, 2010 at 5:33 PM, Christopher Done
chrisd...@googlemail.com wrote:
 So I went through the Applications_and_libraries/Web_programming page
 and pulled out any remaining goodness from it into pages under the
 Web/ umbrella and then set it up as a redirect to Web/

 I made an infobox which I put on every Web/ page, which makes it very
 nice for navigating between the sections.

 I also added a tiny introduction to the main page.
 http://www.haskell.org/haskellwiki/Web

 I also updated the Practical Web Programming in Haskell tutorial to
 remove irrelevant/out-dated references and links, updated some bits,
 and generally improved the formatting so that it's not just a huge
 chunk of headings and whitespace:
 http://www.haskell.org/haskellwiki/Web/Literature/Practical_web_programming_in_Haskell

 I think on the Web/ page we should have a hot frameworks or
 something like that, listing Happstack, Yesod and Snap, preferably
 with their logos. Do you have a logo for Yesod? I'm thinking of just
 tastefully taking the cube.


Well done, it all looks *very* nice. Regarding Yesod: yes, use the
cube for now, I may eventually make a better logo, but that's it for
the moment. The only concern I have is the practical web programming
in Haskell page, which frankly isn't very practical. I personally
would put a big fat warning at the top saying most people do not
recommend using straight CGI these days.

One other possibility is putting together a tutorials section
(descending order by date) linking to various blog posts. But I think
you've done an amazing job on cleaning things up and getting it
presentable. A big thank you!

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


Re: [Haskell-cafe] I still cannot seem to get a GUI working under Windows.

2010-10-03 Thread Steve Schafer
On Fri, 01 Oct 2010 13:45:00 +0100, you wrote:

I think that the issue is that making things better on Windows (and
likely OS X as well) requires co-ordinated and agreed action across a
number of areas. This means getting a moderate number of people, most
of whom give up their time and effort for free, and for the good of the
community, to agree on what is needed and to prioritize it in a
co-ordinated way. The action needed by any individual might be
relatively small, but without community agreement and action, the end
goal cannot be achieved.

Thank you. That's basically what I was trying to say: The project is too
big for one person, or a small group of people. But it also can't happen
unless there's a shared understanding of what is important and why it is
important, and that's what seems to be lacking here.

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


Re: [Haskell-cafe] Re: I still cannot seem to get a GUI working under Windows.

2010-10-03 Thread Steve Schafer
On Sat, 2 Oct 2010 11:02:21 -0700, you wrote:

I imagine someone looking at a lovely app and saying, Wow -- great
interface!  I bet it was programmed in Haskell.

While I can agree with the sentiment...well, good luck with that. ;-)

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


[Haskell-cafe] Re: Haskell web development entries on the Wiki

2010-10-03 Thread Christopher Done
On 3 October 2010 17:41, Michael Snoyman mich...@snoyman.com wrote:
 Well done, it all looks *very* nice. Regarding Yesod: yes, use the
 cube for now, I may eventually make a better logo, but that's it for
 the moment.

Righteo.

 The only concern I have is the practical web programming
 in Haskell page, which frankly isn't very practical. I personally
 would put a big fat warning at the top saying most people do not
 recommend using straight CGI these days.

Yeah, it's not the best.

 One other possibility is putting together a tutorials section
 (descending order by date) linking to various blog posts.

There is the http://www.haskell.org/haskellwiki/Web/Literature
labelled Literature (research, talks and blogs) section which
contains blog posts, but perhaps a tutorial-centric page would be in
order.

Really we should link to a yesod, snap, happstack tutorial and cgi on
the first page, I think.

 But I think
 you've done an amazing job on cleaning things up and getting it
 presentable. A big thank you!

Cheers! I'm looking forward to when the new Wiki version and template
is rolled out. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Big Arrays

2010-10-03 Thread Henry Laxen
Dear Group,

I am trying to create a (relatively) big array, 
but it seems I cannot make anything larger 
than 2^30 or so.  Here is the code:

import Data.Word
import Data.Array.Unboxed
import Control.Monad.ST
import Data.Array.ST
import Control.Exception
import Prelude hiding (catch)


t1 :: Word64 - UArray Word64 Bool
t1 size = runSTUArray 
  (do a - newArray (0,size) True
 :: ST s (STUArray s Word64 Bool)
  writeArray a 0 False
  return a)

catchArrayException x = do
  let err = show (x :: SomeException)
  putStrLn $ Exception [ ++ err ++ ]
  return ()   

main = do
  let a1 = t1 (2^30)
  a2 = t1 (2^31)
  a3 = t1 (2^32)
  catch (print $ (a1!0,a1!1)) catchArrayException
  catch (print $ (a2!0,a2!1)) catchArrayException
  catch (print $ (a3!0,a3!1)) catchArrayException
  

This results in:
*Main GOA main
(False,True)
(Exception [Negative range size]
(False,Exception [Error in array index; 1 not in range [0..1)]

It looks like array ranges can only be Ints, and not Int64 or Word64 types.  
Any pointers would be appreciated.
Best wishes,
Henry Laxen



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


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread Bulat Ziganshin
Hello Henry,

Sunday, October 3, 2010, 7:54:49 PM, you wrote:

 It looks like array ranges can only be Ints, and not Int64 or Word64 types.

yes, it's Int internally got efficiency reasons. you can do your own
implementation to override this limit :)


-- 
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] Re: A parsec question

2010-10-03 Thread Ben Franksen
Stephen Tetley wrote:
 Does this one give the expected error message for Parsec3.1 -
 unfortunately I can't test as I'm still using Parsec 2.1.0.1.
 
 parser = block (many digit ? digit)

Unfortunately, no.

Cheers
Ben

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


[Haskell-cafe] Re: Re: Non-existing types in existential quantification?

2010-10-03 Thread Ben Franksen
Henning Thielemann wrote:
 On Sun, 3 Oct 2010, Ben Franksen wrote:
 Christopher Done wrote:

 Consider the following program:

 main = putStrLn $ show $ length [undefined :: a,undefined :: b]

 A concrete type of the element in list doesn't need to be determined
 at runtime, or any time. a unifies with b, and that unifies with x in
 length :: [x] - Int.

 A simpler example is

  main = print Nothing
 
 This seems to be a different example, because GHCi -Wall says that the
 type variable defaults to (). Thus 'Nothing' has monomorphic type at
 runtime. The difference is certainly that 'print' requires a Show
 instance, whereas Christopher's example does not require a type
 constraint.

Right. I always forget about defaulting. This is an obscure feature of the
language.

Are there any programs that rely on defaulting and could not be easily
re-written so as not to?

Cheers
Ben

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


[Haskell-cafe] A question regarding cmdargs package

2010-10-03 Thread Ben Franksen
How can I disable the standard arguments 'help' and 'version'?

Cheers

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


[Haskell-cafe] Haskell Helper

2010-10-03 Thread Eduardo Ribeiro
Hello,
I 'm developing a new language in haskell and I need someone to help me. Anyone 
would like to help?




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


Re: [Haskell-cafe] Haskell Helper

2010-10-03 Thread Daniel Peebles
Is the language secret? because I'm sure lots of people would like to help
on this mailing list, but you'd need to tell us what help you need first :)

On Sun, Oct 3, 2010 at 8:38 PM, Eduardo Ribeiro asaferibei...@ymail.comwrote:

 Hello,
 I 'm developing a new language in haskell and I need someone to help me.
 Anyone
 would like to help?




 ___
 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: Haskell Helper

2010-10-03 Thread c8h10n4o2

No, it is not secret. I'm having trouble to define functions. Take a look at
my code(please be gentle)
http://haskell.1045720.n5.nabble.com/file/n3100036/hai1.hs hai1.hs 
-- 
View this message in context: 
http://haskell.1045720.n5.nabble.com/Haskell-Helper-tp3093854p3100036.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-03 Thread Luke Palmer
On Sun, Oct 3, 2010 at 1:24 AM, Kevin Jardine kevinjard...@gmail.com wrote:
 I had a situation where I had some related types that all had toString
 functions.

 Of course in Haskell, lists all have to be composed of values of
 exactly the same type, so instead of passing around lists of values
 with these related types, I created a polyvariadic function
 polyToString so that I could write:

 (polyToString value1 value2 value3 ... valueN)

 which would then become a list of strings:

 [toString value1, toString value2, ... , toString valueN]

First of all, you are not using the monoidal structure of String at
all.  This trick ought to work for any type whatsoever -- you're just
throwing them in a list.

Other than a few brackets, commas, and a repeated identifier (which
you can let-bind to shorten), what benefit is it giving you?  I
strongly recommend against polyvariadic functions.  While you get a
little bit of notational convenience, you lose composability.  There
are pains when you try to write a function that takes a polyvariadic
function as an argument, or when you try to feed the function values
from a list, etc.  The mechanisms to create polyvariadic functions are
brittle and hacky (eg. you cannot have a polymorphic return type, as
you want in this case).

Since all your values are known statically, I would recommend biting
the bullet and doing it the way you were doing it.

[ s value1, s value2, s value3, ... ]
   where
   s x = toString x

(I had to eta expand s so that I didn't hit the monomorphism restriction)

When you want to be passing around heterogeneous lists, it usually
works to convert them before you put them in the list, like you were
doing.

 I finally figured out how to do this, but it was a bit harder to
 figure this out than I expected, and I was wondering if it might be
 possible to create a small utility library to help other developers do
 this.

 It seems to me that in the general case, we would be dealing with a
 Monoid rather than a list of strings. We could have a toMonoid
 function and then return

 polyToMonoid value1 value2 ... valueN =

 (toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid
 valueN)

 So anyone who wanted to convert a bunch of values of different types
 to a Monoid  could easily pass them around using polyToMonoid so long
 as they defined the appropriate toMonoid function.

 Basically, a generalised list.

 So I tried writing the following code but GHC said it had undecidable
 instances.

 Has this ever been done successfully?

 class Monoidable a where
    toMonoid :: Monoid r = a - r

 polyToMonoid :: (Monoidable a, Monoid r) = a - r
 polyToMonoid k = polyToMonoid' k mempty

 class PolyVariadic p where
    polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

 instance Monoid r = PolyVariadic r where
    polyToMonoid' k ss = (toMonoid k) `mappend` ss

 instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
    polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
 ss)

 ___
 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] Polyvariadic functions operating with a monoid

2010-10-03 Thread Luke Palmer
On Sun, Oct 3, 2010 at 1:26 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Sun, Oct 3, 2010 at 1:24 AM, Kevin Jardine kevinjard...@gmail.com wrote:
 I had a situation where I had some related types that all had toString
 functions.

 Of course in Haskell, lists all have to be composed of values of
 exactly the same type, so instead of passing around lists of values
 with these related types, I created a polyvariadic function
 polyToString so that I could write:

 (polyToString value1 value2 value3 ... valueN)

 which would then become a list of strings:

 [toString value1, toString value2, ... , toString valueN]

 First of all, you are not using the monoidal structure of String at
 all.  This trick ought to work for any type whatsoever -- you're just
 throwing them in a list.

Oops, sorry for not reading your message more closely.  You were
indeed talking about the monoidal structure of list.  So... nevermind
about this comment.  :-P

 Other than a few brackets, commas, and a repeated identifier (which
 you can let-bind to shorten), what benefit is it giving you?  I
 strongly recommend against polyvariadic functions.  While you get a
 little bit of notational convenience, you lose composability.  There
 are pains when you try to write a function that takes a polyvariadic
 function as an argument, or when you try to feed the function values
 from a list, etc.  The mechanisms to create polyvariadic functions are
 brittle and hacky (eg. you cannot have a polymorphic return type, as
 you want in this case).

 Since all your values are known statically, I would recommend biting
 the bullet and doing it the way you were doing it.

    [ s value1, s value2, s value3, ... ]
       where
       s x = toString x

 (I had to eta expand s so that I didn't hit the monomorphism restriction)

 When you want to be passing around heterogeneous lists, it usually
 works to convert them before you put them in the list, like you were
 doing.

 I finally figured out how to do this, but it was a bit harder to
 figure this out than I expected, and I was wondering if it might be
 possible to create a small utility library to help other developers do
 this.

 It seems to me that in the general case, we would be dealing with a
 Monoid rather than a list of strings. We could have a toMonoid
 function and then return

 polyToMonoid value1 value2 ... valueN =

 (toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid
 valueN)

 So anyone who wanted to convert a bunch of values of different types
 to a Monoid  could easily pass them around using polyToMonoid so long
 as they defined the appropriate toMonoid function.

 Basically, a generalised list.

 So I tried writing the following code but GHC said it had undecidable
 instances.

 Has this ever been done successfully?

 class Monoidable a where
    toMonoid :: Monoid r = a - r

 polyToMonoid :: (Monoidable a, Monoid r) = a - r
 polyToMonoid k = polyToMonoid' k mempty

 class PolyVariadic p where
    polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

 instance Monoid r = PolyVariadic r where
    polyToMonoid' k ss = (toMonoid k) `mappend` ss

 instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
    polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
 ss)

 ___
 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] Suggestions for improvement

2010-10-03 Thread N. Raghavendra
I am reading the book `The Haskell Road to Math, Logic,   One of
the exercises in the first chapter asks for a function that maps a
string abcd to abbccc and bang! to baannn!.  Since
such a function f fixes the empty word, and maps wa to
f(w)a^(length(w)+1) for any word w and any letter a, I came up with the
following solution:

-- Map abcd to abbccc and bang! to baannn!.
blowup :: String - String
blowup [] = []
blowup x = blowup (allButLast x) ++ lastToTheLength x

-- Map abcd to abc.
allButLast :: String - String
allButLast [] = []
allButLast [x] = []
allButLast (x : xs) = x : allButLast xs

-- Map abcd to d^4 = .
lastToTheLength :: String - String
lastToTheLength [] = []
lastToTheLength [x] = [x]
lastToTheLength (_ : xs) = lastToTheLength xs ++ [last xs]

One question I have is whether I can eliminate points in the above
definition of blowup, and write something like

blowup = (++) . (blowup . allButLast, lastToTheLength)

thinking of (++) as a function String x String - String.  Also, I can't
figure out whether it is possible to get a shorter solution using fold.
I have tried Hlint on my file, but it gave no suggestions.

I am sure there are better ways, and would like some pointers and any
general suggestions for improvement.

Thanks and regards,
Raghavendra.

-- 
N. Raghavendra ra...@mri.ernet.in | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread Antoine Latter
On Sun, Oct 3, 2010 at 11:18 AM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Henry,

 Sunday, October 3, 2010, 7:54:49 PM, you wrote:

 It looks like array ranges can only be Ints, and not Int64 or Word64 types.

 yes, it's Int internally got efficiency reasons. you can do your own
 implementation to override this limit :)


A good place to start when rolling your own is the primitive
package[1] on Hackage. It is intimately tied to GHC, however.

Antoine

[1] http://hackage.haskell.org/package/primitive
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Polyvariadic functions operating with a monoid

2010-10-03 Thread Kevin Jardine
Luke, I had no idea polyvariadic functions would be controversial.

Yes, in my original case the function would be trivial:

toMonoid k =  [toString k]

I do prefer the less cluttered look. I think that

(poly value1 value2 value3)

is easier to follow when the values are all of related types (in my
case, all in the same type class).

But in the more general Monoid case there would not necessarily be a
list result.

Eg.

sumOf 1 2 3

could also be implemented using a Monoid approach with mempty = 0 and
mappend = +

Kevin

On Oct 3, 9:30 pm, Luke Palmer lrpal...@gmail.com wrote:
 On Sun, Oct 3, 2010 at 1:26 PM, Luke Palmer lrpal...@gmail.com wrote:
  On Sun, Oct 3, 2010 at 1:24 AM, Kevin Jardine kevinjard...@gmail.com 
  wrote:
  I had a situation where I had some related types that all had toString
  functions.

  Of course in Haskell, lists all have to be composed of values of
  exactly the same type, so instead of passing around lists of values
  with these related types, I created a polyvariadic function
  polyToString so that I could write:

  (polyToString value1 value2 value3 ... valueN)

  which would then become a list of strings:

  [toString value1, toString value2, ... , toString valueN]

  First of all, you are not using the monoidal structure of String at
  all.  This trick ought to work for any type whatsoever -- you're just
  throwing them in a list.

 Oops, sorry for not reading your message more closely.  You were
 indeed talking about the monoidal structure of list.  So... nevermind
 about this comment.  :-P



  Other than a few brackets, commas, and a repeated identifier (which
  you can let-bind to shorten), what benefit is it giving you?  I
  strongly recommend against polyvariadic functions.  While you get a
  little bit of notational convenience, you lose composability.  There
  are pains when you try to write a function that takes a polyvariadic
  function as an argument, or when you try to feed the function values
  from a list, etc.  The mechanisms to create polyvariadic functions are
  brittle and hacky (eg. you cannot have a polymorphic return type, as
  you want in this case).

  Since all your values are known statically, I would recommend biting
  the bullet and doing it the way you were doing it.

     [ s value1, s value2, s value3, ... ]
        where
        s x = toString x

  (I had to eta expand s so that I didn't hit the monomorphism restriction)

  When you want to be passing around heterogeneous lists, it usually
  works to convert them before you put them in the list, like you were
  doing.

  I finally figured out how to do this, but it was a bit harder to
  figure this out than I expected, and I was wondering if it might be
  possible to create a small utility library to help other developers do
  this.

  It seems to me that in the general case, we would be dealing with a
  Monoid rather than a list of strings. We could have a toMonoid
  function and then return

  polyToMonoid value1 value2 ... valueN =

  (toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid
  valueN)

  So anyone who wanted to convert a bunch of values of different types
  to a Monoid  could easily pass them around using polyToMonoid so long
  as they defined the appropriate toMonoid function.

  Basically, a generalised list.

  So I tried writing the following code but GHC said it had undecidable
  instances.

  Has this ever been done successfully?

  class Monoidable a where
     toMonoid :: Monoid r = a - r

  polyToMonoid :: (Monoidable a, Monoid r) = a - r
  polyToMonoid k = polyToMonoid' k mempty

  class PolyVariadic p where
     polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

  instance Monoid r = PolyVariadic r where
     polyToMonoid' k ss = (toMonoid k) `mappend` ss

  instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
     polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
  ss)

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Suggestions for improvement

2010-10-03 Thread Dominique Devriese
 One question I have is whether I can eliminate points in the above
 definition of blowup, and write something like

blowup = (++) . (blowup . allButLast, lastToTheLength)

 thinking of (++) as a function String x String - String.

Actually (++) is of type String - String - String. When you want
something of the type you mean (you normally write that as (String,
String) - String in Haskell, then you can use (uncurry (++)).

Additionally, you can't combine the functions (blowup . allButLast)
and lastToTheLength into a function that returns a pair like you seem
to attempt. You need a function like the following for that:

comma :: (a - b) - (a - c) - a - (b,c)
comma f g x = (f x, g x)

Then you could say:

blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

Ignore this if you haven't read about Applicative or type classes yet,
but using the Applicative instance for arrow types (-) a, you can
also write

comma = liftA2 (,)

or

blowup = (uncurry (++)) . liftA2 (,) (blowup . allButLast) lastToTheLength

 Also, I can't
 figure out whether it is possible to get a shorter solution using fold.
 I have tried Hlint on my file, but it gave no suggestions.

 I am sure there are better ways, and would like some pointers and any
 general suggestions for improvement.

By the way, shorter is not always better. Trying to recognize
abstraction patterns in your code is never a bad thing though.

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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Gregory Crosswhite

 On 10/3/10 1:45 PM, Dominique Devriese wrote:

Additionally, you can't combine the functions (blowup . allButLast)
and lastToTheLength into a function that returns a pair like you seem
to attempt. You need a function like the following for that:

comma :: (a -  b) -  (a -  c) -  a -  (b,c)
comma f g x = (f x, g x)

Then you could say:

blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength


It is worth noting that such a function already exists in the standard 
libraries;  it is the  operator in Control.Arrow:


blowup = uncurry (++) . (blowup . allButLast  lastToTheLength)

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


Re: [Haskell-cafe] Haskell Platform, Hackage and Cabal : The 2nd Year : Status Report

2010-10-03 Thread Ketil Malde
Matthias Kilian k...@outback.escape.de writes:

 http://www.vimeo.com/15462768

 And is there any way to just *download* the video? For people not
 using adobe flash?

+1.  I'd like to watch video offline on my phone, so Flash isn't really
a good option.  It doesn't work on my computer either, at least not
without requiring me to download Flash 10 from Adobe.

-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] Haskell Platform, Hackage and Cabal : The 2nd Year : Status Report

2010-10-03 Thread Vo Minh Thu
2010/10/3 Ketil Malde ke...@malde.org:
 Matthias Kilian k...@outback.escape.de writes:

     http://www.vimeo.com/15462768

 And is there any way to just *download* the video? For people not
 using adobe flash?

 +1.  I'd like to watch video offline on my phone, so Flash isn't really
 a good option.  It doesn't work on my computer either, at least not
 without requiring me to download Flash 10 from Adobe.

http://ossguy.com/?p=172

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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Dominique Devriese
Gregory,

2010/10/3 Gregory Crosswhite gcr...@phys.washington.edu:
  On 10/3/10 1:45 PM, Dominique Devriese wrote:

 Additionally, you can't combine the functions (blowup . allButLast)
 and lastToTheLength into a function that returns a pair like you seem
 to attempt. You need a function like the following for that:

 comma :: (a -  b) -  (a -  c) -  a -  (b,c)
 comma f g x = (f x, g x)

 Then you could say:

 blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

 It is worth noting that such a function already exists in the standard
 libraries;  it is the  operator in Control.Arrow:

    blowup = uncurry (++) . (blowup . allButLast  lastToTheLength)

Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;)

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


[Haskell-cafe] Re: Haskell Helper

2010-10-03 Thread Ben Franksen
c8h10n4o2 wrote:
 No, it is not secret. I'm having trouble to define functions. Take a look
 at my code(please be gentle)
 http://haskell.1045720.n5.nabble.com/file/n3100036/hai1.hs hai1.hs

Can you explain in a few words what the Func constructor should represent
why it has three arguments? I ask because I am not sure whether it
represents function definition or function call.

Maybe yuou can give a small example for a function definition as well as a
function application (call) in your Hai language.

Cheers
Ben

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


[Haskell-cafe] Re: Haskell Helper

2010-10-03 Thread c8h10n4o2

The problem is there. A function in Hai would be function-name,
arg1,argn=body.
Func stores function name,arguments and body as Strings(I was thinking to
put Func String String String).
The parser func that I wrote so far try to parse a function definition, not
a function call.
But when I try to store the function on my Map I get a error with somthing
called 'functional dependencies'(which I don't know what is).
-- 
View this message in context: 
http://haskell.1045720.n5.nabble.com/Haskell-Helper-tp3093854p3117672.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Gregory Crosswhite

 On 10/3/10 2:24 PM, Dominique Devriese wrote:

Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;)

Dominique


I know, I just mentioned it to increase awareness of the fact that the 
instance methods for all the classes in Control.Arrow can equivalently 
be interpreted as useful pre-defined combinators for ordinary functions.


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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Victor Nazarov
I suggest to pay more attention to haskell's standard library.

allButLast is called init in Data.List module.

Second, do not use explicit recursion. You can capture recursion using
some high-order function like map, filter, foldr and so on:

lastToTheLength xs = map f xs
  where f = const . last $ xs

And last, your type signatures are too restrictive. You can apply your
functions to arbitrary lists.

lastToTheLength :: [a] - [a]

Standard library knowledge is very helpful in producing short and
clear definitions.

blowup = concat . zipWith replicate [1..]

On Mon, Oct 4, 2010 at 1:24 AM, Dominique Devriese
dominique.devri...@cs.kuleuven.be wrote:
 Gregory,

 2010/10/3 Gregory Crosswhite gcr...@phys.washington.edu:
  On 10/3/10 1:45 PM, Dominique Devriese wrote:

 Additionally, you can't combine the functions (blowup . allButLast)
 and lastToTheLength into a function that returns a pair like you seem
 to attempt. You need a function like the following for that:

 comma :: (a -  b) -  (a -  c) -  a -  (b,c)
 comma f g x = (f x, g x)

 Then you could say:

 blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

 It is worth noting that such a function already exists in the standard
 libraries;  it is the  operator in Control.Arrow:

    blowup = uncurry (++) . (blowup . allButLast  lastToTheLength)

 Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail 
 ;)

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




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


[Haskell-cafe] Re: Haskell Helper

2010-10-03 Thread Ben Franksen
c8h10n4o2 wrote:
 The problem is there. A function in Hai would be function-name,
 arg1,argn=body.
 Func stores function name,arguments and body as Strings(I was thinking to
 put Func String String String).
 The parser func that I wrote so far try to parse a function definition,
 not a function call.
 But when I try to store the function on my Map I get a error with somthing
 called 'functional dependencies'(which I don't know what is).

You mean:

hai1.hs:41:6:
Couldn't match expected type `Hai' against inferred type `[Hai]'
  Expected type: Map.Map Hai Hai
  Inferred type: Map.Map [Hai] Hai
When using functional dependencies to combine
  MonadState (Map.Map [Hai] Hai) m,
arising from a use of `get' at hai1.hs:52:17-19
  MonadState (Map.Map Hai Hai) m,
arising from a use of `get' at hai1.hs:47:16-18
When generalising the type(s) for `w'

The type checker tells you that you are using the same Map with different
key types: at 52:17-19 the key has type [Hai], whereas at 47:16-18 it has
type Hai.

The latter is in your Func case:

  e -return $ Map.insert (a :[b]) c d

where you use  a :[b]  which is the same as  [a,b]  for the key.

Everywhere else, the key has type Hai. This in itself is questionable: do
you really want to use arbitrary expressions as keys? Usually one would
have a

  Map String Hai

representing a map from variable (or function) names to expressions.

For functions you then want

  data Hai = ... | Func [String] Hai | ...

so that

  Func args body

represents the (anonymous) function with the formal arguments  args  and the
resulting expression  body . The function gets a name by inserting it into
the variable map. This means that a definition

  function-name,arg1,...,argn=body

actually defines a variable named  function-name  which, when it gets
looked up in the environment, yields the value  Func [arg1,...,argn] body .

Cheers
Ben

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


Re: [Haskell-cafe] Re: A parsec question

2010-10-03 Thread Antoine Latter
On Sun, Oct 3, 2010 at 11:55 AM, Ben Franksen ben.frank...@online.de wrote:
 Stephen Tetley wrote:
 Does this one give the expected error message for Parsec3.1 -
 unfortunately I can't test as I'm still using Parsec 2.1.0.1.

 parser = block (many digit ? digit)

 Unfortunately, no.

 Cheers
 Ben


Hey folks, sorry about this one - my changes to parsec in 3.1 made
these error messages worse. I've sent a patch off to the maintainer
which fixes the examples in this thread.

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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-03 Thread Conal Elliott
I like it!

Are the other sections available as well, e.g.,

(if False then else Cafe) Haskell -- Cafe

- Conal

On Sat, Oct 2, 2010 at 11:23 AM, Max Bolingbroke batterseapo...@hotmail.com
 wrote:

 Hi Cafe,

 I implemented the proposed Haskell' feature lambda-case/lambda-if [1]
 during the Haskell Implementors Workshop yesterday for a bit of fun.
 The patches are online [2, 3].

 The feature is demonstrated in this GHCi session:

 $ inplace/bin/ghc-stage2 --interactive -XLambdaCase
 GHCi, version 7.1.20101002: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Prelude (if then Haskell else Cafe) False
 Cafe
 Prelude (case of 1 - One; _ - Not-one) 1
 One
 Prelude :q

 Do you like this feature and think it would be worth incorporating
 this into GHC? Or is it too specialised to be of use? If there is
 enough support, I'll create a ticket and see what GHC HQ make of it.

 Max

 [1] http://hackage.haskell.org/trac/haskell-prime/ticket/41
 [2] http://www.omega-prime.co.uk/files/LambdaCase-Testsuite.patch
 [3] http://www.omega-prime.co.uk/files/LambdaCase-Compiler.patch
 ___
 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: Re: A parsec question

2010-10-03 Thread Ben Franksen
Antoine Latter wrote:
 On Sun, Oct 3, 2010 at 11:55 AM, Ben Franksen ben.frank...@online.de
 wrote:
 Stephen Tetley wrote:
 Does this one give the expected error message for Parsec3.1 -
 unfortunately I can't test as I'm still using Parsec 2.1.0.1.

 parser = block (many digit ? digit)

 Unfortunately, no.

 Hey folks, sorry about this one - my changes to parsec in 3.1 made
 these error messages worse. I've sent a patch off to the maintainer
 which fixes the examples in this thread.

Thanks! I hope we get a new minor release with these fixes soon. I love
parsec-3 very much, especially since you fixed the speed problems.

Cheers
Ben

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


[Haskell-cafe] Re: Haskell Helper

2010-10-03 Thread Ben Franksen
Ben Franksen wrote:
 The type checker tells you that you are using the same Map with different
 key types: at 52:17-19 the key has type [Hai], whereas at 47:16-18 it has
 type Hai.
 
 The latter is in your Func case:

s/latter/former/

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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread wren ng thornton

On 10/3/10 5:52 PM, Victor Nazarov wrote:

I suggest to pay more attention to haskell's standard library.

allButLast is called init in Data.List module.

Second, do not use explicit recursion. You can capture recursion using
some high-order function like map, filter, foldr and so on:

lastToTheLength xs = map f xs
   where f = const . last $ xs


And just to play a little Haskell golf:

lastToTheLength = ap (flip map) (const . last)

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Michael Vanier
 I'm having a problem with a simple monad transformer stack that has me 
stumped.  Here's the sample code:


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.Error
import Control.Monad.State
import Data.Typeable

data SomeError =
Error1
  | Error2
  | ErrorFail
  deriving (Eq, Show, Typeable)

data MyData a = MyData [a]

instance Error SomeError where
  noMsg = ErrorFail

{- This works: -}
{-
newtype StateError e s a =
  StateError ((StateT s (Either e) a))
  deriving (Monad,
MonadState s,
MonadError e,
Typeable)

type MyMonad a = StateError SomeError (MyData a) a
-}

{- This doesn't work: -}
newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)

--

Basically, the more abstracted (commented-out) version works, but the 
more specific one gives this error:


Weird.hs:33:12:
Can't make a derived instance of `Monad MyMonad'
  (even with cunning newtype deriving):
  cannot eta-reduce the representation type enough
In the newtype declaration for `MyMonad'

Weird.hs:34:12:
Cannot eta-reduce to an instance of form
  instance (...) = MonadState (MyData a) MyMonad
In the newtype declaration for `MyMonad'

Weird.hs:35:12:
Can't make a derived instance of `MonadError SomeError MyMonad'
  (even with cunning newtype deriving):
  cannot eta-reduce the representation type enough
In the newtype declaration for `MyMonad'

These error messages mean nothing to me.  What's going on?  Can the more 
specific code be made to work?  This is with ghc 6.12.3.


Thanks,

Mike




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


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Christopher Done
On 4 October 2010 03:40, Michael Vanier mvanie...@gmail.com wrote:
 newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
            MonadState (MyData a),
            MonadError SomeError,
            Typeable)

I think it's the `a'. I think it needs to be a concrete type. E.g. the
following is OK:

newtype MyMonad a =
 MyMonad ((StateT (MyData ()) (Either SomeError) a))
 deriving (Monad,
   MonadState (MyData ()),
   MonadError SomeError,
   Typeable)

But

newtype MyMonad a =
 MyMonad ((StateT (MyData ()) (Either SomeError) [a]))
 deriving (Monad,
   MonadState (MyData ()),
   MonadError SomeError,
   Typeable)

is not. This reminds me of the restriction that impredicative types
remove, but I don't think it's related.

 These error messages mean nothing to me.  What's going on?  Can the more
 specific code be made to work?  This is with ghc 6.12.3.

It seems like eta-reducing `X' or `x' is enough, but Foo x,, i.e. a
parametrized type with a type variable isn't enough. I think that's
what's going on, but I don't know why.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Bryan O'Sullivan
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier mvanie...@gmail.com wrote:


 {- This doesn't work: -}
 newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)


This simply isn't allowed by the generalised newtype derivation machinery,
because the type variable a appears in one of the classes you're deriving.

In fact, I'm not sure how you're hoping for your type to actually work as a
monad. If you try using (=) on your type synonym that currently appears to
typecheck, you'll find that the only value that can inhabit the state
parameter is bottom. Try writing out and using a definition of (=) by hand
to understand your confusion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread Bryan O'Sullivan
On Sun, Oct 3, 2010 at 11:54 AM, Henry Laxen nadine.and.he...@pobox.comwrote:


 I am trying to create a (relatively) big array,
 but it seems I cannot make anything larger
 than 2^30 or so.  Here is the code:


Use a 64-bit machine, where Int is 64 bits wide. Trying to create a larger
array on a 32-bit machine doesn't make any sense.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Michael Vanier

 On 10/3/10 7:06 PM, Bryan O'Sullivan wrote:
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier mvanie...@gmail.com 
mailto:mvanie...@gmail.com wrote:



{- This doesn't work: -}
newtype MyMonad a =
 MyMonad ((StateT (MyData a) (Either SomeError) a))
 deriving (Monad,
   MonadState (MyData a),
   MonadError SomeError,
   Typeable)


This simply isn't allowed by the generalised newtype derivation 
machinery, because the type variable a appears in one of the classes 
you're deriving.


In fact, I'm not sure how you're hoping for your type to actually work 
as a monad. If you try using (=) on your type synonym that currently 
appears to typecheck, you'll find that the only value that can inhabit 
the state parameter is bottom. Try writing out and using a definition 
of (=) by hand to understand your confusion.

I disagree with your second point.  I have this in working code:

--
newtype StateErrorIO e s a =
  StateErrorIO { runS :: (StateT s (ErrorT e IO) a) }
  deriving (Monad,
MonadIO,
MonadState s,
MonadError e,
Typeable)
--

I can assure you that it works on non-bottom types.

As for the first point, that makes sense.  So if I do this:

--
newtype MyMonadS s a =
  MyMonad ((StateT s (Either SomeError) a))
  deriving (Monad,
MonadState s,
MonadError SomeError,
Typeable)

type MyMonad a = MyMonadS (MyData a) a
--

it type checks.  And yeah, writing out the instances by hand is the best 
way to understand what's going on.


Mike



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


Re: Re[2]: [Haskell-cafe] EDSL for Makefile

2010-10-03 Thread C K Kashyap

 mention_only_once file action = do
   want [file]
   file * action

 main = mention_only_once file1 $ \x - do need [file2]
                                            putStrLn Hello
                                            putStrLn World



Thanks Bulat 
I guess even this should work -

main = do
  let file1=file1
  want [file1]
  file1 * \x - do
    need [file2]
    putStrLn Hello
    putStrLn World


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


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread John Millikin
On Sun, Oct 3, 2010 at 19:09, Bryan O'Sullivan b...@serpentine.com wrote:
 On Sun, Oct 3, 2010 at 11:54 AM, Henry Laxen nadine.and.he...@pobox.com
 wrote:

 I am trying to create a (relatively) big array,
 but it seems I cannot make anything larger
 than 2^30 or so.  Here is the code:

 Use a 64-bit machine, where Int is 64 bits wide. Trying to create a larger
 array on a 32-bit machine doesn't make any sense.

Sure it does; a 32-bit system can address much more than 2**30
elements. Artificially limiting how much memory can be allocated by
depending on a poorly-specced type like 'Int' is a poor design
decision in Haskell and GHC.

OP: for this particular use case (unboxed Word64), an easily solution
is to have some structure like (data BigArray a = BigArray (UArray
Word32 a) ((UArray Word32 a) ((UArray Word32 a) ((UArray Word32 a)),
with each array containing 2^30 elements. You'll need to write custom
indexing and modification functions, to process the index and pass it
to the appropriate array. Something like:

idxBig :: BigArray a - Word32 - (UArray Word32 a, Word32)
idxBig (BigArray a0 a1 a2 a3) i
| i  2^30 = (a0, i)
| i  2^31 = (a1, i - 2^30)
| i  2^30 + 2^31 = (a2, i - 2^31)
| i  2^32 = (a3, i - 2^31 - 2^30)

Then wrap the existing array functions:

idx :: BigArray a - Word32 - a
idx arr i = let (arr', i') = idxBig arr i in arr' ! i'
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Suggestions for improvement

2010-10-03 Thread N. Raghavendra
At 2010-10-03T22:45:30+02:00, Dominique Devriese wrote:

 Additionally, you can't combine the functions (blowup . allButLast)
 and lastToTheLength into a function that returns a pair like you seem
 to attempt. You need a function like the following for that:

 comma :: (a - b) - (a - c) - a - (b,c)
 comma f g x = (f x, g x)

 Then you could say:

 blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

Thanks, I'll try that.

 Ignore this if you haven't read about Applicative or type classes yet,
 but using the Applicative instance for arrow types (-) a, you can
 also write

 comma = liftA2 (,)

I hadn't come up to that point, but will read about it now.

Regards,
Raghavendra.

-- 
N. Raghavendra ra...@mri.ernet.in | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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