[Haskell-cafe] Declarative configuration languages?

2011-08-07 Thread Richard O'Keefe
A colleague just asked me
I'm trying to kick off some work into middleware for configuration of 
large-scale,
distributed systems.  Have you come across any elegant, declarative 
configuration
languages used for this sort of job?

I've found a couple of papers, but I've never _used_ any of the systems.
Any recommendations?


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


Re: [Haskell-cafe] Simple Parsec example

2011-08-07 Thread michael rice
Thanks, Albert.
The code is from this page, just below the definition of parse:
http://hackage.haskell.org/packages/archive/parsec/latest/doc/html/Text-Parsec-Prim.html#v:parse
Michael

--- On Sun, 8/7/11, Albert Y. C. Lai  wrote:

From: Albert Y. C. Lai 
Subject: Re: [Haskell-cafe] Simple Parsec example
To: haskell-cafe@haskell.org
Date: Sunday, August 7, 2011, 8:00 PM

On 11-08-07 02:44 PM, michael rice wrote:
> What other imports must I add to get this to run. I can't seem to get it
> right.
[...]
> import Text.ParserCombinators.Parsec.Prim
> 
> main = case (parse numbers "" "11, 2, 43") of
> Left err -> print err
> Right xs -> print (sum xs)
> 
> numbers = commaSep integer

The problem is deeper than imports.

import Text.Parsec.Prim(parse)
import Text.Parsec.Token(makeTokenParser,
  GenTokenParser(TokenParser, commaSep, integer))
import Text.Parsec.Language(emptyDef)

main = case (parse numbers "" "11, 2, 43") of
         Left err  -> print err
         Right xs  -> print (sum xs)

numbers = c i where
  TokenParser{commaSep=c, integer=i} = makeTokenParser emptyDef

___
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] Simple Parsec example

2011-08-07 Thread Albert Y. C. Lai

On 11-08-07 02:44 PM, michael rice wrote:

What other imports must I add to get this to run. I can't seem to get it
right.

[...]

import Text.ParserCombinators.Parsec.Prim

main = case (parse numbers "" "11, 2, 43") of
Left err -> print err
Right xs -> print (sum xs)

numbers = commaSep integer


The problem is deeper than imports.

import Text.Parsec.Prim(parse)
import Text.Parsec.Token(makeTokenParser,
  GenTokenParser(TokenParser, commaSep, integer))
import Text.Parsec.Language(emptyDef)

main = case (parse numbers "" "11, 2, 43") of
 Left err  -> print err
 Right xs  -> print (sum xs)

numbers = c i where
  TokenParser{commaSep=c, integer=i} = makeTokenParser emptyDef

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


Re: [Haskell-cafe] Rotating calipers

