[Haskell-cafe] Detecting numeric overflows

2012-07-30 Thread Евгений Пермяков
Can someone tell me if there are any primitives, that used to detect 
machine type overflows, in ghc haskell ? I perfectly understand, that I 
can build something based on preconditioning of variables, but this will 
kill any performance, if needed.


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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-30 Thread Paolo Capriotti
On Sun, Jul 29, 2012 at 7:04 PM, Richard Cobbe co...@ccs.neu.edu wrote:
 I'm working on an application that involves processing a lot of Unicode
 data, and I'm finding the built-in Show implementation for Char to be
 really inconvenient.  Specifically, it renders all characters at U+0080 and
 above with decimal escapes:

 Prelude '\x80'
 '\128'

 This is annoying because all of the Unicode charts give the code points in
 hex, and indeed the charts are split into different PDFs at numbers that
 are nice and round in hex but not in decimal.  So in order to figure out
 which character I'm looking at, I have to convert back to hex and then look
 it up in the charts.

 Is there any way to ask GHC to render super-ASCII characters with their
 hexadecimal escapes, instead?  I'm perfectly happy to write my own custom
 Show instance, but I don't know how to hook that into ghci's REPL (or, for
 that matter, the routines that HUnit uses to generate the messages on
 failed tests, etc.).

 I'm using GHC 7.4.1 on MacOS 10.7.4.

In GHC HEAD there is a new flag -interactive-print that allows to
change the function used for printing values in GHCi. It will be in
7.6.1. That won't help with HUnit output, though.

BR,
Paolo

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


Re: [Haskell-cafe] Capturing the parent element as I parse XML using parsec

2012-07-30 Thread C K Kashyap
Thank you Richard and Antoine.

I think I see the pointlessness of my ask.

Regards,
Kashyap

On Mon, Jul 30, 2012 at 4:14 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 On 29/07/2012, at 6:21 PM, C K Kashyap wrote:
  I am struggling with an idea though - How can I capture the parent
 element of each element as I parse? Is it possible or would I have to do a
 second pass to do the fixup?

 Why do you *want* the parent element of each element?
 One of the insanely horrible aspects of the Document Object Model is that
 every
 element is nailed in place by pointers everywhere, with the result that you
 cannot share elements, and even moving an element was painful.
 I still do a fair bit of SGML/XML process in C using a Document Value
 Model
 library that uses hash consing, and it's so much easier it isn't funny.

 While you are traversing a document tree it is useful to keep track of the
 path from the root.  Given

 data XML
= Element String [(String,String)] [XML]
| Text String

 you do something like

 traverse :: ([XML] - [a] - a) - ([XML] - String - a) - XML - a
 traverse f g xml = loop [] xml
   where loop ancs (Text s)   = g ancs  s
 loop ancs e@(Element _ _ ks) = f ancs' (map (loop ancs') ks)
