Re: [Haskell-cafe] problem with happy

2010-10-26 Thread Stephen Tetley
Hello

I would change you Alex specification to this:

$digit = 0-9-- digits
$alpha = [a-zA-Z]   -- alphabetic characters
$eol = [\r\n]
$any = [^$eol]

tokens :-

  $eol   { tok $ \_ - Eol }
  $any+  { tok $ \s - Str s }


The complementation operator (^) works of character sets so I don't
expect your original formulation to work:

$any = [^\r\n]

(maybe it should, but I never liked the Alex syntax...)

You can test alex scanners like this:

demo01 = alexScanTokens happy?\n
demo02 = readFile sample = print . alexScanTokens

Note - your sample file is using extended characters so it fails for
me with Alex 2.3.2. I'm now sure how capable the current version of
Alex is or whether better Unicode support can be enabled with flags.

Regards

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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread David Virebayre
2010/10/25 Gregory Collins g...@gregorycollins.net

 Andrew Coppin andrewcop...@btinternet.com writes:

  Hypothesis: The fact that the average Haskeller thinks that this kind of 
  dense
  cryptic material is pretty garden-variety notation possibly explains why
  normal people think Haskell is scary.

 That's ridiculous.

That's not so ridiculous in the sense that some people might (wrongly)
think they won't understand haskell until they understand at least
some of that cryptic material.
Many long discussion about Haskell on reddit seem to have a beginner
thinking he must understand monads before going on.
Yes, the  famous monads which aren't that complicated at all, still
they are part of this dense cryptic material when you're a newbie that
used to think he's smart because he knows c, pascal, basic, php , and
learned postscript's basics in a few days (Then you start looking at
this curiosity called haskell, and you stumple upon haskell-cafe, and
then you are humbled.) (I might be talking about the 3 years ago me,
here :) )

 You're comparing apples to oranges: using Haskell and understanding the
 underlying theory are two completely different
 things.

Agree 100%, but it's not automatic to see it that way for a newcomer.

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


Re: [Haskell-cafe] Parsec in Haskell platform

2010-10-26 Thread Joachim Breitner
Hi,

Am Sonntag, den 24.10.2010, 15:56 +0200 schrieb Simon Hengel:
  It would be convenient to have a page which would list all the HP packages
  with their versions. The release page [2] only has a list of packages
  whose versions has changed since the last release, as I understood.
  
  It would be nice to have a page that lists everything included in
  every HP release, together with their version numbers. (So that,
  e.g., I can see at a glance what version of GHC, Haddock or
  cabal-install is in HP-2009.1.0.0.) All this information must exist
  somewhere, it's just not easily viewable on the web.
 
 Yes, I needed the same information recently.  I ended up reading the
 Cabal file at [1].  A convenient way to see what packages are included
 in what version of the platform would still be very useful, though.

Until this is offered in an official position, this might be helpful if
you ignore the Debian-related columns:
http://people.debian.org/~nomeata/platform.html

Greetings,
Joachim

-- 
Joachim Breitner
  e-Mail: m...@joachim-breitner.de
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
  Jabber-ID: nome...@joachim-breitner.de


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec in Haskell platform

2010-10-26 Thread Jonas Almström Duregård
 Regardless, 7zip (LGPL) can do it. But you have to first inzip, and then
untar as a seperate step.

This is pretty far off topic, but you can actually unpack it in a single
run. If you use the GUI version of 7z (a.k.a. the 7zip File Manager) you can
open the .tar.gz and it will list a single .tar file as its content. Double
click that file and you can see/extract its contents.

/J

On 25 October 2010 22:58, Andrew Coppin andrewcop...@btinternet.com wrote:

 On 25/10/2010 03:49 PM, Brandon S Allbery KF8NH wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1

 On 10/24/10 06:59 , Andrew Coppin wrote:

 now I can't seem to find it. Instead, I had to navigate to the Unix
 download
 page, download the source tarball, untar it (non-trivial under Windows),
 and

 I thought WinZip added tar and tar.gz several years ago?


 You know that WinZip actually costs money, right?

 Regardless, 7zip (LGPL) can do it. But you have to first inzip, and then
 untar as a seperate step.

 Regardless of that, cabal-install can download the correct URL and untar it
 for you. Assuming you happen to be sitting at a PC with Haskell tools on it
 at the moment you want to check this information out...


 ___
 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] vector-space and standard API for vectors

2010-10-26 Thread Alexey Khudyakov

On 24.10.2010 03:38, wren ng thornton wrote:

On 10/23/10 4:53 PM, Alexey Khudyakov wrote:

On 23.10.2010 05:11, wren ng thornton wrote:

I'd rather see,

class Additive v where -- or AdditiveMonoid, if preferred
zeroV :: v
(^+^) :: v - v - v

class Additive v = AdditiveGroup v where
negateV :: v - v


Seems good for me. One more instance declaration to write and no changes
in usage.

However when written this way it becomes obvious that
`zeroV' == `mempty' and ^+^ = mappend. Is Additive really needed then?


It depends on the usage, since we don't have a nice way of having
multiple Monoid instances in scope with different identifiers for their
respective mzero/mappend. For example, in Edward Kmett's monoids[1]
library he reuses Monoid for additive monoids and adds a new
Multiplicative class for multiplicative monoids; that way you can use
operators for a semiring without needing newtype wrappers everywhere in
order to distinguish the two structures on the same type.

