[Haskell-cafe] ANN: leapseconds-announced-2012

2012-01-07 Thread Bjorn Buckwalter
Dear all,

The International Earth Rotation and Reference Systems Service (IERS)
recently announced[1] that a positive leap second will be introduced
at the end of June 2012. Consequently I have updated the
leapseconds-announced library[2].

The original announcement of leapseconds-announced can be found below.

Best regards,
Bjorn Buckwalter

[1] http://hpiers.obspm.fr/eoppc/bul/bulc/bulletinc.dat
[2] http://hackage.haskell.org/package/leapseconds-announced


-- Forwarded message --
From: Bjorn Buckwalter bjorn.buckwal...@gmail.com
Date: Sat, Jan 17, 2009 at 13:23
Subject: ANN: leapseconds-announced-2009
To: hask...@haskell.org, haskell-cafe@haskell.org


Dear all,

I'm pleased to announce the upload of the leapseconds-announced
package[1] to Hackage. leapseconds-announced contains a single module
and a single function implementing the
Data.Time.Clock.TAI.LeapSecondTable interface (type).

The documentation[2] for Data.Time.Clock.TAI.LeapSecondTable says No
table is provided, as any program compiled with it would become out of
date in six months and with that I have no objections. However, I
frequently find myself needing a LeapSecondTable for a quick-and-dirty
one-off analysis or simulation of the present or past. In these cases
I've lazily used (const 33) (or more recently: (const 34)) as my
LeapSecondTable.

leapseconds-announced is a pragmatic, if imperfect, improvement over
my past practices. It provides a LeapSecondTable with all leap seconds
announced to date (hence the name). Once the IERS announces[3] another
leap second the package will need an update and all code using it a
recompile. While this precludes its use in long-running production
applications it is eminently adequate for my one-off uses or for
applications that can afford to recompile infrequently.

While, in the words of the Data.Time.Clock.TAI documentation, most
people won't need this module I hope it can be of utility to someone.

Thanks,
Bjorn Buckwalter

[1] 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/leapseconds-announced
[2] 
http://www.haskell.org/ghc/docs/latest/html/libraries/time/Data-Time-Clock-TAI.html
[3] http://hpiers.obspm.fr/eoppc/bul/bulc/bulletinc.dat

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


[Haskell-cafe] ANNOUNCE: normaldistribution-1.0 – Minimum fuss normally distributed random values.

2011-04-09 Thread Bjorn Buckwalter
Dear all,

I'm pleased to announce the immediate availability of the
normaldistribution library on hackage:

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

This purpose of this library is to have a simple API and no
dependencies beyond Haskell 98 in order to let you produce normally
distributed random values with a minimum of fuss. This library does
not attempt to be blazingly fast nor to pass stringent tests of
randomness. It attempts to be very easy to install and use while being
good enough for many applications (simulations, games, etc.).  The
API builds upon and is largely analogous to that of the Haskell 98
Random module (more recently System.Random).

Pure:

 (sample,g) = normal  myRandomGen  -- using a Random.RandomGen
 samples= normals myRandomGen  -- infinite list
 samples2   = mkNormals 10831452   -- infinite list using a seed

In the IO monad:

 sample- normalIO
 samples   - normalsIO  -- infinite list

With custom mean and standard deviation:

 (sample,g) = normal'(mean,sigma) myRandomGen
 samples= normals'   (mean,sigma) myRandomGen
 samples2   = mkNormals' (mean,sigma) 10831452

 sample- normalIO'  (mean,sigma)
 samples   - normalsIO' (mean,sigma)

Internally the library uses the Central Limit Theorem to approximate
normally distributed values from multiple uniformly distributed random
values.

Enjoy,
Bjorn

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


[Haskell-cafe] ANNOUNCE: normaldistribution-1.1 – Minimum fuss normally distributed random values.

2011-04-09 Thread Bjorn Buckwalter
Dear all,

Thanks to enlightening advice from Tom Nielsen and Zoltan Novak
normaldistribution now generates normally distributed values using the
Box-Muller method instead of the Central Limit Theorem. This change
provides a 5-10x speedup.

The only API impact is that the random values must now be instances of
Floating rather than just Fractional. (The pre-canned Random instances
that satisfy Fractional, i.e. Double and Float, also satisfy
Floating.)

Cheers,
Bjorn


-- Forwarded message --
From: Bjorn Buckwalter bjorn.buckwal...@gmail.com
Date: Sat, Apr 9, 2011 at 15:21
Subject: ANNOUNCE: normaldistribution-1.0 – Minimum fuss normally
distributed random values.


Dear all,

I'm pleased to announce the immediate availability of the
normaldistribution library on hackage:

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

This purpose of this library is to have a simple API and no
dependencies beyond Haskell 98 in order to let you produce normally
distributed random values with a minimum of fuss. This library does
not attempt to be blazingly fast nor to pass stringent tests of
randomness. It attempts to be very easy to install and use while being
good enough for many applications (simulations, games, etc.).  The
API builds upon and is largely analogous to that of the Haskell 98
Random module (more recently System.Random).

Pure:

 (sample,g) = normal  myRandomGen  -- using a Random.RandomGen
 samples    = normals myRandomGen  -- infinite list
 samples2   = mkNormals 10831452   -- infinite list using a seed

In the IO monad:

 sample    - normalIO
 samples   - normalsIO  -- infinite list

With custom mean and standard deviation:

 (sample,g) = normal'    (mean,sigma) myRandomGen
 samples    = normals'   (mean,sigma) myRandomGen
 samples2   = mkNormals' (mean,sigma) 10831452

 sample    - normalIO'  (mean,sigma)
 samples   - normalsIO' (mean,sigma)