where ancs' = e:ancs

 (This is yet another area where Haskell's non-strictness pays off.)
 If you do that, then you have the parent information available without
 it being stored in the tree.





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


Re: [Haskell-cafe] Current state of garbage collection in Haskell

2012-07-30 Thread C K Kashyap
Thank you so much Alexander and Thomas.

Regards,
Kashyap

On Sun, Jul 29, 2012 at 11:59 PM, Thomas Schilling
nomin...@googlemail.comwrote:

 GHC does not provide any form of real-time guarantees (and support for
 them is not planned).

 That said, it's not as bad as it sounds:

  - Collecting the first (young) generation is fast and you can control
 the size of that first generation via runtime system (RTS) options.

  - The older generation is collected rarely and can be collected in
 parallel.

  - You can explicitly invoke the GC via System.Mem.performGC

 In a multi-threaded / multi-core program collecting the first
 generation still requires stopping all application threads even though
 only one thread (CPU) will perform GC (and having other threads help
 out usually doesn't work out due to locality issues). This can be
 particularly expensive if the OS decides to deschedule an OS thread,
 as then the GHC RTS has to wait for the OS. You can avoid that
 particular problem by properly configuring the OS via (linux boot
 isolcpus=... and taskset(8)). The GHC team has been working on a
 independent *local* GC, but it's unlikely to make it into the main
 branch at this time. It turned out to be very difficult to implement,
 with not large enough gains. Building a fully-concurrent GC is
 (AFAICT) even harder.

 I don't know how long the pause times for your 500MB live heap would
 be. Generally, you want your heap to be about twice the size of your
 live data. Other than that it depends heavily on the characteristics
 of you heap objects. E.g., if it's mostly arrays of unboxed
 non-pointer data, then it'll be very quick to collect (since the GC
 doesn't have to do anything with the contents of these arrays). If
 it's mostly many small objects with pointers to other objects, GC will
 be very expensive and bound by the latency of your RAM. So, I suggest
 you run some tests with realistic heaps.

 Regarding keeping up, Simon Marlow is the main person working on GHC's
 GC (often collaborating with others) and he keeps a list of papers on
 his homepage: http://research.microsoft.com/en-us/people/simonmar/

 If you have further questions about GHC's GC, you can ask them on the
 glasgow-haskell-us...@haskell.org mailing list (but please consult the
 GHC user's guide section on RTS options first).

 HTH

 On 29 July 2012 08:52, C K Kashyap ckkash...@gmail.com wrote:
  Hi,
  I was looking at a video that talks about GC pauses. That got me curious
  about the current state of GC in Haskell - say ghc 7.4.1.
  Would it suffer from lengthy pauses when we talk about memory in the
 range
  of 500M +?
  What would be a good way to keep abreast with the progress on haskell GC?
  Regards,
  Kashyap
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-30 Thread Max Rabkin
On Sun, Jul 29, 2012 at 8:04 PM, Richard Cobbe co...@ccs.neu.edu wrote:
 This is annoying because all of the Unicode charts give the code points in
 hex, and indeed the charts are split into different PDFs at numbers that
 are nice and round in hex but not in decimal.  So in order to figure out
 which character I'm looking at, I have to convert back to hex and then look
 it up in the charts.

My reading of the Haskell 98 report is that the Show instance for Char
*could* use hex escapes, so this is a compiler choice. If there isn't
a good reason for this choice, perhaps GHC could change?

--Max

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


Re: [Haskell-cafe] Logging pure code

2012-07-30 Thread Johan Brinch
On Mon, Jul 30, 2012 at 1:54 AM, Thomas Schilling
nomin...@googlemail.com wrote:
 On 27 July 2012 14:52, Marco Túlio Gontijo e Silva
 marcotmar...@gmail.com wrote:
 thread blocked indefinitely in an MVar operation

 IIRC, that means that a thread is blocked on an MVar and the MVar is
 only reachable by that thread.

This sounds right. STM has noticed that there's a thread waiting for
something that will never be available. It seems it have found a
deadlock.

I once tried mixing IO and STM actions (IO inside STM) and ended up
rewriting the code to seperate the two. Before the rewrite, I got some
of the strangest and most unpredictable errors I've ever seen in a
Haskell program. I reckon this could be related.

Here's the thread from back then:
http://www.haskell.org/pipermail/haskell-cafe/2012-January/098453.html

-- 
Johan Brinch

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-07-30 Thread Niklas Broberg
On Wed, Jul 25, 2012 at 12:22 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 As I understand it, the plan is to modify the following packages in
 hackage in-situ to remove the test sections (which contain the troublesome
 conditionals):

   HUnit-1.2.5.0
   bloomfilter-1.2.6.10
   codemonitor-0.1
   codemonitor-0.2
   fixhs-0.1.4
   leksah-server-0.12.0.3
   leksah-server-0.12.0.4
   leksah-server-0.12.0.5
   pqc-0.5
   pqc-0.5.1

 Does anyone object?


No objections, but some impatience. ;-)

Cheers,

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-07-30 Thread Ross Paterson
On Mon, Jul 30, 2012 at 01:46:24PM +0100, Niklas Broberg wrote:
 On Wed, Jul 25, 2012 at 12:22 PM, Ross Paterson r...@soi.city.ac.uk wrote:
 
 As I understand it, the plan is to modify the following packages in
 hackage in-situ to remove the test sections (which contain the troublesome
 conditionals):
 
   HUnit-1.2.5.0
   bloomfilter-1.2.6.10
   codemonitor-0.1
   codemonitor-0.2
   fixhs-0.1.4
   leksah-server-0.12.0.3
   leksah-server-0.12.0.4
   leksah-server-0.12.0.5
   pqc-0.5
   pqc-0.5.1
 
 Does anyone object?
 
 No objections, but some impatience. ;-)

OK, done.

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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-30 Thread Ivan Lazar Miljenovic
On 30 July 2012 04:04, Richard Cobbe co...@ccs.neu.edu wrote:
 I'm working on an application that involves processing a lot of Unicode
 data, and I'm finding the built-in Show implementation for Char to be
 really inconvenient.  Specifically, it renders all characters at U+0080 and
 above with decimal escapes:

 Prelude '\x80'
 '\128'

 This is annoying because all of the Unicode charts give the code points in
 hex, and indeed the charts are split into different PDFs at numbers that
 are nice and round in hex but not in decimal.  So in order to figure out
 which character I'm looking at, I have to convert back to hex and then look
 it up in the charts.

Can I ask what you're doing here? Are you printing individual
characters or entire chunks of text?

putStrLn and similar IO-based functions (at least for me) will
un-escape characters if that helps.  Otherwise, are you using Text or
String?


 Is there any way to ask GHC to render super-ASCII characters with their
 hexadecimal escapes, instead?  I'm perfectly happy to write my own custom
 Show instance, but I don't know how to hook that into ghci's REPL (or, for
 that matter, the routines that HUnit uses to generate the messages on
 failed tests, etc.).

 I'm using GHC 7.4.1 on MacOS 10.7.4.

 Thanks,

 Richard

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



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] AI - machine learning

2012-07-30 Thread Chris Taylor
miro miroslav.karpis at gmail.com writes:

 
 Hi All, recently I started to take a look at haskell,
   especially at AI. I can see some email addresses of interested
   people there but not so much of other activity behind. Does it
   exist some mailing group especially for AI? 
   Basically I'm interested in trying some machine learning
   algorithms. Start with reinforcement learning and value-based),
   and go towards AGI (Artificial General Intelligence). Does anybody
   know about some already existing haskell approaches, or is there
   anybody working on this?
   Cheers,
   m.
 

Hi Miro

For the past month or so I've been working through some of the algorithms in 
Artificial Intelligence: A Modern Approach by Russell and Norvig, and 
implementing them in Haskell. The code is available on github 
(https://github.com/chris-taylor/aima-haskell), you may be interested in taking 
a look. I haven't written any code for reinforcement learning yet, though I 
have 
implemented value iteration and policy iteration for MDPs.

Chris


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


Re: [Haskell-cafe] AI - machine learning

2012-07-30 Thread Mihai Maruseac
On Mon, Jul 30, 2012 at 4:39 PM, Chris Taylor crntay...@gmail.com wrote:
 miro miroslav.karpis at gmail.com writes:


 Hi All, recently I started to take a look at haskell,
   especially at AI. I can see some email addresses of interested
   people there but not so much of other activity behind. Does it
   exist some mailing group especially for AI?
   Basically I'm interested in trying some machine learning
   algorithms. Start with reinforcement learning and value-based),
   and go towards AGI (Artificial General Intelligence). Does anybody
   know about some already existing haskell approaches, or is there
   anybody working on this?
   Cheers,
   m.


 Hi Miro

 For the past month or so I've been working through some of the algorithms in
 Artificial Intelligence: A Modern Approach by Russell and Norvig, and
 implementing them in Haskell. The code is available on github
 (https://github.com/chris-taylor/aima-haskell), you may be interested in 
 taking
 a look. I haven't written any code for reinforcement learning yet, though I 
 have
 implemented value iteration and policy iteration for MDPs.


Hi,

I have an implementation of maze solving via genetic algorithms in
Haskell at https://github.com/mihaimaruseac/HsMaze

It was a homework with some added extensions but I guess that it is
worth a look and some feedabck if possible :)

Thanks

-- 
MM

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


[Haskell-cafe] Polyvariadic composition

2012-07-30 Thread Artyom Kazak

Hello,

I have accidentally written my version of polyvariadic composition  
combinator, `mcomp`. It differs from Oleg’s version (  
http://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp ) in three  
aspects: a) it is simpler, b) it works without enumerating basic cases  
(all existing types, in other words), and c) it needs more type extensions.



{-# LANGUAGE
  MultiParamTypeClasses
, FunctionalDependencies
, FlexibleInstances
, UndecidableInstances
, TypeFamilies  , OverlappingInstances
  #-}

class Mcomp a ar b br | a br - b where
  mcomp :: a - (ar - br) - b

instance (a ~ ar, b ~ br) = Mcomp a ar b br where
  mcomp a f = f a

instance (Mcomp a ar b br) = Mcomp (x - a) ar (x - b) br where
  mcomp a f = \x - mcomp (a x) f


My question is: why doesn’t it work when I replace

instance (a ~ ar, b ~ br) = Mcomp a ar b br

with

instance Mcomp a a b b

? I thought that equal letters mean equal types…

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


Re: [Haskell-cafe] Detecting numeric overflows

2012-07-30 Thread Artyom Kazak
Евгений Пермяков permea...@gmail.com писал в своём письме Mon, 30 Jul  
2012 09:47:48 +0300:


Can someone tell me if there are any primitives, that used to detect  
machine type overflows, in ghc haskell ? I perfectly understand, that I  
can build something based on preconditioning of variables, but this will  
kill any performance, if needed.


In GHC.Prim — primitives addIntC# and subIntC#:


addIntC# :: Int# - Int# - (#Int#, Int##)
Add with carry. First member of result is (wrapped) sum; second member  
is 0 iff no overflow occured.



subIntC# :: Int# - Int# - (#Int#, Int##)
Subtract with carry. First member of result is (wrapped) difference;  
second member is 0 iff no overflow occured.


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


Re: [Haskell-cafe] Polyvariadic composition

2012-07-30 Thread MigMit
Works here.

GHC 7.4.2

On Jul 30, 2012, at 11:32 PM, Artyom Kazak artyom.ka...@gmail.com wrote:

 Hello,
 
 I have accidentally written my version of polyvariadic composition 
 combinator, `mcomp`. It differs from Oleg’s version ( 
 http://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp ) in three 
 aspects: a) it is simpler, b) it works without enumerating basic cases (all 
 existing types, in other words), and c) it needs more type extensions.
 
 {-# LANGUAGE
  MultiParamTypeClasses
, FunctionalDependencies
, FlexibleInstances
, UndecidableInstances
, TypeFamilies  , OverlappingInstances
  #-}
 
 class Mcomp a ar b br | a br - b where
  mcomp :: a - (ar - br) - b
 
 instance (a ~ ar, b ~ br) = Mcomp a ar b br where
  mcomp a f = f a
 
 instance (Mcomp a ar b br) = Mcomp (x - a) ar (x - b) br where
  mcomp a f = \x - mcomp (a x) f
 
 My question is: why doesn’t it work when I replace
 
instance (a ~ ar, b ~ br) = Mcomp a ar b br
 
 with
 
instance Mcomp a a b b
 
 ? I thought that equal letters mean equal types…
 
 ___
 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] Detecting numeric overflows

2012-07-30 Thread Евгений Пермяков

On 07/31/2012 12:04 AM, Artyom Kazak wrote:
Евгений Пермяков permea...@gmail.com писал в своём письме Mon, 30 
Jul 2012 09:47:48 +0300:


Can someone tell me if there are any primitives, that used to detect 
machine type overflows, in ghc haskell ? I perfectly understand, that 
I can build something based on preconditioning of variables, but this 
will kill any performance, if needed.


In GHC.Prim — primitives addIntC# and subIntC#:


addIntC# :: Int# - Int# - (#Int#, Int##)
Add with carry. First member of result is (wrapped) sum; second 
member is 0 iff no overflow occured.



subIntC# :: Int# - Int# - (#Int#, Int##)
Subtract with carry. First member of result is (wrapped) difference; 
second member is 0 iff no overflow occured.


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

Still no way to detect overflow in *.

Strangely enough, I found some relevant descriptions in *.pp in dev 
branch, so I expect them in 7.6.1. They applies to native-size Word and 
Int only.


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


Re: [Haskell-cafe] why does a foldr not have a space leak effect?

2012-07-30 Thread Ryan Ingram
The difference is that foldl *must* produce the entire list of thunks, even
if f is lazy in its first argument.

There's no foldl that can perform better given a sufficiently-lazy f; given

head = foldr go fail where
go x y = x
fail = error head: empty list

head [a,b,c,d]
= foldr go fail [a,b,c,d]
= go a (foldr go fail [b,c,d])
= a

you might think you can define

last = foldl go fail where
go x y = y
fail = error last: empty list

but this fails to be sufficiently lazy:

last [a,b,c,d]
= foldl go fail [a,b,c,d]
= foldl go (go fail a) [b,c,d]
= foldl go (go (go fail a) b) [c,d]
= foldl go (go (go (go fail a) b) c) [d]
= foldl go (go (go (go (go fail a) b) c) d) []
= go (go (go (go fail a) b) c) d
= d

which allocates lots of extra space for thunks, which may even take more
memory than the original list.

Whereas if last uses foldl':

last [a,b,c,d]
= foldl' go fail [a,b,c,d]
= let z = go fail a in seq z $ foldl' go z [b,c,d]
= foldl' go a [b,c,d]
= let z = go a b in seq z $ foldl' go z [c,d]
= foldl' go b [c,d]
= ...
= let z = go c d in seq z $ foldl' go z []
= foldl' go d []
= d

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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-30 Thread Henk-Jan van Tuyl
On Mon, 16 Jul 2012 00:03:49 +0200, Henk-Jan van Tuyl hjgt...@chello.nl  
wrote:




I am willing to do administrator tasks.


4. ReCAPTCHA enabled for 'edits adding new, unrecognized external
links' - which is all of the spam.


This is already enabled.


The HaskellWiki is still flooded with spam; we should take some measure to  
reduce the stream severely. Most spam seems to be created  
(semi-)automated; the pages do not contain links, the usernames end with  
two digits, most of the time. Some cures I have thought up:


 - Verify new wiki accounts, before granting them rights,
   based on e-mails in the Haskell mailing lists
   (or subscription of a Haskell mailing list)

 - Let new users only change pages, not create new pages

 - Block creation of usernames
o ending with two or more digits
o with more than one x or q
o starting with buy
o longer than 20 characters
o with more than 4 consonants in a row

 - Block creation of pages with words in a certain list
   (Coach, Vuitton, Chanel, handbags, purses, outlet, luggage, Nike Air  
Jordan)


Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-30 Thread timothyhobbs

Can we have at least 5 consonants?  There are enough people with names such
as Srbský in eastern European  In fact, the Czechs can make use of as
many as 9 consonants in a row!  http://ld.johanesville.net/perlicky/03-
jazykova-nej-a-jine-hricky




On a side note, image based CAPACHA's can cause problems for blind people.







-- Původní zpráva --
Od: Henk-Jan van Tuyl hjgt...@chello.nl
Datum: 30. 7. 2012
Předmět: Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki
On Mon, 16 Jul 2012 00:03:49 +0200, Henk-Jan van Tuyl hjgt...@chello.nl
wrote:


 I am willing to do administrator tasks.

 4. ReCAPTCHA enabled for 'edits adding new, unrecognized external
 links' - which is all of the spam.

 This is already enabled.

The HaskellWiki is still flooded with spam; we should take some measure to
reduce the stream severely. Most spam seems to be created
(semi-)automated; the pages do not contain links, the usernames end with 
two digits, most of the time. Some cures I have thought up:

- Verify new wiki accounts, before granting them rights,
based on e-mails in the Haskell mailing lists
(or subscription of a Haskell mailing list)

- Let new users only change pages, not create new pages

- Block creation of usernames
o ending with two or more digits
o with more than one x or q
o starting with buy
o longer than 20 characters
o with more than 4 consonants in a row

- Block creation of pages with words in a certain list
(Coach, Vuitton, Chanel, handbags, purses, outlet, luggage, Nike Air
Jordan)

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/(http://Van.Tuyl.eu/)
http://members.chello.nl/hjgtuyl/tourdemonad.html
(http://members.chello.nl/hjgtuyl/tourdemonad.html)
Haskell programming
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
(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] [Haskell] Spam on the Haskell wiki

2012-07-30 Thread Alexander Solla
On Mon, Jul 30, 2012 at 2:35 PM, Henk-Jan van Tuyl hjgt...@chello.nlwrote:


  - Verify new wiki accounts, before granting them rights,
based on e-mails in the Haskell mailing lists
(or subscription of a Haskell mailing list)


This is a nice idea, but I think it will end up moving spam onto the
mailing lists.  There is hardly any policy in place to keep people out of
the mailing lists.  Mailing list spam is attractive to spammers, since it
all gets mirrored to archive sites all over the place.

Not to volunteer others, but how feasible would it be to require
credentials from Haskellers.org?


  - Let new users only change pages, not create new pages


This is good for stopping the creation of walled gardens full of spam.  But
it won't stop vandalism spam, where somebody goes to a page that isn't
accessed much and changes it.

Does anybody have statistics about how often pages are edited/added?  If
the numbers aren't too big, I'd volunteer to moderate insofar as scanning
new edits/adds for spam.  Maybe this role should just forward articles with
spam on them to a real moderator to roll-back.  We could even have a
report spam button on each page, and if enough users click on it (for a
given revision), the revision gets forwarded to a moderator.


  - Block creation of usernames
 o ending with two or more digits
 o with more than one x or q
 o starting with buy
 o longer than 20 characters
 o with more than 4 consonants in a row


I don't see this providing any security against spam, and I'm thinking it
will take longer to implement than it will take for a spammer to fix his
scripts in response.


  - Block creation of pages with words in a certain list
(Coach, Vuitton, Chanel, handbags, purses, outlet, luggage, Nike Air
 Jordan)


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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-30 Thread Ricardo Wurmus
On 31 July 2012 05:35, Henk-Jan van Tuyl hjgt...@chello.nl wrote:

... with more than one x or q

This would exclude legitimate Chinese (pinyin) usernames for not much gain.

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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-30 Thread Michael Orlitzky
On 07/30/2012 05:35 PM, Henk-Jan van Tuyl wrote:
 On Mon, 16 Jul 2012 00:03:49 +0200, Henk-Jan van Tuyl hjgt...@chello.nl  
 wrote:
 

 I am willing to do administrator tasks.

 4. ReCAPTCHA enabled for 'edits adding new, unrecognized external
 links' - which is all of the spam.

 This is already enabled.
 
 The HaskellWiki is still flooded with spam; we should take some measure to  
 reduce the stream severely. Most spam seems to be created  
 (semi-)automated; the pages do not contain links, the usernames end with  
 two digits, most of the time. Some cures I have thought up:
 

There are two (easy) things that will make a huge dent in the automated
stuff.

  1. Add a fake field, hidden through CSS, labeled something like You
 must leave this field blank to submit the form (for non-visual
 browsers). Put it on every page with a submit button. If it isn't
 empty, don't process the submission. You can give it a /name/ that
 sounds tempting, though.

  2. Force previews. If the bots are targeted at your wiki software and
 you modify it to preview all submissions, the bots will stop
 working.


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


Re: [Haskell-cafe] Polyvariadic composition

2012-07-30 Thread Ryan Ingram
My completely off-the-cuff guess is that
a a b b
isn't considered more or less specific than
(x - a) ar (x - b) br
since they both apply some constraint on the types.  For example, it's not
immediately clear that the first instance can't be used for (x - a) (x -
a) (x - b) (x - b)

Whereas when you say
a ar b br
the type
(x - a) ar (x - b) br
is strictly more specific, so the overlapping instance can be chosen.

Remember instance selection is done entirely via the instance head, so
instance X a a
is not the same as
instance (a ~ b) = X a b

The first case supplies an instance for any two equal types, and the second
case supplies an instance for *any two types*, then throws an error if the
compiler can't prove that the two types are equal.

For example, without overlapping instances, you can write

class X a b where foo :: a - b

instance X a a where foo = id
instance X Int Bool where foo = (== 0)

But if instead you specify
instance (a ~ b) = X a b where foo = id
you can't specify the Int Bool instance without overlap.

  -- ryan

On Mon, Jul 30, 2012 at 12:32 PM, Artyom Kazak artyom.ka...@gmail.comwrote:

 Hello,

 I have accidentally written my version of polyvariadic composition
 combinator, `mcomp`. It differs from Oleg’s version (
 http://okmij.org/ftp/Haskell/**polyvariadic.html#polyvar-comphttp://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp)
  in three aspects: a) it is simpler, b) it works without enumerating basic
 cases (all existing types, in other words), and c) it needs more type
 extensions.

  {-# LANGUAGE
   MultiParamTypeClasses
 , FunctionalDependencies
 , FlexibleInstances
 , UndecidableInstances
 , TypeFamilies  , OverlappingInstances
   #-}

 class Mcomp a ar b br | a br - b where
   mcomp :: a - (ar - br) - b

 instance (a ~ ar, b ~ br) = Mcomp a ar b br where
   mcomp a f = f a

 instance (Mcomp a ar b br) = Mcomp (x - a) ar (x - b) br where
   mcomp a f = \x - mcomp (a x) f


 My question is: why doesn’t it work when I replace

 instance (a ~ ar, b ~ br) = Mcomp a ar b br

 with

 instance Mcomp a a b b

 ? I thought that equal letters mean equal types…

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-30 Thread Ryan Ingram
With apologies to Jim Coplien :)

I've been seeing this pattern in a surprising number of instance
definitions lately:

instance (a ~ ar, b ~ br) = Mcomp a ar b br [1]
instance (b ~ c, CanFilterFunc b a) = CanFilter (b - c) a [2]

The trick is that since instance selection is done entirely on the instance
head, these instances are strictly more general than the ones they replace:

instance Mcomp a a b b
instance CanFilterFunc b = CanFilter (b - b) a

The compiler has to do a lot more work to select these instances; it has to
prove that the matching types actually match before it can select the
instance; if it can't, it won't select an instance, and instead will
complain about no instance CLASS Int a.  But with the CRIP, you help the
compiler--it chooses the general instance, and then gets a constraint to
solve.  The constraint forces the two types to unify, or else there is a
type error.

What I'm wondering is--are there many cases where you really want the
non-constraint-generating behavior?  It seems like (aside from contrived,
ahem, instances) whenever you have instance CLASS A B where A and B share
some type variables, that there aren't any valid instances of the same
class where they don't share the types in that way.  For example, I've
never really seen a class in practice with instances like

class Foo a b
instance Foo a a
instance Foo ConcreteTypeA ConcreteTypeB

Note that it's very difficult to use polymorphic types in the second
instance without risking overlap.

TL;DR: I, for one, welcome our new type equality constraint overlords.

  -- ryan

[1] http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/99611
[2] http://www.yesodweb.com/blog/2012/07/classy-prelude
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is (==) commutative?

2012-07-30 Thread Christian Sternagel

Thanks Wren, for the explanations (also in your previous mail)!

On 07/30/2012 01:29 PM, wren ng thornton wrote:

On 7/24/12 9:19 PM, Christian Sternagel wrote:

(x == y) = True == x = y
(x == y) = False == not (x = y)
(x == _|_) = _|_
(_|_ == y) = _|_

Those axioms state that (==) is sound w.r.t. to meta-equality and strict
in both it's arguments.


An immediate problem that arises here is: what exactly does
meta-equality denote in Isabelle/HOLCF? If it is meant to denote
syntactic identity or Leibniz equality a la Coq, then the first axiom is
certainly too strong for any interesting data types (e.g., Rational,
Data.Set, Data.Map, Data.IntSet,...)
Yes, we also stumbled about this (but I was only discussing it on the 
isabelle mailing list and not here, sorry). The conclusion was that for 
many type classes there are several interesting (whatever that means) 
instances. Thus, in the formalization we will use different formal 
type classes for different intended use-cases of Haskell type classes 
(e.g., one eq class for syntactic equality and another one that merely 
requires an equivalence relation, ...). That just means that there will 
not be a bijection between the formal class hierarchy and the actual 
class hierarchy of Haskell, but should not pose any further problems (I 
hope).


Btw: I don't agree that the axioms are too strong for *any* interesting 
data types ;). What about Bool, Int, [a], ...? (Again, this depends on 
how we interpret interesting; in formalizations the threshold for 
being interesting is typically lower.)


cheers

chris

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


Re: [Haskell-cafe] specifying using type class

2012-07-30 Thread Ryan Ingram
Generally the way this is done in Haskell is that the interface to the type
is specified in a typeclass (or, alternatively, in a module export list,
for concrete types), and the axioms are specified in a method to be tested
in some framework (i.e. QuickCheck, SmallCheck, SmartCheck) which can
automatically generate instances of your type and test that the axioms hold.

For example:

class QueueLike q where
empty :: q a
insert :: a - q a - q a
viewFirst :: q a - Maybe (a, q a)
size :: q a - Integer

-- can use a single proxy type if have kind polymorphism, but that's an
experimental feature right now
data Proxy2 (q :: * - *) = Proxy2
instance Arbitrary (Proxy2 q) where arbitrary = return Proxy2

prop_insertIncrementsSize :: forall q. QueueLike q = q () - Bool
prop_insertIncrementsSize q = size (insert () q) == size q + 1

prop_emptyQueueIsEmpty :: forall q. QueueLike q = Proxy2 q = Bool
prop_emptyQueueIsEmpty Proxy2 = maybe True (const False) $ view (empty :: q
())

Then you specialize these properties to your type and test them:

instance QueueLike [] where ...

ghci quickCheck (prop_insertIncrementsSize :: [()] - Bool)
Valid, passed 100 tests
or
Failed with: [(), (), ()]

QuickCheck randomly generates objects of your data structure and tests your
property against them.  While not as strong as a proof, programs with 100%
quickcheck coverage are *extremely* reliable.  SmartCheck is an extension
of QuickCheck that tries to reduce test cases to the minimum failing size.

SmallCheck does exhaustive testing on the properties for finite data
structures up to a particular size.  It's quite useful when you can prove
your algorithms 'generalize' after a particular point.

There aren't any libraries that I know of for dependent-type style program
proof for haskell; I'm not sure it's possible.  The systems I know of have
you program in a more strongly typed language (Coq/agda) and export Haskell
programs once they are proven safe.  Many of these rely on unsafeCoerce in
the Haskell code because they have proven stronger properties about the
types than Haskell can; I look at that code with some trepidation--I am not
sure what guarantees the compiler makes about unsafeCoerce.

  -- ryan

On Sun, Jul 22, 2012 at 7:19 AM, Patrick Browne patrick.bro...@dit.iewrote:

 {-
 Below is a *specification* of a queue.
 If possible I would like to write the equations in type class.
 Does the type class need two type variables?
 How do I represent the constructors?
 Can the equations be written in the type class rather than the instance?
 -}

 module QUEUE_SPEC where
 data Queue e   = New | Insert (Queue e) e deriving Show

 isEmpty :: Queue  e  - Bool
 isEmpty  New  = True
 isEmpty (Insert q e) = False

 first :: Queue  e  - e
 first (Insert q e) =  if (isEmpty q) then e else (first q)


 rest :: Queue  e  - Queue  e
 rest (Insert  q e ) = if (isEmpty q) then New  else (Insert (rest q) e)


 size :: Queue  e  - Int
 size New  = 0
 size (Insert q e) = succ (size q)

 {-
 some tests of above code
 size (Insert (Insert (Insert New 5) 6) 3)
 rest (Insert (Insert (Insert New 5) 6) 3)

 My first stab at a class
 class QUEUE_SPEC q e where
  new :: q e
  insert :: q e - q e
  isEmpty :: q  e  - Bool
  first :: q  e  - e
  rest :: q  e  - q e
  size :: q e  - Int

 -}


 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís
 Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a
 bheith slán. http://www.dit.ie
 This message has been scanned for content and viruses by the DIT
 Information Services E-Mail Scanning Service, and is believed to be clean.
 http://www.dit.ie
 ___
 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] What does unpacking an MVar really mean?

2012-07-30 Thread Leon Smith
I admit I don't know exactly how MVars are implemented,  but given that
they can be aliased and have indefinite extent,   I would think that they
look something vaguely like a  cdatatype ** var,  basically a pointer to an
MVar (which is itself a pointer,  modulo some other things such as a thread
queue.)

And,  I would think that unpacking such an structure would basically be
eliminating one layer of indirection,  so it would then look vague like a
cdatatype * var.But again,  given aliasing and indefinite extent, this
would seem to be a difficult thing to do.

Actually this isn't too difficult if an MVar only exists in a single
unpacked structure:   other references to the MVar can simply be pointers
into the structure.   But the case where an MVar is unpacked into two
different structures suggests that,  at least in some cases,  an unpacked
MVar is still a cdatatype ** var;

So, is my understanding more or less correct?  Does anybody have a good,
succinct explanation of how MVars are implemented,  and how they are
unpacked?

One final question,   assuming that unpacking an MVar really does eliminate
a layer of indirection,  and that other references to that MVar are simply
pointers into a larger structure,   what happens to that larger structure
when there are no more references to it (but still some references to the
MVar?)Given the complications that must arise out of a doubly
unpacked MVar,  I'm going to guess that the larger structure does get
garbage collected in this case,  and that the MVar becomes dislodged from
this structure.   Would that MVar then be placed directly inside another
unpacked reference, if one is available?

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


Re: [Haskell-cafe] What does unpacking an MVar really mean?

2012-07-30 Thread Ryan Ingram
I'm not sure I totally understand your question about 'unpacking' an MVar,
but I'm going to assume you mean data structures that use the {-# UNPACK
#-} pragma, like in Control.Concurrent.Future [1] and
Control.Concurrent.NamedLock [2].

Here is how MVar is defined in GHC [3]:
data MVar a = MVar (MVar# RealWorld a)

A MVar# s a is an unboxed pointer to a structure understood by the GHC
runtime.

So yes, you can imagine a MVar as a pointer-to-pointer.  The structure it
points at likely has another pointer to the embedded boxed a, so it may
even be pointer-to-pointer-to-pointer.

The MVar data structure exists to allow laziness; for example

   let x = unsafePerformIO (newMVar ()) in ()

is likely to not allocate an MVar#, just a thunk that would create an MVar
if it was evaluated.  Unboxed objects (represented by convetion with # in
GHC), on the other hand, are strict, so if you have an MVar# RealWorld (),
you know it points to a valid MVar#.

From [2] we have
data NLItem = NLItem {-# UNPACK #-} !Int
 {-# UNPACK #-} !(MVar ())

All the {-# UNPACK #-} pragma does is embed the contents of a strict
single-constructor data declaration *directly* into the structure
containing it; it's like you declared NLItem as such:

data NLItem = NLItem Word# (MVar# RealWorld ())

except that if you call functions that want an Int or MVar thunk, the
compiler will automatically re-box them in a new I#/MVar constructor.

Many copies of pointers to the same MVar# may exist; they are all
'identical' MVars; equality is defined as such:
instance Eq (MVar a) where
(MVar mvar1#) == (MVar mvar2#) = sameMVar# mvar1# mvar2#

where sameMVar# is a primitive that is probably just raw pointer equality.

Because of this, boxed MVars can be garbage collected without necessarily
garbage-collecting the MVar# it holds, if a live reference to that MVar#
still exists elsewhere.

  -- ryan

[1]
http://hackage.haskell.org/packages/archive/future/2.0.0/doc/html/src/Control-Concurrent-Future.html
[2]
http://hackage.haskell.org/packages/archive/named-lock/0.1/doc/html/src/Control-Concurrent-NamedLock.html
[3]
http://www.haskell.org/ghc/docs/7.4.1/html/libraries/base/src/GHC-MVar.html#MVar

On Mon, Jul 30, 2012 at 9:25 PM, Leon Smith leon.p.sm...@gmail.com wrote:

 I admit I don't know exactly how MVars are implemented,  but given that
 they can be aliased and have indefinite extent,   I would think that they
 look something vaguely like a  cdatatype ** var,  basically a pointer to an
 MVar (which is itself a pointer,  modulo some other things such as a thread
 queue.)

 And,  I would think that unpacking such an structure would basically be
 eliminating one layer of indirection,  so it would then look vague like a
 cdatatype * var.But again,  given aliasing and indefinite extent, this
 would seem to be a difficult thing to do.

 Actually this isn't too difficult if an MVar only exists in a single
 unpacked structure:   other references to the MVar can simply be pointers
 into the structure.   But the case where an MVar is unpacked into two
 different structures suggests that,  at least in some cases,  an unpacked
 MVar is still a cdatatype ** var;

 So, is my understanding more or less correct?  Does anybody have a good,
 succinct explanation of how MVars are implemented,  and how they are
 unpacked?

 One final question,   assuming that unpacking an MVar really does
 eliminate a layer of indirection,  and that other references to that MVar
 are simply pointers into a larger structure,   what happens to that larger
 structure when there are no more references to it (but still some
 references to the MVar?)Given the complications that must arise out of
 a doubly unpacked MVar,  I'm going to guess that the larger structure
 does get garbage collected in this case,  and that the MVar becomes
 dislodged from this structure.   Would that MVar then be placed directly
 inside another unpacked reference, if one is available?

 Best,
 Leon

 ___
 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] What does unpacking an MVar really mean?

2012-07-30 Thread Leon Smith
Let me clarify a bit.

I am familiar with the source of Control.Concurrent.MVar,  and I do see {-#
UNPACK #-}'ed MVars around,  for example in GHC's IO manager. What I
should have asked is,  what does an MVar# look like?  This cannot be
inferred from Haskell source;  though I suppose I could have tried to read
the Runtime source.

Now,  one would hope that and (MVar# RealWorld footype) would
 approximately correspond to a footype * mvar; variable in C.   The
problem is this cannot _always_ be the case,  because you can alias the
(MVar# RealWorld footype) by placing a single MVar into two unpacked
columns in two different data structures.So you would need to be able
to still sometimes represent an MVar# by a footype ** mvar at runtime,
 even though one would hope that it would be represented by a footype *
mvar in one particular data structure.

On Tue, Jul 31, 2012 at 1:04 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 Because of this, boxed MVars can be garbage collected without necessarily
 garbage-collecting the MVar# it holds, if a live reference to that MVar#
 still exists elsewhere.


I was asking the dual question:  if the MVar# exists in some data
structure,  can that data structure still be garbage collected when there
is a reference to the MVar#,  but not the data structure it is contained
within.

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


Re: [Haskell-cafe] How to define a Monad instance

2012-07-30 Thread Ryan Ingram
To take this a step further, if what you really want is the syntax sugar
for do-notation (and I understand that, I love sweet, sweet syntactical
sugar), you are probably implementing a Writer monad over some monoid.

Here's two data structures that can encode this type;

data Replacer1 k a = Replacer1 (k - Maybe k) a
data Replacer2 k a = Replacer2 [(k,k)] a

instance Monad Replacer1 where
return x = Replacer1 (\_ - Nothing) x
Replacer1 ka a = f = result where
Replacer1 kb b = f a
result = Replacer1 (\x - ka x `mplus` kb x) b

(!) :: Eq k = k - k - Replacer1 k ()
x ! y = Replacer1 (\k - if k == x then Just y else Nothing) ()

replace1 :: Replacer1 k () - [k] - [k]-- look ma, no Eq requirement!
replace1 (Replacer k ()) = map (\x - fromMaybe x $ k x) -- from Data.Maybe

table1 :: Replacer1 Char ()
table1 = do
'a' ! 'b'
'A' ! 'B'

test = replace1 table1 All I want

-- Exercise: what changes if we switch ka and kb in the result of (=)?
When does it matter?

-- Exercises for you to implement:
instance Monad Replacer2 k where
replacer :: Eq k = Replacer2 k - [k] - [k]
($) :: k - k - Replacer2 k

-- Exercise: Lets make use of the fact that we're a monad!
--
-- What if the operator ! had a different type?
-- (!) :: Eq k = k - k - Replacer k Integer
-- which returns the count of replacements done.
--
-- table3 = do
-- count - 'a' ! 'b'
-- when (count  3) ('A' ! 'B')
-- return ()
--
-- Do any of the data structures I've given work?  Why or why not?
-- Can you come up with a way to implement this?

  -- ryan

On Sat, Jul 28, 2012 at 10:07 AM, Steffen Schuldenzucker 
sschuldenzuc...@uni-bonn.de wrote:

 On 07/28/2012 03:35 PM, Thiago Negri wrote:
  [...]

  As Monads are used for sequencing, first thing I did was to define the
 following data type:

 data TableDefinition a = Match a a (TableDefinition a) | Restart


 So TableDefinition a is like [(a, a)].

  [...]

 

 So, to create a replacement table:

 table' :: TableDefinition Char
 table' =
  Match 'a' 'b'
  (Match 'A' 'B'
   Restart)

 It look like a Monad (for me), as I can sequence any number of
 replacement values:

 table'' :: TableDefinition Char
 table'' = Match 'a' 'c'
   (Match 'c' 'a'
   (Match 'b' 'e'
   (Match 'e' 'b'
Restart)))


 Yes, but monads aren't just about sequencing. I like to see a monad as a
 generalized computation (e.g. nondeterministic, involving IO, involving
 state etc). Therefore, you should ask yourself if TableDefinition can be
 seen as some kind of abstract computation. In particular, can you
 execute a computation and extract its result? as in

   do
 r - Match 'a' 'c' Restart
 if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

 Doesn't immediately make sense to me. In particular think about the
 different possible result types of a TableDefinition computation.

 If all you want is sequencing, you might be looking for a Monoid instance
 instead, corresponding to the Monoid instance of [b], where b=(a,a) here.

   [...]

 

 I'd like to define the same data structure as:

 newTable :: TableDefinition Char
 newTable = do
  'a' :  'b'
  'A' :  'B'

 But I can't figure a way to define a Monad instance for that. :(


 The desugaring of the example looks like this:

   ('a' : 'b')  ('A' : 'B')

 Only () is used, but not (=) (i.e. results are always discarded). If
 this is the only case that makes sense, you're probably looking for a
 Monoid instead (see above)

 -- Steffen


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] How to define a Monad instance

2012-07-30 Thread Ryan Ingram
A couple typos:

instance Monad Replacer1 where
-
instance Monad (Replacer1 k) where

instance Monad Replacer2 k where
-
instance Monad (Replacer2 k) where

I haven't tested any of this code, so you may have to fix some minor type
errors.

On Mon, Jul 30, 2012 at 10:38 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 To take this a step further, if what you really want is the syntax sugar
 for do-notation (and I understand that, I love sweet, sweet syntactical
 sugar), you are probably implementing a Writer monad over some monoid.

 Here's two data structures that can encode this type;

 data Replacer1 k a = Replacer1 (k - Maybe k) a
 data Replacer2 k a = Replacer2 [(k,k)] a

 instance Monad Replacer1 where
 return x = Replacer1 (\_ - Nothing) x
 Replacer1 ka a = f = result where
 Replacer1 kb b = f a
 result = Replacer1 (\x - ka x `mplus` kb x) b

 (!) :: Eq k = k - k - Replacer1 k ()
 x ! y = Replacer1 (\k - if k == x then Just y else Nothing) ()

 replace1 :: Replacer1 k () - [k] - [k]-- look ma, no Eq requirement!
 replace1 (Replacer k ()) = map (\x - fromMaybe x $ k x) -- from Data.Maybe

 table1 :: Replacer1 Char ()
 table1 = do
 'a' ! 'b'
 'A' ! 'B'

 test = replace1 table1 All I want

 -- Exercise: what changes if we switch ka and kb in the result of (=)?
 When does it matter?

 -- Exercises for you to implement:
 instance Monad Replacer2 k where
 replacer :: Eq k = Replacer2 k - [k] - [k]
 ($) :: k - k - Replacer2 k

 -- Exercise: Lets make use of the fact that we're a monad!
 --
 -- What if the operator ! had a different type?
 -- (!) :: Eq k = k - k - Replacer k Integer
 -- which returns the count of replacements done.
 --
 -- table3 = do
 -- count - 'a' ! 'b'
 -- when (count  3) ('A' ! 'B')
 -- return ()
 --
 -- Do any of the data structures I've given work?  Why or why not?
 -- Can you come up with a way to implement this?

   -- ryan


 On Sat, Jul 28, 2012 at 10:07 AM, Steffen Schuldenzucker 
 sschuldenzuc...@uni-bonn.de wrote:

 On 07/28/2012 03:35 PM, Thiago Negri wrote:
  [...]

  As Monads are used for sequencing, first thing I did was to define the
 following data type:

 data TableDefinition a = Match a a (TableDefinition a) | Restart


 So TableDefinition a is like [(a, a)].

  [...]

 

 So, to create a replacement table:

 table' :: TableDefinition Char
 table' =
  Match 'a' 'b'
  (Match 'A' 'B'
   Restart)

 It look like a Monad (for me), as I can sequence any number of
 replacement values:

 table'' :: TableDefinition Char
 table'' = Match 'a' 'c'
   (Match 'c' 'a'
   (Match 'b' 'e'
   (Match 'e' 'b'
Restart)))


 Yes, but monads aren't just about sequencing. I like to see a monad as a
 generalized computation (e.g. nondeterministic, involving IO, involving
 state etc). Therefore, you should ask yourself if TableDefinition can be
 seen as some kind of abstract computation. In particular, can you
 execute a computation and extract its result? as in

   do
 r - Match 'a' 'c' Restart
 if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

 Doesn't immediately make sense to me. In particular think about the
 different possible result types of a TableDefinition computation.

 If all you want is sequencing, you might be looking for a Monoid instance
 instead, corresponding to the Monoid instance of [b], where b=(a,a) here.

   [...]

 

 I'd like to define the same data structure as:

 newTable :: TableDefinition Char
 newTable = do
  'a' :  'b'
  'A' :  'B'

 But I can't figure a way to define a Monad instance for that. :(


 The desugaring of the example looks like this:

   ('a' : 'b')  ('A' : 'B')

 Only () is used, but not (=) (i.e. results are always discarded). If
 this is the only case that makes sense, you're probably looking for a
 Monoid instead (see above)

 -- Steffen


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



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