When dealing with modules and vector spaces we have three or four
different monoids in play: the additive and multiplicative monoids of
the underlying semiring/ring/field, and the additive and multiplicative
monoids of the module/vectorspace. Lacking the aforementioned feature,
that means there are good reasons to have duplicate classes (i.e.,
they're all monoids) so long as they are documented as capturing
different notions (e.g., distinguishing scalar and vectorial uses).

I don't care much about the name of the class, I'd just like support for
monoids, semirings,... when they lack a group, ring,... structure.

Then what about following type class hierarchy? I think it supports 
those structures. Only restriction is that it forces one to have both 
left and right modules. It's possible to split them but I think it will 
be to painful for vector spaces over R and C.



class AdditiveMonoid v where
  (^+^) :: v → v → v
  zeroV :: v

class AdditiveMonoid ⇒ AdditiveGroup v where
  negateV :: v → v
  -- For performance sake
  (^-^) :: v → v → v
  v ^-^ u = v ^+^ negateV u

class Module v where
  type Scalar v :: *
  (*^) :: Scalar v → v → v
  (^*) :: v → Scalar v → v
  (^*) = flip (*^)

class (AdditiveGroup v, Module v) ⇒ VectorSpace v

class VectorSpace v ⇒ InnerSpace v where
  (.) :: v → v → Scalar v

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


[Haskell-cafe] Working Generic/Polytypic Haskell extension

2010-10-26 Thread mulhern
Hi all,

I would like to teach a small section on polytypism/genericity in the
functional programming using Haskell course I'm teaching. I won't, though,
unless I can assign an actual programming exercise in polytypic programming,
however brief. Can anybody recommend a functioning compiler that I can
reasonably require the students to use in doing this assignment? I am not
up-to-date on the current state of research in this topic in Haskell and
hope that some people on the list can help me out.

Thanks!

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


Re: [Haskell-cafe] Working Generic/Polytypic Haskell extension

2010-10-26 Thread Sean Leather
Hi Mulhern,

I would like to teach a small section on polytypism/genericity in the
 functional programming using Haskell course I'm teaching. I won't, though,
 unless I can assign an actual programming exercise in polytypic programming,
 however brief. Can anybody recommend a functioning compiler that I can
 reasonably require the students to use in doing this assignment? I am not
 up-to-date on the current state of research in this topic in Haskell and
 hope that some people on the list can help me out.


There is of course Generic Haskell [1], which works. It is not being
maintained anymore, but it still does what it was designed to do. There are
plenty of publications to use for resources.

Currently, most of the work on datatype-generic programming generally ends
up in libraries and not in language extensions. You can see quite a few on
Hackage [2]. Many of them have links to publications for further study.

At Utrecht University, we have a master's course on Generic Programming [3].
That may be more than you want, but you can refer to our slides for further
information. We also use lecture notes [4] for this course. They provide a
pretty good introduction to a few libraries, LIGD, EMGM, and SYB.

Hope this helps! Let us know if you would like something else.

Regards,
Sean

[1] http://www.cs.uu.nl/research/projects/generic-haskell/
[2] http://hackage.haskell.org/packages/archive/pkg-list.html#cat:generics
[3] http://www.cs.uu.nl/wiki/GP
[4] http://www.cs.uu.nl/research/techreps/UU-CS-2008-025.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haddock API and .haddock interface files questions

2010-10-26 Thread Claus Reinke

Some questions about Haddock usage:

1. Haddock executable and library are a single hackage package,
   but GHC seems to include only the former (haddock does not
   even appear as a hidden package anymore). Is that intended?

2. Naively, I'd expect Haddock processing to involve three stages:
   1. extract information for each file/package
   2. mix and match information batches for crosslinking
   3. generate output for each file/package

   I would then expect .haddock interface files to repesent the
   complete per-package information extracted in step 1, so 
   that packages with source can be used interchangeably

   with packages with .haddock files.

   However, I can't seem to use 'haddock --hoogle', say, with
   only .haddock interface files as input (No input file(s).).

3. It would be nice if the Haddock executable was just a thin
   wrapper over the Haddock API, if only to test that the API
   exposes sufficient functionality for implementing everything
   Haddock can do.

   Instead, there is an awful lot of useful code in Haddock's
   Main.hs, which is not available via the API. So when coding
   against the API, for instance, to extract information from
   .haddock files, one has to copy much of that code.

   Also, some inportant functionality isn't exported (e.g., the
   standard form of constructing URLs), so it has to be copied
   and kept in synch with the in-Haddock version of the code.

   It might also be useful to think about the representation
   of the output of stage 2 above: currently, Haddock directly
   generates indices in XHtml form, even though much of
   the index computation should be shareable accross
   backends. That is, current backends seem to do both
   stage 2 and stage 3, with little reuse of code for stage 2.

It seems that exposing sufficient information in the API, and
allowing .haddock interface files as first-class inputs, there
should be less need for hardcoding external tools into Haddock
(such as --hoogle, or haddock-leksah). Instead, clients should
be able to code alternative backends separately, using Haddock
to extract information from sources into .haddock files, and
the API for processing those .haddock files. 

Are these expectations reasonable, or am I misreading the 
intent behind API and .haddock files? Is there any 
documentation about the role and usage of these two

Haddock features, as well as the plans for their development?

Claus

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


Re: [Haskell-cafe] problem with happy

2010-10-26 Thread Roman Dzvinkovsky
lexer works fine, problem is in happy parser.

2010/10/26 Stephen Tetley stephen.tet...@gmail.com

 Hello

 I would change you Alex specification to this:

 $digit = 0-9-- digits
 $alpha = [a-zA-Z]   -- alphabetic characters
 $eol = [\r\n]
 $any = [^$eol]

 tokens :-

  $eol   { tok $ \_ - Eol }
  $any+  { tok $ \s - Str s }


 The complementation operator (^) works of character sets so I don't
 expect your original formulation to work:

 $any = [^\r\n]

 (maybe it should, but I never liked the Alex syntax...)

 You can test alex scanners like this:

 demo01 = alexScanTokens happy?\n
 demo02 = readFile sample = print . alexScanTokens

 Note - your sample file is using extended characters so it fails for
 me with Alex 2.3.2. I'm now sure how capable the current version of
 Alex is or whether better Unicode support can be enabled with flags.

 Regards

 Stephen
 ___
 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] problem with happy

2010-10-26 Thread Stephen Tetley
The lexer was wrong - but it was the lexer function not the lexer spec
- try the one below.

Note that you have to take 'len' chars from the original input.
Previously you were taking the whole of the rest-of--input:

lexer :: (TheToken - P a) - P a
lexer f input@(_,_,instr) =
  case alexScan input 0 of
AlexEOF - f Eof input
AlexError (pos, _, _) -
  Failed $ showPos pos ++ : lexical error
AlexSkip input' len - lexer f input'
AlexToken (pos, c, str) len act -
  let (Token newpos thetok) = act pos (take len instr)
  in f thetok (newpos, c, str)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Map constructor in a DSL

2010-10-26 Thread Dupont Corentin
Hello café,

I have a little DSL in my program as follow.
Now I'd like to add a Map constructor in it. Thats where I would need help!

 data Obs a where

 AllPlayers :: Obs [Int]
 Plus   :: (Num a) = Obs a - Obs a - Obs a
 And:: Obs Bool - Obs Bool - Obs Bool
 Vote   :: Obs String - Obs Int - Obs Bool
 *Map:: (Obs a - Obs b) - Obs [a] - Obs [b]*
 -- and others