Internally the library uses the Central Limit Theorem to approximate
normally distributed values from multiple uniformly distributed random
values.

Enjoy,
Bjorn

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


[Haskell-cafe] Why does cabal select base-3.0.3.2 when base-4.2.0.0 is available?

2010-04-26 Thread Bjorn Buckwalter
Dear all,

Why does cabal seem to prefer base-3.0.3.2 over base-4.2.0.0 when
installing packages with an unqualified base requirement? Example:


$ cabal install -v fad --reinstall
[snip]
Resolving dependencies...
selecting fad-1.0 (hackage)
selecting base-3.0.3.2 (installed) and 4.2.0.0 (installed) and discarding
syb-0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.2 and 0.2.1
[snip]
Configuring fad-1.0...
Dependency base ==3.0.3.2: using base-3.0.3.2
[snip]
[1 of 1] Compiling Numeric.FAD  ( Numeric/FAD.hs, dist/build/Numeric/FAD.o )

Numeric/FAD.hs:1:0:
Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.
[snip]


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


Re: [Haskell-cafe] Why does cabal select base-3.0.3.2 when base-4.2.0.0 is available?

2010-04-26 Thread Bjorn Buckwalter
On Mon, Apr 26, 2010 at 19:38, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Bjorn Buckwalter bjorn.buckwal...@gmail.com writes:
 Why does cabal seem to prefer base-3.0.3.2 over base-4.2.0.0 when
 installing packages with an unqualified base requirement? Example:

 You mean cabal-install rather than Cabal.  The reason that base-3 is
 chosen is because many of these old libraries won't build with base-4;
 as such, if no upper bound restriction is found on the base package then
 base-3 is chosen as it is more likely to work than base-4 (there were a
 _lot_ of breakages when base-4 first came out with 6.10.1).

I see, I guess that's pragmatic although the deprecation warning is unfortunate.

(I'm aware of the cabal-install versus Cabal distinction, but I
understand that cabal-install uses Cabal to resolve dependencies; thus
I assumed Cabal was the culprit.)

Thanks,
Bjorn


 $ cabal install -v fad --reinstall
 [snip]
 Resolving dependencies...
 selecting fad-1.0 (hackage)
 selecting base-3.0.3.2 (installed) and 4.2.0.0 (installed) and discarding
 syb-0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.2 and 0.2.1
 [snip]
 Configuring fad-1.0...
 Dependency base ==3.0.3.2: using base-3.0.3.2
 [snip]
 [1 of 1] Compiling Numeric.FAD      ( Numeric/FAD.hs, 
 dist/build/Numeric/FAD.o )

 Numeric/FAD.hs:1:0:
     Warning: Module `Prelude' is deprecated:
                You are using the old package `base' version 3.x.
                Future GHC versions will not support base version 3.x. You
                should update your code to use the new base version 4.x.
 [snip]


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

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


[Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Bjorn Buckwalter
Dear all,

Does it make good sense that 'and []' returns 'True' and 'or []'
returns 'False'? The Haskell Road to Logic, Maths and Programming says
so:

The function or takes a list of truth values and returns True if at
least one member of the list equals True, while and takes a list of
truth values and returns True if all members of the list equal True.

Should the conjunction of all elements of [] count as true or false?
As true, for it is indeed (trivially) the case that all elements of []
are true. So the identity element for conjunction is True. Should the
disjunction of all elements of [] count as true or false? As false,
for it is false that [] contains an element which is true. Therefore,
the identity element for disjunction is False.

While the above reasoning is fine, and allows straight-forward
implementations, it isn't extremely convincing. In particular, it
isn't clear that, while simple, the definitions of the first paragraph
are the most sensible. Perhaps one of the more mathematically versed
readers on the Cafe could enlighten me?

What got me thinking about this was the apparently incorrect intuition
that 'and xs' would imply 'or xs'.

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


Re: [Haskell-cafe] Why does cabal select base-3.0.3.2 when base-4.2.0.0 is available?

2010-04-26 Thread Bjorn Buckwalter
On Mon, Apr 26, 2010 at 20:07, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Bjorn Buckwalter bjorn.buckwal...@gmail.com writes:

 On Mon, Apr 26, 2010 at 19:38, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
 Bjorn Buckwalter bjorn.buckwal...@gmail.com writes:
 Why does cabal seem to prefer base-3.0.3.2 over base-4.2.0.0 when
 installing packages with an unqualified base requirement? Example:

 [snip]

 The reason that base-3 is chosen is because many of these old
 libraries won't build with base-4; as such, if no upper bound
 restriction is found on the base package then base-3 is chosen as it
 is more likely to work than base-4 (there were a _lot_ of breakages
 when base-4 first came out with 6.10.1).

 I see, I guess that's pragmatic although the deprecation warning is
 unfortunate.

 The deprecation warning is due to GHC 6.12; this is a not-so-subtle hint
 to package maintainers to fix their code up, and to users to poke the
 maintainers of packages they use to do so!

Understood, but in this case the warning seems misdirected since fad
does not restrict itself to base-3.*...

So what would be the fix, to set an upper bound on base? Is the
general recommendation that all packages should specify upper bounds
on all dependencies (if so why doesn't Cabal tell us?)? I can see that
this would make some sense as a package might be broken by an API
change in its dependencies. On the other hand I can also see it
causing headaches occasionally...

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


Re: [Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Bjorn Buckwalter
Ok Guys, you've convinced me thrice within ten minutes of posing my
question. The quality of the mailing list is just ridiculous! ;)

And Miguel, thanks for the follow-up regarding for all and exists
– it's an excellent analogy and easy to remember!


On Mon, Apr 26, 2010 at 20:23, Jochem Berndsen joc...@functor.nl wrote:
 Bjorn Buckwalter wrote:
 Dear all,

 Does it make good sense that 'and []' returns 'True' and 'or []'
 returns 'False'? The Haskell Road to Logic, Maths and Programming says
 so:

 The function or takes a list of truth values and returns True if at
 least one member of the list equals True, while and takes a list of
 truth values and returns True if all members of the list equal True.

 Should the conjunction of all elements of [] count as true or false?
 As true, for it is indeed (trivially) the case that all elements of []
 are true. So the identity element for conjunction is True. Should the
 disjunction of all elements of [] count as true or false? As false,
 for it is false that [] contains an element which is true. Therefore,
 the identity element for disjunction is False.

 While the above reasoning is fine, and allows straight-forward
 implementations, it isn't extremely convincing. In particular, it
 isn't clear that, while simple, the definitions of the first paragraph
 are the most sensible. Perhaps one of the more mathematically versed
 readers on the Cafe could enlighten me?

 The empty sum is regarded to be zero. The empty product is equal to one.
 The empty conjunction is True. The empty disjunction is False.

 The reason for this is that these are the neutral elements, i.e.
  0 + x = x
  1 * x = x
  True AND x = x
  False OR x = x

 This allows some laws to hold also in degenerate cases, and it is quite
 useful in general to accept these conventions. An example of such a law is
 (∀ x : x ∈ A : P(x)) ∧ (∀ x : x ∈ B : P(x))
  ==
 (∀ x : x ∈ A ∪ B : P(x)).

 This also works if A or B is empty, provided that we say that the empty
 conjunction is true.

 In Haskell, we now have that

 (and xs)  (and ys)
  ==
 and (xs ++ ys),

 even if xs or ys is the empty list.

 Cheers, Jochem
 --
 Jochem Berndsen | joc...@functor.nl

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


[Haskell-cafe] ANNOUNCE: numtype 1.0 -- Type-level (low cardinality) integers

2009-06-06 Thread Bjorn Buckwalter
Dear all,

Since its inception my dimensional library has been built around a
unary type-level representation of integers (NumTypes) defined in the
Numeric.NumType module. This module has proven itself useful outside
the context of dimensional and after dragging my feet for a long time
I've finally gotten around packaging it up in its own library:
numtype[1].

The Numeric.NumType module is completely self-contained (only imports
Prelude) and is heavily commented in a narrative manner inspired by
Oleg Kiselyov's expositions. I believe it provides a good case study
for type-level programming with multi-parameter type classes and
functional dependencies.

Addition, subtraction, division, and multiplication of NumTypes is
supported. NumTypes have no value-level representation but can be
converted to any Num instance with the 'toNum' function.

The numtype library has two significant short-comings:

* Minimal haddocks -- as with my dimensional library the literate
  Haskell source code is the documentation. The flip-side is that
  the code is very well-commented.

* Due to the unary implementation the practical size of the
  NumTypes is severely limited, making them unsuitable for
  large-cardinality applications. If you will be working with
  integers beyond (-20, 20) this package probably isn't for you.

(If the second bullet is a show-stopper Edward Kmett's type-int[2]
library may be a better choice. Peter Gavin's tfp[3] library also
provides type-level integers but uses type families instead of MPTCs
and fundeps. I cannot vouch for either of these libraries as I haven't
used them.)

Numtype version 1.0 can be downloaded from Hackage or the dimensional
project page[4]. I've also updated dimensional to version 0.8 with the
Numeric.NumType module removed and Julian 'year' and 'century' units
added. Enjoy!

Thanks,
Bjorn Buckwalter


[1]:  http://code.google.com/p/dimensional/wiki/numtype
[2]:  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/type-int
[3]:  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/tfp
[4]:  http://dimensional.googlecode.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-02 Thread Bjorn Buckwalter
I'm pleased to announce the initial release of the Haskell fad
library, developed by Barak A. Pearlmutter and Jeffrey Mark Siskind.
Fad provides Forward Automatic Differentiation (AD) for functions
polymorphic over instances of 'Num'. There have been many Haskell
implementations of forward AD, with varying levels of completeness,
published in papers and blog posts[1], but alarmingly few of these
have made it into hackage -- to date Conal Elliot's vector-spaces[2]
package is the only one I am aware of.

Fad is an attempt to make as comprehensive and usable a forward AD
package as is possible in Haskell. However, correctness is given
priority over ease of use, and this is in my opinion the defining
quality of fad. Specifically, Fad leverages Haskell's expressive
type system to tackle the problem of _perturbation confusion_,
brought to light in Pearlmutter and Siskind's 2005 paper Perturbation
Confusion and Referential Transparency[3]. Fad prevents perturbation
confusion by employing type-level branding as proposed by myself
in a 2007 post to haskell-cafe[4]. To the best of our knowledge all
other forward AD implementations in Haskell are susceptible to
perturbation confusion.

As this library has been in the works for quite some time it is
worth noting that it hasn't benefited from Conal's ground-breaking
work[5] in the area. Once we wrap our heads around his beautiful
constructs perhaps we'll be able to borrow some tricks from him.

As mentioned already, fad was developed primarily by Barak A.
Pearlmutter and Jeffrey Mark Siskind. My own contribution has been
providing Haskell infrastructure support and wrapping up loose ends
in order to get the library into a releasable state. Many thanks
to Barak and Jeffrey for permitting me to release fad under the BSD
license.

Fad resides on GitHub[6] and hackage[7] and is only a cabal install
fad away! What follows is Fad's README, refer to the haddocks for
detailed documentation.

Thanks,
Bjorn Buckwalter


[1] http://www.haskell.org/haskellwiki/Functional_differentiation
[2] http://www.haskell.org/haskellwiki/Vector-space
[3]:  http://www.bcl.hamilton.ie/~qobi/nesting/papers/ifl2005.pdf
[4]: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/
[5]: http://conal.net/papers/beautiful-differentiation/
[6] http://github.com/bjornbm/fad/
[7] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fad




   Copyright  : 2008-2009, Barak A. Pearlmutter and Jeffrey Mark Siskind
   License: BSD3

   Maintainer : bjorn.buckwal...@gmail.com
   Stability  : experimental
   Portability: GHC only?

Forward Automatic Differentiation via overloading to perform
nonstandard interpretation that replaces original numeric type with
corresponding generalized dual number type.

Each invocation of the differentiation function introduces a
distinct perturbation, which requires a distinct dual number type.
In order to prevent these from being confused, tagging, called
branding in the Haskell community, is used.  This seems to prevent
perturbation confusion, although it would be nice to have an actual
proof of this.  The technique does require adding invocations of
lift at appropriate places when nesting is present.

For more information on perturbation confusion and the solution
employed in this library see:
http://www.bcl.hamilton.ie/~barak/papers/ifl2005.pdf
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/


Installation

To install:
cabal install

Or:
runhaskell Setup.lhs configure
runhaskell Setup.lhs build
runhaskell Setup.lhs install


Examples

Define an example function 'f':

 import Numeric.FAD
 f x = 6 - 5 * x + x ^ 2  -- Our example function

Basic usage of the differentiation operator:

 y   = f 2  -- f(2) = 0
 y'  = diff f 2 -- First derivative f'(2) = -1
 y'' = diff (diff f) 2  -- Second derivative f''(2) = 2

List of derivatives:

 ys = take 3 $ diffs f 2  -- [0, -1, 2]

Example optimization method; find a zero using Newton's method:

 y_newton1 = zeroNewton f 0   -- converges to first zero at 2.0.
 y_newton2 = zeroNewton f 10  -- converges to second zero at 3.0.


Credits
===
Authors: Copyright 2008,
Barak A. Pearlmutter ba...@cs.nuim.ie 
Jeffrey Mark Siskind q...@purdue.edu

Work started as stripped-down version of higher-order tower code
published by Jerzy Karczmarczuk jerzy.karczmarc...@info.unicaen.fr
which used a non-standard standard prelude.

Initial perturbation-confusing code is a modified version of
http://cdsmith.wordpress.com/2007/11/29/some-playing-with-derivatives/

Tag trick, called branding in the Haskell community, from
Bjorn Buckwalter bjorn.buckwal...@gmail.com
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http

[Haskell-cafe] Re: Ease of Haskell development on OS X?

2009-03-20 Thread Bjorn Buckwalter
Haskell on Mac OS X has been mostly painless for me. I have a PowerPC 
mac which means there are rarely binaries for me to download from
haskell.org. I've either used MacPorts or compiled the GHC from source, 
both have worked well. I prefer the latter, but you'll probably want
MacPorts anyway for gcc and non-haskell libs.

I did some HOpenGL stuff about a year ago and cannot recall having any
problems.

Occasionally you'll have to do something like install PCRE using
MacPorts and add /opt/local/lib to $LD_LIBRARY_PATH[1] but mostly
things just work.

I believe the readline/libedit thing caused minor headache at some point
(but far less than on the Red Hat linux box on which I have no root/sudo
access).

Everything certainly works infinitely better than on Cygwin. :P

Sorry about not being able to give more details, any issues I may have
had are not fresh in memory. But in short I don't think you'll have any
more/significantly different problems than on Linux, and probably
substantially less than on Windows (or I'm doing something wrong). 

Barring where the above contradicts him I concur with Thomas Davie. ;)

Thanks,
Bjorn Buckwalter

[1] http://tinyurl.com/cw64nd


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


[Haskell-cafe] Apologies for spamming Planet Haskell

2009-03-17 Thread Bjorn Buckwalter
Dear Planet Haskell readers,

Just want to apologize for spamming Planet Haskell. I did some minor
formatting edits of old posts and it seems Planet Haskell picked them
up and republished them. I didn't expect this to happen (Google Reader
doesn't do that) and will be more careful about gratuitously editing
old posts in the future.

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


[Haskell-cafe] Parsing floating point numbers

2009-03-08 Thread Bjorn Buckwalter
Hi all,

What is your preferred method of parsing floating point numbers (from
String to Float/Double)? Parsec it seems only does positive floats out
of the box and PolyParse requires the float to be on scientific form
(exponential). While I've worked around these shortcomings in the past
I feel that I am reinventing the wheel as surely I am not the only to
run into these limitations. How do you parse your floats? Can you
recommend a parsing library that handles them solidly?

(For my current needs the formats accepted by read are sufficient,
but I want reasonable error handling (Maybe or Either) instead of an
exception on bad inputs.)

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


[Haskell-cafe] Re: ANN: leapseconds-announced-2009

2009-01-18 Thread Bjorn Buckwalter
On Sun, Jan 18, 2009 at 00:37, Ashley Yakeley ash...@semantic.org wrote:
 On Sun, 2009-01-18 at 00:34 -0500, Bjorn Buckwalter wrote:
 Thanks for the pointer. My source is the Earth Orientation Parameter
 (EOP) data at http://www.celestrak.com/SpaceData/; specifically I
 autogenerate the module from
 http://www.celestrak.com/SpaceData/eop19620101.txt. Probably looks
 more complicated than necessary but I'm parsing the file anyway for
 other purposes.

 With tz, though, you could discover the table at run-time and so be more
 likely to be up to date.

Ah yes. However, just like time this library does not attempt to
solve that particular problem. The purpose of leapseconds-announced is
to be dead easy to use (no IO and treading of the LeapSecondTable to
the usage point), at the cost of longevity. Of course, as I pointed
out in the announcement this trade-off isn't suitable for all
applications.

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


[Haskell-cafe] Re: ANN: leapseconds-announced-2009

2009-01-17 Thread Bjorn Buckwalter
On Sun, Jan 18, 2009 at 00:00, Ashley Yakeley ash...@semantic.org wrote:
 Bjorn Buckwalter wrote:

 leapseconds-announced is a pragmatic, if imperfect, improvement over
 my past practices. It provides a LeapSecondTable with all leap seconds
 announced to date (hence the name). Once the IERS announces[3] another
 leap second the package will need an update and all code using it a
 recompile. While this precludes its use in long-running production
 applications it is eminently adequate for my one-off uses or for
 applications that can afford to recompile infrequently.

 You should consider using the tz database, which provides a leap-seconds
 table in the right/UTC timezone (and much other useful information).

Thanks for the pointer. My source is the Earth Orientation Parameter
(EOP) data at http://www.celestrak.com/SpaceData/; specifically I
autogenerate the module from
http://www.celestrak.com/SpaceData/eop19620101.txt. Probably looks
more complicated than necessary but I'm parsing the file anyway for
other purposes.

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


[Haskell-cafe] Re: Reader monad, implicit parameters, or something else altogether?

2008-12-16 Thread Bjorn Buckwalter
Richard A. O'Keefe ok at cs.otago.ac.nz writes:

 Just an idiot-level question: so these constants are subject
 to revision, but *how often*?  What is the actual cost of
 recompiling and using them *as* constants, compared with the
 cost of rereading the stuff every time you run the program and
 passing it around?

My apologies but I kind of lost track of this thread after the initial helpful
replies and didn't follow up diligently on what went only to haskell-cafe (which
I don't follow regularly) and not to my inbox. 

In case you are still curious an example of data that changes frequently is
Earth orientation parameters (of which the leap seconds which Andrew elaborated
on are one). These include e.g. the difference between UT1 and UTC (UT1-UTC)
which is necessary to accurately relate the position and orientation of e.g. a
ground based observer to an object in inertial space. UT1-UTC is continuously
monitored with new observed an predicted values being published daily.
Additional parameters and their update frequencies are listed at [1] and
available compiled and with some documentation at [2].

[1] http://www.celestrak.com/SpaceData/EOP-format.asp
[2] http://www.celestrak.com/SpaceData/

A piece of software precessing e.g. satellite orbit observations would ideally
use the latest Earth orientation parameter data without requiring a recompile
for each day.

Thanks,
Bjorn


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


[Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
All,

I have a growing amount of astrodynamics code that relies on various
physical constants. The problem with these so called constants are
that they either aren't really constants or aren't well known. An
example is the leap second table (see Data.Time.Clock.TAI). I'd like
to be able to fetch current values of these constants at runtime and
make them accessible to my astrodynamics functions by some means. To
clarify, once initialized the constants will be considered constant
for the remainder of the program.

I'd store the constants in a data structure along the lines of:

 data AstroData a = AstroData
   { mu_Earth:: GravitationalParameter a
   , leapSeconds :: LeapSecondTable
   }

I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...

What do you people recommend?

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


[Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
All,

I have a growing amount of astrodynamics code that relies on various
physical constants. The problem with these so called constants are
that they either aren't really constants or aren't well known. An
example is the leap second table (see Data.Time.Clock.TAI). I'd like
to be able to fetch current values of these constants at runtime and
make them accessible to my astrodynamics functions by some means. To
clarify, once initialized the constants will be considered constant
for the remainder of the program.

I'd store the constants in a data structure along the lines of:

 data AstroData a = AstroData
   { mu_Earth:: GravitationalParameter a
   , leapSeconds :: LeapSecondTable
   }

I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...

What do you people recommend?

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


Fwd: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
On Mon, Aug 18, 2008 at 2:02 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:

 On Mon, Aug 18, 2008 at 11:16 AM, Henning Thielemann
 [EMAIL PROTECTED] wrote:

 On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:

 I would like to know if there is any consensus on what is the best way
 to make such a data structure accessible in pure functions. Passing it
 explicitly would be a mess. It seems that two options are to use
 either a Reader monad or implicit parameters. Using a Reader monad is
 straight forward enough though it requires writing/converting code
 in/to monadic style and adds some clutter to the formulae. It seems
 implicit parameters could be cleaner but I've seen them referred to as
 everything from evil to just what you need and rendering the Reader
 monad obsolete...

 I expect that you will get the same range of opinions as you got from
 your
 search. As far as I know implicit parameters break referential
 transparency.

  
 http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters
  So I prefer Reader monad. The burden of converting to monadic style pays
 off when you need to use the same code with different values for the
 constants. (E.g. find out for which value of the Planck constant the
 universe collapses and for which it oscillates etc. :-)

 Love the example but could you elaborate a little on how monadic style
 helps with this? (This is probably a matter of it not being obvious to
 me what approach you would take to solving the problem.)

 Instead of
  muEarth :: GravitationalParameter a
  muEarth = ???

  escapeVelocity :: a
  escapeVelocity = ... muEarth ...

 you would write

  data AstroData a = AstroData
{ muEarth :: GravitationalParameter a
, leapSeconds :: LeapSecondTable
}

  escapeVelocity :: Reader (AstroData a) a
  escapeVelocity =
 do mu - asks muEarth
return (... mu ...)

 Even better you would introduce a newtype for Reader (AstroData a). This way
 you can add any monadic functionality later (Writer et.al.).

Right, and I'd evaluate it using e.g.:

 runReader escapeVelocity myAstroData

But with implicit params I suppose I'd define (untested) e.g.:

 escapeVelocity :: (?astro :: AstroData a) = a
 escapeVelocity = ... mu ... where mu = muEarth ?astro

To evaluate this I'd use:

 let ?astro = myAstroData in escapeVelocity

Which is comparable to the Reader version (with the
advantage/disadvantage of the body of 'escapeVelocity' not being
monadic).

In retrospect I think I misunderstood what you were saying in you
first email. I thought you were arguing that the monadic style would
have an advantage over implicit params in the Planck problem. But you
probably only meant to reemphasize the advantage (of either solution)
over hard-coding constants...

Thanks again, your Reader example is virtually identical to what I
started off with so at least I know I'm not completely off target for
a monadic implementation.

(Sorry about the reposts Henning, I keep forgetting to cc the café!)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: I am new to haskell

2008-05-08 Thread Bjorn Buckwalter
Ambrish Bhargava bhargava.ambrish at gmail.com writes:
 Hi All,I am new to Haskell. Can anyone guide me how can I start on it (Like
getting binaries, some tutorials)?Thanks in advance.-- Regards,Ambrish Bhargava


Ambrish,

When I started learning Haskell I had no previous exposure to functional
programming. The sources I found most useful were Hal Daume III's Yet Another
Haskell Tutorial and Eric Etheridge's Haskell Tutorial for C Programmers,
both linked to from the tutorials wiki page:

  http://www.haskell.org/haskellwiki/Tutorials

I found the Gentle Introduction... mentioned elsewhere in this thread to be
not-so-gentle as described on the tutorials wiki page. I'd avoid it unless
you're already comfortable with functional programming.

Good luck!

-Bjorn


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


[Haskell-cafe] Re: I am new to haskell

2008-05-08 Thread Bjorn Buckwalter
Bjorn Buckwalter bjorn.buckwalter at gmail.com writes:

 I found the Gentle Introduction... mentioned elsewhere in this thread to be
 not-so-gentle as described on the tutorials wiki page. I'd avoid it unless
 you're already comfortable with functional programming.

Let me modify that statement. I'd avoid it until you've made your way through
one or two of the other tutorials, and then give it a good reading. It's an
excellent introduction, only not for beginners. ;)

-Bjorn

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


[Haskell-cafe] Re: An offer to any haskell projects out there.

2008-03-13 Thread Bjorn Buckwalter
 michael at schmong.org writes:

 Hello,
   My name is Michael Litchard. I'm a techie living in silicon
   valley, and I want to move into tech writing. I've got the
   background, now I need a portfolio. I figured the best way to go
   is to attach myself to some open source projects, and haskell
   has had my heart for a few years now. I am by no means an expert
   at haskell. My expertise is writing. So I make this offer.
   If you need documentation written for your haskell project, I'm
   your man. Whatever it is, I'll write it or edit it. Thanks for
   your time.
 
   P.S
   If this was the wrong list, or if anyone has other ideas
   about how to propogate my proposal, please let me know.
 
   Michael

Michael, that's an awesome offer. As others have already noted there
are plenty of areas where you could make a significant contribution.

I'd specifically recommend reposting your offer to the HAppS
(http://happs.org) list/group. HAppS is a high profile project which
seems to be getting quite a bit of interest from outside the Haskell
community. If you're unfamiliar with it I recommend taking a look
at the BayFP Presentation linked on the site.

Unfortunately HAppS has a serious deficit of documentation (including
the web site not being up to date) and consequently there is a high
barrier to entry.

While HAppS could certainly benefit from you help I would imagine
that you could also benefit from helping HAppS. The high profile
of HAppS should increase the chance of prospective clients being
able to relate to your portfolio, and I'd also imagine that
comprehensive documentation focused on a specific project is more
portfoliable than random pieces scattered around the standard
libraries (not that I want to disuade you from contributing there
too!).

Good luck!

-Bjorn

(I'm not involved in the HAppS project, nor have I used it.)




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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Bjorn Buckwalter
On Feb 6, 2008 8:47 PM, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 7, 2008 2:30 AM, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
  Ok. Is this what people want -- one big hold-all library with
  everything, as opposed to smaller more specialized packages? I guess I
  can see advantages (real or perceived) to both approaches.

 Apart from Dockins' typenats library there are no other user-friendly
 specific type-level libraries that know, so I cannot really tell if
 people would prefer a hold-all library or a couple of more granular
 specialized ones.

 Right now is not hold-all at all (it is still vaporware actually :)),
 so I think there's no reason to discuss that at this point. Let's see
 what people think.

Right, of course. I'll be taking a look at your no-longer-vaporware! ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-06 Thread Bjorn Buckwalter
On Feb 6, 2008 1:03 PM, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 6, 2008 4:32 AM, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
  I understand that you (and Wolfgang) are creating a library of type
  level decimals for the purpose of constraining vector (list?) lengths.
  After that I haven't been paying attention fully to the thread. Is the
  goal to create a general-purpose library for type-level programming
  and my module would fit into that grander scheme?

 Yes,the idea is to create a Cabal-ready wide-scope type-level
 programming library, joining the operations implemented in the
 different type-level libraries which are around. The goal (or at least
 mine) is to provide a common reusable type-level library which saves
 constantly reinventing the wheel.

Ok. Is this what people want -- one big hold-all library with
everything, as opposed to smaller more specialized packages? I guess I
can see advantages (real or perceived) to both approaches.

The other library I use for type-level programming is HList. It has
type-level booleans already so you might what to take a look at it if
you're not already familiar with it. In fact, if you are serious about
creating the de facto(?) type-level programming library trying to get
Oleg involved would be very beneficial both in terms of innovation and
credibility.


  Or did you have something else in mind with joining efforts? E.g. help
  reviewing your code or writing new code?
 

 This would certainly help too.

I'm sure it would. ;)  I didn't mean to imply that I have plenty of
spare time to invest in this but I'll certainly be paying attention
when you start releasing code.

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-05 Thread Bjorn Buckwalter
On Feb 5, 2008 2:16 PM, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 5, 2008 4:10 PM, Henning Thielemann
 [EMAIL PROTECTED] wrote:
 
  On Fri, 1 Feb 2008, Aaron Denney wrote:
 
   On 2008-02-01, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
If Naturals had been sufficient for me I wouldn't have done my own
implementation (I'm unaware of any other implementation of Integers).
And there is certainly a lot of value to the clearer error messages
from a decimal representation.
  
   I did a balanced-base-three (digits are 0, and +- 1) representation to
   get negative decimals.
 
  Nice. In German the digit values are sometimes called eins, keins, meins. 
  :-)

 I'm almost done with the decimal library but it would be nice to check
 some Integer implementations for future inclusion. So, Aaron, Björn,
 are your implementations available somewhere?

As noted elsewhere in the thread my implementation is available at:

http://www.buckwalter.se/~bjorn/darcs/dimensional/Numeric/NumType.lhs

It is my intent to extract this (self-contained) module to its own
package and put on hackage. It's been a low priority for me but I'm
rather incentivized by this thread.

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-05 Thread Bjorn Buckwalter
   I'm almost done with the decimal library but it would be nice to check
   some Integer implementations for future inclusion. So, Aaron, Björn,
   are your implementations available somewhere?
 
  As noted elsewhere in the thread my implementation is available at:
 
  http://www.buckwalter.se/~bjorn/darcs/dimensional/Numeric/NumType.lhs

 Thanks!

  It is my intent to extract this (self-contained) module to its own
  package and put on hackage. It's been a low priority for me but I'm
  rather incentivized by this thread.

 Great!

 How about joining efforts? As I said I almost have a preliminary
 version of the decimal library which I'll realease for reviewing
 purpouses soon (It won't include Integer computations though)

Well, could you elaborate a little on joining efforts? The effort I
was planning to invest in my package consists mainly of creating a
.cabal file plus some logistics to get tarballs to where they have to
be.

I understand that you (and Wolfgang) are creating a library of type
level decimals for the purpose of constraining vector (list?) lengths.
After that I haven't been paying attention fully to the thread. Is the
goal to create a general-purpose library for type-level programming
and my module would fit into that grander scheme?

Or did you have something else in mind with joining efforts? E.g. help
reviewing your code or writing new code?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Dimensional 0.7.2

2008-01-02 Thread Bjorn Buckwalter
Dear all,

I've released version 0.7.2 of the Dimensional library. The only
change from version 0.7.1 is that the CGS module has been re-enabled.
Unless you use the CGS module there is no need to upgrade from 0.7.1.

Note that this version is incompatible with GHC 6.8.1 due to bug #1919
(introduced in GHC 6.8.1 and fixed in 6.8.2). For GHC 6.8.1 use
version Dimensional 0.7.1 which lacks the CGS module.

Thanks,
Bjorn Buckwalter

http://dimensional.googlecode.com
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dimensional


On Nov 23, 2007 8:32 AM, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
 Dear all,

 The Dimensional library has been ported to GHC 6.8.1 (it remains
 backwards-compatible with GHC 6.6.1, and also with Cabal 1.1.6 I
 believe). The new version number is 0.7.1.

 Due to a GHC 6.8.1 bug (#1919) the CGS module will not compile and has
 been disabled.

 Thanks,
 Bjorn Buckwalter

 http://dimensional.googlecode.com
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dimensional
 http://hackage.haskell.org/trac/ghc/ticket/1919

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


Re: [Haskell-cafe] Re: DSL question -- was: New slogan for haskell.org

2007-12-27 Thread Bjorn Buckwalter
On Dec 26, 2007 10:28 PM, Steve Lihn [EMAIL PROTECTED] wrote:
 arising from use of `/' at DSLTest.hs:11:14-28

 Thanks for the example. I am particularly amazed GHC is complaining at
 '/', not '+'. The type mismatch occurs (is reported) at much lower
 level. It would be nice if there is a way to bump it up a couple
 levels...

I suppose that is how the type inferencer works. To start with all it
really knows is the types of 'phi' and 'mu'. Since it knows the type
of 'mu' it can assume that 'v_GEO' has the same type, and from the
definition of 'v_GEO' (and 'phi') it can infer a type for 'r_GEO'. But
when checking that assumption against the definition of 'r_GEO' which
depends on only 'phi' and 'mu' it realizes that things are amiss. (I'm
just guessing here, the order, or way, in which the compiler does
stuff may be totally different.)

To be fair to the compiler it really has no way of knowing which
definition is wrong without explicit type signatures. As I noted in my
previous reply adding type signatures to all definitions allows the
compiler to locate the error:

  In the second argument of `(+)', namely `mu'
  In the expression: v_GEO + mu

I added this as an example to the library wiki[1]. The version of the
code with type signatures is there and the whole page can be
copy-pasted as literate haskell if you want to try it:

[1] http://code.google.com/p/dimensional/wiki/ErrorMessagesAndDebugging


 On Dec 26, 2007 12:56 PM, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
  Steve Lihn stevelihn at gmail.com writes:
 
   I do come aross a question while reading the DSL page on Wikipedia.
  
   http://en.wikipedia.org/wiki/Domain-specific_programming_language
  
   In the Disadvantage section (near the end), there is an item -- hard
   or impossible to debug. Can anybody explain why or what it means? And
   how does it apply to Haskell?
 
 
  I think I can give a good example of how this can apply to EMBEDDED DSLs. My
  library Dimensional (http://dimensional.googlecode.com) defines what someone
  referred to as a EDSL for working with physical units. The library 
  leverages the
  Haskell type checker to provide static checking of physical dimensions. 
  Without
   doing this I don't know how I could make such checking static.
 
  The downside of this is that while you will be informed at compile time if 
  you
  physical calculations are incorrect the error message itself is rarely 
  useful.
  Here is an example with lines numbered:
 
   1 import Numeric.Units.Dimensional.Prelude
   2 import qualified Prelude
   3
   4 -- The angular velocity of Earth's rotation (Soop p. 7).
   5 phi = 360.985647 *~ (degree / day)
   6
   7 -- The gravitational parameter of Earth.
   8 mu = 3.98600448003e14 *~ (meter ^ pos3 / second ^ pos2)
   9
   10 -- The ideal geostationary radius and velocity.
   11 r_GEO = cbrt (mu / phi ^ pos2)
   12 v_GEO = phi * r_GEO
   13
   14 -- Something obviously wrong.
   15 dont_try_this_at_home = v_GEO + mu
 
  Obviously we shouldn't be adding a velocity to a gravitational parameter on 
  line
  15 and the compiler will catch this. However, this is the error message from
  GHCi (6.6.1):
 
  DSLTest.hs:1:0:
 Couldn't match expected type `Numeric.NumType.Neg n'
against inferred type `Numeric.NumType.Zero'
 When using functional dependencies to combine
   Numeric.NumType.Sub a Numeric.NumType.Zero a,
 arising from the instance declaration at Defined in Numeric.NumType
   Numeric.NumType.Sub Numeric.NumType.Zero
   Numeric.NumType.Zero
   (Numeric.NumType.Neg n),
 arising from use of `/' at DSLTest.hs:11:14-28
 
  I think you will agree that this isn't very helpful in pin-pointing the 
  problem.
  The compiler is pointing at the definition of 'r_GEO' which is twice removed
  from the actual offender. Stuff like this can make EDSLs difficult to debug.
 
  (In this particular example adding type signatures to all definitions will 
  allow
  the compiler to pin-point the error to line 15, although the error message
  remains cryptic.)
 
  Hope that helps,
  Bjorn
 
  ___
  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] Re: DSL question -- was: New slogan for haskell.org

2007-12-26 Thread Bjorn Buckwalter
Steve Lihn stevelihn at gmail.com writes:

 I do come aross a question while reading the DSL page on Wikipedia.
 
 http://en.wikipedia.org/wiki/Domain-specific_programming_language
 
 In the Disadvantage section (near the end), there is an item -- hard
 or impossible to debug. Can anybody explain why or what it means? And
 how does it apply to Haskell?


I think I can give a good example of how this can apply to EMBEDDED DSLs. My
library Dimensional (http://dimensional.googlecode.com) defines what someone
referred to as a EDSL for working with physical units. The library leverages the
Haskell type checker to provide static checking of physical dimensions. Without
 doing this I don't know how I could make such checking static.

The downside of this is that while you will be informed at compile time if you
physical calculations are incorrect the error message itself is rarely useful.
Here is an example with lines numbered:

  1 import Numeric.Units.Dimensional.Prelude
  2 import qualified Prelude
  3
  4 -- The angular velocity of Earth's rotation (Soop p. 7).
  5 phi = 360.985647 *~ (degree / day)
  6
  7 -- The gravitational parameter of Earth.
  8 mu = 3.98600448003e14 *~ (meter ^ pos3 / second ^ pos2)
  9
 10 -- The ideal geostationary radius and velocity.
 11 r_GEO = cbrt (mu / phi ^ pos2)
 12 v_GEO = phi * r_GEO
 13
 14 -- Something obviously wrong.
 15 dont_try_this_at_home = v_GEO + mu

Obviously we shouldn't be adding a velocity to a gravitational parameter on line
15 and the compiler will catch this. However, this is the error message from
GHCi (6.6.1):

DSLTest.hs:1:0:
Couldn't match expected type `Numeric.NumType.Neg n'
   against inferred type `Numeric.NumType.Zero'
When using functional dependencies to combine
  Numeric.NumType.Sub a Numeric.NumType.Zero a,
arising from the instance declaration at Defined in Numeric.NumType
  Numeric.NumType.Sub Numeric.NumType.Zero
  Numeric.NumType.Zero
  (Numeric.NumType.Neg n),
arising from use of `/' at DSLTest.hs:11:14-28

I think you will agree that this isn't very helpful in pin-pointing the problem.
The compiler is pointing at the definition of 'r_GEO' which is twice removed
from the actual offender. Stuff like this can make EDSLs difficult to debug.

(In this particular example adding type signatures to all definitions will allow
the compiler to pin-point the error to line 15, although the error message
remains cryptic.)

Hope that helps,
Bjorn

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


[Haskell-cafe] ANN: Dimensional 0.7.1 (GHC 6.8.1 compatibility)

2007-11-23 Thread Bjorn Buckwalter
Dear all,

The Dimensional library has been ported to GHC 6.8.1 (it remains
backwards-compatible with GHC 6.6.1, and also with Cabal 1.1.6 I
believe). The new version number is 0.7.1.

Due to a GHC 6.8.1 bug (#1919) the CGS module will not compile and has
been disabled.

Thanks,
Bjorn Buckwalter

http://dimensional.googlecode.com
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dimensional
http://hackage.haskell.org/trac/ghc/ticket/1919
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe