[Haskell-cafe] Re: (Lazy) SmallCheck and peano numbers

2008-06-20 Thread Benedikt Huber

Levi Stephen schrieb:

On Fri, Jun 20, 2008 at 3:30 AM, Benedikt Huber [EMAIL PROTECTED] wrote:

Levi Stephen schrieb:

Hi,

I have the following definitions

type Zero
type Succ a

so that I can muck around with a Vector type that includes its length
encoded in its type.

I was wondering whether it was possible to use SmallCheck (or
QuickCheck) to generate random Peano numbers? Is there an issue here
in that what I actually want to generate is a type rather than a
value?

I do have

reifyInt :: Int - (forall a. ReflectNum a = a - b) - b

but, I'm not sure if this can help me when I need to generate other
values based upon that type (e.g., two vectors with the same size
type)

Hi Levi,

For QuickCheck, I know it is possible as long as you do not need to use type
level functions in your tests. For example, using Alfonso's type-level and
parametrized-data packages, one can write:


instance (Nat n, Arbitrary a) = Arbitrary (FSVec n a) where
   arbitrary =
 liftM (unsafeVector (undefined :: n)) $
   mapM (const arbitrary) [1..toInt (undefined :: n)]
propLength :: forall n a. (Nat n) = FSVec n Integer - Bool
propLength (FSVec xs) = P.length xs == toInt (undefined :: n)
propLengthEqual :: forall n a. (Nat n) =
   FSVec n Integer - FSVec n Integer - Bool
propLengthEqual v1 v2 = length v1 == length v2
tests1 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
   quickCheck (propLength :: FSVec ty Integer - Bool)
tests2 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
   quickCheck (uncurry propLengthEqual ::
(FSVec ty Integer,FSVec ty Integer) - Bool)


Thanks for the example code. Ideally it would be great to have n generated also.


Generating n isn't hard, in IO above you could just use Random.
But I assume you want to use QuickCheck, so see below.


Any thoughts on whether something like

propLengthEqual :: forall n a. (Nat n) = n - FSVec n Integer -
FSVec n Integer - Bool
propLengthEqual _ v1 v 2 = length v1 == length v2

with an arbitrary instance for generate all Nat n's is possible?


propLengthEqual is exactly the same as propLength, I just left out the 
first argument (it is redundant).


You cannot use an `Arbitrary' instance to generate some type level 
number, at least not in the same way as for ordinary numbers.


What you can do is introduce an existential type

 data SomeNat = forall n. (Nat n) = SomeNat Int n
 instance Show SomeNat where show (SomeNat value typ) = show value

 instance Arbitrary SomeNat where
arbitrary = sized $ \n - reifyIntegral n (return . SomeNat n)


If you look into the QuickCheck source, you'll find that a property
is a result generator: newtype Property = Prop (Gen Result)

So a property can be written as a result generator:

 propLength' :: SomeNat - Gen Result
 propLength' (SomeNat vn (n :: t)) = do
(vector :: FSVec t Integer) - arbitrary
buildResult [show vn , show vec] $ propLength vector

--
What follows next is the neccessary boilerplate to have a working example

 buildResult :: [String] - Bool - Gen Result
 buildResult args b = evaluate b = \r -
return $ r { arguments = show args : arguments r}
 natProp :: (SomeNat - Gen Result) - Property
 natProp f = flip forAll id $ do
(k::Int) - choose (0,10)
n - resize k arbitrary
f n
 deriving instance Show Result


Finally, run the tests

 tests = verboseCheck (natProp propLength')

Hope that helps.


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


Re: [Haskell-cafe] This is a bug?

2008-06-20 Thread Malcolm Wallace

How I solve this issue when call readXml:

in score-partwise, In a sequence:
in part, In a sequence:
  in measure, Too many elements inside measure at
  file ../../../parsers/elite2.xml  at line 75 col 15
  Found excess:


So, your XML document contains a score-partwise, which contains a  
sequence of part, at least one of which contains a sequence of  
measure.  But the measure at line 75 does not match the declared  
DTD.  The non-conforming text appears to be pure whitespace, which  
does seem a little odd.  This could be a bug in the HaXml parser, but  
it is hard to know for sure without seeing both the DTD and the  
failing file.  Can you send them to me (not to the list)?


Regards,
Malcolm

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


Re: [Haskell-cafe] Haddock compilation problem

2008-06-20 Thread David Waern
2008/6/20 Ronald Guida [EMAIL PROTECTED]:
 I just upgraded to ghc-6.8.3, using a linux binary, and I am having a
 problem compiling Haddock.  Haddock 2.1.0 and Haddock 2.0.0.0 both
 fail to build under ghc-6.8.3, but they both build successfully with
 ghc-6.8.2.  I don't know if this is a Haddock problem, or a GHC
 problem, or perhaps something else entirely?

The current Haddock isn't compatible with GHC 6.8.3, but I think the
next release will be.

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


Re: [Haskell-cafe] Access to Oracle database from Haskell

2008-06-20 Thread Alistair Bayley
2008/6/20 Alistair Bayley [EMAIL PROTECTED]:
 Is there a way of accessing a remote Oracle database by one of the common
 Haskell database interfaces (HaskellDB, Takusen, etc.) ? I tried to get
 unixODBC and Oracle's Instant Client running on a Linux machine, but I'm
 trapped in the notorious error:

 Takusen's Oracle backend uses the Oracle Call Interface (OCI) library
 directly. I think most Oracle client drivers (ODBC, ADO.Net, etc) use
 the OCI. I don't know what the Oracle Instant Client is; I'll assume
 that it includes an oci.so or liboci.so. On Windows, with which I am
 most familiar, the Oracle client software is all installed in
 $ORACLE_HOME, and the OCI library is $ORACLE_HOME/bin/oci.dll. If you
 can locate that, then you ought to be able to use Takusen with it.

Having just taken a closer took at what Oracle Instant Client is, I
suspect that you might have some trouble getting Takusen to compile
against it. The Instant Client lacks header files, while Takusen's FFI
imports specify oci.h. I don't know what happens if ghc can't find the
header files. Oracle do state that the Instant Client is for
deployment only; developers (that means you) will need the full client
installation.

Another problem is that the Oracle installation process assumes that,
for all platforms, the library is called oci i.e. the linker option
-loci is used. For Unix clients, the OCI library seems to be
libclnstsh.so, so I guess it should pass -lclnstsh. This highlights
the lack of testing on non-Windows platforms. If you'd like to help
get this working better, perhaps we can discuss off-list.

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


Re: [Haskell-cafe] Lambda and closures in PHP -- could someone please comment?

2008-06-20 Thread Jules Bean

Derek Elkins wrote:

Lambda abstractions should close over bindings.  Full stop.


Interesting. I agree with your analysis. I don't think I agree with your 
conclusion.




The first surprising behaviour is the correct one.  The latter would
be broken.

In my opinion, the reason this behaviour is surprising isn't
mutability, but -implicit- mutability.  Let's make bindings immutable,
but add ML-style references to your example.

char ref c = ref(undefined);
while(!eof(fp)) {
c := getChar(fp);
bind_event( ... print !c; ... );
}

compare this to

while(!eof(fp)) {
char c = getChar(fp);
bind_event( ... print c; ...);
}

or

while(!eof(fp)) {
char ref c = ref(getChar(fp));
bind_event( ... print !c; ...);
}

Each of these examples makes it clearer what is going on. 


Agreed.

I think where I differ on you is how to map the semantics of a C-like 
language to explicit references.


I would argue that the glyph c in a C-like language denotes the value 
of C, not the reference to it. C-like languages have, for the most part, 
value semantics, and call-by-value.


The exception of course is what C-like languages called lvalues, but 
lvalues are only really on the left of the = sign and a few other 
special positions. I think that's the exception and not the rule. I 
think the rule is that c denotes the value of c, and that's why I 
expect a closure to capture the value, not the reference.


In C, of course, if you want to capture the reference you do it 
explicitly with c.


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


[Haskell-cafe] number-parameterized types and heterogeneous lists

2008-06-20 Thread Harald ROTTER

Dear Haskellers,

after reading Oleg Kiselyov's paper on number-parameterized types I started
to play around with
the class Digits that encodes decimal numbers in types. The typed number
10 would e.g. be defined as

  D1 $ D0 $ Sz

I wondered if it would be possible replace the expression above by a
heterogeneous list like

  [D1,D0]

so I tried to define

  data Digit = forall a b.(Digits a, Digits (b a)) = Digit (a - b a)

Loading this into ghci yields:

:t Digit D0

interactive:1:0:
Ambiguous type variable `a' in the constraint:
  `Digits a' arising from a use of `Digit' at interactive:1:0-7
Probable fix: add a type signature that fixes these type variable(s)

Removing the type constraints in the definition of Digit:

  data Digit = forall a b.Digit (a - b a)

makes it work like this:

  :t Digit D0
  Digit D0 :: Digit

  :t [Digit D0, Digit D1]
  [Digit D0, Digit D1] :: [Digit]

Digit, however, is far too general (it also includes e.g. \x - [x]), but
I would like it to be restricted to the Digit class.

Any help is appreciated.

Thanks

Harald.


CODE:

module Test where

data D0 a = D0 a
data D1 a = D1 a
data D2 a = D2 a
data D3 a = D3 a
data D4 a = D4 a
data D5 a = D5 a
data D6 a = D6 a
data D7 a = D7 a
data D8 a = D8 a
data D9 a = D9 a

class Digits ds where
d2num :: Num a = ds - a - a

data Sz = Sz-- zero size
instance Digits Sz where
d2num _ acc = acc

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

t22 :: f x - x
t22 = undefined

--data Digit = forall a b.(Digits a, Digits (b a)) = Digit (a - b a)
data Digit = forall a b.Digit (a - b a)

-



 Ce courriel et les documents qui y sont attaches peuvent contenir des 
informations confidentielles. Si vous n'etes  pas le destinataire escompte, 
merci d'en informer l'expediteur immediatement et de detruire ce courriel  
ainsi que tous les documents attaches de votre systeme informatique. Toute 
divulgation, distribution ou copie du present courriel et des documents 
attaches sans autorisation prealable de son emetteur est interdite. 

 This e-mail and any attached documents may contain confidential or 
proprietary information. If you are not the intended recipient, please advise 
the sender immediately and delete this e-mail and all attached documents from 
your computer system. Any unauthorised disclosure, distribution or copying 
hereof is prohibited.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] number-parameterized types and heterogeneous lists

2008-06-20 Thread Anton Tayanovskyy
Hi Harald,

Can you give a link to the paper? Interesting stuff. Thanks.

This is stretching my abilities a bit, but is this what you are after?

data Digit = forall b.(Digits (b Sz)) = Digit (Sz - b Sz)

instance Digits [Digit] where
d2num []   acc = acc
d2num (Digit x:xs) acc = d2num xs (10*acc + d2num (x Sz) 0)

I assumed you only want D0..D9 as digits, maybe this is too narrow.

I've put this up on hpaste:

http://hpaste.org/8437#a1



Bests,

Anton



On Fri, Jun 20, 2008 at 3:01 PM, Harald ROTTER [EMAIL PROTECTED] wrote:

 Dear Haskellers,

 after reading Oleg Kiselyov's paper on number-parameterized types I started
 to play around with
 the class Digits that encodes decimal numbers in types. The typed number
 10 would e.g. be defined as

  D1 $ D0 $ Sz

 I wondered if it would be possible replace the expression above by a
 heterogeneous list like

  [D1,D0]

 so I tried to define

  data Digit = forall a b.(Digits a, Digits (b a)) = Digit (a - b a)

 Loading this into ghci yields:

 :t Digit D0

 interactive:1:0:
Ambiguous type variable `a' in the constraint:
  `Digits a' arising from a use of `Digit' at interactive:1:0-7
Probable fix: add a type signature that fixes these type variable(s)

 Removing the type constraints in the definition of Digit:

  data Digit = forall a b.Digit (a - b a)

 makes it work like this:

  :t Digit D0
  Digit D0 :: Digit

  :t [Digit D0, Digit D1]
  [Digit D0, Digit D1] :: [Digit]

 Digit, however, is far too general (it also includes e.g. \x - [x]), but
 I would like it to be restricted to the Digit class.

 Any help is appreciated.

 Thanks

 Harald.


 CODE:

 module Test where

 data D0 a = D0 a
 data D1 a = D1 a
 data D2 a = D2 a
 data D3 a = D3 a
 data D4 a = D4 a
 data D5 a = D5 a
 data D6 a = D6 a
 data D7 a = D7 a
 data D8 a = D8 a
 data D9 a = D9 a

 class Digits ds where
d2num :: Num a = ds - a - a

 data Sz = Sz-- zero size
 instance Digits Sz where
d2num _ acc = acc

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

 t22 :: f x - x
 t22 = undefined

 --data Digit = forall a b.(Digits a, Digits (b a)) = Digit (a - b a)
 data Digit = forall a b.Digit (a - b a)

 -



  Ce courriel et les documents qui y sont attaches peuvent contenir des 
 informations confidentielles. Si vous n'etes  pas le destinataire escompte, 
 merci d'en informer l'expediteur immediatement et de detruire ce courriel  
 ainsi que tous les documents attaches de votre systeme informatique. Toute 
 divulgation, distribution ou copie du present courriel et des documents 
 attaches sans autorisation prealable de son emetteur est interdite.

  This e-mail and any attached documents may contain confidential or 
 proprietary information. If you are not the intended recipient, please advise 
 the sender immediately and delete this e-mail and all attached documents from 
 your computer system. Any unauthorised disclosure, distribution or copying 
 hereof is prohibited.
 ___
 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] Quantitative Trading Developer Position at Hutchin Hill Capital

2008-06-20 Thread Neil Mehra

Job Description:

Quantitative Trading Developer

Description:

* Newly formed multi-strategy hedge fund, Hutchin Hill Capital, located 
in midtown Manhattan, seeks a Quantitative Trading Developer;

* Focus on building infrastructure, applications, and technical support 
for quantitative equity trading business;

* Candidate should have demonstrated interest or passion for functional 
programming-with experience using Haskell, F#, Kdb+/q, OCaml, ML, and related 
technologies;

* Position reports directly to portfolio manager, and will work closely 
with other technology and research professionals.


Responsibilities Include:

 *   Developing data management, quant research, and analytical tools for 
model-driven equity trading strategies;
 *   Building production environment for real-time content capture, trade 
generation, and risk management;
 *   Deploying equity trading technology, methods, and protocols, including 
electronic execution algorithms and market impact analysis;
 *   Conducting quantitative portfolio research using cutting-edge tools and 
techniques.

Required Experience/Education:

 *   2 - 5 years in IT development or quantitative analytics;
 *   Advanced degree or equivalent experience in a technical field such as 
computer science, mathematics, physics, or engineering;

Other Requirements:

 *   Exceptional technical and analytical problem-solving;
 *   Desire to master the latest technology, hardware, and quantitative methods;
 *   Willingness to work in a fast-paced, high pressure environment;
 *   Team-oriented and highly resourceful;
 *   Entrepreneurial drive.

Please contact [EMAIL PROTECTED]mailto:[EMAIL PROTECTED] with resume if 
interested.



__
This communication, including any attachment(s), may contain confidential 
and/or privileged information. If you are not the intended recipient or have 
received this communication in error, please destroy/delete this email and any 
attachments. We do not waive confidentiality or privilege by mistransmission. 
This communication does not constitute an offer of employment, or an offer, or 
the solicitation of an offer, to buy or sell any security or investment 
advisory services, and is not an official confirmation of any transaction.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HDBC converting a date sql value to UTCTime

2008-06-20 Thread George Moschovitis
Alternatively is there a way to create a UTCTime value from an epoch integer
(no of seconds since epoch).
I can't find a suitable constructor with Hoogle.

thank you in advance,
George.


On Thu, Jun 19, 2008 at 10:08 PM, George Moschovitis 
[EMAIL PROTECTED] wrote:

 Hello,

 I am HDBC with the Postgres driver. I am trying to read a simple date
 column from the DB:

 stmt - DB.prepare conn SELECT date FROM my_table ORDER BY date DESC LIMIT
 1
 DB.execute stmt []
 DB.commit conn
 rows - fetchAllRows' stmt
 let ((d:_):_) = rows

 the d variable is of type:

 SqlEpochTime 1213736400

 I am wondering how to convert this value to an UTCTime value.

 Any help appreciated (I am a newbie).

 -g.



 --
 http://gmosx.me.gr
 http://joy.gr
 http://cull.gr
 http://nitroproject.org
 http://phidz.com
 http://joyerz.com




-- 
Walt Disney  - I love Mickey Mouse more than any woman I have ever known.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Checking packages before upload to Hackage

2008-06-20 Thread Henning Thielemann


Is there some command which tests a tar.gz created by 'Setup.lhs sdist' by 
unpacking the archive to say /tmp and compiling and documenting the 
sources? Hackage should recommend this tool before package upload.

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


Re: [Haskell-cafe] Checking packages before upload to Hackage

2008-06-20 Thread Gwern Branwen
On Fri, Jun 20, 2008 at 11:43 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 Is there some command which tests a tar.gz created by 'Setup.lhs sdist' by
 unpacking the archive to say /tmp and compiling and documenting the sources?
 Hackage should recommend this tool before package upload.

There isn't. However, I do have some shell scripts which I use to the
same effect. They go like this:

function rh { nice runhaskell Setup $@ --verbose; }
function build { rh build $@; }
function build_clean { rh clean  rh build $@; }
function build_sdist { clean_configure  sdist 
cd dist/  untar *.tar.gz  cd `ls -t ./ | grep / | head -n 1` 
clean_configure  build  hinstall; haddock  hinstall; }
function clean { rh clean $@; }
function clean_configure { clean  configure; }
function configurenop { rh configure --enable-split-objs --user
--prefix=$HOME/bin $@; }
function configure { configurenop --enable-executable-profiling -p  $@; }
function haddock { rh haddock --executables $@; }
function hinstall { rh install --user $@; }
function sdist { rh sdist $@; }
function haskell { ( http_proxy= pull )  clean_configure  (build_sdist)  }

(Obviously you would either run 'haskell' or 'build_sdist' to test things out.)

If you're interested in a Haskell solution, there is an open Cabal bug
for this: http://hackage.haskell.org/trac/hackage/ticket/274.

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


Re: [Haskell-cafe] Checking packages before upload to Hackage

2008-06-20 Thread Duncan Coutts

On Fri, 2008-06-20 at 12:12 -0400, Gwern Branwen wrote:
 On Fri, Jun 20, 2008 at 11:43 AM, Henning Thielemann
 [EMAIL PROTECTED] wrote:
 
  Is there some command which tests a tar.gz created by 'Setup.lhs sdist' by
  unpacking the archive to say /tmp and compiling and documenting the sources?
  Hackage should recommend this tool before package upload.

 If you're interested in a Haskell solution, there is an open Cabal bug
 for this: http://hackage.haskell.org/trac/hackage/ticket/274.

This would indeed be a very useful feature.

If anyone wants to have a go at implementing it that would be great.
They can ask on cabal-devel for pointers and advice.

Duncan

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Well, Achim you were almost exactly correct.  I have a functional function
interface in about half an hour's worth of work.  I have one question, which
is how to create a Ptr to four CFloats on the fly, pass them to the bounding
box functions, and then come back out with a [Float]

