Re: [Haskell-cafe] Wanted: Haskell binding for libbdd (buddy)

2012-08-21 Thread Johannes Waldmann
Peter Gammie peteg42 at gmail.com writes:

 My hBDD bindings are on Hackage. 

Great!  Perhaps add category: logic in the cabal file?

J.W.



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


[Haskell-cafe] Lazy decoding of a list with Data.Binary

2012-08-21 Thread Niklas Hambüchen
I just encountered the following problem:

http://stackoverflow.com/questions/11695373/lazy-decoding-of-a-list-with-data-binary

If I get that correctly, there once was a discussion about adding a
Data.Binary.Lazy to binary:

http://www.haskell.org/pipermail/haskell-cafe/2007-November/034758.html

What happened to this?

And if binary is strict by default now, shouldn't the binary-strict
package be deprecated?

Is there an alternative these days how to lazily write/read binary?

Thanks
Niklas

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


[Haskell-cafe] Pure and monadic functions using the Repa arrays

2012-08-21 Thread felipe zapata
Hi Haskellers,

I have been playing with the Repa functions and trying the Repa-examples.
In order to gain experience with the Repa functions I have written some
small linear algebra utilities and import this module to a bigger project.
In the beginning of my project I used the mmultP function from the
repa-examples to calculate a big matrix, therefore I have and array of type:


 arr :: Monad m = m (Array U DIM2 Double)


 Then I carried this array in a lot of functions which become Monadic
function and then it is necessary to introduce the monadic machinery for
manipulating this functions . The Question is then if there is the
possibility to work with a pure function in place of the monadic version?

There is something like a runRepa function?

runRepa :: Monad m = m (Array U DIM2 Double) -  Array U DIM2 Double


or could I used the unsafePerformIO function ?


 or the evaluation of the parallel arrays must be postponed until the
Repa.Array is called in the main function?


 Thanks in Advance,


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


Re: [Haskell-cafe] [Haskell] Compositional Compiler Construction, Oberon0 examples available

2012-08-21 Thread S. Doaitse Swierstra

On Aug 21, 2012, at 13:46 , Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 Doaitse Swierstra wrote:
 Heinrich Apfelmus wrote:
 I have a small question: Last I remember, you've mainly been using
 your UUAGC preprocessor to write attribute grammars in Haskell,
 especially for UHC. Now that you have first-class attribute
 grammars in Haskell (achievement unlocked), what do you intend to
 do with the preprocessor? How do these two approaches compare at
 the moment and where would you like to take them?
 On the page http://www.cs.uu.nl/wiki/bin/view/Center/CoCoCo there is
 a link (http://www.fing.edu.uy/~mviera/papers/VSM12.pdf) to a paper
 we presented at LDTA (one of the ETAPS events) this spring. It
 explains how UUAGC can be used to generate first class compiler
 modules.
 We have also a facility for grouping attributes, so one can trade
 flexibility for speed. The first class approach stores list of
 attributes as nested cartesian products, access to which a clever
 compiler might be able to optimize. This however would correspond  a
 form of specialisation, so you can hardly say that we have really
 independent modules; as always global optimisation is never
 compositional). From the point of view of the first class approach
 such grouped non-termionals are seen as a single composite
 non-terminal.
 
 Ah, I see. So the custom syntax offered by UUAGC is still appreciated, but 
 you now intend to compile it to first-class attribute grammars instead of 
 bare metal Haskell. Makes sense. Thanks!

It is not much that it is our intention, but it is an easy way to make an 
existing compiler extensible. The main (fixed) part of the compiler is 
constructed in the old way from an UUAGC description, and those attributes 
are grouped (and quite a bit more efficient). On top of this you can define 
extra attributes and computations, which plug in to the old system.

Notice that there is a main difference between the two approaches is that the 
uuagc route gives you fast compilers, because we can analyse the grammar, and  
generate efficient tree walking evaluators, whereas the first-class approach 
gives you great flexibility and the possibility to abstract from common 
patterns for which others prefer to get lost in stacks of monads, or find out 
that monads do not work at all since they cannot feed back information into a 
computation easily.


 Doaitse






 
 
 Best regards,
 Heinrich Apfelmus
 
 --
 http://apfelmus.nfshost.com
 
 
 ___
 Haskell mailing list
 hask...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


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


Re: [Haskell-cafe] phantom types

2012-08-21 Thread Doaitse Swierstra

On Aug 19, 2012, at 5:29 , wren ng thornton w...@freegeek.org wrote:

 On 8/17/12 5:35 AM, TP wrote:
 Hi,
 
 I am currently reading documentation on Generalized Algebraic Data Types:
 
 http://en.wikibooks.org/wiki/Haskell/GADT
 
 I have a question concerning this page. Let us consider the following code
 proposed in the page:
 
 --
 -- Phantom type variable a (does not appear in any Expr: it is just a
 -- dummy variable).
 data Expr a = I Int
 | B Bool
 | Add (Expr a) (Expr a)
 | Mul (Expr a) (Expr a)
 | Eq (Expr a) (Expr a)
 deriving (Show)
 [...]
 I don't understand. When we write eval (I n) = n, as I is a constructor
 which takes an Int as argument, we are able to deduce that the type of n is
 Int; so the type of eval should be in this case Expr Int - Int.
 What do I miss?
 
 Perhaps it'd help to rewrite the above ADT using GADT syntax (but note that 
 its the exact same data type):
 
data Expr :: * - * where
I   :: Int - Expr a
B   :: Bool - Expr a
Add :: Expr a - Expr a - Expr a
Mul :: Expr a - Expr a - Expr a
Eq  :: Expr a - Expr a - Expr a

But if you use the real power of GADT's you would write:

{-# LANGUAGE KindSignatures, GADTs #-}
data Expr :: * - * where
   I   :: Int  - Expr Int
   B   :: Bool - Expr Bool
   Val :: a- Expr a
   Add :: Expr Int - Expr Int - Expr Int
   Mul :: Expr Int - Expr Int - Expr Int
   Eq  :: Eq a = Expr a   - Expr a   - Expr Bool

eval :: Expr a - a
eval (I i) = i
eval (B b) = b
eval (Val v) = v
eval (Add e1 e2) = eval e1 + eval e2
eval (Mul e1 e2) = eval e1 * eval e2
eval (Eq e1 e2) = eval e1 == eval e2
 


Note that the I and B cases are actually superfluous, and are covered by the 
val case. This has all nothing to do with phnatom types, but with a proper 
understanding of the GADT concept.

Doaitse

 So, when looking at the pattern (I n), since I :: Int - Expr a we know that 
 n :: Int and that (I n) :: Expr a.
 
 -- 
 Live well,
 ~wren
 
 ___
 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] Pure and monadic functions using the Repa arrays

2012-08-21 Thread Michael Orlitzky
On 08/21/12 09:19, felipe zapata wrote:
 Hi Haskellers,
 
 I have been playing with the Repa functions and trying the
 Repa-examples. In order to gain experience with the Repa functions I
 have written some small linear algebra utilities and import this module
 to a bigger project. In the beginning of my project I used the mmultP
 function from the repa-examples to calculate a big matrix, therefore I
 have and array of type:
 
 
 arr :: Monad m = m (Array U DIM2 Double)
 
 
 Then I carried this array in a lot of functions which become Monadic
 function and then it is necessary to introduce the monadic machinery for
 manipulating this functions . The Question is then if there is the
 possibility to work with a pure function in place of the monadic version?
 
 There is something like a runRepa function?
 
 runRepa :: Monad m = m (Array U DIM2 Double) -  Array U DIM2 Double
 
 
 or could I used the unsafePerformIO function ?
 
 
 or the evaluation of the parallel arrays must be postponed until the
 Repa.Array is called in the main function?

When this change was introduced (there wasn't always the arbitrary monad
m around everything), I remember I just wrapped my one big repa function
in the identity monad and it worked fine. For example,

  -- Grid.hs
  import Control.Monad.Identity (Identity)
  ...
  zoom :: Values3D - ScaleFactor - Identity Values3D

  -- Main.hs
  import Control.Monad.Identity (runIdentity)
  ...
  let output = runIdentity $ zoom dbl_data zoom_factor

This gives you the warm/fuzzy of knowing that the function is pure, but
I think I eventually just let it run in IO to avoid introducing mtl as a
dependency.

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


[Haskell-cafe] salvia

2012-08-21 Thread Sergey Mironov
Hi. Does anybody know anything about Sebastiaan Visser, the maintainer
of Salvia-* packages (web server) ? Looks like his email is dead.
Sergey

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


Re: [Haskell-cafe] fclabels 0.5

2012-08-21 Thread Sergey Mironov
just what I was looking for, thanks!

2012/8/20 Erik Hesselink hessel...@gmail.com:
 Untested, but this should be about right:

 osi (Bij f b) = iso (Bij b f)

 Erik

 On Mon, Aug 20, 2012 at 2:35 PM, Sergey Mironov ier...@gmail.com wrote:
 Hi. I'm porting old code, which uses fclabels 0.5. Old fclabels
 define Iso typeclass as follows:

 class Iso f where
   iso :: a :-: b - f a - f b
   iso (Lens a b) = osi (b - a)
   osi :: a :-: b - f b - f a
   osi (Lens a b) = iso (b - a)

 Newer one defines iso:

 class Iso (~) f where
   iso :: Bijection (~) a b - f a ~ f b

 instance Arrow (~) = Iso (~) (Lens (~) f) where
   iso bi = arr ((\a - lens (fw bi . _get a) (_set a . first (bw bi))) . 
 unLens)

 instance Arrow (~) = Iso (~) (Bijection (~) a) where
   iso = arr . (.)

 but no osi. I'm not a guru in categories, can you help me define osi?

 Thanks
 Sergey.

 ___
 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] Combining databases from packages installed with cabal install

2012-08-21 Thread Marco Túlio Pimenta Gontijo
Hi.

I'm configuring haddock via cabal install (see [0]) to build the
hoogle database.  The database is being installed in
~/.cabal/share/doc/$package-$version/html/$package.txt, but is not
being combined with the default database.  That is, if right after the
installation I try to search with the hoogle command for some a
function, it will not work.  I wrote the following script, which I
called cabal-install:

#!/bin/sh

set -e
set -x

cabal \
install \
--enable-documentation \
--enable-library-profiling \
--haddock-hyperlink-source \
--haddock-hoogle \
--haddock-html \
$@

cd ~/.cabal/share/hoogle-4.2.13/databases/
for file in ~/.cabal/share/doc/*/html/*.txt
do
hoo=`echo $file | sed 's/.txt$/.hoo/;s#.*/##'`
if [ ! -f $hoo ]
then
hoogle convert $file $hoo || true
hoogle combine default.hoo $hoo -o /tmp/cabal-install-$$.hoo
mv /tmp/cabal-install-$$.hoo default.hoo
fi
done

Basically, it searches for .txt hoogle databases installed that were not
combined yet with the default database, and combines them.  I think it would be
good if this was the default behaviour of cabal install when called with
--haddock-hoogle.  Is this a bug?

Greetings.

0: http://hackage.haskell.org/trac/hackage/ticket/517

-- 
marcot
http://marcot.eti.br/

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


[Haskell-cafe] Galois internships available

2012-08-21 Thread Lee Pike

*  ANNOUNCING:
*  INTERNSHIP AT GALOIS, Inc.


Galois, Inc. www.galois.com has an internship available in Portland,
Oregon, USA.

PROJECT OVERVIEW:

The project is a 4+ year research project on build high-assurance
autonomous vehicles.
Galois will be working on three aspects of this problem:

 * Synthesizing software components from Haskell-based embedded DSLs.
 * Building/porting a hardware platform for testing our prototypes.
 * Performing static/dynamic analysis on C/C++ code to detect vulnerabilities.

We intend to release open-source most (if not all) source code developed on the
project and we will be publishing on our research results.

Being an intern for repeated terms is a possibility.

LOGISTICS:

The length and start date of the internship are all negotiable: anytime from
this fall through next fall is acceptable.  Ideally, you can be at Galois for at
least 3 continuous months.  The internship is paid competitively, and the intern
will be responsible for her own living arrangements (although we can certainly
help you find arrangements).  Galois is located in the heart of downtown, with
multiple public transportation options available and world-class bicycle
infrastructure, so living here without an automobile is a viable option.

QUALIFICATIONS:
  * MUST-HAVES:
* The ability to be geographically located in Portland during the
internship.
* Good knowledge of C/C++.
* Some experience with low-level/embedded design.
* Excellent software engineering ability and aptitude.

  * NICE-TO-HAVES (not necessary, but let me know if you have these
qualifications!):
* Experience with Haskell and particularly embedded DSLs.
* Experience with microcontrollers (particularly ARM Cortex M).
* Experience with control systems.
* Interest in/experience with real-time systems and RTOSes.
* Interest in/experience with software security.
* Interest in/experience with static analysis.
* Experience with ArduPilot http://code.google.com/p/ardupilot-mega/ or
  other autopilot systems.
* Good writing skills/experience in writing technical papers.

  * DO NOT NEED:
* A specific degree (we're interested in hearing from anyone from post-docs
  to undergrads).

ABOUT GALOIS:

Galois, Inc. is located in Portland, Oregon with a mission to create
trustworthiness in critical systems.  We're in the business of taking
blue-sky ideas and turning them into real-world technology solutions.
We've been developing real-world systems for over 10 years using
Haskell.

To get a sense of life at Galois, one of our previous interns documented his
internship here:
http://blog.ezyang.com/2010/08/day-in-the-life-of-a-galois-intern/.

TO APPLY:

In one email,

 * Please attach a C.V. (PDF, plain text, or markdown only).
 * In the body of the email, include a brief non-HTML note stating your interest
   and experience and any other relevant details.

Send this to Lee Pike (leepike at galois.com) with the subject line Internship
2012.  If you follow these directions, you'll get a confirmation from me.

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


Re: [Haskell-cafe] regex-pcre is not working with UTF-8

2012-08-21 Thread Konstantin Litvinenko

On 08/18/2012 06:16 PM, José Romildo Malaquias wrote:

Hello.

It seems that the regex-pcre has a bug dealing with utf-8:

I hope this bug can be fixed soon.

Is there a bug tracker to report the bug? If so, what is it?


You need something like that

let pat = makeRegexOpts (compUTF8 .|. defaultCompOpt) defaultExecOpt 
(@'(.+?)'@ :: B.ByteString)


and than pat will match correctly.


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


Re: [Haskell-cafe] salvia

2012-08-21 Thread Sean Leather
On Tue, Aug 21, 2012 at 5:02 PM, Sergey Mironov wrote:

 Hi. Does anybody know anything about Sebastiaan Visser, the maintainer
 of Salvia-* packages (web server) ? Looks like his email is dead.


I responded to Sergey off-list, so others don't have to.

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


Re: [Haskell-cafe] regex-pcre is not working with UTF-8

2012-08-21 Thread José Romildo Malaquias
On Tue, Aug 21, 2012 at 10:25:53PM +0300, Konstantin Litvinenko wrote:
 On 08/18/2012 06:16 PM, José Romildo Malaquias wrote:
  Hello.
 
  It seems that the regex-pcre has a bug dealing with utf-8:
 
  I hope this bug can be fixed soon.
 
  Is there a bug tracker to report the bug? If so, what is it?
 
 You need something like that
 
 let pat = makeRegexOpts (compUTF8 .|. defaultCompOpt) defaultExecOpt 
 (@'(.+?)'@ :: B.ByteString)
 
 and than pat will match correctly.

The bug is related to String (not ByteString) in a UTF-8 locale.

Until it is fixed, I am using the workaround of converting the regular
expression and the text to ByteString, doing the matching, and then
converting the results back to String.

Romildo

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


[Haskell-cafe] explicit annotations on kind polymorphism for data types

2012-08-21 Thread dude

Hello All:

I'm working through Giving Haskell a Promotion.

Section 2.4 presents an explicitly annotated data type declaration 
similar to the following:


data EqRefl (a::X)(b::X) where
  Refl :: forall X. forall (a::X). EqRefl a a

Has this been implemented in GHC 7.4.2?

7.8.3 in the GHC User Guide leads me to believe it has not.

--
dude

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


[Haskell-cafe] Cloud Haskell real usage example

2012-08-21 Thread Thiago Negri
Hello everyone. I'm taking my first steps in Cloud Haskell and got
some unexpected behaviors.

I used the code from Raspberry Pi in a Haskell Cloud [1] as a first
example. Did try to switch the code to use Template Haskell with no
luck, stick with the verbose style.
I changed some of the code, from ProcessId-based messaging to typed
channel to receive the Pong; using startSlave to start the worker
nodes; and changed the master node to loop forever sending pings to
the worker nodes.

The unexpected behaviors:
- Dropping a worker node while the master is running makes the master
node to crash.
- Master node do not see worker nodes started after the master process.

In order to fix this, I tried to findSlaves at the start of the
master process and send ping to only these ones, ignoring the list of
NodeId enforced by the type signature of startMaster.

Now the master finds new slaves. The bad thing is that when I close
one of the workers, the master process freezes. It simply stop doing
anything. No more messages and no more Pings to other slaves. :(


My view of Cloud Haskell usage would be something similar to this: a
master node sending work to slaves; slave instances getting up or down
based on demand. So, the master node should be slave-failure-proof and
also find new slaves somehow.

Am I misunderstanding the big picture of Cloud Haskell or doing
anything wrong in the following code?

Code (skipped imports and wiring stuff):

--
newtype Ping = Ping (SendPort Pong)
deriving (Typeable, Binary, Show)

newtype Pong = Pong ProcessId
deriving (Typeable, Binary, Show)

worker :: Ping - Process ()
worker (Ping sPong) = do
  wId - getSelfPid
  say Got a Ping!
  sendChan sPong (Pong wId)

master :: Backend - [NodeId] - Process ()
master backend _ = forever $ do
  workers - findSlaves backend
  say $ Slaves:  ++ show workers

  (sPong, rPong) - newChan

  forM_ workers $ \w - do
say $ Sending a Ping to  ++ (show w) ++ ...
spawn w (workerClosure (Ping sPong))

  say $ Waiting for reply from  ++ (show (length workers)) ++  worker(s)

  replicateM_ (length workers) $ do
  (Pong wId) - receiveChan rPong
  say $ Got back a Pong from  ++ (show $ processNodeId wId) ++ !

  (liftIO . threadDelay) 200 -- Wait a bit before return

main = do
  prog - getProgName
  args - getArgs

  case args of
[master, host, port] - do
  backend - initializeBackend host port remoteTable
  startMaster backend (master backend)

[worker, host, port] - do
  backend - initializeBackend host port remoteTable
  startSlave backend

_ -
  putStrLn $ usage:  ++ prog ++  (master | worker) host port
--

[1] http://alenribic.com/writings/post/raspberry-pi-in-a-haskell-cloud

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


Re: [Haskell-cafe] Cloud Haskell real usage example

2012-08-21 Thread Felipe Almeida Lessa
On Tue, Aug 21, 2012 at 9:01 PM, Thiago Negri evoh...@gmail.com wrote:
 My view of Cloud Haskell usage would be something similar to this: a
 master node sending work to slaves; slave instances getting up or down
 based on demand. So, the master node should be slave-failure-proof and
 also find new slaves somehow.

 Am I misunderstanding the big picture of Cloud Haskell or doing
 anything wrong in the following code?

(Disclaimer: I can't speak for Cloud Haskell's developers.)

AFAIK this is CH's goal.  However, they're not quite there yet.  Their
network implementation is still a lot naive as you're seeing =).

Cheers,

-- 
Felipe.

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


Re: [Haskell-cafe] Cloud Haskell real usage example

2012-08-21 Thread yi huang
On Wed, Aug 22, 2012 at 8:30 AM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Tue, Aug 21, 2012 at 9:01 PM, Thiago Negri evoh...@gmail.com wrote:
  My view of Cloud Haskell usage would be something similar to this: a
  master node sending work to slaves; slave instances getting up or down
  based on demand. So, the master node should be slave-failure-proof and
  also find new slaves somehow.
 
  Am I misunderstanding the big picture of Cloud Haskell or doing
  anything wrong in the following code?

 (Disclaimer: I can't speak for Cloud Haskell's developers.)

 AFAIK this is CH's goal.  However, they're not quite there yet.  Their
 network implementation is still a lot naive as you're seeing =).


I believe this behavior is due to the usage of channel, you just need to
implement some kind of timeout function.



 Cheers,

 --
 Felipe.

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




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