Re: [Haskell-cafe] Monads with The contexts?

2012-07-19 Thread oleg

 http://en.pk.paraiso-lang.org/Haskell/Monad-Gaussian
 What do you think? Will this be a good approach or bad?

I don't think it is a Monad (or even restricted monad, see
below). Suppose G a is a `Gaussian' monad and n :: G Double is a
random number with the Gaussian (Normal distribution).  Then 
(\x - x * x) `fmap` n 
is a random number with the chi-square distribution (of
the degree of freedom 1). Chi-square is _not_ a normal
distribution. Perhaps a different example is clearer:

(\x - if x  0 then 1.0 else 0.0) `fmap` n

has also the type G Double but obviously does not have the normal
distribution (since that random variable is discrete).

There are other problems

 Let's start with some limitation; we restrict ourselves to Gaussian
 distributions and assume that the standard deviations are small
 compared to the scales we deal with.

That assumption is not stated in types and it is hard to see how can
we enforce it. Nothing prevents us from writing
liftM2 n n
in which case the variance will no longer be small compared with the
mean.

Just a technical remark: The way G a is written, it is a so-called
restricted monad, which is not a monad (the adjective `restricted' is
restrictive here). 
http://okmij.org/ftp/Haskell/types.html#restricted-datatypes



___
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-19 Thread Simon Hengel
On Wed, Jul 18, 2012 at 05:51:51PM -0600, Richard G. wrote:
 What's the best way to fix this?  I can see two options:
 - Move the test stanzas to a different Cabal file, allowing users to
 perform the tests with a little fiddling.
 - Remove the conditional statements from the test stanzas, which may
 break compatibility with some compilers and interpreters.
 
 Is there another option?

I think it is preferable to have a test section in the main cabal file.

Just an idea:

What about having just a single test suite that *depends on the
library*?  I think that way the test suit would not require any
conditionals, but you could not test with different optimization levels
anymore.  We could then add a Makefile/script that configures, builds
and tests with the different optimization levels.

This approach also has the advantage, that we are testing exactly the
same thing (the library!) that the user is going to use.

Cheers,
Simon

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


[Haskell-cafe] Probabilistic programming [Was: Monads with The contexts?]

2012-07-19 Thread oleg

  Exercise: how does the approach in the code relate to the approaches
  to sharing explained in
  http://okmij.org/ftp/tagless-final/sharing/sharing.html
 
 Chapter 3 introduces an  implicit impure counter, and Chapter 4 uses a
 database that is passed around.
 let_ in Chapter 5 of sharing.pdf realizes the sharing with sort of
 continuation-passing style.The unsafe counter works across the module
 (c.f. counter.zip) but is generally unpredictable...

The reason sharing has the type m a - m (m a) rather than
m a - m a is the fact new calculations to share may be created
dynamically. Therefore, we need a supply of keys (gensym). We count on
the monad m to provide the supply. However, top-level computations
(bound to top-level identifiers) are created only once, at the
initialization time. Therefore, a static assignment of identifiers
will suffice. The static assignment is similar to the manual label
assignment technique -- the first technique described Sec 3 of the
sharing.pdf paper. John T. O'Donnell has automated this manual
assignment using TH.

 Now I'm on to the next task; how we represent continuous probability
 distributions? The existing libraries:

 Seemingly have restricted themselves to discrete distributions, or at
 least providing Random support for Monte-Carlo simulations. 

I must warn that although it is ridiculously easy to implement
MonadProb in Haskell, the result is not usable. Try to implement HMM
with any of the available MonadProb and see how well it scales. (Hint: we
want the linear time scaling as we evolve the model -- not
exponential). There is a *huge* gap between a naive MonadProb and
something that could be used even for passingly interesting
problems. We need support for so-called `variable elimination'. We
need better sampling procedures: rejection sampling is better
forgotten. Finally, GHC is actually not a very good language system
for probabilistic programming of generative-model--variety. See
http://okmij.org/ftp/Haskell/index.html#memo-off
for details. 

To give you the flavor of difficulties, consider a passingly
interesting target tracking problem: looking at a radar screen and
figuring out how many planes are there and where they are going:
http://okmij.org/ftp/kakuritu/index.html#blip
Since the equipment is imperfect, there could be a random blip on the radar
that corresponds to no target. If we have a 10x10 screen and 2%
probability of a noise blip in every of the 100 `pixels', we get the
search space of 2^100 -- even before we get to the planes and their
stochastic equations of motion. Hansei can deal with the problem --
and even scale linearly with time. 

I don't think you can make a monad out of Gaussian distributions. That
is not to say that monads are useless in these problems -- monads are
useful, but at a different level, to build a code for say, MCMC (Monte
Carlo Markov Chain). It this this meta-programming approach that
underlies Infer.net
http://research.microsoft.com/en-us/um/cambridge/projects/infernet/
and Avi Pfeffer's Figaro
http://www.cs.tufts.edu/~nr/cs257/archive/avi-pfeffer/figaro.pdf


I should point out Professor Sato of Toukyou Tech, who is the pioneer
in the probabilistic programming
http://sato-www.cs.titech.ac.jp/sato/
http://sato-www.cs.titech.ac.jp/en/publication/
You can learn from him all there is to know about probabilistic
programming.




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


Re: [Haskell-cafe] Fwd: hackage compile failure with QuickCheck 2.5

2012-07-19 Thread Ross Paterson
On Wed, Jul 18, 2012 at 09:35:52AM +0100, Erik Hesselink wrote:
 I don't think you can install this package on 7.4. As Andres said, it
 requires containers 0.5, but ghc 7.4's base libraries (in this case,
 template-haskell) use containers 0.4, and can't be reinstalled. I
 guess your best bet is to use sbv-2.1, which depends on containers =
 0.3, or to unpack it and see if you can loosen the containers
 dependency and see if it still works with 0.4

So the moral of this story is that libraries should avoid depending on
features of the containers package that have not yet been released with GHC.

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


[Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread C K Kashyap
Dear gentle Haskellers,

I was trying to whet my Haskell by trying out Parsec today to try and parse
out XML. Here's the code I cam up with -

I wanted some help with the gettext parser that I've written. I had to do
a dummy char '  ') in there just to satisfy the many used in the xml
parser. I'd appreciate it very much if someone could give me some feedback.


data XML =  Node String [XML]
  | Body String deriving Show

gettext = do
 x - many (letter | digit )
 if (length x)  0 then
return (Body x)
 else (char ' '  (return $ Body ))

xml :: Parser XML
xml = do {
  name - openTag
; innerXML - many innerXML
; endTag name
; return (Node name innerXML)
 }

innerXML = do
 x - (try xml | gettext)
 return x

openTag :: Parser String
openTag = do
char ''
content - many (noneOf )
char ''
return content

endTag :: String - Parser String
endTag str = do
char ''
char '/'
string str
char ''
return str

h1 = parse xml  aA/a
h2 = parse xml  abA/b/a
h3 = parse xml  abc/c/b/a
h4 = parse xml  ab/bc/c/a

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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Christian Maeder

Am 19.07.2012 14:53, schrieb C K Kashyap:

Dear gentle Haskellers,

I was trying to whet my Haskell by trying out Parsec today to try and
parse out XML. Here's the code I cam up with -

I wanted some help with the gettext parser that I've written. I had to
do a dummy char '  ') in there just to satisfy the many used in the
xml parser. I'd appreciate it very much if someone could give me some
feedback.


You don't want empty bodies! So use many1 in gettext.

  gettext = fmap Body $ many1 $ letter | digit

If you have spaces in your bodies, skip them or allow them with
noneOf .

HTH Christian




data XML =  Node String [XML]
   | Body String deriving Show

gettext = do
  x - many (letter | digit )
  if (length x)  0 then
 return (Body x)
  else (char ' '  (return $ Body ))

xml :: Parser XML
xml = do {
   name - openTag
 ; innerXML - many innerXML
 ; endTag name
 ; return (Node name innerXML)
  }

innerXML = do
  x - (try xml | gettext)
  return x

openTag :: Parser String
openTag = do
 char ''
 content - many (noneOf )
 char ''
 return content

endTag :: String - Parser String
endTag str = do
 char ''
 char '/'
 string str
 char ''
 return str

h1 = parse xml  aA/a
h2 = parse xml  abA/b/a
h3 = parse xml  abc/c/b/a
h4 = parse xml  ab/bc/c/a

Regards,
Kashyap


___
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] Need help with learning Parsec

2012-07-19 Thread Christian Maeder

Am 19.07.2012 14:53, schrieb C K Kashyap:

innerXML = do
  x - (try xml | gettext)
  return x


Omit try (and return).
xml always starts with  whereas gettext never does.

C.



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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Sai Hemanth K
gettext =  (many1 $ noneOf ) = (return . Body)

works for your case.



On Thu, Jul 19, 2012 at 6:37 PM, Christian Maeder
christian.mae...@dfki.dewrote:

 Am 19.07.2012 14:53, schrieb C K Kashyap:

  Dear gentle Haskellers,

 I was trying to whet my Haskell by trying out Parsec today to try and
 parse out XML. Here's the code I cam up with -

 I wanted some help with the gettext parser that I've written. I had to
 do a dummy char '  ') in there just to satisfy the many used in the
 xml parser. I'd appreciate it very much if someone could give me some
 feedback.


 You don't want empty bodies! So use many1 in gettext.

   gettext = fmap Body $ many1 $ letter | digit

 If you have spaces in your bodies, skip them or allow them with
 noneOf .

 HTH Christian



 data XML =  Node String [XML]
| Body String deriving Show

 gettext = do
   x - many (letter | digit )
   if (length x)  0 then
  return (Body x)
   else (char ' '  (return $ Body ))

 xml :: Parser XML
 xml = do {
name - openTag
  ; innerXML - many innerXML
  ; endTag name
  ; return (Node name innerXML)
   }

 innerXML = do
   x - (try xml | gettext)
   return x

 openTag :: Parser String
 openTag = do
  char ''
  content - many (noneOf )
  char ''
  return content

 endTag :: String - Parser String
 endTag str = do
  char ''
  char '/'
  string str
  char ''
  return str

 h1 = parse xml  aA/a
 h2 = parse xml  abA/b/a
 h3 = parse xml  abc/c/b/a
 h4 = parse xml  ab/bc/c/a

 Regards,
 Kashyap


 __**_
 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-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Christian Maeder

Am 19.07.2012 15:14, schrieb Christian Maeder:

Am 19.07.2012 14:53, schrieb C K Kashyap:

innerXML = do
  x - (try xml | gettext)
  return x


Omit try (and return).
xml always starts with  whereas gettext never does.


I was wrong, you do not want to swallow an endTag as openTag.

openTag should start with:
try $ char ''  notFollowedBy (char '/')

and endTag should start with:
try $ string /

C.



C.





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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Simon Hengel
On Thu, Jul 19, 2012 at 06:45:05PM +0530, Sai Hemanth K wrote:
 gettext =  (many1 $ noneOf ) = (return . Body)

You can simplify this to:


import Control.Applicative hiding ((|))

gettext = Body $ many1 (noneOf )


And some of your other parsers can be simplified as well:

innerXML = xml | gettext

openTag :: Parser String
openTag = char '' * many (noneOf ) * char ''

endTag :: String - Parser String
endTag str = string / * string str * char ''

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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Simon Hengel
 gettext = Body $ many1 (noneOf )

Note that this is the same as:

gettext = Body `fmap` many1 (noneOf )

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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Simon Hengel
On Thu, Jul 19, 2012 at 03:34:47PM +0200, Simon Hengel wrote:
 openTag :: Parser String
 openTag = char '' * many (noneOf ) * char ''
 
 endTag :: String - Parser String
 endTag str = string / * string str * char ''

Well yes, modified to what Christian Maeder just suggested.

Cheers,
Simon

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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Christian Maeder

Am 19.07.2012 15:26, schrieb Christian Maeder:

Am 19.07.2012 15:14, schrieb Christian Maeder:

Am 19.07.2012 14:53, schrieb C K Kashyap:

innerXML = do
  x - (try xml | gettext)
  return x


Omit try (and return).
xml always starts with  whereas gettext never does.


I was wrong, you do not want to swallow an endTag as openTag.

openTag should start with:
 try $ char ''  notFollowedBy (char '/')

and endTag should start with:
 try $ string /


Strictly, the try in endTag is not necessary (only in openTag)

C.

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


Re: [Haskell-cafe] How to add constraint to .cabal?

2012-07-19 Thread Brent Yorgey
On Thu, Jul 19, 2012 at 09:37:52AM +0800, Magicloud Magiclouds wrote:
 Hi,
   Say I have a package that only appends
 --constraint=template-haskell==2.7.0.0
 --constraint=warp-tls==1.2.1 could I install it. Now I want to
 release the package, then how could I have these constraint into the
 .cabal so the user would not get troubled?

Using the build-depends field.  See
http://www.haskell.org/cabal/users-guide/developing-packages.html#build-information

-Brent

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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread Christian Maeder

Am 19.07.2012 15:41, schrieb Simon Hengel:

On Thu, Jul 19, 2012 at 03:34:47PM +0200, Simon Hengel wrote:

 openTag :: Parser String
 openTag = char '' * many (noneOf ) * char ''


if you disallow empty tags and / within tags, then you can avoid the
notFollowedBy construct by:

   openTag = try (char '' * many1 (noneOf /)) * char ''

C.



 endTag :: String - Parser String
 endTag str = string / * string str * char ''


Well yes, modified to what Christian Maeder just suggested.

Cheers,
Simon




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


Re: [Haskell-cafe] Need help with learning Parsec

2012-07-19 Thread C K Kashyap
Thank you so much ... I've updated my monad version here -

https://github.com/ckkashyap/LearningPrograms/blob/master/Haskell/Parsing/xml_1.hshttps://github.com/ckkashyap/LearningPrograms/blob/master/Haskell/Parsing/xml_2.hs


and the Applicative version here -
https://github.com/ckkashyap/LearningPrograms/blob/master/Haskell/Parsing/xml_2.hs


The applicative version however does not seem to work.

Is there a good tutorial that I can look up for Parsec - I am checking out
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html but  I am looking
for a tutorial where a complex parser would be built ground up.

Next I'd like to take care of escaped angular brackets.

Regards,
Kashyap


On Thu, Jul 19, 2012 at 7:40 PM, Christian Maeder
christian.mae...@dfki.dewrote:

 Am 19.07.2012 15:41, schrieb Simon Hengel:

  On Thu, Jul 19, 2012 at 03:34:47PM +0200, Simon Hengel wrote:

  openTag :: Parser String
  openTag = char '' * many (noneOf ) * char ''


 if you disallow empty tags and / within tags, then you can avoid the
 notFollowedBy construct by:

openTag = try (char '' * many1 (noneOf /)) * char ''

 C.



  endTag :: String - Parser String
  endTag str = string / * string str * char ''


 Well yes, modified to what Christian Maeder just suggested.

 Cheers,
 Simon



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