My prototype looks like this:
foreign import ccall unsafe ftglGetFontBBox fgetFontBBox :: Font -
CString - Ptr CFloat - IO ()

the ptr to cfloat should be a float[4], which is modified inside the
original C function.

On Fri, Jun 20, 2008 at 1:16 AM, Achim Schneider [EMAIL PROTECTED] wrote:

 Jefferson Heard [EMAIL PROTECTED] wrote:

  I've been looking for awhile now for a simple way to get truetype
  fonts into my visualizations so I can abandon the hideous GLUT fonts
  and make things that look like they were developed in the 1990s
  instead of back in the days of TRON.  I found FTGL, but I'm mostly a
  Haskell developer these days, and resent having to go back to C just
  to write a simple application.
 
  So I was wondering if anyone had ever wrapped the FTGL library in
  Haskel FFI or whether those out there who are experts on the FFI
  think at first glance it should be readily wrappable by a rank
  amateur at FFI such as myself.
 
  http://ftgl.sourceforge.net/docs/html/
 
 Using the FFI is generally straight forward, as long as you can live
 with using the IO monad and the C code uses objects (well,
 pointers to structs passed as first argument, where's the
 difference...).

 Things only depend on the purity of the C code and how high-level you
 want your interface to be. In this case, I estimate half an hour if
 you're a fast typist. That includes the time needed to read the FFI
 docs.

 --
 (c) this sig last receiving data processing entity. Inspect headers for
 past copyright information. All rights reserved. Unauthorised copying,
 hiring, renting, public performance and/or broadcasting of this
 signature prohibited.

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




-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Oh, and I should say the function I want to implement is

getFontBBox :: Font - String - IO [Float]

I do know how to marhsal/unmarshal the String.  Just not the CFloat array to
Haskell [Float]

On Fri, Jun 20, 2008 at 2:25 PM, Jefferson Heard 
[EMAIL PROTECTED] wrote:

 Well, Achim you were almost exactly correct.  I have a functional function
 interface in about half an hour's worth of work.  I have one question, which
 is how to create a Ptr to four CFloats on the fly, pass them to the bounding
 box functions, and then come back out with a [Float]

 My prototype looks like this:
 foreign import ccall unsafe ftglGetFontBBox fgetFontBBox :: Font -
 CString - Ptr CFloat - IO ()

 the ptr to cfloat should be a float[4], which is modified inside the
 original C function.


 On Fri, Jun 20, 2008 at 1:16 AM, Achim Schneider [EMAIL PROTECTED] wrote:

 Jefferson Heard [EMAIL PROTECTED] wrote:

  I've been looking for awhile now for a simple way to get truetype
  fonts into my visualizations so I can abandon the hideous GLUT fonts
  and make things that look like they were developed in the 1990s
  instead of back in the days of TRON.  I found FTGL, but I'm mostly a
  Haskell developer these days, and resent having to go back to C just
  to write a simple application.
 
  So I was wondering if anyone had ever wrapped the FTGL library in
  Haskel FFI or whether those out there who are experts on the FFI
  think at first glance it should be readily wrappable by a rank
  amateur at FFI such as myself.
 
  http://ftgl.sourceforge.net/docs/html/
 
 Using the FFI is generally straight forward, as long as you can live
 with using the IO monad and the C code uses objects (well,
 pointers to structs passed as first argument, where's the
 difference...).

 Things only depend on the purity of the C code and how high-level you
 want your interface to be. In this case, I estimate half an hour if
 you're a fast typist. That includes the time needed to read the FFI
 docs.

 --
 (c) this sig last receiving data processing entity. Inspect headers for
 past copyright information. All rights reserved. Unauthorised copying,
 hiring, renting, public performance and/or broadcasting of this
 signature prohibited.

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




 --
 I try to take things like a crow; war and chaos don't always ruin a picnic,
 they just mean you have to be careful what you swallow.

 -- Jessica Edwards




-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Re: Haddock compilation problem

2008-06-20 Thread Matti Niemenmaa

Ronald Guida wrote:

I just upgraded to ghc-6.8.3, using a linux binary, and I am having a
problem compiling Haddock.  Haddock 2.1.0 and Haddock 2.0.0.0 both
fail to build under ghc-6.8.3, but they both build successfully with
ghc-6.8.2.  I don't know if this is a Haddock problem, or a GHC
problem, or perhaps something else entirely?

Here is the error I'm getting.  It is the same error for either
version of Haddock.

[15 of 24] Compiling Haddock.GHC.Typecheck (
src/Haddock/GHC/Typecheck.hs,
dist/build/haddock/haddock-tmp/Haddock/GHC/Typecheck.o )