2011-08-07 Thread mukesh tiwari
Thank you Tillmann Vogt. I really appreciate your help . Finally
implemented working code [ http://hpaste.org/49957 ] .
Thank you
Mukesh Tiwari

On Aug 7, 3:16 pm, Tillmann Vogt  wrote:
> Am 06.08.2011 22:23, schrieb mukesh tiwari:
>
>
>
>
>
>
>
>
>
> >> There are several algorithms mentioned on that page. Do you need the
> >> diameter, width, or something else?
> > Oh , I did not realize that .Actually first i implemented diameter
> > algorithm [http://hpaste.org/49925] and tested it on couple of test
> > cases . Its working fine then i tried  to implement " The minimum area
> > enclosing rectangle for a convex polygon"  using four calipers but i
> > don't know whats wrong code.
> >> Do you have some example data and what wrong result you  get?
> > For any test input [ which i tried ] it outputs 4 . If its implemented
> > correctly then it will accepted here with slight modification [
> >http://www.spoj.pl/problems/WLOO0707] since it asks for square area.
> > Couple of test cases which i tried .
>
> > ghci>final [ P 1 1 , P 2 2 , P 0 100 , P 0 1 ]
> > Loading package array-0.3.0.0 ... linking ... done.
> > Loading package bytestring-0.9.1.5 ... linking ... done.
> > 4.0
>
> > ghci>final [ P 0 0 ,P 5 1 , P 9 2 , P 12 3 , P 14 4 , P 15 5 , P 16
> > 7 , P 17 10 , P 18 14 , P 19 19 ]
> > 3.9982
>
> > ghci>final [ P 2 ( -3 ) , P (-1 ) 2 , P 0 5 , P (-5) (-1) , P (-4)
> > ( 2 ) , P 4 0 , P 1 3 , P 4 3 , P (-3) (-4) , P 0 (-2)]
> > 4.0
>
> > Thank you
> > Mukesh Tiwari
>
> I found the error!
>
> In
>  >    width = distVec cpa' cpb'
>  >    length = distVec cqa' cqb'
> the length of the direction vectors is used to compute the area and the
> area is then always 4.
>
> Replace it with
>  >    width = distVec (V x1 y1) (V x3 y3)
>  >    length = distVec (V x5 y5) (V x7 y7)
>
> and it seems to work:
>
> ghci> final [ P 1 1 , P 2 2 , P 0 100 , P 0 1 ]
>            221.3707297724792
>
> ___
> Haskell-Cafe mailing list
> Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Simple Parsec example

2011-08-07 Thread Thomas DuBuisson
I suggest you install hoogle or use the web interface as it can easily
answer such questions for you:

http://www.haskell.org/hoogle/?hoogle=commaSep
http://www.haskell.org/hoogle/?hoogle=integer+%2bparsec

Cheers,
Thomas

On Sun, Aug 7, 2011 at 11:44 AM, michael rice  wrote:

> What other imports must I add to get this to run. I can't seem to get it
> right.
>
> Michael
>
> =
>
> import Text.ParserCombinators.Parsec.Prim
>
> main = case (parse numbers "" "11, 2, 43") of
>  Left err  -> print err
>  Right xs  -> print (sum xs)
>
> numbers = commaSep integer
>
> ==
>
> [michael@sabal ~]$ ghc --make parsetest.hs
> [1 of 1] Compiling Main ( parsetest.hs, parsetest.o )
>
> parsetest.hs:7:11: Not in scope: `commaSep'
>
> parsetest.hs:7:20: Not in scope: `integer'
> [michael@sabal ~]$
>
>
> ___
> 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] Simple Parsec example

2011-08-07 Thread michael rice
What other imports must I add to get this to run. I can't seem to get it right.
Michael
=
import Text.ParserCombinators.Parsec.Prim
main = case (parse numbers "" "11, 2, 43") of         Left err  -> print err    
     Right xs  -> print (sum xs)
numbers = commaSep integer
==
[michael@sabal ~]$ ghc --make parsetest.hs[1 of 1] Compiling Main             ( 
parsetest.hs, parsetest.o )
parsetest.hs:7:11: Not in scope: `commaSep'
parsetest.hs:7:20: Not in scope: `integer'[michael@sabal ~]$ 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xmonad on xkcd

2011-08-07 Thread Christopher Done
Y'all missing out:
http://www.reddit.com/r/haskell/comments/j9nef/that_seems_like_a_challenge_whatever_happened_to/

On 7 August 2011 20:31, Brandon Allbery  wrote:
> On Sun, Aug 7, 2011 at 08:07, Jon Fairbairn 
> wrote:
>>
>> http://xkcd.com/934/
>
> I am suddenly imagining an unexpected increase in development activity on
> YHC and the YHC Core to JavaScript translator
> --
> brandon s allbery                                      allber...@gmail.com
> wandering unix systems administrator (available)     (412) 475-9364 vm/sms
>
>
> ___
> 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] xmonad on xkcd

2011-08-07 Thread Brandon Allbery
On Sun, Aug 7, 2011 at 08:07, Jon Fairbairn wrote:

> http://xkcd.com/934/
>

I am suddenly imagining an unexpected increase in development activity on
YHC and the YHC Core to JavaScript translator

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] library-profiling default

2011-08-07 Thread Albert Y. C. Lai

On 11-08-04 03:06 AM, Tom Doris wrote:

Is there a good reason that the default for library-profiling in
.cabal/config is set to False?


The combination of two defaults

-- library-profiling: False
-- documentation: False

points towards optimizing for people who use applications such as xmonad 
but otherwise would not write in Haskell.


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


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-07 Thread Eugene Kirpichov
What about using unsafe array indexing operations? (i.e. array `unsafeAt` index)

2011/8/7 Chris Yuen :
> Here is an updated version using Data.Array.Unboxed  http://ideone.com/YXuVL
> And the profile http://hpaste.org/49940
>
> Still taking 5+ minutes...
>
> Chris
>
> On Sun, Aug 7, 2011 at 5:20 PM, Daniel Fischer
>  wrote:
>>
>> On Sunday 07 August 2011, 10:52:20, Max Bolingbroke wrote:
>> > In short I don't see how to get further without changing the algorithm
>> > or doing some hacks like manual unrolling. Maybe someone else has some
>> > ideas?
>>
>> Well, the C# implementation uses arrays for lookup while the Haskell
>> version uses list lookups
>>
>>                      in (tens !! fromIntegral t) ++ wordify x
>>
>> and case'd functions
>>
>> lenTens 0 = 0
>> lenTens 1 = 3
>> lenTens 2 = 6
>> lenTens 3 = 6
>> lenTens 4 = 5
>> lenTens 5 = 5
>> lenTens 6 = 5
>> lenTens 7 = 7
>> lenTens 8 = 6
>> lenTens 9 = 6
>>
>> wordify is only called once at the end, so that should not have a
>> measurable impact, but the lenXXXs might.
>> I'm not sure what
>>
>> CaseLen.$wlenTens :: GHC.Prim.Int# -> GHC.Prim.Int#
>> [GblId,
>>  Arity=1,
>>  Str=DmdType L,
>>  Unf=Unf{Src=, TopLvl=True, Arity=1, Value=True,
>>         ConLike=True, Cheap=True, Expandable=True,
>>         Guidance=IF_ARGS [12] 11 0}]
>> CaseLen.$wlenTens =
>>  \ (ww_shY :: GHC.Prim.Int#) ->
>>    case ww_shY of _ {
>>      __DEFAULT ->
>>        CaseLen.lenTens1
>>        `cast` (CoUnsafe GHC.Types.Int GHC.Prim.Int#
>>                :: GHC.Types.Int ~ GHC.Prim.Int#);
>>      0 -> 0;
>>      1 -> 3;
>>      2 -> 6;
>>      3 -> 6;
>>      4 -> 5;
>>      5 -> 5;
>>      6 -> 5;
>>      7 -> 7;
>>      8 -> 6;
>>      9 -> 6
>>    }
>>
>> means at a lower level, but it's certainly worth trying out whether an
>> unboxed array lookup is faster.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/

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


[Haskell-cafe] ANN: Netwire AFRP library

2011-08-07 Thread Ertugrul Soeylemez
Hi there,

after a few weeks of development time, I have released the first
official version of my arrowized FRP library called Netwire:

http://hackage.haskell.org/package/netwire

I have written it with networking applications in mind, but it is a
general purpose library, so it can be used in all of the classic fields
like gaming, animation, user interfaces and others.

Its basic idea is the same as in Yampa, but its internal structure is
much simpler and hence it's easier to extend.  Also like in most of my
libraries I have specifically decided to expose the internals, so you
can extend Netwire without having to fork.

Features not found in Yampa/Animas:

  * switching by ArrowChoice,
  * suspended signal transformers,
  * signal inhibition,
  * combination through ArrowZero and ArrowPlus,
  * impure signal transformers.

There exists a wiki page, which should give you a quickstart:

http://haskell.org/haskellwiki/Netwire

I would be grateful for any constructive feedback.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-07 Thread Chris Yuen
Here is an updated version using Data.Array.Unboxed  http://ideone.com/YXuVL
And the profile http://hpaste.org/49940

Still taking 5+ minutes...

Chris

On Sun, Aug 7, 2011 at 5:20 PM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:

> On Sunday 07 August 2011, 10:52:20, Max Bolingbroke wrote:
> > In short I don't see how to get further without changing the algorithm
> > or doing some hacks like manual unrolling. Maybe someone else has some
> > ideas?
>
> Well, the C# implementation uses arrays for lookup while the Haskell
> version uses list lookups
>
>  in (tens !! fromIntegral t) ++ wordify x
>
> and case'd functions
>
> lenTens 0 = 0
> lenTens 1 = 3
> lenTens 2 = 6
> lenTens 3 = 6
> lenTens 4 = 5
> lenTens 5 = 5
> lenTens 6 = 5
> lenTens 7 = 7
> lenTens 8 = 6
> lenTens 9 = 6
>
> wordify is only called once at the end, so that should not have a
> measurable impact, but the lenXXXs might.
> I'm not sure what
>
> CaseLen.$wlenTens :: GHC.Prim.Int# -> GHC.Prim.Int#
> [GblId,
>  Arity=1,
>  Str=DmdType L,
>  Unf=Unf{Src=, TopLvl=True, Arity=1, Value=True,
> ConLike=True, Cheap=True, Expandable=True,
> Guidance=IF_ARGS [12] 11 0}]
> CaseLen.$wlenTens =
>  \ (ww_shY :: GHC.Prim.Int#) ->
>case ww_shY of _ {
>  __DEFAULT ->
>CaseLen.lenTens1
>`cast` (CoUnsafe GHC.Types.Int GHC.Prim.Int#
>:: GHC.Types.Int ~ GHC.Prim.Int#);
>  0 -> 0;
>  1 -> 3;
>  2 -> 6;
>  3 -> 6;
>  4 -> 5;
>  5 -> 5;
>  6 -> 5;
>  7 -> 7;
>  8 -> 6;
>  9 -> 6
>}
>
> means at a lower level, but it's certainly worth trying out whether an
> unboxed array lookup is faster.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] xmonad on xkcd

2011-08-07 Thread Jon Fairbairn

http://xkcd.com/934/ (and look at the “hover text”) — so who’s
going to implement it?

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk



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


Re: [Haskell-cafe] Rotating calipers

2011-08-07 Thread Tillmann Vogt

Am 06.08.2011 22:23, schrieb mukesh tiwari:

There are several algorithms mentioned on that page. Do you need the
diameter, width, or something else?

Oh , I did not realize that .Actually first i implemented diameter
algorithm [ http://hpaste.org/49925 ] and tested it on couple of test
cases . Its working fine then i tried  to implement " The minimum area
enclosing rectangle for a convex polygon"  using four calipers but i
don't know whats wrong code.

Do you have some example data and what wrong result you  get?

For any test input [ which i tried ] it outputs 4 . If its implemented
correctly then it will accepted here with slight modification [
http://www.spoj.pl/problems/WLOO0707 ] since it asks for square area.
Couple of test cases which i tried .

ghci>final [ P 1 1 , P 2 2 , P 0 100 , P 0 1 ]
Loading package array-0.3.0.0 ... linking ... done.
Loading package bytestring-0.9.1.5 ... linking ... done.
4.0

ghci>final [ P 0 0 ,P 5 1 , P 9 2 , P 12 3 , P 14 4 , P 15 5 , P 16
7 , P 17 10 , P 18 14 , P 19 19 ]
3.9982

ghci>final [ P 2 ( -3 ) , P (-1 ) 2 , P 0 5 , P (-5) (-1) , P (-4)
( 2 ) , P 4 0 , P 1 3 , P 4 3 , P (-3) (-4) , P 0 (-2)]
4.0

Thank you
Mukesh Tiwari


I found the error!

In
>width = distVec cpa' cpb'
>length = distVec cqa' cqb'
the length of the direction vectors is used to compute the area and the 
area is then always 4.


Replace it with
>width = distVec (V x1 y1) (V x3 y3)
>length = distVec (V x5 y5) (V x7 y7)

and it seems to work:

ghci> final [ P 1 1 , P 2 2 , P 0 100 , P 0 1 ]
  221.3707297724792


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


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-07 Thread Daniel Fischer
On Sunday 07 August 2011, 10:52:20, Max Bolingbroke wrote:
> In short I don't see how to get further without changing the algorithm
> or doing some hacks like manual unrolling. Maybe someone else has some
> ideas?

Well, the C# implementation uses arrays for lookup while the Haskell 
version uses list lookups

  in (tens !! fromIntegral t) ++ wordify x

and case'd functions

lenTens 0 = 0
lenTens 1 = 3
lenTens 2 = 6
lenTens 3 = 6
lenTens 4 = 5
lenTens 5 = 5
lenTens 6 = 5
lenTens 7 = 7
lenTens 8 = 6
lenTens 9 = 6
 
wordify is only called once at the end, so that should not have a 
measurable impact, but the lenXXXs might.
I'm not sure what

CaseLen.$wlenTens :: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId,
 Arity=1,
 Str=DmdType L,
 Unf=Unf{Src=, TopLvl=True, Arity=1, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=IF_ARGS [12] 11 0}]
CaseLen.$wlenTens =
  \ (ww_shY :: GHC.Prim.Int#) ->
case ww_shY of _ {
  __DEFAULT ->
CaseLen.lenTens1
`cast` (CoUnsafe GHC.Types.Int GHC.Prim.Int#
:: GHC.Types.Int ~ GHC.Prim.Int#);
  0 -> 0;
  1 -> 3;
  2 -> 6;
  3 -> 6;
  4 -> 5;
  5 -> 5;
  6 -> 5;
  7 -> 7;
  8 -> 6;
  9 -> 6
}

means at a lower level, but it's certainly worth trying out whether an 
unboxed array lookup is faster.

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


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-07 Thread Max Bolingbroke
On 7 August 2011 06:15, Chris Yuen  wrote:
> I am mainly interested in making the Haskell version perform
> comparatively to the C# version. Right now it is at least 5x slower so
> obviously I am missing something obvious)

You have a "map" call which is immediately consumed by "solve". GHCs
fusion wont' help you because "solve" is not defined in terms of
foldr. Fusing this manually (http://hpaste.org/49936) you can get 10%
improvement.

Another source of problems is the divMod calls. There are two issues:
  1. The result of the divMod is a pair of boxed Int64s. This can be
worked around by using div and mod seperately instead, but that is
actually slower even though it avoids the boxing.
  2. The divMod is "checked": i.e. it throws a Haskell exception if
the first argument is minBound or the second is 0. This means that
divMod does two equality checks and one unboxing operation (which will
just be an always-taken branch, thanks to pointer tagging) before it
actually reaches GHC.Base.divInt#

If I use divInt# and modInt# directly like so:

{{{
wordLength' :: Int64 -> Int64 -> Int64
wordLength' !pad !n@(I64# n#)
| n < 10 = lenOnes n + pad
| n < 20 = lenTeens (n-10) + pad
| n < 100= splitterTen
| n < 1000   = splitter 100 7
| n < 100= splitter 1000 8
| otherwise  = splitter 100 7
where
splitterTen = let -- !(!t, !x) =  n `divMod` 10
  t = n# `divInt#` 10#
  x = n# `modInt#` 10#
  in wordLength' (lenTens (I64# t) + pad) (I64# x)
splitter !(I# d#) !suffix = let -- !(!t, !x) = n `divMod` d
  t = n# `divInt#` d#
  x = n# `modInt#` d#
  in wordLength' (wordLength' (suffix+pad)
(I64# t)) (I64# x)
}}}

We sacrifice these checks but the code gets 25% faster again.

I can't see anything else obviously wrong with the core, so the
remaining issues are likely to be things like loop unrolling, turning
div by a constant int divisor into a multiply and other code
generation issues. I tried -fllvm but it has no effect. At a guess,
this is because optimisations are impeded by the call to stg_gc_fun in
the stack check that solve makes.

In short I don't see how to get further without changing the algorithm
or doing some hacks like manual unrolling. Maybe someone else has some
ideas?

Max

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