Re: [Haskell-cafe] Mathematics and Statistics libraries

2012-03-27 Thread Vivian McPhail
Date: Sun, 25 Mar 2012 17:54:11 +0400

 From: Aleksey Khudyakov alexey.sklad...@gmail.com
 Subject: Re: [Haskell-cafe] Mathematics and Statistics libraries
 To: haskell-cafe@haskell.org
 Message-ID: 4f6f2383.6070...@gmail.com
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed

 On 25.03.2012 14:52, Tom Doris wrote:
  Hi Heinrich,

 And of course data visualization. Only library I know of is Chart[1] but
 I don't like API much.


There is the plot[1] library which provides for updateable plots from GHCi
REPL and has a gnuplot-like interface.  I wrote it for this very reason, a
mathematics/statistics development environment.

It uses Data.Vector.Storable, which provides for compatability with both
statistics and hmatrix packages (as well as hstatistics).


 I think talking about data frames is a bit pointless unless we specify
 what is data frame. Basically there are two representations of tabular
 data structure: array of tuples or tuple of arrays. If you want first go
 for Data.Vector.Vector YourData. If you want second you'll probably end
 up with some HList-like data structure to hold arrays.

 Matrices from hmatrix are easily converted to rows or columns of
Data.Vector.Storable and can be sliced and otherwise manipulated.


 [1] 
http://hackage.haskell.org/package/plot%20%20[1]%20http://hackage.haskell.org/package/plot

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


Re: [Haskell-cafe] Cabal license combinations

2011-02-09 Thread Vivian McPhail
  It seems then that a package should be the least restrictive
  combination of all the licenses in all the contained modules.

 Omit the words least restrictive and I think you are correct.

 To combine licences, just aggregate them.  There is no lattice of
 subsumption; no more or less restrictive ordering.


I was thinking that the lattice was already flattened into a list of
licences.  Currently the top-level package has a single licence field which
is an arbitrary disjunctive choice.  Much better is a conjunctive
aggregation which is just as or less restrictive than the arbitrary
disjunctive choice.

Cheers,

Vivian

P.S. OK := acknowledge [ACK]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal license combinations

2011-02-08 Thread Vivian McPhail
 On Mon, 2011-02-07 at 14:42 +, Malcolm Wallace wrote:
   It seems then that a package should be the least restrictive
   combination of all the licenses in all the contained modules.
 
  Omit the words least restrictive and I think you are correct.


OK.


 
  To combine licences, just aggregate them.  There is no lattice of
  subsumption; no more or less restrictive ordering.  It's simple:
  you must obey all of them.  Some aggregations introduce a
  contradiction of terms, so you cannot legally aggregate those modules
  without breaking some term.  But if the terms of the aggregated
  licences are compatible rather than contradictory, then all is good.

 Right, so the effect of per-file/mixed licenses could be achieved by
 letting packages specify a list of licenses:

 license: Foo, Bar


Could this be computed automatically from the source files by Cabal?



 Meaning you may copy/distribute provided you comply with all these
 licenses.

 Note that this does not cover dual licensing, e.g. Foo or Bar at
 distributor's choice.

 Duncan


Looking specifically at hmatrix, there are three kinds of modules

   i) bindings to GSLGPL
   ii) bindings to LAPACK BSD
   iii) pure Haskellhmatrix author's choice

1) Am I correct in thinking that even the bindings modules (the Haskell
parts, not the C files) can be under any licence, FOO, chosen by the author,
but the binary _linked_ to, say, GSL has to comply with FOO and GPL?

2) If someone uses hmatrix but no GSL functions (hence there are no GSL
functions in the linked binary) can they get away with not complying with
the GSL requirement?

Cheers,

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


[Haskell-cafe] Cabal license combinations

2011-02-07 Thread Vivian McPhail
Dear All,

There was recently a discussion on haskell-cafe (
http://www.mail-archive.com/haskell-cafe@haskell.org/msg86472.html) about
licenses of libraries such as hmatrix and the combination of various
different licences.

One question was about per-package versus by-file licenses:

In Haskell the compilation unit is the module, and the per-file cabal header
allows for a license field.  It seems then that a package should be the
least restrictive combination of all the licenses in all the contained
modules.  If this has to become a hand-coded fancy function of various GPLx,
BSDy, OpenSource, and other licenses then so be it.  That is the legal
reality.  And use of a BSD3 module in hmatrix that does not depend upon
GPL'd GSL modules would be acceptable.

In short, I argue for a per-file(module) license regime.

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


Re: [Haskell-cafe] GPL License of H-Matrix and prelude numeric

2011-01-25 Thread Vivian McPhail
Hi,

 On Wed, 2011-01-26 at 08:18 +1000, Ivan Lazar Miljenovic wrote:
  Or else because the developers _wanted_ to license it under the GPL.
  Some people do, you know.

 Sure, but I agree it would be nice to know whether the authors chose the
 GPL, or applied it because of linking with GPLed native libraries and
 might be open to relicensing the native stuff.  Seems like a good
 question to me.

 --
 Chris Smith

hmatrix contains a binding to (i) the GNU GSL library (for fast vector
optimisations) and (ii) BLAS/LAPACK (for linear algebra).

The GNU GSL library _requires_ a LGPL license.

In the short term I do not think this can change.

In the longer term, once dph and friends are working well and performance is
optimised (dph can do fast linear algebra), the reliance on GSL and LAPACK
might be removed.

The hmatrix package can be configured to use Data.Vector.Storable of the
vector package, and there is work being done on improving fast vector
operations in that package.  As far as I know, the vector package is _not_
intending to supply mathematical operations.

Alberto?

Cheers,

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


Re: [Haskell-cafe] hmatrix's fitModel function crashes ghc(i)

2010-11-07 Thread Vivian McPhail
On 7 November 2010 15:19, Vivian McPhail
haskell.vivian.mcph...@gmail.comwrote:


 Message: 29
 Date: Sat, 6 Nov 2010 13:22:10 +0100
 From: Roel van Dijk vandijk.r...@gmail.com
 Subject: [Haskell-cafe] hmatrix's fitModel function crashes ghc(i)
 To: Haskell Caf? haskell-cafe@haskell.org
 Message-ID:
aanlktim5egsl_bz+ruv-=d-z3db65sc8o=ckqltcy...@mail.gmail.com
 Content-Type: text/plain; charset=UTF-8

 Hello,

 I would like to use hmatrix to do some function fitting with the
 Levenberg Marquardt algorithm. As an example I would like to fit the
 very simple function f x = a*x + b on some data points. The problem
 is that executing the 'fitModel' function crashes GHC(i) with a
 segmentation fault. This makes debugging difficult. Can anyone spot
 what I am doing wrong? Given all the lists of Double's it seems very
 easy to make an error regarding the number of arguments with the model
 function or the derivative.


 I think the problem is with linking static data in GHCi on x86_64.

 Hope this helps.  I seem to recall there might be a ghc trac ticket related
 to this but a quick search turned up nothing.

 Here's the ticket:

http://hackage.haskell.org/trac/ghc/ticket/781

They aim to fix the problem (with fPIC) by ghc 7.2.

Cheers,

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


[Haskell-cafe] hmatrix's fitModel function crashes ghc(i)

2010-11-06 Thread Vivian McPhail
 Message: 29
 Date: Sat, 6 Nov 2010 13:22:10 +0100
 From: Roel van Dijk vandijk.r...@gmail.com
 Subject: [Haskell-cafe] hmatrix's fitModel function crashes ghc(i)
 To: Haskell Caf? haskell-cafe@haskell.org
 Message-ID:
aanlktim5egsl_bz+ruv-=d-z3db65sc8o=ckqltcy...@mail.gmail.com
 Content-Type: text/plain; charset=UTF-8

 Hello,

 I would like to use hmatrix to do some function fitting with the
 Levenberg Marquardt algorithm. As an example I would like to fit the
 very simple function f x = a*x + b on some data points. The problem
 is that executing the 'fitModel' function crashes GHC(i) with a
 segmentation fault. This makes debugging difficult. Can anyone spot
 what I am doing wrong? Given all the lists of Double's it seems very
 easy to make an error regarding the number of arguments with the model
 function or the derivative.

 Try to evaluate the 'test' function in the small program listed below.
 I would expect an output of [1, 0] (y = 1*x + 0) instead of a
 segmentation fault.

 Relevant versions:
  - hmatrix-0.10.0.0
  - gsl-1.14
  - ghc-6.12.3 (64 bit)


Is that the 64 bit Linux ghc?

I think the problem is with the GSL random number generation through GHCi.

Try:

 module Test where

 Import Numeric.Container(RandDist,randomVector)

 seed = 0
 size = 100

 main = putStrLn $ show $ randomVector seed Gaussian size

This should work when compiled with `ghc --make` and crash when invoked in
`ghci`.

I think the problem is with linking static data in GHCi on x86_64.

Hope this helps.  I seem to recall there might be a ghc trac ticket related
to this but a quick search turned up nothing.

Cheers,

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


RE: [Haskell-cafe] Candlestick charts

2010-09-30 Thread Vivian McPhail
 Hi

Message-ID: aanlktinrozniqf4+ykxofho0fb=3b_7tfdux=vvbg...@mail.gmail.com

Hi -

What are the libraries to use in Haskell to generate a stock
candlestick chart like
http://stockcharts.com/h-sc/ui?s=SPYp=Db=5g=5id=p05007254056http://stockcharts.com/h-sc/ui?s=SPYp=Db=5g=5id=p05007254056

I will use Finance-Quote-Yahoo to get the quote data from Yahoo.

thanks for all your help.

The plot 0.1.1 package supports candle and whisker charts.

http://hackage.haskell.org/plot

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


[Haskell-cafe] Why Mathematical Soundness Matters.

2007-04-20 Thread Vivian McPhail

Hi All,

This is in regard to previous posts about mathematical preludes.


class Set a

class (Set s) = SemiGroup s o where
semigroup_op :: o - (s,s) - s
-- closure
-- associative

class (SemiGroup s o) = Monoid s o where
   identity :: o - s

class (Monoid s o) = Group s o where
inverse :: o - s - s

class Optimisable a where
   cost :: Set b = a - b


First, consider a semigroup, which is a set with an associative operation.
Into this structure falls Matrices with multiplication.  There is scope for
optimisation of a series of multiplications.  Inductively for each m1 * m2 *
m3 compare the cost of m1 * m2 versus m2 * m3 which can be simply obtained
from the size of the index of the matrix.  Thus expressions like (14,3) x
(3,15) x (15,2) can be computed as (14,3) x ((3,15) x (15,2)) and not in a
more expensive way.

Furthermore, if we tag identities with a phantom type, we can eliminate
needless operations like 3 + 0.

Not as much optimisation can be achieved with inverses (3 + -3) because it
might be just as expensive to calculate that something is an inverse as to
do actual calculation.

So how can this optimisation be performed?   Well this is a question that I
put forward to you, Gentle Reader.

Static:

It seems to me that expressions the types of which are known at compile-time
can be optimised by using type-level programming in combination with
compiler rewrite rules, e.g. if we have a type class SizeLarger then  the
expression


semigroup_op (semigroup_op m1 m2) m3


can be rewritten as


semigroup_op m1 (semigroup_op m2 m3)


depending upon the SizeLarger types of the various (semigroup_op _ _)
function calls.

Another method is to manipulate the expressions as ASTs and convert to the
concrete using TH.

But what about dynamic data?

Dynamic:

These are terms whose types are not known until run-time (such as would
happen when loading an arbitrary matrix from a file).  In this case we can't
use compiler term-rewriting or TH, but what options are there?  Depending
upon the speed/complexity of type-checking versus computation would it not
be feasible to use run-time type checking (a polymorphic Dynamic type) to
achieve this optimisation?  Yes there is a lot to said in favour of static
type-checking, but there are cases in which it is not feasible, witness
type-level bounds checking of run-time loaded matrices of unknown shape.  In
a program that used run-time typechecking (yes there would be a
computational overhead) the dynamic stuff would be isolated from the
'trusted' statically checked program and values could only be injected
through trusted entry points (e.g. get4SquareDoubleMatrix :: Dynamic - IO
(Array ((D4 $ Sz),(D4 $ Sz)) Double).

In any case, writing 'simple' arithmetic expressions would become more
cumbersome because of the overhead of annotating types and possibly moving
between ASTs and the concrete.  But if we a had collection of mathematically
sound classes like SemiGroup, Monoid, Group, Field, etc... then these
optimisations could be built into the compiler and we could sugar the
programmer-side just as it has been for Monads.

In conclusion,  I put this forward as a reason for Mathematically Meaningful
Numeric Classes and in obiter I am putting forward support for polymorphic
Dynamic types (run-time typechecking).

Cheers,

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


[Haskell-cafe] Type level programming to eliminate array bound checking, a real world use

2007-04-10 Thread Vivian McPhail

Hi All,Inspired by Oleg's Eliminating Array Bound Checking through
Non-dependent types  http://okmij.org/ftp/Haskell/types.html#branding,I am
attempting to write code that will receive an array from C land and convert
it to a type safe representation.  The array could have n dimensions where n

2.  I receive the number of dimensions as a list of Ints [Int].  To do

type-safe programming I need to convert this to a type level
representation.  Using CPS (thanks to ski on #haskell) I can convert an Int
to the type level.  But I have found it impossible to insert this type-level
Digits representation into an HList.

In Oleg's examples with vectors he types in by hand the data whose type
represents the size of the vector:

sample_v = listVec (D2 Sz) [True,False]

where (D2 Sz) is the size of the vector and the type is:

ArbPrecDecT :t sample_v
Vec (D2 Sz) Bool

In a real program we can't expect the programmer to type in the size of the
data, it needs to be done programmatically, and this is where I am stuck.

Could someone please point me in the right direction, or explain why what
I'm trying to do won't work?  Basically I'm looking for a function
int2typelevel :: (HList l) :: [Int] - l

I thought that this would work because HLists can have elements of different
types and I can already (modulo CPS) convert an Int to it's Digits type
level representation.

One approach which won't work is existentially wrapping the result of
num2digits in a GADT, because this hides the type from the type-checker and
then can't be used for bounds checking.

Here is an example of what I want to be able to do:

add :: Equal size1 size2 = Array size1 idx - Array size2 idx - Array
size1 idx

for example:

data Array size idx = Array size (MArray idx Double)

add (Array (DCons (D1 (D2 Sz)) (DCons (D3 Sz) DNil)) (12,3)) (Array (DCons
(D1 (D2 Sz)) (DCons (D3 Sz) DNil)) (12,3))

the sizes are statically checked and I don't have to do runtime checking on
the idx.

This message is a literate source file.  The commented out function at the
end illustrates the problem.

Thanks,

Vivian


{-# OPTIONS -fglasgow-exts #-}

-- copied from http://okmij.org/ftp/Haskell/number-parameterized-types.html

module Digits where

data D0 a = D0 a deriving(Eq,Read,Show)
data D1 a = D1 a deriving(Eq,Read,Show)
data D2 a = D2 a deriving(Eq,Read,Show)
data D3 a = D3 a deriving(Eq,Read,Show)
data D4 a = D4 a deriving(Eq,Read,Show)
data D5 a = D5 a deriving(Eq,Read,Show)
data D6 a = D6 a deriving(Eq,Read,Show)
data D7 a = D7 a deriving(Eq,Read,Show)
data D8 a = D8 a deriving(Eq,Read,Show)
data D9 a = D9 a deriving(Eq,Read,Show)

class Digits ds where-- class of digit sequences
   ds2num:: (Num a) = ds - a - a -- CPS style

data Sz = Sz-- zero size (or the Nil of the sequence)
 deriving(Eq,Read,Show)

instance Digits Sz where
   ds2num _ acc = acc

instance (Digits ds) = Digits (D0 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc)
instance (Digits ds) = Digits (D1 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 1)
instance (Digits ds) = Digits (D2 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 2)
instance (Digits ds) = Digits (D3 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 3)
instance (Digits ds) = Digits (D4 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 4)
instance (Digits ds) = Digits (D5 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 5)
instance (Digits ds) = Digits (D6 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 6)
instance (Digits ds) = Digits (D7 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 7)
instance (Digits ds) = Digits (D8 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 8)
instance (Digits ds) = Digits (D9 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 9)

t22::(f x)   - x; t22 = undefined

-- Class of non-negative numbers
-- This is a restriction on Digits. It is not possible to make
-- such a restriction in SML.
class {- (Digits c) = -} Card c where
   c2num:: (Num a) = c - a

instance Card Sz where c2num c = ds2num c 0
--instance (NonZeroDigit d,Digits (d ds)) = Card (Sz (d ds)) where
instance (Digits ds) = Card (D1 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D2 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D3 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D4 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D5 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D6 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D7 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D8 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D9 ds) where c2num c = ds2num c 0

-- Support for generic cards
-- We introduce a data constructor CardC_unused merely for the sake of
-- Haskell98. With the GHC extension, we can simply omit the data
-- constructor and keep the type CardC purely abstract and phantom.
data CardC c1 c2 = CardC_unused

cardc:: 

Re: [Haskell-cafe] Why the Prelude must die

2007-03-24 Thread Vivian McPhail
I agree with Sven, but...

What I want to push is a 'mathematically sound' numeric prelude.  A proper
numerical prelude should have bona fide mathematical obects like groups,
rings, and fields underlying common numerical classes.  It would be edifying
to the student who discovered that the particular data type he is using is
an inhabitant of a known class and can thus take advantage of known
properties, presupplied as class methods.  Reasoning and communication about
programs, data types, and functions would be enhanced.

[Conjecture 1 (2007). Haskell Mathematical Prelude and Mathematicians] If
Haskell had a mathematically sound prelude then more mathematicians would
use Haskell.

Cheers,

Vivian

 
 Message: 1
 Date: Sat, 24 Mar 2007 17:56:11 +0100
 From: Sven Panne [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] Why the Prelude must die
 To: haskell-cafe@haskell.org
 Cc: [EMAIL PROTECTED]
 Message-ID: [EMAIL PROTECTED]
 Content-Type: text/plain;  charset=iso-8859-1
 
 On Saturday 24 March 2007 03:48, Stefan O'Rear wrote:
  1. Namespace pollution
 
  The Prelude uses many simple and obvious names.  Most 
 programs don't 
  use the whole Prelude, so names that aren't needed take up 
 namespace 
  with no benefit. [...]
 
 Even though I think that the current Prelude is far from 
 perfect, one should not forget that is a very solid 
 foundation of a common language: If one sees e.g. '(.)' or 
 'map', it is immediately clear to everybody what this means, 
 without having to scan through (perhaps long) import lists. 
 Of course one could hide some parts of the Prelude etc., but 
 I think in the long run this only leads to confusion. 
 Redefining common things, heavy use of tons of self-defined 
 operators etc. all make maintenance much harder.
 
 Try reading Lisp code with heavy use of macros or C++ code 
 with tons of overloadings. This is more like Sudoku solving 
 than anything else, because there is no common language 
 between the author and the reader anymore.
 
 And taking away the prelude is a little bit like taking away 
 'int', 'double', 'for', 'while' etc. from the C programmer...
 
  11. Committeeism
 
  Because the Prelude has such a wide audience, a strong committee 
  effect exists on any change to it.  This is the worst kind of 
  committeeism, and impedes real progress while polluting the Prelude 
  with little-used features such as fail in Monad (as opposed to
  MonadZero) and until.
 
 Depending on your viewpoint, you can see this as a plus. 
 Everybody agrees that finalizers are evil, but propose the 
 removal of that method from java.lang.Object to the Java people. :-)
 
 My proposal would be to incrementally improve the Prelude, 
 modularize it a bit more, fix the Num hierarchy, but 
 basically leave it as it is.
 
 Cheers,
S.
 
 

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


[Haskell-cafe] Re: Re: HS-Plugins 1.0 chokes on simple test, WinXP GHC-6.6 (Conal Elliott)

2007-03-18 Thread Vivian McPhail
Hi,

I just setup and installed hs-plugins from darcs on WinXP using ghc-6.6 and
MSYS.

The hs-plugin test suite all passes.

Can you send me something that generates your error and I'll have a look at
it.

Vivian

 Message: 2
 Date: Sat, 17 Mar 2007 18:06:12 -0700
 From: Conal Elliott [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] Re: HS-Plugins 1.0 chokes on simple test,
   WinXP GHC-6.6
 To: haskell-cafe@haskell.org, Donald Stewart [EMAIL PROTECTED]
 Message-ID:
   [EMAIL PROTECTED]
 Content-Type: text/plain; charset=iso-8859-1
 
 Glad to know, Ian.  Thanks.
 
 I'd sure love to have a working hs-plugins again, especially 
 in time to help with my ICFP submission.  I wouldn't begin to 
 know how to crack something like this bug.  Does anyone have 
 any ideas?
 
 Cheers,  - Conal
 
 
 On 3/17/07, Ian Lynagh [EMAIL PROTECTED] wrote:
 
  c:/ghc/ghc-6.6/HSbase.o: unknown symbol `_free'
 
  
   Don mentioned this is a known problem.  Is it on 
 anyone's todo list?
 
  Not mine.
 
 
 
 
 
 
 On 3/17/07, Ian Lynagh [EMAIL PROTECTED] wrote:
 
  On Fri, Mar 16, 2007 at 09:52:10PM -0700, Conal Elliott wrote:
   BTW, to get hs-plugins to build, I changed two lines in 
   hs-plugins/configure.
 
  As it happens, I sent Don a similar patch last night, so hopefully 
  it'll be fixed in darcs soon.
 
   First I tried tr -d '\n', but it didn't work, and I don't 
 know why.
 
  Because it's a \r you're trying to delete.
 
   On 3/16/07, Conal Elliott [EMAIL PROTECTED] wrote:
   
   I got hs-plugins to compile fine on  winxp, but now when 
 I run it I 
   get
  a
   crash with this message:
   
   c:/ghc/ghc-6.6/HSbase.o: unknown symbol `_free'
   
   Don mentioned this is a known problem.  Is it on 
 anyone's todo list?
 
  Not mine.
 
 
  Thanks
  Ian
 
 
 -- next part --
 An HTML attachment was scrubbed...
 URL: 
 http://www.haskell.org/pipermail/haskell-cafe/attachments/2007
 0317/1b021224/attachment-0001.htm
 
 --
 

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


[Haskell-cafe] Re: Why is type 'b' forced to be type 'm a' and not possibly 'm a - m a'

2006-09-20 Thread Vivian McPhail
 Vivian McPhail wrote:
class Forkable a where
fork :: String - a - a - a
 
  What I would like to be able to do is
  differentiate between Forkable (m a -
  b) and Forkable (function type - b).
 
 Have you tried this combination of instances?
 
 instance Forkable (IO a) where ...
 -- and similarly for all the concrete
 -- monad types you will use fork with
 
 instance (Forkable a, Forkable b) =
  Forkable (a - b) where ...
 
 Alternatively, since the fork function seems to be all about
 propagating a value (the String), would Control.Monad.Reader
 serve your purpose?

The value that gets 'forked' is not actually the string, it is the result of
a monadic computation.

 
 Regards,
 Tom
 

I have tried:

 instance Forkable (USM NRef) where...

Which is my Monad

The problem lies with 

 instance (Forkable a, Forkable b) = Forkable (a - b) where
 fork n a1 a2 a = fork n (a1 a) (a2 a)

because I need the arg a to be evaluated before it gets passed to a1 and a2.
This definition does the right thing when type 'a' is a function type,
because it is not a value, but with something like 'm a - (m a - m a) - m
a' with Forkable (a - b) the first arg gets evaluated twice, to be more
concrete:

With

(and golden white) eggs

I want the 'eggs' that is passed to 'golden' to be the same as the 'eggs'
that is passed to 'white', i.e.

- and1 (golden2 eggs3) (white4 eggs3) and not - and1 (golden2 eggs3)
(white4 eggs5)

So to do this I need to be able to recognise the case where the 'a' of (a -
b) is of type 'm a' so that I can evaluate it

-- doesn't typecheck
instance (Monad m, Forkable (m a), Forkable b) = Forkable (m a - b) where
fork n a1 a2 a = do
 a' - a
 fork n (a1 $ return a') (a2 $ return a')

Tom suggested that I might be able to use the Reader monad, but I'm not
clear as to how I could do this.

Cheers,

Vivian





-- 
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.405 / Virus Database: 268.12.5/451 - Release Date: 19/09/2006
 

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


[Haskell-cafe] Re: Why is type 'b' forced to be type 'm a' and not possibly 'm a - m a' (Anatoly Zaretsky)

2006-09-18 Thread Vivian McPhail
 Message: 6
 Date: Fri, 15 Sep 2006 18:36:35 +0300
 From: Anatoly Zaretsky [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] Why is type 'b' forced to be type 'm a'
   and not possibly 'm a - m a'
 To: Vivian McPhail [EMAIL PROTECTED]
 Cc: Haskell Cafe haskell-cafe@haskell.org
 Message-ID:
   [EMAIL PROTECTED]
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed
 
 On 9/15/06, Vivian McPhail [EMAIL PROTECTED] wrote:
 
  class Forkable a where
  fork :: String - a - a - a
 
  ...
  {-
  instance (Monad m, Forkable (m a), Forkable b) = Forkable (m a - b)
where
  fork n a1 a2 a = do
   a' - a
   fork n (a1 $ return a') (a2 $ return a')
  -}
 
 
 Let's do manual type checking.
 First, fork :: Forkable a = String - a - a - a
 So for Forkable (m a - b)
   fork :: String - (m a - b) - (m a - b) - m a - b
 Then
   fork n a1 a2 a :: b
 But you define it as
   fork n a1 a2 a = do {...}
 So it should be of type Monad t = t a, not just any `b'.
 
 Instead, you can define
   instance (Monad m, Forkable (m b)) = Forkable (m a - m b) where
 ...
 

Well, I can partially instantiate what I am trying to achieve by enumerating
cases.  Note that when the first type is a monadic type the computation gets
evaluated and then forked, but when the first type is a function it merely
gets passed.  My problem is that there are a very large number of possible
cases.  So in the case Forkable (m a - b), a number of instances of which I
can implement (e.g. Forkable (m a - m a - m a), Forkable ((m a - m a) -
m a), and Forkable (m a - (m a - m a) - m a)), I don't see why 'b' should
necessarily typecheck to 't t1'.

What I would like to be able to do is differentiate between Forkable (m a -
b) and Forkable (function type - b).

By the way, the following code typechecks and runs correctly, my problem is
that enumerating all possible types requires five factorial (120) different
instances, and to a lazy functional programmer who can 'see' the pattern it
seems that there must be a nicer way of achieving my end.

\begin{code}
instance (Monad m, Forkable (m a)) = Forkable (m a - m a) where
fork n a1 a2 a = do
 a' - a
 fork n (a1 $ return a') (a2 $ return a')

instance (Monad m, Forkable (m a)) = Forkable (m a - m a - m a) where
fork n a1 a2 a b = do
   a' - a
   fork n (a1 $ return a') (a2 $ return a') b

instance (Monad m, Forkable (m a)) = Forkable ((m a - m a) - m a) where
fork n a1 a2 a = do
 fork n (a1 a) (a2 a)

instance (Monad m, Forkable (m a)) = Forkable (m a - (m a - m a) - m a)
where
fork n a1 a2 a b = do
   a' - a
   fork n (a1 $ return a') (a2 $ return a') b

\end{code}

 Note that to compile it you also need -fallow-undecidable-instances
 and -fallow-overlapping-instances.
 
 --
 Tolik
 

Thanks for your help so far!



Cheers,

Vivian

-- 
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.405 / Virus Database: 268.12.4/449 - Release Date: 15/09/2006
 

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


[Haskell-cafe] Why is type 'b' forced to be type 'm a' and not possibly 'm a - m a'

2006-09-14 Thread Vivian McPhail





Dear Haskell 
Cafe,

I have a problem I can't get my head around. 
The 
code below sets the problem out. What I need to be able to do is commented 
out.

This code works, the 
only problem is that what I need is that an argument will be evaluated before it 
is passed,
so ((and fries eats) 
eggs) has a single `eggs`(fries1 eggs2 and3 eats4 egg2) not (fries1 eggs2 
and3 eats4 eggs5).

The code that 
doesn't work is commented out at the bottom. I'm not sure the 
behaviour of ghc is correct, because 
when 
it typechecks it tries to unify `b = t t1` 
but `b` could actually be `t t1 - t t1`.

I want to be able to 
specify that when the first argument of `b` is of type `m a` that fork should 
run it and _then_
fork the 
argument to the first two arguments of 'fork'. The instance for (a - b) covers the rest of 
the possibilities.

just type "run test[1-4]" to see 
results.

\begin{code}
{-# OPTIONS_GHC -fglasgow-exts 
-fno-monomorphism-restriction #-}

module Fork where

{-}

import Prelude hiding (and)

import Control.Monad.State

{-}

data NRef = NS0 
String | NS1 String 
NRef | NS2 String NRef 
NRef 
deriving(Show)

{-}

data UniqueS = US { nums :: [String] 
} deriving(Show)

type USM a = StateT UniqueS IO a

newUniqueS :: UniqueSnewUniqueS = US { nums = [ 
show x | x - [1..] ] }

freshInstance :: String - USM 
StringfreshInstance x = 
do 
(f:fs) - gets 
nums 
put $ US { nums = fs 
} 
return $ x ++ f

{-}

single x = do x' - 
freshInstance x return $ NS0 x'

unary x n = do x' - 
freshInstance x n' - n return $ 
NS1 x' n'

binary x n1 n2 = do x' - 
freshInstance x n1' - n1 n2' 
- n2 return $ NS2 x' n1' n2'

{-}

foxy = single "foxy"eggs = single 
"eggs"golden = unary "golden"white = unary "white"fries = binary 
"fries"eats = binary "eats"

{-}

class Forkable a where fork 
:: String - a - a - a

instance (Forkable a, Forkable b) = Forkable (a 
- b) where fork n a1 a2 a = fork n (a1 a) (a2 
a)

{-instance (Monad m, Forkable (m a), 
Forkable b) = Forkable (m a - b) where fork n a1 
a2 a = 
do 
a' - 
a 
fork n (a1$ return a') 
(a2$ return 
a')-}{-}

instance Forkable (USM NRef) 
where fork n a1 a2 = 
do 
a1' - 
a1 
a2' - 
a2 
return $ NS2 n a1' a2'

{-}

and = fork "and"

test1 = (and foxy eggs)test2 = (and golden 
white) eggstest3 = (and fries eats) foxy eggstest4 = (eats foxy (and 
(golden eggs) (white eggs))) 

run x = runStateT x newUniqueS = 
(putStrLn . show . fst)\end{code


--
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.405 / Virus Database: 268.12.4/448 - Release Date: 14/09/2006
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe