Re: [Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Tony Morris
Ivan Miljenovic wrote: > On 20 May 2010 14:42, Tony Morris wrote: > >> We all know that "class (Functor f) => Monad f" is preferable but its >> absence is a historical mistake. We've all probably tried once: >> >> instance (Functor f) => Monad f where >> > > Do you mean the reverse of this

Re: [Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Ivan Miljenovic
On 20 May 2010 14:42, Tony Morris wrote: > We all know that "class (Functor f) => Monad f" is preferable but its > absence is a historical mistake. We've all probably tried once: > > instance (Functor f) => Monad f where Do you mean the reverse of this (instance (Monad m) => Functor m where) ? >

[Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Tony Morris
We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once: instance (Functor f) => Monad f where ... However, is there a type system extension (even proposed but not implemented) that allows me to retrospectively apply

Re: [Haskell-cafe] Bird problem 1.6.2 -- is there an easier method?

2010-05-19 Thread John Millikin
You've been asking a lot of very tutorial-ish questions on this list. Although this isn't necessarily a *bad* thing, you may receive responses more appropriate to your skill level on the haskell-beginners list < http://www.haskell.org/mailman/listinfo/beginners >. I don't own the Bird book, but wh

Re: [Haskell-cafe] Intuitive function given type signature

2010-05-19 Thread Richard O'Keefe
On May 20, 2010, at 3:18 AM, Brent Yorgey wrote: On Wed, May 19, 2010 at 04:27:14AM +, R J wrote: What are some simple functions that would naturally have the following type signatures: f :: (Integer -> Integer) -> Integer Well, this means f is given a function from Integer to Intege

Re: [Haskell-cafe] Deducing a type signature

2010-05-19 Thread Dan Weston
> (i) strange f g = g (f g) > > Assume g :: a -> b. Then f :: (a -> b) -> c. But since g :: a -> b, > f g :: a, so c = a. Therefore, f :: (a -> b) -> a, and g (f g) :: a. > Therefore, strange :: ((a -> b) -> a) -> (a -> b) -> a. Almost. The return type of strange is the same as the return typ

Re: [Haskell-cafe] Deducing a type signature

2010-05-19 Thread Richard O'Keefe
On May 20, 2010, at 11:03 AM, R J wrote: stranger f = f f This doesn't have a type in Haskell. Suppose f :: a -> b Then if f f made sense, a = (a -> b) would be true, and we'd have an infinite type. Type the definition into a file, and try loading it into ghci: Occurs check: cannot con

[Haskell-cafe] Deducing a type signature

2010-05-19 Thread R J
Bird 1.6.3 requires deducing type signatures for the functions "strange" and "stranger." Are my solutions below correct? (i) strange f g = g (f g) Assume g :: a -> b. Then f :: (a -> b) -> c. But since g :: a -> b,f g :: a, so c = a. Therefore, f :: (a -> b) -> a, and g (f g) :: a.Therefore,

[Haskell-cafe] Bird problem 1.6.2 -- is there an easier method?

2010-05-19 Thread R J
Bird problem 1.6.2 is: If f :: (a, b) -> c, then define a function "swap" such that: flip (curry f) = curry (f . swap). I'd very much appreciate if someone could tell me whether there's a rigorous solution simpler than mine, which is: Since (.) :: (q -> r) -> (p -> q) -> (p -> r), we have f :: q

Re: [Haskell-cafe] Devices and Webcams, The Basics

2010-05-19 Thread Ivan Lazar Miljenovic
aditya siram writes: > Haskell has bindings to USB [1]. I don't know of any USB tutorials or > any webcam specific libraries. I don't know of any, but if using Linux then maybe writing a binding to v4l (video for linux) might be the best/easiest approach. -- Ivan Lazar Miljenovic ivan.miljeno.

Re: [Haskell-cafe] Devices and Webcams, The Basics

2010-05-19 Thread aditya siram
Haskell has bindings to USB [1]. I don't know of any USB tutorials or any webcam specific libraries. -deech [1] http://hackage.haskell.org/package/usb On 5/19/10, Eitan Goldshtrom wrote: > Hi everyone, > > I would like to start working on a program that requires access to a > camera attached to

[Haskell-cafe] Devices and Webcams, The Basics

2010-05-19 Thread Eitan Goldshtrom
Hi everyone, I would like to start working on a program that requires access to a camera attached to the computer probably via USB or otherwise internally. Unfortunately I don't know anything about using devices in haskell. I tried looking up how to access the microphone one too and had littl

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Don Stewart
schlepptop: > Don Stewart schrieb: > > Or use things from the download-curl package, which provides a nice > > openURL function. > > The openURL function from TagSoup is lazy, which the proposed > replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is > the openURL function from do

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Henning Thielemann
Don Stewart schrieb: > Or use things from the download-curl package, which provides a nice > openURL function. The openURL function from TagSoup is lazy, which the proposed replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is the openURL function from download-curl lazy? ___

Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-19 Thread adam vogt
On Thu, May 13, 2010 at 7:16 PM, HASHIMOTO, Yusaku wrote: > Sorry for spamming, what I wanted to write is I think `has' has better > interface than other record packages in types. > > There are many libraries to write function "takes an record has Foo > and Bar and returns something." But writing

[Haskell-cafe] Extensible Records and Functional References

2010-05-19 Thread Günther Schmidt
Hi all, I just read "Functional References are a cheap and cheerful technique for working with the existing (non-extensible) record system, and may be of interest to extensible record implementers. A good implementation can be found on ..." on http://hackage.haskell.org/trac/ghc/wik

[Haskell-cafe] Haskell for control system [was: [reactive] A pong and integrate]

2010-05-19 Thread Ben Franksen
David Leimbach wrote: > I find it's often the most practical chapter that I hit a lot during > writes and changes to my server process I have in Haskell in our control > system code :-) Are you actually saying that you use Haskell for a control system server? Thta would be very interesting to me.

Re: [Haskell-cafe] cabal-install

2010-05-19 Thread Serguey Zefirov
>>> I tried it and it didn't work. I don't know reason, though, maybe it >>> was because my current password not entirely alphanumeric. >> Shouldn't matter as long as you put it within quotes. > I imagine things will go wrong if it includes an @... urlencoding is > probably a smart idea. Thank you

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Neil Mitchell
Hi Ralph, > I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this > error: > > TQ\TagSoup\TagSoupExtensions.lhs:29:17: >`Tag' is not applied to enough type arguments >Expected kind `*', but `Tag' has kind `* -> *' >In the type synonym declaration for `Bundle' > F

[Haskell-cafe] Re: cabal: problem building ffi shared library and significance of __stginit

2010-05-19 Thread Anthony LODI
> I'm trying to build some haskell code as a .so/.dll so that it can > ultimately be used by msvc.  I have it working when I compile by hand > (listed below) but I can't get the exact same thing built/linked with > cabal.  On linux everything builds fine, but when I try to link the > resulting .so

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Don Stewart
Or use things from the download-curl package, which provides a nice openURL function. daniel.is.fischer: > On Wednesday 19 May 2010 19:46:57, Ralph Hodgson wrote: > > Forgot to add: I now need to understand the following warnings on this > > line "> import Text.HTML.Download": > > > > > > In Text

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Daniel Fischer
On Wednesday 19 May 2010 19:46:57, Ralph Hodgson wrote: > Forgot to add: I now need to understand the following warnings on this > line "> import Text.HTML.Download": > > In Text.HTML.Download, there's the following: {-| /DEPRECATED/: Use the HTTP package instead: > import Network.HTTP

Re: [Haskell-cafe] cabal-install

2010-05-19 Thread Brandon S. Allbery KF8NH
On May 19, 2010, at 04:49 , Ivan Lazar Miljenovic wrote: Serguey Zefirov writes: export http_proxy="http://${username}:${passwo...@${proxy_url}"; I tried it and it didn't work. I don't know reason, though, maybe it was because my current password not entirely alphanumeric. Shouldn't matter

RE: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Ralph Hodgson
Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download": TagSoupExtensions.lhs:24:2: Warning: In the use of `openItem' (imported from Text.HTML.Download): Deprecated: "Use package HTTP, module Network.HTTP, getR

RE: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Ralph Hodgson
Thanks Malcolm, Providing a 'String' type argument worked: > type Bundle = [Tag String] > extractTags :: Tag String -> Tag String -> Bundle -> Bundle > extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= > fromTag ) tags From: Malcolm Wallace [mailto:mal

Re: [Haskell-cafe] cabal: problem building ffi shared library and significance of __stginit

2010-05-19 Thread Duncan Coutts
On Tue, 2010-05-18 at 17:31 -0400, Anthony LODI wrote: > Hello, > > I'm trying to build some haskell code as a .so/.dll so that it can > ultimately be used by msvc. I have it working when I compile by hand > (listed below) but I can't get the exact same thing built/linked with > cabal. On linux

Re: [Haskell-cafe] (no subject)

2010-05-19 Thread Brent Yorgey
On Wed, May 19, 2010 at 01:37:49PM +, R J wrote: > > This is another proof-layout question, this time from Bird 1.4.7. > We're asked to define the functions curry2 and uncurry2 for currying and > uncurrying functions with two arguments. Simple enough: > curry2 :: ((a, b) -> c) ->

Re: [Haskell-cafe] Proof format

2010-05-19 Thread Brent Yorgey
On Wed, May 19, 2010 at 01:12:16PM +, R J wrote: > > Is this how a rigorous Haskeller would lay out the proofs of the following > theorems? This is Bird 1.4.6. > (i) > Theorem: (*) x = (* x) > Proof: > (*) x ={definition of partial application} \y

Re: [Haskell-cafe] Intuitive function given type signature

2010-05-19 Thread Brent Yorgey
On Wed, May 19, 2010 at 04:27:14AM +, R J wrote: > > What are some simple functions that would naturally have the following type > signatures: > f :: (Integer -> Integer) -> Integer Well, this means f is given a function from Integer to Integer, and it has to somehow return an Integer, (poss

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 23:44, Ben Millwood wrote: > On Wed, May 19, 2010 at 10:57 AM, Serguey Zefirov wrote: >> >> PS >> Rationals: >> Prelude> [1,1+2/3..10] :: [Rational] >> [1 % 1,5 % 3,7 % 3,3 % 1,11 % 3,13 % 3,5 % 1,17 % 3,19 % 3,7 % 1,23 % >> 3,25 % 3,9 % 1,29 % 3,31 % 3] >> >> Same result. >

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Lutz Donnerhacke
* Ben Millwood wrote: >> Prelude> [1,1+2/3..10] :: [Rational] >> [1 % 1,5 % 3,7 % 3,3 % 1,11 % 3,13 % 3,5 % 1,17 % 3,19 % 3,7 % 1,23 % >> 3,25 % 3,9 % 1,29 % 3,31 % 3] >> >> Same result. > > This sounds like a bug to me. The section of the Haskell Report that > deals with the Enum class mentions Fl

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Ben Millwood
On Wed, May 19, 2010 at 10:57 AM, Serguey Zefirov wrote: > > PS > Rationals: > Prelude> [1,1+2/3..10] :: [Rational] > [1 % 1,5 % 3,7 % 3,3 % 1,11 % 3,13 % 3,5 % 1,17 % 3,19 % 3,7 % 1,23 % > 3,25 % 3,9 % 1,29 % 3,31 % 3] > > Same result. This sounds like a bug to me. The section of the Haskell Rep

[Haskell-cafe] (no subject)

2010-05-19 Thread R J
This is another proof-layout question, this time from Bird 1.4.7. We're asked to define the functions curry2 and uncurry2 for currying and uncurrying functions with two arguments. Simple enough: curry2 :: ((a, b) -> c) -> (a -> (b -> c))curry2 f x y = f (x, y) uncurry2

[Haskell-cafe] Proof format

2010-05-19 Thread R J
Is this how a rigorous Haskeller would lay out the proofs of the following theorems? This is Bird 1.4.6. (i) Theorem: (*) x = (* x) Proof: (*) x ={definition of partial application} \y -> x * y = {commutativity of "*"} \y -> y * x ={defi

Re: [Haskell-cafe] Numerical Analysis

2010-05-19 Thread Alberto G. Corona
SAGE is the kind of thing that I dreamed to have available online a few years ago. To recode everithing in haskell perhaps does not worth the pain, but perhapts it would be nice to do something similar to SAGE in an advanced environment such is Google Wave, with all the collaborative facilities fo

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 20:36, Ivan Lazar Miljenovic wrote: > Roman Leshchinskiy writes: >> Personally, I consider the Enum class itself to be broken. > > Oh? In what sense? Firstly, the enumFrom* family of functions shouldn't be methods and the class itself should provide enough facilities for imp

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Ivan Lazar Miljenovic
Roman Leshchinskiy writes: > Personally, I consider the Enum class itself to be broken. Oh? In what sense? It seems to work fine for data types representing bounded enumerable values with a proper mapping to/from Int (it's not bijective since there's no proper mapping from Int -> Bool for examp

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 19:24, Dmitry Olshansky wrote: > Prelude> [1,1+2/3..10] > [1.0,1.6665,2.333,2.9996,3.666,4.332,4.998,5.664,6.33,6.9964,7.6625,8.329,8.99

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Dmitry Olshansky
Thanks, it's clear now. 2010/5/19 Serguey Zefirov : > 2010/5/19 Erik de Castro Lopo : >> Dmitry Olshansky wrote: >> >>> It seems that I saw something like this in Cafe recevtly. But I am not >>> sure... >>> In GHC 6.12.1 (Platform 2010 on Windows Vista) I have >> >> >> >> >>> Any comments? >> >>

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Dmitry Olshansky
But Prelude Data.List> [1,1+2/3..4] :: [Double] [1.0,1.6665,2.333,2.9996,3.666,4.332] Prelude Data.List> unfoldr (\n -> let n'=n+2/3 in if n' <= 4 then Just (n',n') else Nothing) 1 :: [Double] [1.6665,2.333,2.

[Haskell-cafe] Type famillies & Lifting IO

2010-05-19 Thread Maciej Piechotka
I started playing with type families. I wanted to achieve, for the beginning, something like: > import qualified Control.Monad.IO.Class as IOC > import Control.Monad.Trans.Class > import Control.Monad.Trans.Cont > import Data.Functor.Identity > class (Monad m, Monad (IO' m)) => MonadIO m where >

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Ivan Lazar Miljenovic
Ivan Lazar Miljenovic writes: > Dmitry Olshansky writes: > >> Hello all, >> >> It seems that I saw something like this in Cafe recevtly. But I am not >> sure... >> In GHC 6.12.1 (Platform 2010 on Windows Vista) I have >> >> Prelude> [1,1+2/3..10] >> [1.0,1.6665,2.333,2.9

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Serguey Zefirov
2010/5/19 Erik de Castro Lopo : > Dmitry Olshansky wrote: > >> It seems that I saw something like this in Cafe recevtly. But I am not >> sure... >> In GHC 6.12.1 (Platform 2010 on Windows Vista) I have > > > > >> Any comments? > > The problem you point out is not a problem with Haskell, but a pro

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Ivan Lazar Miljenovic
Dmitry Olshansky writes: > Hello all, > > It seems that I saw something like this in Cafe recevtly. But I am not sure... > In GHC 6.12.1 (Platform 2010 on Windows Vista) I have > > Prelude> [1,1+2/3..10] > [1.0,1.6665,2.333,2.9996,3.666,4.33

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Erik de Castro Lopo
Dmitry Olshansky wrote: > It seems that I saw something like this in Cafe recevtly. But I am not sure... > In GHC 6.12.1 (Platform 2010 on Windows Vista) I have > Any comments? The problem you point out is not a problem with Haskell, but a problem with the whole concept of floating point arit

[Haskell-cafe] Bug with [Double]

2010-05-19 Thread Dmitry Olshansky
Hello all, It seems that I saw something like this in Cafe recevtly. But I am not sure... In GHC 6.12.1 (Platform 2010 on Windows Vista) I have Prelude> [1,1+2/3..10] [1.0,1.6665,2.333,2.9996,3.666,4.332,4.998,5.6

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Malcolm Wallace
Neil says that the API of TagSoup changed in 0.9. All usages of the type Tag should now take a type argument, e.g. Tag String. Regards, Malcolm On Wednesday, May 19, 2010, at 08:05AM, "Ralph Hodgson" wrote: >___ >Haskell-Cafe mailing list >Hask

Re: [Haskell-cafe] cabal-install

2010-05-19 Thread Ivan Lazar Miljenovic
Serguey Zefirov writes: >> export http_proxy="http://${username}:${passwo...@${proxy_url}"; > > I tried it and it didn't work. I don't know reason, though, maybe it > was because my current password not entirely alphanumeric. Shouldn't matter as long as you put it within quotes. -- Ivan Lazar M

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-19 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: > Heinrich Apfelmus writes: >> Yes; what I mean is that you can retrofit a custom vertex type to any >> graph implementation that uses a fixed vertex type. So, let's say that >> >>data Gr a b = .. -- graph with vertex type Vertex Gr = Int >> >> then >> >>type G

[Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Ralph Hodgson
Hello Neil , I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error: TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' F