Here is the evaluator for Obs:

 evalObs :: Obs a - Evaluator a
 evalObs (Konst a)   = return $ pure a
 evalObs (Not a) = liftE  not   (evalObs a)
 evalObs (Plus a b)  = liftE2 (+)   (evalObs a) (evalObs b)
 evalObs (Minus a b) = liftE2 (-)   (evalObs a) (evalObs b)
 evalObs (Time a b)  = liftE2 (*)   (evalObs a) (evalObs b)
 evalObs (And a b)   = liftE2 ()  (evalObs a) (evalObs b)
 evalObs (Or a b)= liftE2 (||)  (evalObs a) (evalObs b)
 evalObs (Equ a b)   = liftE2 (==)  (evalObs a) (evalObs b)
 evalObs (If a b c)  = liftE3 (if3) (evalObs a) (evalObs b) (evalObs c)

How you can see it is quite neat...
But how can I write the evaluator for Map?

Actually I have some half baked solution, 15 lines long that I don't
dare to show ;)

Actually compiling code excerpt is here:
http://hpaste.org/40897/map_contstructor_in_a_dsl


Thanks for your help.
Corentin


Below is some helper code:

type Evaluator a = StateT Game Comm a (Either Actions a)


-- | Combined lifters for Evaluator
liftE  = liftM  . liftA
liftE2 = liftM2 . liftA2
liftE3 = liftM3 . liftA3


instance Applicative (Either Actions) where

pure x = Right x
(Right f) * (Right x) = Right $ f x

(Right _) * (Left u) = Left u
(Left u) * (Right _) = Left u

(Left u) * (Left v) = Left $ u ++ v
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Test command line programs

2010-10-26 Thread Dupont Corentin
Hello again café,

I have a command line program that takes input from various handles
(actually network sockets) like this:

 s - hGetLine h
 etc.

I'd like to unit test this. How can I do?
I'd like to inject data on the handle so that all the input chain is tested.

How are command line programs' IO automatically tested usually?

Another little question:
How can I access the name of a function inside a function (for Trace
purpose)?
I have to use the CPP preprocessor?

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


Re: [Haskell-cafe] Test command line programs

2010-10-26 Thread Edward Z. Yang
Hello Dupont,

If your code follows good style and has kept as much code out of IO as
possible, you should be able to easily unit test the pure portions of your
code.  Otherwise, classic integration tests, by setting up the network jigs
yourself, is standard.

 Another little question:
 How can I access the name of a function inside a function (for Trace
 purpose)?
 I have to use the CPP preprocessor?

I think most people usually explicitly write in their function name.
CPP can also work for this purpose.

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


[Haskell-cafe] Functional Programming in Industry Symposiun: update

2010-10-26 Thread Jeroen Janssen
Dear all,

For organizatorial reasons, we would like to ask that everyone interested in 
attending the symposium on functional programming in industry (see below) 
registers at 
https://spreadsheets.google.com/ccc?key=0Ak5F96CGaVoJdFVsNWZPWTdyT3NYOWRnT25GUzdJSFEhl=en#gid=0

Kind Regards,
The GhentFPG Organizing Committee

Begin forwarded message:

 From: Jeroen Janssen jejan...@gmail.com
 Date: 25 oktober 2010 23:25:32 GMT+02:00
 To: ghent-...@googlegroups.com
 Bcc: haskell-cafe@haskell.org, cic...@elis.ugent.be, le...@zeus.ugent.be
 Subject: Functional Programming in Industry
 
 Dear all,
 
 I am pleased to announce to you that, on the occasion of BelHac, the first 
 Belgian Haskell Hackathon from 5-7 Nov 2010, the Ghent Functional Programming 
 Group is organizing a symposium on Functional Programming in Industry, to 
 which you are all cordially invited. These talks will be held on Friday, 
 November 5th at 17:00 in the Jozef Plateauzaal in the Plateau building of 
 Ghent University (Jozef Plateaustraat 22, 9000 Gent). The program is as 
 follows:
 
 - Duncan Coutts* (Well-Typed, http://www.well-typed.com/, BelHac sponsor) who 
 will be talking on how Well-Typed are providing consultancy services for 
 Haskell, a pure functional programming language.
 - Romain Slootmaekers (Incubaid, http://www.incubaid.com, BelHac sponsor) who 
 will be talking on the use of functional programming in Incubaid, a company 
 based in the Ghent area.
 - Don Stewart (Galois, http://www.galois.com) who will be talking on how 
 Galois is using Haskell in many of their projects, including government 
 contracts.
 
 The talks will be followed by a reception to which all attendees are 
 cordially invited.
 
 * Actual speaker has yet to be confirmed, but the talk will take place.
 
 Kind Regards,
 The GhentFPG Organizing Committee.

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


[Haskell-cafe] Fwd: Functional Programming in Industry Symposium: update correction

2010-10-26 Thread Jeroen Janssen
Dear all,

The link provided below is incorrect.
The correct link is 
https://spreadsheets.google.com/viewform?hl=enformkey=dFVsNWZPWTdyT3NYOWRnT25GUzdJSFE6MQ#gid=0

Sorry for your inconvenience.

Begin forwarded message:

 From: Jeroen Janssen jejan...@gmail.com
 Date: 26 oktober 2010 18:30:58 GMT+02:00
 To: ghent-...@googlegroups.com
 Cc: haskell-cafe@haskell.org, le...@zeus.ugent.be
 Subject: Functional Programming in Industry Symposiun: update
 
 Dear all,
 
 For organizatorial reasons, we would like to ask that everyone interested in 
 attending the symposium on functional programming in industry (see below) 
 registers at 
 https://spreadsheets.google.com/ccc?key=0Ak5F96CGaVoJdFVsNWZPWTdyT3NYOWRnT25GUzdJSFEhl=en#gid=0
 
 Kind Regards,
 The GhentFPG Organizing Committee
 
 Begin forwarded message:
 
 From: Jeroen Janssen jejan...@gmail.com
 Date: 25 oktober 2010 23:25:32 GMT+02:00
 To: ghent-...@googlegroups.com
 Bcc: haskell-cafe@haskell.org, cic...@elis.ugent.be, le...@zeus.ugent.be
 Subject: Functional Programming in Industry
 
 Dear all,
 
 I am pleased to announce to you that, on the occasion of BelHac, the first 
 Belgian Haskell Hackathon from 5-7 Nov 2010, the Ghent Functional 
 Programming Group is organizing a symposium on Functional Programming in 
 Industry, to which you are all cordially invited. These talks will be held 
 on Friday, November 5th at 17:00 in the Jozef Plateauzaal in the Plateau 
 building of Ghent University (Jozef Plateaustraat 22, 9000 Gent). The 
 program is as follows:
 
 - Duncan Coutts* (Well-Typed, http://www.well-typed.com/, BelHac sponsor) 
 who will be talking on how Well-Typed are providing consultancy services for 
 Haskell, a pure functional programming language.
 - Romain Slootmaekers (Incubaid, http://www.incubaid.com, BelHac sponsor) 
 who will be talking on the use of functional programming in Incubaid, a 
 company based in the Ghent area.
 - Don Stewart (Galois, http://www.galois.com) who will be talking on how 
 Galois is using Haskell in many of their projects, including government 
 contracts.
 
 The talks will be followed by a reception to which all attendees are 
 cordially invited.
 
 * Actual speaker has yet to be confirmed, but the talk will take place.
 
 Kind Regards,
 The GhentFPG Organizing Committee.
 

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


Re: [Haskell-cafe] Map constructor in a DSL

2010-10-26 Thread Christopher Done
On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com wrote:
 But how can I write the evaluator for Map?

Where do values for PlayerNumber come from? Unless I'm mistaken, the
only thing that Map can be used with is Obs [PlayerNumber], a list of
values PlayerNumber which we have no means of acquiring in order to
provide to the Map function.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[haskell-cafe] [ANNOUNCE] MissingPy 0.10.5

2010-10-26 Thread Matt Brown
Hello all,

I've recently taken over maintenance of MissingPy, and pushed version
0.10.5 to hackage[1].  This includes two notable improvements:
 - fix build errors for python = 2.5
 - allow calling into multi-threaded python code (requires python = 2.3).

I'm trying to provide support for as many python versions as possible,
though I still have more testing to do. Help in this area would be
most appreciated.  Please report any bugs via my github repo [2].
Examples can be found in the testsrc directory.   A good introduction
by Tim Lopez is also available [3].

withGIL provides the easiest way to call into threaded python code.  I
haven't added any examples of its usage yet, but the gist of it is:
 withGIL $ do some python stuff

I'll try to add some actual examples soon.

Thanks,
-matt

[1]: http://hackage.haskell.org/package/MissingPy
[2]: http://github.com/softmechanics/missingpy/issues
[3]: http://www.brool.com/index.php/using-missingpy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map constructor in a DSL

2010-10-26 Thread Dupont Corentin
Hey Chris!
Values for PlayerNumber are acquired at evaluation time, from the state of
the system.

I have not included the evaluation of AllPlayers.
Here how it looks:

evalObs AllPlayers  = return . pure  = gets players

But when you build your Obs, you have yet no idea how much players it will
be.
This is just symbolic at this stage.

To give you a better insight, here is want I want to do with Map:

everybodyVote :: Obs [Bool]
everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

In memory, everybodyVote is just a tree.
This rule can be executed latter whenever I want to perform this democratic
vote ;)

Hope this answer to your question.
Corentin


On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
chrisd...@googlemail.comwrote:

 On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
 wrote:
  But how can I write the evaluator for Map?

 Where do values for PlayerNumber come from? Unless I'm mistaken, the
 only thing that Map can be used with is Obs [PlayerNumber], a list of
 values PlayerNumber which we have no means of acquiring in order to
 provide to the Map function.

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


[Haskell-cafe] [ANNOUNCE] csound-expression - csound combinator library

2010-10-26 Thread Anton Kholomiov
Hi,

I'm glad to announce csound combinator library.

It features liberation from id-style csound code, haskore-like composition
structures, type-safe composable opcodes and simple instrument interface (no
interface at all, instrument is just a function from some note
representation to signal).

http://hackage.haskell.org/package/csound-expression

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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Andrew Coppin

On 25/10/2010 11:01 PM, Lauri Alanko wrote:

On Mon, Oct 25, 2010 at 10:10:56PM +0100, Andrew Coppin wrote:

Type theory doesn't actually interest me, I just wandered what the
hell all the notation means.

That sounds like an oxymoron. How could you possibly learn what the
notation means without learning about the subject that the notation
is about? That's like saying I'm not actually interested in calculus,
I'd just like to know what the hell all these funny S-like symbols
mean.


You can explain the integral notation in a few short sentences without 
having to undergo an entire semester of integral calculus training. 
Hell, the other night I was laying in bed with my girlfriend (who hates 
mathematics) and I managed to make her understand what a partial 
derivative is.


Now of course if you needed to *use* integral calculus for something, 
that's another matter entirely. But just to get the gist of what it's 
about and what it's for is much simpler.



So I will add voice to those recommending TAPL.


OK, well maybe I'll see if somebody will buy it for me for Christmas or 
something...


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


Re: [Haskell-cafe] Test command line programs

2010-10-26 Thread Ben Millwood
On Tue, Oct 26, 2010 at 5:11 PM, Dupont Corentin
corentin.dup...@gmail.com wrote:
 Hello again café,

 I have a command line program that takes input from various handles
 (actually network sockets) like this:

 s - hGetLine h
 etc.

 I'd like to unit test this. How can I do?

If all you ever do in some part of the code is read from the socket,
consider passing an IO action to do that into your function, instead
of the handle itself.
Then:
a. you can easily replace the IO String with (return testdata), or a
read from an MVar you feed data into, or whatever else you like.
b. you can statically guarantee the function doesn't do anything
unexpected to the handle, like closing it or seeking or setting a
buffering option.
c. you will probably not have to write as much, saving on keyboard wear.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec in Haskell platform

2010-10-26 Thread Andrew Coppin

On 26/10/2010 11:33 AM, Joachim Breitner wrote:

Hi,
Until this is offered in an official position, this might be helpful if
you ignore the Debian-related columns:
http://people.debian.org/~nomeata/platform.html


That's quite useful. It doesn't list the version numbers for GHC itself 
or for Haddock (but curiosly cabal-install is listed), but it's still a 
step in the right direction.


I suppose we could put a page on the main Haskell wiki somewhere. (BTW, 
wasn't haskell.org supposed to be getting moved to a new server with a 
newer version of WikiMedia soon?)


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


[Haskell-cafe] cross-platform compile

2010-10-26 Thread Hong Yang
Just curious if Haskell can or will generate cross-platform executable code,
e.g., generate code for Linux from a Windows machine.

Thanks,

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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Benedict Eastaugh
On 26 October 2010 19:29, Andrew Coppin andrewcop...@btinternet.com wrote:

 I don't even know the difference between a proposition and a predicate.

A proposition is an abstraction from sentences, the idea being that
e.g. Snow is white, Schnee ist weiß and La neige est blanche are
all sentences expressing the same proposition.

Propositional logic is quite a simple logic, where the building blocks
are atomic formulae and the usual logical connectives. An example of a
well-formed formula might be P → Q. It tends to be the first system
taught to undergraduates, while the second is usually the first-order
predicate calculus, which introduces predicates and quantifiers.

Predicates are usually interpreted as properties; we might write
P(x) or Px to indicate that object x has the property P.

 I also don't know exactly what discrete mathematics actually covers.

Discrete mathematics is concerned with mathematical structures which
are discrete, rather than continuous. Real analysis, for example, is
concerned with real numbers—the continuum—and thus would not be
covered. Graph theory, on the other hand, concerns objects (nodes and
edges) which have sharp cutoffs—if an edge directly connects two
nodes, there are no intermediate nodes, whereas if you consider an
interval between any two real numbers, no matter how close, there are
more real numbers between them. Computers being the kind of things
they are, discrete mathematics has a certain obvious utility.

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


Re: [Haskell-cafe] problem with happy

2010-10-26 Thread Roman Dzvinkovsky
Great thanks! All work right now.

2010/10/26 Stephen Tetley stephen.tet...@gmail.com

 The lexer was wrong - but it was the lexer function not the lexer spec
 - try the one below.

 Note that you have to take 'len' chars from the original input.
 Previously you were taking the whole of the rest-of--input:

 lexer :: (TheToken - P a) - P a
 lexer f input@(_,_,instr) =
  case alexScan input 0 of
AlexEOF - f Eof input
AlexError (pos, _, _) -
  Failed $ showPos pos ++ : lexical error
AlexSkip input' len - lexer f input'
AlexToken (pos, c, str) len act -
  let (Token newpos thetok) = act pos (take len instr)
  in f thetok (newpos, c, str)
 ___
 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] In what language...?

2010-10-26 Thread Andrew Coppin

On 26/10/2010 07:54 PM, Benedict Eastaugh wrote:

On 26 October 2010 19:29, Andrew Coppinandrewcop...@btinternet.com  wrote:

I don't even know the difference between a proposition and a predicate.

A proposition is an abstraction from sentences, the idea being that
e.g. Snow is white, Schnee ist weiß and La neige est blanche are
all sentences expressing the same proposition.


Uh, OK.


Propositional logic is quite a simple logic, where the building blocks
are atomic formulae and the usual logical connectives. An example of a
well-formed formula might be P → Q. It tends to be the first system
taught to undergraduates, while the second is usually the first-order
predicate calculus, which introduces predicates and quantifiers.


Already I'm feeling slightly lost. (What does the arrow denote? What's 
are the usual logcal connectives?)



Predicates are usually interpreted as properties; we might write
P(x) or Px to indicate that object x has the property P.


Right. So a proposition is a statement which may or may not be true, 
while a predicate is some property that an object may or may not possess?



I also don't know exactly what discrete mathematics actually covers.

Discrete mathematics is concerned with mathematical structures which
are discrete, rather than continuous.


Right... so its domain is simply *everything* that is discrete? From 
graph theory to cellular automina to finite fields to difference 
equations to number theory? That would seem to cover approximately 50% 
of all of mathematics. (The other 50% being the continuous mathematics, 
presumably...)


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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Alexander Solla


On Oct 26, 2010, at 12:43 PM, Andrew Coppin wrote:

Propositional logic is quite a simple logic, where the building  
blocks
are atomic formulae and the usual logical connectives. An example  
of a
well-formed formula might be P → Q. It tends to be the first  
system

taught to undergraduates, while the second is usually the first-order
predicate calculus, which introduces predicates and quantifiers.


Already I'm feeling slightly lost. (What does the arrow denote?  
What's are the usual logcal connectives?)


The arrow is notation for If P, then Q.  The other usual logical  
connectives are not (denoted by ~, !, the funky little sideways L,  
and probably others); or (denoted by \/, v, (both are pronounced  
or or vee even meet) |, ||,  and probably others);  
and (denoted by /\, or a smaller upside-down v (pronounced wedge  
or and or even join),  , , and probably others).





Predicates are usually interpreted as properties; we might write
P(x) or Px to indicate that object x has the property P.


Right. So a proposition is a statement which may or may not be true,  
while a predicate is some property that an object may or may not  
possess?


Yes.  For any given object a (which is not a variable -- we usually  
reserve x, y, z to denote variables, and objects are denoted by  a, b,  
c), P(a) is a proposition about a.  Something like forall x P(x)  
means that P(x) is true for every object in the domain you are  
considering.




I also don't know exactly what discrete mathematics actually  
covers.

Discrete mathematics is concerned with mathematical structures which
are discrete, rather than continuous.


Right... so its domain is simply *everything* that is discrete? From  
graph theory to cellular automina to finite fields to difference  
equations to number theory? That would seem to cover approximately  
50% of all of mathematics. (The other 50% being the continuous  
mathematics, presumably...)


Basically, yes.  There are some nuances, in that continuous structures  
might be studied in terms of discrete structures, and vice-versa. ___

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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Benedict Eastaugh
On 26 October 2010 20:43, Andrew Coppin andrewcop...@btinternet.com wrote:

 Propositional logic is quite a simple logic, where the building blocks
 are atomic formulae and the usual logical connectives. An example of a
 well-formed formula might be P → Q. It tends to be the first system
 taught to undergraduates, while the second is usually the first-order
 predicate calculus, which introduces predicates and quantifiers.

 Already I'm feeling slightly lost. (What does the arrow denote? What's are
 the usual logcal connectives?)

The arrow is just standard logical notation for the conditional: if
... then in English. If you were to read P → Q aloud, it would
sound like If P then Q. It's one of the usual logical connectives I
mentioned.

The others are ∧ (conjunction; and, in English); ∨ (disjunction;
or. Note that it's inclusive: if both operands are true then the
whole expression is true. This is different to how the word or
functions in everyday English, where it's exclusive: you can have
cheesecake or apple pie, but not both); ¬ (negation; not--the only
unary operator in the usual group of connectives) and ↔
(biconditional; if and only if).

They are the usual logical connectives purely in virtue of the fact
that they're the ones we tend to use most of the time. Historically
speaking this is because they seem to map well onto use cases in
natural language.

However, there are many other possible logical connectives; I have
only mentioned a few unary and binary connectives. There are 4 unary
operators, 16 binary operators, 256 ternary operators, and in general,
2 ^ 2 ^ n logical connectives for n  ω (i.e. the first infinite
ordinal: we only consider operators with a finite number of operands).

We could write the four unary operators quite easily in Haskell,
assuming that we take them as functions from Bool to Bool:

 data Bool = True | False

 not :: Bool - Bool
 not True = False
 not False = True

 id :: Bool - Bool
 id True = True
 id False = False

 true :: Bool - Bool
 true _ = True

 false :: Bool - Bool
 false _ = False

The `true` and `false` functions are constant functions: they always
produce the same output regardless of their inputs. For this reason
they're not very interesting. The `id` function's output is always
identical to its input, so again it's not very interesting. The `not`
function is the only one which looks like it holds any interest,
producing the negation of its input. Given this it shouldn't surprise
us that it's the one which actually gets used in formal languages.

 Predicates are usually interpreted as properties; we might write
 P(x) or Px to indicate that object x has the property P.

 Right. So a proposition is a statement which may or may not be true, while a
 predicate is some property that an object may or may not possess?

Exactly. The sentence There is a black beetle could be taken to
express the proposition that there is a black beetle. It includes the
predicates is black and is a beetle. We might write this in
first-order logic, to make the predicates (and the quantification)
more explicit, as ∃x [Black(x) ∧ Beetle(x)]. I.e., There exists
something that is black and is a beetle.

I hedged, saying that we usually interpret predicates as properties,
because the meaning of an expression in a formal language (or, indeed,
any language) depends on the interpretation of that language, which
assigns meanings to the symbols and truth-values to its sentences.

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


Re: [Haskell-cafe] Map constructor in a DSL

2010-10-26 Thread Ryan Ingram
Instead of answering your question directly, I'll give you some code
for a different DSL:

data Exp ref a where
EVar ::  ref a - Exp ref a
ELam :: (ref a - Exp ref b) - Exp ref (a - b)
EAp :: Exp ref (a - b) - Exp ref a - Exp ref b

-- simple data structures
EPair :: Exp ref a - Exp ref b - Exp ref (a,b)
EFst :: Exp ref (a,b) - Exp ref a
ESnd :: Exp ref (a,b) - Exp ref b

ELeft :: Exp ref a - Exp ref (Either a b)
ERight :: Exp ref b - Exp ref (Either a b)
EEither :: Exp ref (a - c) - Exp ref (b - c) - Exp ref (Either
a b) - Exp ref c

-- closed expressions can work for any reference type
typedef CExp a = (forall ref. CExp ref a)

newtype SimpleRef a = SR a

evalSimple :: Exp SimpleRef a - a
evalSimple (EVar (SR a)) = a
evalSimple (ELam f) = \x - evalSimple $ f (SR x)
evalSimple (EAp e1 e2) = evalSimple e1 $ evalSimple e2
evalSimple (EPair e1 e2) = (evalSimple e1, evalSimple e2)
evalSimple (EFst e) = fst $ evalSimple e
evalSimple (ESnd e) = snd $ evalSimple e
evalSimple (ELeft e) = Left $ evalSimple e
evalSimple (ERight e) = Right $ evalSimple e
evalSimple (EEither l r e) = either (evalSimple l) (evalSimple r) (evalSimple e)

eval :: CExp a - a
eval = evalSimple

-- some examples
eid :: CExp (a - a)
eid = ELam (\r - EVar r)

type EBool = Either (a - a) (a - a)

true :: CExp EBool
true = ELeft eid

false :: CExp EBool
false = ERight eid

eif :: CExp (EBool - a - a - a)
eif = ELam $ \b - ELam $ \t - ELam $ \f - EEither (ELam $ \_ -
EVar t) (ELam $ \_ - EVar f) b

The key is in EVar/ELam; this gives you the ability to do actual
abstraction.  And you can use different reference types to create
different kinds of interpreters.  A fun exercise is writing an
interpreter that prints out the expression; that is, implement
showExp :: CExp - String.  My implementation shows eif as

ELam (\x - ELam (\y - ELam (\z - EEither (ELam (\w - EVar y))
(ELam (\w - EVar z)) x)

I'm assuming that the inside of evalObs (Map ...) is a giant mess of
operations.  This 'higher order' way of representing expressions has
tended to simplify that mess for me.

  -- ryan

On Tue, Oct 26, 2010 at 10:42 AM, Dupont Corentin
corentin.dup...@gmail.com wrote:
 Hey Chris!
 Values for PlayerNumber are acquired at evaluation time, from the state of
 the system.

 I have not included the evaluation of AllPlayers.
 Here how it looks:

 evalObs AllPlayers  = return . pure  = gets players

 But when you build your Obs, you have yet no idea how much players it will
 be.
 This is just symbolic at this stage.

 To give you a better insight, here is want I want to do with Map:

 everybodyVote :: Obs [Bool]
 everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

 In memory, everybodyVote is just a tree.
 This rule can be executed latter whenever I want to perform this democratic
 vote ;)

 Hope this answer to your question.
 Corentin


 On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done chrisd...@googlemail.com
 wrote:

 On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
 wrote:
  But how can I write the evaluator for Map?

 Where do values for PlayerNumber come from? Unless I'm mistaken, the
 only thing that Map can be used with is Obs [PlayerNumber], a list of
 values PlayerNumber which we have no means of acquiring in order to
 provide to the Map function.


 ___
 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] Test command line programs

2010-10-26 Thread Antoine Latter
On Tue, Oct 26, 2010 at 11:11 AM, Dupont Corentin
corentin.dup...@gmail.com wrote:
 Hello again café,

 I have a command line program that takes input from various handles
 (actually network sockets) like this:

 s - hGetLine h
 etc.

 I'd like to unit test this. How can I do?
 I'd like to inject data on the handle so that all the input chain is tested.

I haven't tested it yet, but this mock handle will eventually work in GHC 7:

http://hackage.haskell.org/trac/ghc/attachment/ticket/4144/ByteStringHandle.hs

At least, the bug report about how it didn't work has now been closed :-)

I don't remember which operations worked and which didn't - getChar
would work, but getContents would fail.

The others have great advice, that you should try to isolate the logic
of your code from IO for precisely this reason - so it is easily
testable.

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


Re: [Haskell-cafe] vector-space and standard API for vectors

2010-10-26 Thread wren ng thornton

On 10/26/10 8:51 AM, Alexey Khudyakov wrote:

On 24.10.2010 03:38, wren ng thornton wrote:

I don't care much about the name of the class, I'd just like support for
monoids, semirings,... when they lack a group, ring,... structure.


Then what about following type class hierarchy? I think it supports
those structures. Only restriction is that it forces one to have both
left and right modules. It's possible to split them but I think it will
be to painful for vector spaces over R and C.

class Module v where
type Scalar v :: *
(*^) :: Scalar v → v → v
(^*) :: v → Scalar v → v
(^*) = flip (*^)


Is there any good reason for forcing them together? Why not, use the 
hierarchy I proposed earlier? If you want to reduce the clutter in type 
signatures for real and complex vector spaces then just add to my previous


-- Or just call it Module if preferred.
class (LeftModule v, RightModule v) = AssociativeModule v where
-- Law: (^*) == flip (*^)

This way, when (not if) people want nonassociative modules the classes 
are already there. The additional overhead in defining an associative 
module is only three lines when using default implementation; two lines 
otherwise:


type instance Scalar Foo = Bar
instance AssociativeModule Foo where
instance RightModule Foo where
(^*) = flip (^*)
instance LeftModule Foo where
(*^) = ...

vs

instance Module Foo where
type Scalar Foo = Bar
(*^) = ...

And once it's defined, the usage is the same: just require 
AssociativeModule and you'll pull in both (*^) and (^*).


We already know that there are noncommutative modules/vectorspaces of 
interest (e.g., modules over quaternions and modules over graph paths), 
why not support them from the beginning? It seems like you're going out 
of your way to exclude things that would be trivial to include. This is 
exactly why this is my standard complaint against the various proposals 
out there for new numeric hierarchies. People who are used to only using 
R^n think the proposals are just fine, but none of the proposals capture 
the structures I work with daily. Which means the new proposals are no 
better than the Prelude for me.


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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Richard O'Keefe

On 27/10/2010, at 7:29 AM, Andrew Coppin wrote:
 I didn't say people think Haskell is scary because type theory looks crazy. 
 I said people think Haskell is scary because the typical Haskeller thinks 
 that type theory looks *completely normal*. As in, Haskellers seem to think 
 that every random stranger will know all about this kind of thing, and be 
 completely unfazed by it.

I came to Haskell from ML.  The ML community isn't into category theory (much;
Rod Burstall at Edinburgh was very keen on it).  But they are very definitely 
into
type theory.  The experience of ML was that getting the theory right was the key
to getting implementations without major loop-holes.

The way type systems are presented owes a great deal to one approach to
specifying logics; type *inference* is basically a kind of deduction, and
you want type inference to be sound, so you have to define what are
valid deduction steps.  I came to ML from logic, so it all made perfect sense.


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


[Haskell-cafe] what is the status of haskell's mail libraries?

2010-10-26 Thread Günther Schmidt

Hi all,

I was just looking for mail libraries on hackage. You know libraries 
where I can construct an email, or retrieve on from the server.


With retrieving an email I mean something with a bit more structure than 
a String, or, God help me, a ByteString.


Where are we on this subject? I really cannot tell from the first glance.

Günther

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


Re: [Haskell-cafe] Map constructor in a DSL

2010-10-26 Thread Brandon Moore
You have to figure out here how you can use the function which is the argument 
to map.

It seems you want to end up with a function of type a - Evaluator b, to be 
used as an argument to mapM.

One idea is to add a new constructor Var to represent variables, and something 
like
evalVar :: Obs b - a - Evaluator b
which handles Var by returning the second argument, and everything else as in 
evalObs.

Then you can evaluate Map like
evalObs (Map f) as = evalObs as = mapM (evalVar (f Var))

Except, this won't quit work because the type for evalVar is wrong.

That can be fixed by adding an extra parameter for the variable type:

data Obs varType a where
   ...
   Var :: Obs v v
   Map :: (Obs a a - Obs a b) - Obs v [a] - Obs v [b]

or something like that.

Brandon


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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Richard O'Keefe

On 27/10/2010, at 8:43 AM, Andrew Coppin wrote:

 
 Already I'm feeling slightly lost. (What does the arrow denote? What's are 
 the usual logcal connectives?)