src/Haddock/GHC/Typecheck.hs:82:4:
Constructor `HsModule' should have 7 arguments, but has been given 8
In the pattern: HsModule _ _ _ _ _ mbOpts _ _
In a pattern binding: HsModule _ _ _ _ _ mbOpts _ _ = unLoc parsed

snip

I managed to fix this with a bit of hacking:
1) add import FastString to the top of the file
2) remove one of the _'s before mbOpts on that line that gives the error
3) on line 72 of the original file (probably 73 after step 1), insert 'fmap 
unpackFS' before 'mbOpts'.


I now get some sort of System.Process-related link error, though. YMMV.

libHSghc.a(SysTools.o)(.text+0x7200):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_a6_closure'
libHSghc.a(SysTools.o)(.text+0x75c5):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_lvl1_closure'
libHSghc.a(SysTools.o)(.text+0xa6df):fake: undefined reference to 
`__stginit_processzm1zi0zi0zi1_SystemziProcess_'
libHSghc.a(SysTools.o)(.text+0x7215):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcessziInternals_a3_info'
libHSghc.a(SysTools.o)(.text+0x75d4):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_a8_info'
libHSghc.a(SysTools.o)(.data+0xcf8):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_lvl1_closure'
libHSghc.a(SysTools.o)(.data+0xcfc):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_a8_closure'
libHSghc.a(SysTools.o)(.data+0xd00):fake: undefined reference to 
`processzm1zi0zi0zi1_SystemziProcess_a6_closure'


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


[Haskell-cafe] Re: Haddock compilation problem

2008-06-20 Thread Matti Niemenmaa

Matti Niemenmaa wrote:

I now get some sort of System.Process-related link error, though. YMMV.


Audrey Tang gave me the fix for this on the IRC channel: passing 
--ghc-option=-package process-1.0.0.1 dealt with that.


It appears that it was all for naught, though: running the haddock binary on 
pretty much anything results in Segmentation fault/access violation in 
generated code or a downright crash.


I suppose I'll leave this to the Haddock developers, then. g

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


[Haskell-cafe] another FFI question

2008-06-20 Thread Galchin, Vasili
Hello,

I am reading the FFI spec. The following is unclear to me. Say I have

data Bonzo = A | B |C

and I want to poke Bonzo to an Int

A - 0

B - 1

C - 4

I have made  Bonzo an instance of Storable.

How do I write the poke functions and call them?

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jules Bean

Jefferson Heard wrote:

Oh, and I should say the function I want to implement is

getFontBBox :: Font - String - IO [Float]

I do know how to marhsal/unmarshal the String.  Just not the CFloat 
array to Haskell [Float]


import Foreign.C
import Foreign.Ptr
import Foreign.Marshal.Array

import Control.Applicative(($))

oneway :: Ptr CFloat - IO [Float]
oneway p = map real2Frac $ peekArray 4 p

the other way you would probably want withArray, but I think this is the 
way you need?



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


Re: [Haskell-cafe] Re: Haddock compilation problem

2008-06-20 Thread Ronald Guida
I have added ticket #18 to the Haddock Trac.
http://trac.haskell.org/haddock/wiki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Exactly.  thanks!

On Fri, Jun 20, 2008 at 4:26 PM, Jules Bean [EMAIL PROTECTED] wrote:

 Jefferson Heard wrote:

 Oh, and I should say the function I want to implement is

 getFontBBox :: Font - String - IO [Float]

 I do know how to marhsal/unmarshal the String.  Just not the CFloat array
 to Haskell [Float]


 import Foreign.C
 import Foreign.Ptr
 import Foreign.Marshal.Array

 import Control.Applicative(($))

 oneway :: Ptr CFloat - IO [Float]
 oneway p = map real2Frac $ peekArray 4 p

 the other way you would probably want withArray, but I think this is the
 way you need?





-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jules Bean

Sorry, it's realToFrac. Typo!

Jefferson Heard wrote:

Exactly.  thanks!

On Fri, Jun 20, 2008 at 4:26 PM, Jules Bean [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


Jefferson Heard wrote:

Oh, and I should say the function I want to implement is

getFontBBox :: Font - String - IO [Float]

I do know how to marhsal/unmarshal the String.  Just not the
CFloat array to Haskell [Float]


import Foreign.C
import Foreign.Ptr
import Foreign.Marshal.Array

import Control.Applicative(($))

oneway :: Ptr CFloat - IO [Float]
oneway p = map real2Frac $ peekArray 4 p

the other way you would probably want withArray, but I think this is
the way you need?





--
I try to take things like a crow; war and chaos don't always ruin a 
picnic, they just mean you have to be careful what you swallow.


-- Jessica Edwards




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


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


Re: [Haskell-cafe] another FFI question

2008-06-20 Thread Galchin, Vasili
Thanks Bulat!

Vasili

On Fri, Jun 20, 2008 at 3:20 PM, Bulat Ziganshin [EMAIL PROTECTED]
wrote:

 Hello Vasili,

 Friday, June 20, 2008, 11:51:11 PM, you wrote:
  data Bonzo = A | B |C

  How do I write the poke functions and call them?

 instance Storable Bonzo
  poke A = poke 0
  poke B = poke 1
  poke C = poke 4

 call as poke x

 probably, you don't understand differences between OOP classes and
 type classes. look at http://haskell.org/haskellwiki/OOP_vs_type_classes
 and papers mentioned there


 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]


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


[Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Pieter Laeremans
HI,

What 's wrong with this:

type Id = String

class Catalog a where
listItems :: a - IO [String]
getItem :: a - Id - IO (Maybe String)

class Item a where
getCatalog :: Catalog catalog = a - catalog

data Catalog c = Content c = Content {auteur :: String, inhoud::
String, catalog::c}

instance Catalog c = Item (Content c) where
   getCatalog (Content  _ _ c) = c

I get this as error from ghci:

Couldn't match expected type `catalog' against inferred type `c'
  `catalog' is a rigid type variable bound by
the type signature for `getCatalog'
  at
../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
  `c' is a rigid type variable bound by
  the instance declaration
at ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
In the expression: c
In the definition of `getCatalog': getCatalog (Content _ _ c) = c
In the definition for method `getCatalog'
Failed, modules loaded: none.

thanks in advance,

P

-- 
Pieter Laeremans [EMAIL PROTECTED]

The future is here. It's just not evenly distributed yet. W. Gibson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Bulat Ziganshin
Hello Pieter,

Saturday, June 21, 2008, 2:04:10 AM, you wrote:

for me, it seems just like you directly translated OOP classes into
Haskell that is the wrong way. you may look into
http://haskell.org/haskellwiki/OOP_vs_type_classes and
ghc user manual which discuss functional dependencies on the example
of collection classes


 HI,

 What 's wrong with this:

 type Id = String

 class Catalog a where
 listItems :: a - IO [String]
 getItem :: a - Id - IO (Maybe String)

 class Item a where
 getCatalog :: Catalog catalog = a - catalog

data Catalog c = Content c = Content {auteur :: String, inhoud::
 String, catalog::c}

 instance Catalog c = Item (Content c) where
getCatalog (Content  _ _ c) = c

 I get this as error from ghci:

 Couldn't match expected type `catalog' against inferred type `c'
   `catalog' is a rigid type variable bound by
 the type signature for `getCatalog'
   at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
   `c' is a rigid type variable bound by
   the instance declaration
 at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
 In the expression: c
 In the definition of `getCatalog': getCatalog (Content _ _ c) = c
 In the definition for method `getCatalog'
 Failed, modules loaded: none.

 thanks in advance,

 P




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Weston

I think the problem is here:

 getCatalog :: Catalog catalog = a - catalog

This wants to constrain the result of getCatalog to be an instance of 
Catalog, but this only works for function arguments, not results. The 
following code does typecheck, though I have no idea what is does or if 
it is what you want:



type Id = String

class Catalog a where
listItems :: a - IO [String]
getItem :: a - Id - IO (Maybe String)

class Catalog q = Item q a where
getCatalog :: a - q

data Content d = MkContent {auteur  :: String,
inhoud  :: String,
catalog :: d}

instance Catalog c = Item c (Content c) where
   getCatalog (MkContent  _ _ e) = e



Pieter Laeremans wrote:

HI,

What 's wrong with this:

type Id = String

class Catalog a where
listItems :: a - IO [String]
getItem :: a - Id - IO (Maybe String)

class Item a where
getCatalog :: Catalog catalog = a - catalog

data Catalog c = Content c = Content {auteur :: String, inhoud::
String, catalog::c}

instance Catalog c = Item (Content c) where
   getCatalog (Content  _ _ c) = c

I get this as error from ghci:

Couldn't match expected type `catalog' against inferred type `c'
  `catalog' is a rigid type variable bound by
the type signature for `getCatalog'
  at
