Re: [Haskell-cafe] Unfriendly hs-plugins error

2007-10-02 Thread Björn Buckwalter
That helped, thanks!


On 10/2/07, jeeva suresh [EMAIL PROTECTED] wrote:
 I had a similar problem, I solved it by using the development version of
 hs-plugins (ie. darcs get --set-scripts-executable
 http://www.cse.unsw.edu.au/~dons/code/hs-plugins)


 On 02/10/2007, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 
 
  On Oct 1, 2007, at 21:59 , Björn Buckwalter wrote:
 
   Dear all,
  
   I'm getting a rather unfriendly error when trying to load a plugin
   with hs-plugins:
  
   my_program: Ix{Int}.index: Index (65536) out of range ((0,7))
 
  This tends to mean that hs-plugins doesn't understand the format of
  the .hi (compiled haskell module interface) file, which happens every
  time a new ghc is released.  Likely it's not been ported to work with
  6.6.1 yet.
 
  --
  brandon s. allbery [solaris,freebsd,perl,pugs,haskell]
 [EMAIL PROTECTED]
  system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
  electrical and computer engineering, carnegie mellon universityKF8NH
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
 
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 -Jeeva

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


[Haskell-cafe] Unfriendly hs-plugins error

2007-10-01 Thread Björn Buckwalter
Dear all,

I'm getting a rather unfriendly error when trying to load a plugin
with hs-plugins:

my_program: Ix{Int}.index: Index (65536) out of range ((0,7))

The exact numbers in the message vary depending on what I'm trying to
do. I'm using GHC-6.6.1 on MacOS X. Here are three files that exhibit
the behaviour for me:

API.lhs
===
 module API where
 data Config = Config { param :: String }

Main.lhs

 module Main where
 import System (getArgs)
 import System.Plugins
 import API

 getConfig :: [String] - IO Config
 getConfig [file] = do
   status - make file []
   obj- case status of
   MakeSuccess _ o - return o
   MakeFailure es  - mapM_ putStrLn es  error make failed
   putStrLn $ ### loading  ++ file
   m_v- load_ obj [.] config
   putStrLn $ ### checking  ++ file
   val- case m_v of
   LoadSuccess _ v - return v
   LoadFailure es  - mapM_ putStrLn es  error load failed
   return val

 main = getArgs = getConfig = putStrLn . param

CustomConfig.hs
===
module CustomConfig where
 import API
 config = Config { param = Doomed to fail! }


I compile the above with ghc --make -o my_program PluginTest.lhs and
execute with ./my_program CustomConfig.lhs.

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


[Haskell-cafe] Re: Unfriendly hs-plugins error

2007-10-01 Thread Björn Buckwalter
-453973694165307953197296969697410619233826
+Loading package base ... linking ... plugs let fibs = 1 : 1 :
zipWith (+) fibs (tail fibs) in fibs !! 200
+plugs:
+unknown symbol `_base_GHCziList_znzn_closure'
+done
+plugs: user error (resolvedObjs failed.)
+
=== testing testsuite/plugs/runplugs   ... ===
testing testsuite/reload/null  ... ===
testing testsuite/shell/shell  ...
ignored.
=== testing testsuite/shell/simple ... ignored.
=== testing testsuite/unload/null  ... ===
testing testsuite/unload/sjwtrap   ... ===
testing testsuite/unloadAll/null   ...



On 10/1/07, Björn Buckwalter [EMAIL PROTECTED] wrote:
 Dear all,

 I'm getting a rather unfriendly error when trying to load a plugin
 with hs-plugins:

 my_program: Ix{Int}.index: Index (65536) out of range ((0,7))

 The exact numbers in the message vary depending on what I'm trying to
 do. I'm using GHC-6.6.1 on MacOS X. Here are three files that exhibit
 the behaviour for me:

 API.lhs
 ===
  module API where
  data Config = Config { param :: String }

 Main.lhs
 
  module Main where
  import System (getArgs)
  import System.Plugins
  import API

  getConfig :: [String] - IO Config
  getConfig [file] = do
status - make file []
obj- case status of
MakeSuccess _ o - return o
MakeFailure es  - mapM_ putStrLn es  error make failed
putStrLn $ ### loading  ++ file
m_v- load_ obj [.] config
putStrLn $ ### checking  ++ file
val- case m_v of
LoadSuccess _ v - return v
LoadFailure es  - mapM_ putStrLn es  error load failed
return val

  main = getArgs = getConfig = putStrLn . param

 CustomConfig.hs
 ===
 module CustomConfig where
  import API
  config = Config { param = Doomed to fail! }


 I compile the above with ghc --make -o my_program PluginTest.lhs and
 execute with ./my_program CustomConfig.lhs.

 Any hints welcome. Thanks,
 Bjorn Buckwalter

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


[Haskell-cafe] ANNOUNCE: Dimensional 0.6 -- Statically checked physical dimensions

2007-08-02 Thread Björn Buckwalter
Dear all,

 I am pleased to announce version 0.6 of the Dimensional library.

 Dimensional is a library providing data types for performing
arithmetic with physical quantities and units. Information about the
physical dimensions of the quantities/units is embedded in their types
and the validity of operations is verified by the type checker at
compile time. The boxing and unboxing of numerical values as
quantities is done by multiplication and division with units.

 The library is designed to, as far as is practical, enforce/encourage
best practices [1] of unit usage.

 Noteworthy changes/additions since the previous formal announcement
(version 0.4) are:

 - All quantities and SI units from [1] have been added.
 - A Prelude replacement with the SI units and dimensional operators
(+, *, ^...) is provided for convenience.
 - Interface to Data.Time using 'fromDiffTime' and 'toDiffTime'.
 - Phantom type tags make extended dimensions safer.
 - Experimental CGS units with type safe conversions to/from SI. See
appended literate Haskell module for details.

 Additional information and code is available from the project web site [3].

 Thank you,
 Bjorn Buckwalter


 [1] http://physics.nist.gov/Pubs/SP811/
  [2] http://www.haskell.org/pipermail/haskell/2007-May/019496.html
  [3] http://code.google.com/p/dimensional/




 ~~ BEGIN 'Buckwalter/Dimensional/CGS.lhs' ~~
 Buckwalter.Dimensional.CGS -- CGS system of units
 Bjorn Buckwalter, [EMAIL PROTECTED]
 License: BSD3

 *** EXPERIMENTAL ***


 = Introduction =

 This module was prompted by an email from Chuck Blake[1]. He asked if
 the Dimensional library could support other systems of units than
 SI, in particular systems such as the centimeter-gram-second (CGS)
 system where fractional exponents of dimensions occur. He also
 wondered whether it was possible to convert quantities between
 different systems while statically ensuring that a given conversion
 was valid.

 In this module we show that we can in a straight forward manner
 support systems with rational exponents, provided that the rationals
 that may be encountered are known a priori. As an example we provide
 a rudimentary implementation of the CGS system.

 We also show that we can indeed statically prohibit invalid conversions
 between different systems.


 = Caveats =

 I'm ignorantly assuming that when working with the CGS (or MKS)
 system you will only (meaningfully?) encounter half-exponents and
 only of the length and mass dimensions. Of course, in other systems
 other rational exponents may be encountered.

 I am also assuming that the CGS system would not be employed when
 working with temperature, amount or luminosity. This is evident in
 the below type signatures where I have assumed zero extent in the
 temperature, amount and luminosity dimensions. If this is incorrect
 I would appreciate pointers to the CGS representation of these
 dimensions.

 Please correct and inform me if my assumptions are wrong!


 = Preliminaries =

  {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}

  module Buckwalter.Dimensional.CGS where

  import Prelude ( undefined, Num, Fractional, Floating, Show, recip, Double )
  import qualified Prelude
  import Buckwalter.Dimensional hiding ( DLength, DMass, DTime,
DElectricCurrent )
  import Buckwalter.Dimensional.Quantities as SIQ
  import qualified Buckwalter.Dimensional.SIUnits as SI
  import qualified Buckwalter.NumType as N
  import Buckwalter.NumType ( Neg2, Neg1, Zero, Pos, Pos1, Pos2,
Pos3, NumType )
  import Buckwalter.NumType ( neg2, neg1, zero, pos1, pos2, pos3 )
  import Data.Maybe (catMaybes)


 = Dimensions =

 Analogously with the SI we collect the base dimensions of the CGS
 system in the data type 'CGSDim'.

  data CGSDim lh mh t

 In the above 'lh' and 'mh' represent the number of half-exponents
 of length and mass respectively while 't' represents the number of
 whole-exponents. The base dimensions illustrate this.

  type DLength = CGSDim Pos2 Zero Zero
  type DMass   = CGSDim Zero Pos2 Zero
  type DTime   = CGSDim Zero Zero Pos1

 We add a few non-base dimensions for the sake of example. Charge
 is particularly interesting as it illustrates the need for
 half-exponents as described in [2].

  type DElectricCurrent = CGSDim Pos3 Pos1 Neg2
  type DCharge = CGSDim Pos3 Pos1 Neg1


 = 'Mul', 'Div', 'Pow' and 'Root' instances =

 The 'Mul', 'Div', 'Pow' and 'Root' instances are strictly analogous
 with the SI.

  instance ( N.Sum lh lh' lh''
   , N.Sum mh mh' mh''
   , N.Sum t  t'  t'' ) = Mul (CGSDim lh   mh   t)
   (CGSDim lh'  mh'  t')
   (CGSDim lh'' mh'' t'')

  instance ( N.Sum lh lh' lh''
   , N.Sum mh mh' mh''
   , N.Sum t  t'  t'' ) = Div (CGSDim lh'' mh'' t'')
   (CGSDim lh'  mh'  t')
   (CGSDim lh   mh   t)

  instance ( N.Mul lh x lh'
 

Re: [Haskell-cafe] ANNOUNCE: Dimensional 0.6 -- Statically checked physical dimensions

2007-08-02 Thread Björn Buckwalter
David Roundy wrote:

 On Thu, Aug 02, 2007 at 10:27:47PM +0200, Björn Buckwalter wrote:
   I am also assuming that the CGS system would not be employed when
   working with temperature, amount or luminosity. This is evident in
   the below type signatures where I have assumed zero extent in the
   temperature, amount and luminosity dimensions. If this is incorrect
   I would appreciate pointers to the CGS representation of these
   dimensions.
 
   Please correct and inform me if my assumptions are wrong!

 The temperature units are the same in CGS as in MKS (Kelvin).

Which implies that CGS is applicable to temperatures... what is the
(conventional) dimension of temperature in CGS? Is it the same as for
Energy (L^2 M^1 T^-2)?


   This is a very rudimentary implementation. To make it more practical
   a significant number of quantities and units, in particularly those
   commonly used with the CGS, would need to be added. In the mean
   time all units defined for the SI can be used with the CGS by
   applying 'fromSI' to quantities defined from the SI units.
 
   If anyone is willing to add quantities/units (or other enhancements)
   I will happily to accept patches. Personally I do not expect to use
   this module and therefore do not intend to invest much more time
   in it. If the module has other users I might reconsider.
 
   And of course, another direction of future work is to define
   additional systems (e.g. natural, relativistic) using this module
   as a template. I imagine this should be fairly straight forward.

 When atomic units are implemented, this could be useful for me... but alas
 I very seldom use Haskell for physics, and the effort to learn these
 modules seems unlikely to pay off soon.  :(

Learning to use the modules should require little effort. Learning
enough to implement the atomic system of units would require
significant effort though. Unfortunately I don't see myself
implementing atomic units, at lease not anytime soon.

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


[Haskell-cafe] ANNOUNCE: Dimensional 0.4 -- Statically checked physical dimensions

2007-05-16 Thread Björn Buckwalter

Dear all,

I am pleased to announce version 0.4 of Dimensional (working name).

Dimensional is a library providing data types for performing
arithmetic with physical quantities and units. Information about the
physical dimensions of the quantities/units is embedded in their types
and the validity of operations is verified by the type checker at
compile time. The boxing and unboxing of numerical values as
quantities is done by multiplication and division with units.

The library is designed to, as far as is practical, enforce/encourage
best practices [1] of unit usage.

Since the previous formal announcement [2] (version 0.1) Dimensional
has gone through several structural and stylistic improvements but
usage remains fundamentally unchanged. Noteworthy changes are a vastly
solidified 'NumType' module, a complete(?) set of elementary functions
and a 'Prelude'-replacement for users' convenience. There is also an
experimental 'Extensible' module supporting user-defined dimensions.

Additional structural changes and additions (primarily of units) are
planned and the library will continue to have an unstable API until
the 1.0 release. However, apart from module reshuffling no changes are
anticipated that would break user code.

Additional information and code is available from the project web site [3].

Thank you,
Bjorn Buckwalter


[1] http://physics.nist.gov/Pubs/SP811/
[2] http://www.haskell.org/pipermail/haskell/2006-December/018993.html
[3] http://code.google.com/p/dimensional/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Safe forward-mode AD in Haskell?

2007-05-09 Thread Björn Buckwalter

 d :: Num a = (forall b. (Num b) = (a - b) - b - b) - a - a
 d f x = let (Bundle y y') = f lift (Bundle x 1) in y'

The key change is in the type of d, which now accepts a polymorphic
function on numbers, but passes in a lift function, which allows us to
pass in higher-level variables.  In one sense this function is ugly.  In
another sense, it's prettier, as you can now hide *all* of the Bundle data
in a differentiation module.


To summarize:

In my original version it is necessary to export 'd' and 'lift', which
both expose 'Bundle' through their type signatures (and 'lift' even
returns a 'Bundle', though how one could (ab)use it outside the
intended context of a 'd' escapes me).

In constrast, with your variation only 'd' need be exported and
everything else in the module (including 'Bundle) is completely
hidden. The cost is that functions must be conditioned before they
can be differentiated.

Thanks for your input!

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


[Haskell-cafe] Safe forward-mode AD in Haskell?

2007-05-08 Thread Björn Buckwalter

Dear all,





= Introduction =

In [1] Siskind and Pearlmutter expose the danger of perturbation
confusion in forward-mode automatic differentiation. In particular
they state:

   We discuss a potential problem with forward-mode AD common to
   many AD systems, including all attempts to integrate a forward-mode
   AD operator into Haskell.

This literate Haskell message shows how, using a type system extension
of the Glasgow Haskell Compiler[2] (GHC), we can statically guarantee
that perturbation confusion does not occur.


= Code =

The below code closely follows the Haskell code in the appendices
of [1]. It relies on GHC's arbitrary-rank polymorphism(?) extension
to Haskell 98.


{-# OPTIONS_GHC -fglasgow-exts #-}


In our definition of the 'Bundle' data type we add the phantom type
's', which will be the key to disambiguating between different
application of the 'd' operator.


data Bundle s a = Bundle a a



instance Num a = Show (Bundle s a) where
  showsPrec p (Bundle x x') = showsPrec p [x,x']



instance Num a = Eq (Bundle s a) where
  (Bundle x x') == (Bundle y y') = (x == y)



lift z = Bundle z 0



instance Num a = Num (Bundle s a) where
  (Bundle x x') + (Bundle y y') = Bundle (x + y) (x' + y')
  (Bundle x x') * (Bundle y y') = Bundle (x * y) (x * y' + x' * y)
  fromInteger z = lift (fromInteger z)



instance Fractional a = Fractional (Bundle s a) where
  fromRational z = lift (fromRational z)


We provide a type signature for 'd' where we existentially quantify
the phantom type 's' to prevent mixing of bundles from different
'd' operators.


d :: Num a = (forall s. Bundle s a - Bundle s a) - a - a
d f x = let (Bundle y y') = f (Bundle x 1) in y'


The extential quantification makes the definition

] constant_one' x = d (\y - x + y) 1

impossible since 'x' originates externally to the 'd' operator. GHC
rejects the definition with a Inferred type is less polymorphic
than expected. In order to pass the compiler the definition must
be changed to the corrected[1] version.


constant_one x = d (\y - (lift x) + y) 1
should_be_one_a = d (\x - x * (constant_one x)) 1
should_be_one_b = d (\x - x * 1 ) 1



violation_of_referential_transparency = should_be_one_a /= should_be_one_b



= References =

[1] http://www.bcl.hamilton.ie/~qobi/nesting/papers/ifl2005.pdf
[2] http://haskell.org/ghc/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Safe forward-mode AD in Haskell?

2007-05-08 Thread Björn Buckwalter

Oops, that went to soon.

My intention was to ask for comments from those who know better than
I. These corners of the type system are pretty unknown to me but I am
trying to learn from e.g. Oleg's array branding[1].

Anyway, please rip my exposition apart and expose my sure-to-be flawed
logic and terminology. ;)

Cheers,
Bjorn

[1] http://okmij.org/ftp/Haskell/eliminating-array-bound-check.lhs


On 5/8/07, Björn Buckwalter [EMAIL PROTECTED] wrote:

Dear all,





= Introduction =

In [1] Siskind and Pearlmutter expose the danger of perturbation
confusion in forward-mode automatic differentiation. In particular
they state:

We discuss a potential problem with forward-mode AD common to
many AD systems, including all attempts to integrate a forward-mode
AD operator into Haskell.

This literate Haskell message shows how, using a type system extension
of the Glasgow Haskell Compiler[2] (GHC), we can statically guarantee
that perturbation confusion does not occur.


= Code =

The below code closely follows the Haskell code in the appendices
of [1]. It relies on GHC's arbitrary-rank polymorphism(?) extension
to Haskell 98.

 {-# OPTIONS_GHC -fglasgow-exts #-}

In our definition of the 'Bundle' data type we add the phantom type
's', which will be the key to disambiguating between different
application of the 'd' operator.

 data Bundle s a = Bundle a a

 instance Num a = Show (Bundle s a) where
   showsPrec p (Bundle x x') = showsPrec p [x,x']

 instance Num a = Eq (Bundle s a) where
   (Bundle x x') == (Bundle y y') = (x == y)

 lift z = Bundle z 0

 instance Num a = Num (Bundle s a) where
   (Bundle x x') + (Bundle y y') = Bundle (x + y) (x' + y')
   (Bundle x x') * (Bundle y y') = Bundle (x * y) (x * y' + x' * y)
   fromInteger z = lift (fromInteger z)

 instance Fractional a = Fractional (Bundle s a) where
   fromRational z = lift (fromRational z)

We provide a type signature for 'd' where we existentially quantify
the phantom type 's' to prevent mixing of bundles from different
'd' operators.

 d :: Num a = (forall s. Bundle s a - Bundle s a) - a - a
 d f x = let (Bundle y y') = f (Bundle x 1) in y'

The extential quantification makes the definition

] constant_one' x = d (\y - x + y) 1

impossible since 'x' originates externally to the 'd' operator. GHC
rejects the definition with a Inferred type is less polymorphic
than expected. In order to pass the compiler the definition must
be changed to the corrected[1] version.

 constant_one x = d (\y - (lift x) + y) 1
 should_be_one_a = d (\x - x * (constant_one x)) 1
 should_be_one_b = d (\x - x * 1 ) 1

 violation_of_referential_transparency = should_be_one_a /= should_be_one_b


= References =

[1] http://www.bcl.hamilton.ie/~qobi/nesting/papers/ifl2005.pdf
[2] http://haskell.org/ghc/


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


[Haskell-cafe] Re: Haskell Weekly News: January 02, 2007

2007-01-28 Thread Björn Buckwalter

Henning Thielemann lemming at henning-thielemann.de writes:


On Tue, 2 Jan 2007, Donald Bruce Stewart wrote:

Dimensional: Statically checked physical dimensions. Björn Buckwalter
[4]announced version 0.1 of [5]Dimensional, a module for statically
checked physical dimensions. The module facilitates calculations with
physical quantities while statically preventing e.g. addition of
quantities with differing physical dimensions.

4. http://article.gmane.org/gmane.comp.lang.haskell.general/14691
5. http://code.google.com/p/dimensional/


Henning,

First, let me apologize for not answering earlier. I have been
reluctant to subscribe to the café due to the volume of messages.
Instead I tend to occasionally browse the archives. Needless to say
your questions eluded me until now. The same is true for Mike Gunter's
message[1] which I will respond to presently.



How is it related to this one:
  http://www.haskell.org/haskellwiki/Dimensionalized_numbers
?


I ashamedly admit that I am guilty of inventing my own wheel. I
haven't looked too closely at Aaron's code but I believe there are
some conceptual similarities. Regarding completeness user my library
supports all seven base dimensions while Aaron's library currently
supports only length and time (I believe it is meant as a proof of
concept (toy example in his own words) rather than a complete
library). My ambition is to provide a reasonably complete library.



It should certainly be mentioned on
  http://www.haskell.org/haskellwiki/Physical_units
  
http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics#Physical_units


I have added it to the above pages. Thanks,

Björn Buckwalter


[1] http://www.haskell.org/pipermail/haskell-cafe/2007-January/021069.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Extensible static checking of dimensions?

2007-01-28 Thread Björn Buckwalter

Mike Gunter m at ryangunter.com wrote:

| The very nice Buckwalter and Denney dimensional-numbers packages both
| work on a fixed set of base dimensions.  This is a significant
| restriction for me--I want to avoid adding apples to oranges as well
| as avoiding adding meters to grams.  Is it possible to have an
| extensible set of base dimensions?  If so, how usable can such a
| system be made?  Is it very much worse than a system with a fixed set
| of base dimensions?

Mike,

I apologize for not having replied to your message earlier, I have not
been subscribing to the café and only recently noticed your post in
the archives.

As for you question, please see the literate haskell module below. It
allows you to extend the set of SI base dimensions in
'Buckwalter.Dimensional' with an arbitrary number of extra dimensions.
My hope is that it lifts the significant restriction you saw
previously.

As for the usability of such a system, once you have set up the
dimensions relevant to your problem domain usage should be identical
to (and seamless with) the original base dimensions. You will have to
be the judge as to whether it is usable enough for you. I would
certainly appreciate comments on usability. In fact I would also be
interested to hear how you envision applying the functionality you
requested, regardless of this modules usefulness.

Also, I can't promise that the module is rock solid -- I haven't done
a whole lot of testing.

If you don't have the 'Buckwalter.NumTypes' and
'Buckwalter.Dimensional' modules already you can download the latest
tarball with all three modules from the project web site at:
http://code.google.com/p/dimensional/

Thanks,
Björn Buckwalter


~~ BEGIN 'Buckwalter/Dimensional/Extensible.lhs' ~~

Buckwalter.Dimensional.Extensible -- Extensible physical dimensions
Bjorn Buckwalter, [EMAIL PROTECTED]
License: BSD3


= Summary =

On January 3 Mike Gunter asked[1]:

| The very nice Buckwalter and Denney dimensional-numbers packages
| both work on a fixed set of base dimensions.  This is a significant
| restriction for me--I want to avoid adding apples to oranges as
| well as avoiding adding meters to grams.  Is it possible to have
| an extensible set of base dimensions?  If so, how usable can such
| a system be made?  Is it very much worse than a system with a fixed
| set of base dimensions?

In this module we facilitate the addition an arbitrary number of
extra dimensions to the seven base dimensions defined in
'Buckwalter.Dimensional'. A quantity or unit with one or more extra
dimensions will be referred to as an extended dimensional.


= Preliminaries =

Similarly with 'Buckwalter.Dimensional' this module requires GHC
6.6 or later.


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}



module Buckwalter.Dimensional.Extensible
  where



import Prelude hiding
  ((*), (/), (+), (-), (^), sqrt, negate, pi, sin, cos, exp)
import qualified Prelude as P ((*), sin, cos, exp)
import Buckwalter.NumType (NumType, Add, Sub, Halve, Negate, Zero, Pos1)
import Buckwalter.Dimensional hiding (square, cubic, sin, cos, exp)



= DExt, Apples and Oranges =

We define the datatype 'DExt' which we will use to increase the
number of dimensions from the seven SI base dimensions to an arbitrary
number of dimensions. We make 'DExt' an instance of 'Dims' allowing
us to use the 'Dimensional' type without change.


data (NumType n, Dims d) = DExt n d
instance Dims (DExt n d)


Using 'DExt' we can define type synonyms for extended dimensions
applicable to our problem domain. For exampel, Mike Gunter could
define the 'Apples' and 'Oranges' dimensions and the corresponding
quantities.

] type DApples  = DExt Pos1 (DExt Zero DOne)
] type DOranges = DExt Zero (DExt Pos1 DOne)

] type Apples   = Quantity DApples
] type Oranges  = Quantity DOranges

And while he was at it he could define corresponding units.

] apple  :: Num a = Unit DApples a
] apple  = Dimensional 1
] orange :: Num a = Unit DOranges a
] orange = Dimensional 1


= Arithmetic =

We get negation, addition and subtracton for free with extended
dimensionals. However, we will need instances of the 'Mul', 'Div'
and 'Sqrt' classes for the corresponding operations to work.


instance (Add n n' n'', Mul d d' d'')
  = Mul (DExt n d) (DExt n' d') (DExt n'' d'')



instance (Sub n n' n'', Div d d' d'')
  = Div (DExt n d) (DExt n' d') (DExt n'' d'')



instance (Halve n n', Sqrt d d') = Sqrt (DExt n d) (DExt n' d')


Now, in order to work seamlessly with the quantities and units
defined in 'Buckwalter.Dimensional' we must be able to automatically
extend their dimensions when multiplying or dividing by an extended
dimensional.


instance (Mul d (Dim l m t i th n j) d') = Mul (DExt x d)
(Dim l m t i th n j)
(DExt x d')
instance (Mul (Dim l m t i th n j) d d') = Mul (Dim l m t i th n j