You mentioned Information Science, so there's a good chance you know something
about Visual Basic, where they are called
AND IMP
OR  XOR
NOT EQV
connective in this sense means something like operator.


 
 Predicates are usually interpreted as properties; we might write
 P(x) or Px to indicate that object x has the property P.
 
 Right. So a proposition is a statement which may or may not be true, while a 
 predicate is some property that an object may or may not possess?

A predicate is simply any function returning truth values.
 is a (binary) predicate. ( 0) is a (unary) predicate.

 Right... so its domain is simply *everything* that is discrete? From graph 
 theory to cellular automina to finite fields to difference equations to 
 number theory?

Here's the table of contents of a typical 1st year discrete mathematics book,
selected and edited:
- algorithms on integers
- sets
- functions
- relations
- sequences
- propositional logic
- predicate calculus
- proof
- induction and well-ordering
- recursion
- analysis of algorithms
- graphs
- trees
- spanning trees
- combinatorics
- binomial and multinomial theorem
- groups
- posets and lattices
- Boolean algebras
- finite fields
- natural deduction
- correctness of algorithms

Graph theory is in.  Cellular automata could be but usually aren't.
Difference equations are out.  Number theory would probably be out
except maybe in a 2nd or 3rd year course leading to cryptography.





 That would seem to cover approximately 50% of all of mathematics. (The other 
 50% being the continuous mathematics, presumably...)
 
 ___
 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] In what language...?

2010-10-26 Thread Alexander Solla


On Oct 26, 2010, at 4:21 PM, Richard O'Keefe wrote:


Number theory would probably be out
except maybe in a 2nd or 3rd year course leading to cryptography.


Number theory is one of those weird cases.  They are discrete  
structures, but  advanced number theory uses a lot of complex analysis  
and calculus on other complete spaces, like the p-adics.


Difference equations show up in Knuth's Concrete Mathematics, his  
tome on discrete mathematics.  The theory of difference equations is  
the discrete analogue to the theory of differential equations.   
Surprisingly, the continuous/differential case is more general, since  
integral solutions can be modeled by constant functions.

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


Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Richard O'Keefe

On 27/10/2010, at 12:55 PM, Alexander Solla wrote:

 
 Difference equations show up in Knuth's Concrete Mathematics, his tome on 
 discrete mathematics.  The theory of difference equations is the discrete 
 analogue to the theory of differential equations.  Surprisingly, the 
 continuous/differential case is more general, since integral solutions can be 
 modeled by constant functions.


Graham, Knuth, and Patashnik is one of those books that when they come out are
clearly destined to become classics.  My copy of the first edition wore out to
the point where I was delighted to be able to justify getting a copy of the
second.  Much of it is, however, well outside the scope of the discrete 
mathematics
that one would expect to get in a good undergraduate CS course.  The stuff on
probabilities and generating functions, for example, would be more commonly met 
with
in Statistics, likely 2nd year.

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


[Haskell-cafe] HDF5

2010-10-26 Thread Tim Sears
Does anybody know of any utilities in haskell for reading and writing HDF5 
files?
Other number crunchy formats? Thanks.--Tim

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


Re: [Haskell-cafe] what is the status of haskell's mail libraries?

2010-10-26 Thread Michael Snoyman
I just release mime-mail[1], which can construct multipart messages.

Michael

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/mime-mail

2010/10/27 Günther Schmidt gue.schm...@web.de:
 Hi all,

 I was just looking for mail libraries on hackage. You know libraries where I
 can construct an email, or retrieve on from the server.

 With retrieving an email I mean something with a bit more structure than a
 String, or, God help me, a ByteString.

 Where are we on this subject? I really cannot tell from the first glance.

 Günther

 ___
 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] Pretty-printer for Text

2010-10-26 Thread Ivan Lazar Miljenovic
I'm currently working on a pretty-printer for lazy text [1] values,
basing the API on the wl-pprint [2] package.

[1]: http://hackage.haskell.org/package/text
[2]: http://hackage.haskell.org/package/wl-pprint

In terms of API decisions, there are a few things I'm not sure of and
am wondering what other people would prefer:

* Should the SimpleDoc type still be exported?  Or should the
rendering functions just return a Builder or lazy Text value?

* Is the Pretty class wanted/needed?  If so, should the individual
combinators (int, bool, etc.) be kept or just use pretty for
everything?

* Should String values be catered for or just have everything be Text-based?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help me TH code.

2010-10-26 Thread Andy Stewart
Hi all,

I want use TH write some function like below:

  data DataType = StringT
| IntT
| CharT

  parse :: [(String,DataType)] - (TypeA, TypeB, ... TypeN)

Example:
  
  parse [(string, StringT), (001, IntT), (c, CharT)]

will return:

  (string, 001, 'c')

So how to use TH write 'parse' function? 

Thanks!

  -- Andy

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


[Haskell-cafe] Re: Map constructor in a DSL

2010-10-26 Thread steffen
Hi,

I think you may want to over think your types again.
Especially your Evaluator-Monad, and maybe your Map constructor.

The Problem is, due to your use of Either and the need for evalObs to
finally transform from Obs [a] type to Evaluator [a] you will end
up in another Monad for Either:

instance Monad (Either Actions) where
  return = Right
  (Left x) = _ = Left x
  (Right a) = f = f a

Then one solution may be:

evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)

evalMap :: (a - Obs b) - Evaluator [a] - Evaluator [b]
evalMap f o = liftE (map evalObs) (liftE (map f) o) = \x -
 case x of
   Left actions - return $ Left actions
   Right evals  - sequence evals = return .
sequence
-- first sequence evals creates [Either Actions a]
-- second sequence create Either Actions [a]


After building up the Evaluator [a] construct inside your Evaluator-
Monad, you have to join the construct evals back into your real
Monad and since you pass around results using Either inside your
Evaluator-Monad, you have to treat the Either-type just like another
Monad.

If you get stuck on your types, define new toplevel functions (as
undefined) each taking one argument less  and play with the types in
your files and in ghci until it begins to make sense.



On 26 Okt., 19:42, Dupont Corentin corentin.dup...@gmail.com wrote:
 Hey Chris!
 Values for PlayerNumber are acquired at evaluation time, from the state of
 the system.

 I have not included the evaluation of AllPlayers.
 Here how it looks:

 evalObs AllPlayers  = return . pure  = gets players

 But when you build your Obs, you have yet no idea how much players it will
 be.
 This is just symbolic at this stage.

 To give you a better insight, here is want I want to do with Map:

 everybodyVote :: Obs [Bool]
 everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

 In memory, everybodyVote is just a tree.
 This rule can be executed latter whenever I want to perform this democratic
 vote ;)

 Hope this answer to your question.
 Corentin

 On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
 chrisd...@googlemail.comwrote:







  On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
  wrote:
   But how can I write the evaluator for Map?

  Where do values for PlayerNumber come from? Unless I'm mistaken, the
  only thing that Map can be used with is Obs [PlayerNumber], a list of
  values PlayerNumber which we have no means of acquiring in order to
  provide to the Map function.



 ___
 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


[Haskell-cafe] Re: Map constructor in a DSL

2010-10-26 Thread steffen
Ah, it's too early in the morning...
There is still some room to simplify (e.g. fuse the liftE (map ...)
ops).

Here a simpler Version:

evalObs (Map f obs) = liftE (map (evalObs.f.Konst)) (evalObs obs)
=
either (return.Left)
   (sequence = return . sequence)


On 27 Okt., 06:12, steffen steffen.sier...@googlemail.com wrote:
 Hi,

 I think you may want to over think your types again.
 Especially your Evaluator-Monad, and maybe your Map constructor.

 The Problem is, due to your use of Either and the need for evalObs to
 finally transform from Obs [a] type to Evaluator [a] you will end
 up in another Monad for Either:

     instance Monad (Either Actions) where
       return = Right
       (Left x) = _ = Left x
       (Right a) = f = f a

 Then one solution may be:

     evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)

     evalMap :: (a - Obs b) - Evaluator [a] - Evaluator [b]
     evalMap f o = liftE (map evalObs) (liftE (map f) o) = \x -
                  case x of
                    Left actions - return $ Left actions
                    Right evals  - sequence evals = return .
 sequence
     -- first sequence evals creates [Either Actions a]
     -- second sequence create Either Actions [a]

 After building up the Evaluator [a] construct inside your Evaluator-
 Monad, you have to join the construct evals back into your real
 Monad and since you pass around results using Either inside your
 Evaluator-Monad, you have to treat the Either-type just like another
 Monad.

 If you get stuck on your types, define new toplevel functions (as
 undefined) each taking one argument less  and play with the types in
 your files and in ghci until it begins to make sense.

 On 26 Okt., 19:42, Dupont Corentin corentin.dup...@gmail.com wrote:







  Hey Chris!
  Values for PlayerNumber are acquired at evaluation time, from the state of
  the system.

  I have not included the evaluation of AllPlayers.
  Here how it looks:

  evalObs AllPlayers  = return . pure  = gets players

  But when you build your Obs, you have yet no idea how much players it will
  be.
  This is just symbolic at this stage.

  To give you a better insight, here is want I want to do with Map:

  everybodyVote :: Obs [Bool]
  everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

  In memory, everybodyVote is just a tree.
  This rule can be executed latter whenever I want to perform this democratic
  vote ;)

  Hope this answer to your question.
  Corentin

  On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
  chrisd...@googlemail.comwrote:

   On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
   wrote:
But how can I write the evaluator for Map?

   Where do values for PlayerNumber come from? Unless I'm mistaken, the
   only thing that Map can be used with is Obs [PlayerNumber], a list of
   values PlayerNumber which we have no means of acquiring in order to
   provide to the Map function.

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