../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
  `c' is a rigid type variable bound by
  the instance declaration
at ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
In the expression: c
In the definition of `getCatalog': getCatalog (Content _ _ c) = c
In the definition for method `getCatalog'
Failed, modules loaded: none.

thanks in advance,

P




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


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Doel
On Friday 20 June 2008, Pieter Laeremans wrote:
 type Id = String

 class Catalog a where
 listItems :: a - IO [String]
 getItem :: a - Id - IO (Maybe String)

 class Item a where
 getCatalog :: Catalog catalog = a - catalog

 data Catalog c = Content c = Content {auteur :: String, inhoud::
 String, catalog::c}

 instance Catalog c = Item (Content c) where
getCatalog (Content  _ _ c) = c

 I get this as error from ghci:

 Couldn't match expected type `catalog' against inferred type `c'
   `catalog' is a rigid type variable bound by
 the type signature for `getCatalog'
   at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
   `c' is a rigid type variable bound by
   the instance declaration
 at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17 In the
 expression: c
 In the definition of `getCatalog': getCatalog (Content _ _ c) = c
 In the definition for method `getCatalog'
 Failed, modules loaded: none.

The problem is in the type of getCatalog:

  (Item a, Catalog catalog) = a - catalog

That type says that given the a, you can produce a value of any type 'catalog' 
so long as that type is an instance of Catalog.

What you probably meant it to say is that you can produce *some particular* 
type that belongs to catalog. There are a couple ways you could express this. 
For instance, using functional dependencies:

class Catalog cat = HasCatalog a cat | a - cat where
  getCatalog :: a - cat

or the new type families:

class (Catalog (Cat a)) = Item a where
  type Cat a :: *
  getCatalog :: a - Cat a

Or you could wrap catalogues in an existential type:

data SomeCatalog = forall c. Catalog c = Cat c

class Item a where
  getCatalog :: a - SomeCatalog

However, as just a word of warning, I'd say that when you run into something 
like this, it's probably an indication that you're structuring your program 
from an object oriented mindset, and that may not be the best fit for 
programming in Haskell (of course, it's possible an existential type or some 
such is the appropriate way to do things).

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


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Derek Elkins
On Sat, 2008-06-21 at 00:04 +0200, Pieter Laeremans wrote:
 HI,
 
 What 's wrong with this:

It looks like you think Haskell is an OO language or want it to be.  It
is not.

 
 type Id = String
 
 class Catalog a where
 listItems :: a - IO [String]
 getItem :: a - Id - IO (Maybe String)
 
 class Item a where
 getCatalog :: Catalog catalog = a - catalog

This means 
class Item a where
getCatalog :: forall catalog. Catalog catalog = a - catalog

That means, given some Item a, I can create a value of -any- type that
is an instance of Catalog.  There is no well-defined function that could
do that.

 
 data Catalog c = Content c = Content {auteur :: String, inhoud::
 String, catalog::c}
 
 instance Catalog c = Item (Content c) where
getCatalog (Content  _ _ c) = c
 
 I get this as error from ghci:
 
 Couldn't match expected type `catalog' against inferred type `c'
   `catalog' is a rigid type variable bound by
 the type signature for `getCatalog'
   at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
   `c' is a rigid type variable bound by
   the instance declaration
 at 
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
 In the expression: c
 In the definition of `getCatalog': getCatalog (Content _ _ c) = c
 In the definition for method `getCatalog'
 Failed, modules loaded: none.
 
 thanks in advance,
 
 P
 

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


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Pieter Laeremans
Thanks all!

I have to admit, I have an OO mndset :-).

I think I have found a more functional design :

import Text.StringTemplate.Classes
import Text.StringTemplate

data (ToSElem a) = Item  a b = Item {cargo::a , catalog :: (Catalog a b)}

instance (ToSElem a) = ToSElem (Item a b) where
toSElem = (toSElem . cargo)

type Id = String

type ItemToSelem a b = Item a b - SElem b
type ItemParser a b = String - Item a b

type AllItemReader a b = IO [Item a b]
type SingleItemReader a b = Id - IO (Item a b)

data Catalog a b = Catalog  {reader:: (AllItemReader a b),
singleReader ::( SingleItemReader a b)}

data Content = Content {authort :: String, text:: String}

type ContentItem = Item Content String






What I want to express is that there exists differnet kinds of catalogs which,
depending on how they are configured can read from a file system or a database.
And each catalog can contain a specific type of Item.

For each Item I have to be able to produce the toSELem representation
that subsequently can be used by HStringTemplate

I thik that means I could declare

On Sat, Jun 21, 2008 at 12:26 AM, Dan Doel [EMAIL PROTECTED] wrote:
 On Friday 20 June 2008, Pieter Laeremans wrote:
 type Id = String

 class Catalog a where
 listItems :: a - IO [String]
 getItem :: a - Id - IO (Maybe String)

 class Item a where
 getCatalog :: Catalog catalog = a - catalog

 data Catalog c = Content c = Content {auteur :: String, inhoud::
 String, catalog::c}

 instance Catalog c = Item (Content c) where
getCatalog (Content  _ _ c) = c

 I get this as error from ghci:

 Couldn't match expected type `catalog' against inferred type `c'
   `catalog' is a rigid type variable bound by
 the type signature for `getCatalog'
   at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
   `c' is a rigid type variable bound by
   the instance declaration
 at
 ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17 In the
 expression: c
 In the definition of `getCatalog': getCatalog (Content _ _ c) = c
 In the definition for method `getCatalog'
 Failed, modules loaded: none.

 The problem is in the type of getCatalog:

  (Item a, Catalog catalog) = a - catalog

 That type says that given the a, you can produce a value of any type 'catalog'
 so long as that type is an instance of Catalog.

 What you probably meant it to say is that you can produce *some particular*
 type that belongs to catalog. There are a couple ways you could express this.
 For instance, using functional dependencies:

class Catalog cat = HasCatalog a cat | a - cat where
  getCatalog :: a - cat

 or the new type families:

class (Catalog (Cat a)) = Item a where
  type Cat a :: *
  getCatalog :: a - Cat a

 Or you could wrap catalogues in an existential type:

data SomeCatalog = forall c. Catalog c = Cat c

class Item a where
  getCatalog :: a - SomeCatalog

 However, as just a word of warning, I'd say that when you run into something
 like this, it's probably an indication that you're structuring your program
 from an object oriented mindset, and that may not be the best fit for
 programming in Haskell (of course, it's possible an existential type or some
 such is the appropriate way to do things).

 Cheers,
 -- Dan




-- 
Pieter Laeremans [EMAIL PROTECTED]

The future is here. It's just not evenly distributed yet. W. Gibson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread wren ng thornton

Pieter Laeremans wrote:

HI,

What 's wrong with this:

[...]

class Item a where
getCatalog :: Catalog catalog = a - catalog


This is a shorthand for

  class Item a where
  getCatalog :: forall c. (Catalog c) = a - c

That is, the class provides the contract that given some value of type a 
it will be able to return *any* type c which adheres to the contract of 
the class Catalog. This function is polymorphic in the return type.




instance Catalog c = Item (Content c) where
   getCatalog (Content  _ _ c) = c


The problem is, here you're returning a *specific* type c which adheres 
to Catalog. What happens if the caller of getCatalog is expecting some 
other type (Catalog c') = c' or (Catalog c'') = c'' etc?



There are a few different solutions you could take. The easiest one is 
to use multi-parameter type classes and functional dependencies to 
define Item like so:


  class Item a c | a - c where
  getCatalog :: (Catalog c) = a - c

This says that for any given type a there is one particular type c which 
getCatalog returns. Depending on your goals this may be enough, but if 
you really want getCatalog to be polymorphic in c then it won't work. 
(If you only want to be, er, multimorphic in c then you can leave out 
the fundep and define instances for each a*c type pair. This can lead to 
needing to declare excessively many type signatures however.)



If you really want to be able to return any c then there are a couple of 
approaches you could take. First is to add a conversion function to the 
Catalog class:


  class Catalog c where
  ...
  convertCatalog:: forall c'. (Catalog c') = c - c'

Given the rest of the definition for Catalog, this looks to be eminently 
doable-- at least in as far as people don't try to access any other 
fiddly bits inside the value c'. Of course this gives no way of 
preventing them from trying to do that fiddling, which leads to...



The other common approach is to use existential types to wrap values up 
with their class dictionaries like so:


  data CatalogWrapper = forall c. (Catalog c) = CatalogWrapper c

In this case you'd have getCatalog return a CatalogWrapper instead of a 
(Catalog c) = c. If you're not familiar with existential types they can 
be harder to think about since they loose information about what type 
you actually have inside; once wrapped they're only ever accessible by 
the methods of type classes restricting what we can wrap. But if you 
want to restrict people to only ever using the Catalog interface to 
manipulate them, then this is exactly what you want.



--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Pretty little definitions of left and right folds

2008-06-20 Thread George Kangas

Hi, Cafe,

  For no practical purpose, I wrote new definitions of list folds as 
chains of partially applied functions, joined by composition.  I took 
the liberty of rearranging the type signature.


 foldright :: (a - b - b)) - [a] - b - b
 foldright f = chain where
 chain (a:as) = (f a).(chain as)
 chain _ = id

 foldleft :: (a - b - b) - [a] - b - b
 foldleft f = chain where
 chain (a:as) = (chain as).(f a)
 chain _ = id

  These definitions are point free, with respect to the initializer 
argument (which is now the last argument).  Also, you can see how 
similar they are to each other, with the difference boiling down to the 
order of the composition, e.g.:


foldright (+) [1, 2, 3] 0 == ( (1 +).(2 +).(3 +).id ) 0
foldleft (+) [1, 2, 3] 0 == ( id.(3 +).(2 +).(1 +) ) 0


  We can also see the following identities:

foldright f as == foldright (.) (map f as) id
foldleft f as == foldright (flip (.)) (map f as) id

  I like that second one, after trying to read another definition of 
left fold in terms of right fold (in the web book Real World Haskell).


  The type signature, which could be written (a - (b - b)) - ([a] - 
(b - b)), suggests generalization to another type constructor C: (a - 
(b - b)) - (C a - (b - b)).  Would a foldable typeclass make any 
sense?


  Okay, it goes without saying that this is useless dabbling, but have 
I entertained anyone?  Or have I just wasted your time?  I eagerly await 
comments on this, my first posting.


very truly yours,

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


Re: [Haskell-cafe] Pretty little definitions of left and right folds

2008-06-20 Thread Brandon S. Allbery KF8NH


On 2008 Jun 20, at 19:15, George Kangas wrote:

 The type signature, which could be written (a - (b - b)) - ([a] - 
 (b - b)), suggests generalization to another type constructor C:  
(a - (b - b)) - (C a - (b - b)).  Would a foldable typeclass  
make any sense?


http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Foldable.html

--
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


Re: [Haskell-cafe] Access to Oracle database from Haskell

2008-06-20 Thread Steve Lihn
You may want to check this out.

http://www.orafaq.com/wiki/ODBC_FAQ#Where_can_one_get_ODBC_drivers_for_Oracle_and_Rdb.3F

As Oracle is a commercial company who is not interested in open source
historically, it is little chance that you will get robust software
for free -- from someone with many years of Oracle DBA experience :-)


On 6/19/08, Henning Thielemann [EMAIL PROTECTED] wrote:

 Is there a way of accessing a remote Oracle database by one of the common
 Haskell database interfaces (HaskellDB, Takusen, etc.) ? I tried to get
 unixODBC and Oracle's Instant Client running on a Linux machine, but I'm
 trapped in the notorious error:

 $ isql USER -v
 [IM004][unixODBC][Driver Manager]Driver's SQLAllocHandle on SQL_HANDLE_HENV
 failed
 [ISQL]ERROR: Could not SQLConnect

 This error message is discussed in various web forums, but there seems to be
 no systematic way to track down the problem. So I wonder whether there is
 another way to access the Oracle data base from Haskell.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Pretty little definitions of left and right folds

2008-06-20 Thread Brent Yorgey
On Fri, Jun 20, 2008 at 06:15:20PM -0500, George Kangas wrote:
 
 foldright (+) [1, 2, 3] 0 == ( (1 +).(2 +).(3 +).id ) 0
 foldleft (+) [1, 2, 3] 0 == ( id.(3 +).(2 +).(1 +) ) 0
 

Hi George,

This is very cool!  I have never thought of folds in quite this way
before.  It makes a lot of things (such as the identities you point
out) obvious and elegant.

   We can also see the following identities:
 
 foldright f as == foldright (.) (map f as) id
 foldleft f as == foldright (flip (.)) (map f as) id
 
   I like that second one, after trying to read another definition of 
 left fold in terms of right fold (in the web book Real World Haskell).
 
   The type signature, which could be written (a - (b - b)) - ([a] - 
 (b - b)), suggests generalization to another type constructor C: (a - 
 (b - b)) - (C a - (b - b)).  Would a foldable typeclass make any 
 sense?

As Brandon points out, you have rediscovered Data.Foldable. =) There's
nothing wrong with that, congratulations on discovering it for
yourself!  But again, I like this way of organizing the type
signature: I had never thought of a fold as a sort of 'lift' before.
If f :: a - b - b, then foldright 'lifts' f to foldright f :: [a] -
b - b (or C a - b - b, more generally).  

   Okay, it goes without saying that this is useless dabbling, but have 
 I entertained anyone?  Or have I just wasted your time?  I eagerly await 
 comments on this, my first posting.

Not at all!  Welcome, and thanks for posting.

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


Re: [Haskell-cafe] Pretty little definitions of left and right folds

2008-06-20 Thread Derek Elkins
On Fri, 2008-06-20 at 22:31 -0400, Brent Yorgey wrote:
 On Fri, Jun 20, 2008 at 06:15:20PM -0500, George Kangas wrote:
  
  foldright (+) [1, 2, 3] 0 == ( (1 +).(2 +).(3 +).id ) 0
  foldleft (+) [1, 2, 3] 0 == ( id.(3 +).(2 +).(1 +) ) 0
  
 
 Hi George,
 
 This is very cool!  I have never thought of folds in quite this way
 before.  It makes a lot of things (such as the identities you point
 out) obvious and elegant.
 
We can also see the following identities:
  
  foldright f as == foldright (.) (map f as) id
  foldleft f as == foldright (flip (.)) (map f as) id
  
I like that second one, after trying to read another definition of 
  left fold in terms of right fold (in the web book Real World Haskell).
  
The type signature, which could be written (a - (b - b)) - ([a] - 
  (b - b)), suggests generalization to another type constructor C: (a - 
  (b - b)) - (C a - (b - b)).  Would a foldable typeclass make any 
  sense?
 
 As Brandon points out, you have rediscovered Data.Foldable. =) There's
 nothing wrong with that, congratulations on discovering it for
 yourself!  But again, I like this way of organizing the type
 signature: I had never thought of a fold as a sort of 'lift' before.
 If f :: a - b - b, then foldright 'lifts' f to foldright f :: [a] -
 b - b (or C a - b - b, more generally).  
 
Okay, it goes without saying that this is useless dabbling, but have 
  I entertained anyone?  Or have I just wasted your time?  I eagerly await 
  comments on this, my first posting.
 
 Not at all!  Welcome, and thanks for posting.

Look into the theory of monoids, monoid homomorphisms, M-sets and free
monoids.

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


Re: [Haskell-cafe] another FFI question

2008-06-20 Thread Galchin, Vasili
I am still reading the web pages. Here is what I tried:

data SigNotify = Signal | None | Thread | ThreadId


instance Storable SigNotify where

   sizeOf _ = (#const sizeof (int))

   alignment _ = 1

   poke Signal = (#const SIGEV_SIGNAL)

   poke None = poke (#const SIGEV_NONE)

   poke Thread = poke (#const SIGEV_THREAD)

   poke ThreadId = poke (#const SIGEV_THREAD_ID)


but I got ...

Couldn't match expected type `Ptr SigNotify'
   against inferred type `SigNotify'
In the pattern: Signal
In the definition of `poke': poke Signal = poke (0)
In the definition for method `poke'

Basically I want to marshall SigInfo constructors to CInt values. ??

Regards, Vasili


On Fri, Jun 20, 2008 at 3:20 PM, Bulat Ziganshin [EMAIL PROTECTED]
wrote:

 Hello Vasili,

 Friday, June 20, 2008, 11:51:11 PM, you wrote:
  data Bonzo = A | B |C

  How do I write the poke functions and call them?

 instance Storable Bonzo
  poke A = poke 0
  poke B = poke 1
  poke C = poke 4

 call as poke x

 probably, you don't understand differences between OOP classes and
 type classes. look at http://haskell.org/haskellwiki/OOP_vs_type_classes
 and papers mentioned there


 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]


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


Re: [Haskell-cafe] Access to Oracle database from Haskell

2008-06-20 Thread Lanny Ripple
I had luck with this the other day using Database.HDBC.ODBC.  For
Ubuntu's Hardy I found that Oracle's 10.2.0.3 worked best.
(10.2.0.4 and 11 seemed to have problems for me at least.)

http://www.oracle.com/technology/software/tech/oci/instantclient/htdocs/linuxsoft.html

Grab the basic (not basic-lite), odbc, and sqlplus (to test) zips.
The odbc_update_ini.sh should be run from inside the
instantclient_10_2 directory as root

  sudo /bin/sh odbc_update_ini.sh /

(assuming a standard unixODBC install.)  You'll also need a
tnsnames.ora file to describe your connection(s) to the DB(s).
You'll also need to define some environment variables to run against
all this.  I use a small script:

  #!/bin/sh
  oracle_home=/opt/lib/oracle/instantclient_10_2
  export TNS_ADMIN=$oracle_home
  export LD_LIBRARY_PATH=$oracle_home
  [ $# = 0 ]  exit 1
  exec $@

Best of luck,
  -ljr


Steve Lihn wrote:
 You may want to check this out.
 
 http://www.orafaq.com/wiki/ODBC_FAQ#Where_can_one_get_ODBC_drivers_for_Oracle_and_Rdb.3F
 
 As Oracle is a commercial company who is not interested in open source
 historically, it is little chance that you will get robust software
 for free -- from someone with many years of Oracle DBA experience :-)
 
 
 On 6/19/08, Henning Thielemann [EMAIL PROTECTED] wrote:
 Is there a way of accessing a remote Oracle database by one of the common
 Haskell database interfaces (HaskellDB, Takusen, etc.) ? I tried to get
 unixODBC and Oracle's Instant Client running on a Linux machine, but I'm
 trapped in the notorious error:

 $ isql USER -v
 [IM004][unixODBC][Driver Manager]Driver's SQLAllocHandle on SQL_HANDLE_HENV
 failed
 [ISQL]ERROR: Could not SQLConnect

 This error message is discussed in various web forums, but there seems to be
 no systematic way to track down the problem. So I wonder whether there is
 another way to access the Oracle data base from Haskell.
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe