[Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Vasili I. Galchin
Hello,

 I am currently using ghc 6.8.2. With the following,

swishParse :: String - String - SwishStateIO (Maybe RDFGraph)
swishParse fnam inp =
do  { fmt - gets $ format
; case fmt of
N3- swishParseN3 fnam inp
otherwise -
do  { swishError (Unsupported file format: ++(show fmt)) 4
; return Nothing
}
}

I am receiving a shadow warning:

Swish/HaskellRDF/SwishCommands.hs:304:12:
Warning: Defined but not used: `otherwise'

It seems to me that in the code base somewhere that there is a redefine of
the keywordotherwise. I haven't read the Haskell 98 Report but I thought
that it was not possible to redefine keywords. ??

Kind regards,

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Janis Voigtlaender

Vasili I. Galchin wrote:
It seems to me that in the code base somewhere that there is a 
redefine of the keywordotherwise. I haven't read the Haskell 98 
Report but I thought that it was not possible to redefine keywords. ??


otherwise is not a keyword. It is just defined as a normal function
like so:

otherwise = True

Ciao,
Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:vo...@tcs.inf.tu-dresden.de

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


Re: [Haskell-cafe] A Reader Monad Tutorial

2009-06-28 Thread Lee Duhem
On Sun, Jun 28, 2009 at 12:41 AM, Henry Laxennadine.and.he...@pobox.com wrote:
 Dear Group,

 If any of you are struggling with understanding monads, I've tried to put
 together a pretty through explanation of what is behind the Reader monad.  If
 you're interested, have a look at:

 http://www.maztravel.com/haskell/readerMonad.html


Nice post.

I didn't find how to add comments on your blog, so I post them here:

Areas of Confusion

  1. What is the relationship between the Reader on the left hand side of the 
 equals sign in the newtype definition and the Reader on the right hand side?
   2. Why is there a Record field on the right hand side?
   3. What is that r - a doing there?

1) Reader on the left hand side be called a type constructor, Reader
on the right hand side be called a data constructor,
in Haskell 98 Report. You call them type definition and instance
constructor, respectively, I'm not sure it's a good idea, or
it is right.

bug in the explanation:
what you use to make something and instance of a Reader (left hand side)
- what you use to make something an instance of a Reader (left hand side)

2) runReader be called a selector function in Haskell 98 Report.

3) (-) is a type constructor, so r - a is  a function type.

I used found 'instance Monad ((-) r)' hard to understand, but by
follow the hit given by Brent Yorgey, i.e. the data constructor for
type constructor (-) is called lambda abstraction, I found I can
understand them by type inference. I have written a post about how I
figure
it out, maybe you want take a look:
http://leeduhem.wordpress.com/2009/06/07/understanding-monad-instance-by-type-inference/

bug in the explanation after  (Reader f1) = f2  = Reader $ \e -
runReader (Reader b) e:
Reader b is a function that takes and e and returns a c,
- Reader b is a function that takes an e and returns a c,

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Janis Voigtlaender

Vasili I. Galchin wrote:
so Janis I have to look where the original author overrode otherwise? 
If so, just great .. a ton of code. ;^(


No, you don't have to look for this. It is in the code snippet you sent:

swishParse :: String - String - SwishStateIO (Maybe RDFGraph)
swishParse fnam inp =
do  { fmt - gets $ format
; case fmt of
N3- swishParseN3 fnam inp
otherwise -
do  { swishError (Unsupported file format: ++(show
fmt)) 4
; return Nothing
}
}

In the case expression you use otherwise as a variable. But you do not
use that variable in that branch. Hence the warning:

Swish/HaskellRDF/SwishCommands.hs:304:12:
Warning: Defined but not used: `otherwise'

This has nothing to do with someone else shadowing the definition of
otherwise.

Ciao,
Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:vo...@tcs.inf.tu-dresden.de

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh

Hi Vasili,

This isn't really a shadowing/redefinition issue. Here's 
a perfectly legitimate snippet that compiles fine:

f 0 = 0
f otherwise = 1+otherwise

Redefinition is when you have:

g = let otherwise = not in x 


-- Kim-Ee


VasiliIGalchin wrote:
 
 swishParse :: String - String - SwishStateIO (Maybe RDFGraph)
 swishParse fnam inp =
 do  { fmt - gets $ format
 ; case fmt of
 N3- swishParseN3 fnam inp
 otherwise -
 do  { swishError (Unsupported file format: ++(show fmt))
 4
 ; return Nothing
 }
 }
 
 I am receiving a shadow warning:
 
 Swish/HaskellRDF/SwishCommands.hs:304:12:
 Warning: Defined but not used: `otherwise'
 
 It seems to me that in the code base somewhere that there is a redefine
 of
 the keywordotherwise. I haven't read the Haskell 98 Report but I thought
 that it was not possible to redefine keywords. ??
 

-- 
View this message in context: 
http://www.nabble.com/%22shadowing%22-keywords-like-%22otherwise%22-tp24239153p24239430.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh

I meant, of course,

g = let otherwise = not in otherwise

Sorry for the noise.

-- Kim-Ee


Kim-Ee Yeoh wrote:
 
 Hi Vasili,
 
 This isn't really a shadowing/redefinition issue. Here's 
 a perfectly legitimate snippet that compiles fine:
 
 f 0 = 0
 f otherwise = 1+otherwise
 
 Redefinition is when you have:
 
 g = let otherwise = not in x 
 
 
 -- Kim-Ee
 
 
 VasiliIGalchin wrote:
 
 swishParse :: String - String - SwishStateIO (Maybe RDFGraph)
 swishParse fnam inp =
 do  { fmt - gets $ format
 ; case fmt of
 N3- swishParseN3 fnam inp
 otherwise -
 do  { swishError (Unsupported file format: ++(show
 fmt)) 4
 ; return Nothing
 }
 }
 
 I am receiving a shadow warning:
 
 Swish/HaskellRDF/SwishCommands.hs:304:12:
 Warning: Defined but not used: `otherwise'
 
 It seems to me that in the code base somewhere that there is a redefine
 of
 the keywordotherwise. I haven't read the Haskell 98 Report but I
 thought
 that it was not possible to redefine keywords. ??
 
 
 

-- 
View this message in context: 
http://www.nabble.com/%22shadowing%22-keywords-like-%22otherwise%22-tp24239153p24239439.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Bulat Ziganshin
Hello Vasili,

Sunday, June 28, 2009, 10:39:37 AM, you wrote:

     ; case fmt of
      N3    - swishParseN3 fnam inp
     otherwise -
     do  { swishError (Unsupported file format: ++(show fmt)) 4
     ; return Nothing
     }
      }

first, otherwise aka True is used in *condition* part of case
statement. here you should use _

second, otherwise isn't a keyword, just a Prelude definition. here,
you assign fmt value to this identifier


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Rigid type variable error

2009-06-28 Thread Jason Dagit
On Sat, Jun 27, 2009 at 10:45 PM, Darryn djr...@aapt.net.au wrote:


 Thanks for the help previously received, but I still cannot seem to get
 on top of this. The types for the constructor K will not resolve and
 I'm at a loss to work out what to do with it. If anyone can offer
 a further explanation and help I would be very grateful.


 My code (File Test5.hs):
 
 {-# LANGUAGE ExistentialQuantification #-}

 class A a where
a1 :: a
a2 :: a - a
a3 :: (B b) = b - a

 class B b where
b1 :: Int - b

 --data Ainst b = I | J (Ainst b) | K b
 --  a3 :: (B b, A a) = b - a
 --  yet without the constraint on K, K :: b - Ainst b
 --  so the above data definition fails. Trying to
 --  existentially quantify K below seems to make
 --  sense, but also fails ...
 data Ainst b = I | J (Ainst b) | (B b) = K b

 instance (B b) = A (Ainst b) where
a1 = I
 a2 = J
a3 = K -- Reported line of the error

 data Binst = Val Int

 instance B Binst where
b1 = Val
 ---

 The error from ghci is as follows:

 Test5.hs:25:9:
Couldn't match expected type `b' against inferred type `b1'
   `b' is a rigid type variable bound by
   the type signature for `a3' at Test5.hs:7:13
   `b1' is a rigid type variable bound by
the instance declaration at Test5.hs:16:12
   Expected type: b - Ainst b1
   Inferred type: b1 - Ainst b1
In the expression: K
 In the definition of `a3': a3 = K
 Failed, modules loaded: none.

 Thanks in advance for any help. Apologies if what I am doing is odd or
 the answer is obvious, I'm still very new to Haskell.


The actual problem is not that easy to understand until you really get to
know the intricacies of Haskell's type checking.  Do you think you could
explain your problem is less abstract terms?  That is, sometimes if you tell
people here what you want to do and why they can suggest a better approach.

One thing to understand about your type class `A' is that it does not give a
relationship between `b' and `a'.  As far as the definition of `A' is
concerned, `b' is totally arbitrary, so long as it is an instance of `B'.
In particular, no relationship with `a' is implied.  Additionally, I'm
nearly certain that existential types are not needed or even wanted here.

K :: b - Ainst b

In particular, the `b' that `K' takes becomes part of the type that `K'
returns.  This is different than the type of `a3'.  In the type of `a3', the
`b' that it takes doesn't necessarily become part of the return type.  In a
way, that means that `K' is less polymorphic than `a3'.  This may not seem
like a problem, but it is what prevents `K' from having the same type as
`a3', and thus you get your error message.  The type of `a3' is more general
than the type of `K' due to the possible ranges of the type variables
involved.

I have played with it a bit and found that this does compile:
\begin{code}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances, FlexibleContexts #-}

class A a b | b - a where
   a1 :: a
   a2 :: a - a
   a3 :: (B b) = b - a

class B b where
   b1 :: Int - b

data Ainst b = I | J (Ainst b) | K b

instance (B b) = A (Ainst b) b where
   a1 = I
   a2 = J
   a3 = K -- Reported line of the error

data Binst = Val Int

instance B Binst where
   b1 = Val
\end{code}

If you remove all the type class constraints you won't need the
FlexibleContexts, but it's also not hurting anything.

Here I am using the functional dependency between `a' and `b' that says,
once you fix the type of `b', you also fix the type of `a'.  You'll notice
that, that is exactly what `K' does.  Given a `b', it gives you `Ainst a',
where `a = b', and therefore the type depends on, or is fixed by, `b'.
Multi parameter type classes are needed just so we can give the functional
dependency and the flexible things are in there just to work around Haskell
98 restrictions.

I hope this sheds more light on the problem.  I bet you could be using type
families here as well, but I have yet to take the time to understand them.

I hope that helps,
Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rigid type variable error

2009-06-28 Thread Daniel Fischer
Am Sonntag 28 Juni 2009 07:45:33 schrieb Darryn:
 Thanks for the help previously received, but I still cannot seem to get
 on top of this. The types for the constructor K will not resolve and
 I'm at a loss to work out what to do with it. If anyone can offer
 a further explanation and help I would be very grateful.


 My code (File Test5.hs):
 
 {-# LANGUAGE ExistentialQuantification #-}

 class A a where
 a1 :: a
 a2 :: a - a
 a3 :: (B b) = b - a

This means a3 has the type

forall c. (B c) = c - a


 class B b where
 b1 :: Int - b

 --data Ainst b = I | J (Ainst b) | K b
 --  a3 :: (B b, A a) = b - a
 --  yet without the constraint on K, K :: b - Ainst b
 --  so the above data definition fails. Trying to
 --  existentially quantify K below seems to make
 --  sense, but also fails ...
 data Ainst b = I | J (Ainst b) | (B b) = K b

Tis means K can only take an argument of type b, so

K :: (B b) = b - Ainst b


 instance (B b) = A (Ainst b) where
 a1 = I
 a2 = J
 a3 = K -- Reported line of the error

a3 must have type

forall c. (B b, B c) = c - Ainst b

which is more general than K's type.

Depending on what you want to do, you could
a) change Ainst,
data Ainst = I | J Ainst | (B b) = K b

instance (B b) = A Ainst where
a1 = I
a2 = J
a3 = K

but then you don't know what type b has been used to construct J (K x), so you 
can't do 
much with it.

b) make A a multiparameter type class with functional dependencies

class A a b | a - b where
a1 :: a
a2 :: a - a
a3 :: b - a

instance (B b) = A (Ainst b) b where
a1 = I
a2 = J
a3 = K

c) use type families:

class A a where
type S a
a1 :: a
a2 :: a - a
a3 :: S a - a

instance (B b) = A (Ainst b) where
type S (Ainst b) = b
a1 = I
a2 = J
a3 = K

b) and c) are more or less equivalent and restrict the type of a3 to K's type


 data Binst = Val Int

 instance B Binst where
 b1 = Val
 ---

 The error from ghci is as follows:

 Test5.hs:25:9:
 Couldn't match expected type `b' against inferred type `b1'
   `b' is a rigid type variable bound by
   the type signature for `a3' at Test5.hs:7:13
   `b1' is a rigid type variable bound by
the instance declaration at Test5.hs:16:12
   Expected type: b - Ainst b1
   Inferred type: b1 - Ainst b1
 In the expression: K
 In the definition of `a3': a3 = K
 Failed, modules loaded: none.

 Thanks in advance for any help. Apologies if what I am doing is odd or
 the answer is obvious, I'm still very new to Haskell.

 Darryn.



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


[Haskell-cafe] Re: test-framework success

2009-06-28 Thread Max Bolingbroke
2009/6/28 Simon Michael si...@joyful.com:
 But, I can now add -j8 and get the same results output in.. 0.13s. This
 quite surprised me, and now I want to say: thank you very much! :)

Awesome! I'm really glad to hear you are having success with the package!

For anyone else on the list who wants to take a look, the package home
page is at http://batterseapower.github.com/test-framework/

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


[Haskell-cafe] Re: FFI and heap memory usage limit

2009-06-28 Thread Marcin Kosiba
On Friday 26 June 2009, Simon Marlow wrote:
 Maybe bzlib allocates using malloc()?  That would not be tracked by
 GHC's memory management, but could cause OOM.

probably, because it's a binding to a C library. I'm really busy right now, 
but I'll try and create a small program to repro this error.

 Another problem is that if you ask for a large amount of memory in one
 go, the request is usually honoured immediately, and then we GC shortly
 afterward.  If this is the problem for you, please submit a ticket and
 I'll see whether it can be changed.  You could work around it by calling
 System.Mem.performGC just before allocating the memory.

I've already worked around the problem.
-- 
Marcin Kosiba


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Felipe Lessa
On Sun, Jun 28, 2009 at 12:49:12AM -0700, Kim-Ee Yeoh wrote:
 This isn't really a shadowing/redefinition issue. Here's
 a perfectly legitimate snippet that compiles fine:

 f 0 = 0
 f otherwise = 1+otherwise

What?  It is a redefinition issue *as well*, but this kind of
warning isn't active by default

Prelude :s -Wall
Prelude let f 0 = 0; f otherwise = 1 + otherwise

interactive:1:15:
Warning: This binding for `otherwise' shadows the existing binding
   imported from Prelude
 In the definition of `f'

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


[Haskell-cafe] Half-integer

2009-06-28 Thread Andrew Coppin
I just wrote a small module for dealing with half-integers. (That is, 
any number I/2 where I is an integer. Note that the set of integers is a 
subset of this; Wikipedia seems to reserve half-integer for such 
numbers that are *not* integers.)


 module HalfInteger where

 data HalfInteger i

 instance (Eq i) = Eq (HalfInteger i)
 instance (Ord i) = Ord (HalfInteger i)
 instance (Integral i) = Show (HalfInteger i)
 instance (Integral i) = Num (HalfInteger i)

 half :: (Num i) = HalfInteger i

 fromNum :: (Integral i, RealFrac x) = x - HalfInteger i
 toNum :: (Integral i, Fractional x) = HalfInteger i - x

 isInteger :: (Integral i) = HalfInteger i - Bool

Note carefully that the set of half-integers is *not* closed under 
multiplication! This means that for certain arguments, there are two 
reasonable products that could be returned. (E.g., 1/2 * 1/2 = 1/4, so 0 
or 1/2 would be a reasonable rounding.) I haven't put a lot of effort 
into the rounding details of (*) or fromNum; which answer you get is 
kind of arbitrary. (However, addition and subtraction are exact, and for 
multiplications where an exact result is possible, you will get that 
result.)


The Show instance outputs strings such as

 fromInteger 5
 fromInteger 5 + half
 fromInteger (-5) - half

depending on the isInteger predicate.

Now, the question is... Is this useful enough to be worth putting on 
Hackage?


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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Felipe Lessa
On Sun, Jun 28, 2009 at 02:24:30PM +0100, Andrew Coppin wrote:
 Now, the question is... Is this useful enough to be worth putting on
 Hackage?

Why not?  :)

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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Magnus Therning

Felipe Lessa wrote:

On Sun, Jun 28, 2009 at 02:24:30PM +0100, Andrew Coppin wrote:

Now, the question is... Is this useful enough to be worth putting on
Hackage?


Why not?  :)


Just upload it!  I mean, at any point in time most package on hackage will be 
useless _to_me_.  That doesn't mean they won't become useful in the future, 
and it certainly doesn't mean that someone else won't find them useful right 
now.  :-)


/M

--
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Thomas ten Cate
On Sun, Jun 28, 2009 at 15:24, Andrew Coppinandrewcop...@btinternet.com wrote:
 I just wrote a small module for dealing with half-integers. (That is, any
 number I/2 where I is an integer. Note that the set of integers is a subset
 of this; Wikipedia seems to reserve half-integer for such numbers that are
 *not* integers.)

  module HalfInteger where

  data HalfInteger i

  instance (Eq i) = Eq (HalfInteger i)
  instance (Ord i) = Ord (HalfInteger i)
  instance (Integral i) = Show (HalfInteger i)
  instance (Integral i) = Num (HalfInteger i)

  half :: (Num i) = HalfInteger i

  fromNum :: (Integral i, RealFrac x) = x - HalfInteger i
  toNum :: (Integral i, Fractional x) = HalfInteger i - x

  isInteger :: (Integral i) = HalfInteger i - Bool

 Note carefully that the set of half-integers is *not* closed under
 multiplication! This means that for certain arguments, there are two
 reasonable products that could be returned. (E.g., 1/2 * 1/2 = 1/4, so 0 or
 1/2 would be a reasonable rounding.) I haven't put a lot of effort into the
 rounding details of (*) or fromNum; which answer you get is kind of
 arbitrary. (However, addition and subtraction are exact, and for
 multiplications where an exact result is possible, you will get that
 result.)

 The Show instance outputs strings such as

  fromInteger 5
  fromInteger 5 + half
  fromInteger (-5) - half

 depending on the isInteger predicate.

 Now, the question is... Is this useful enough to be worth putting on
 Hackage?

Out of curiosity, what are *you* using it for?

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


[Haskell-cafe] Re: A Reader Monad Tutorial

2009-06-28 Thread Henry Laxen
Lee Duhem lee.duhem at gmail.com writes:

 Nice post.
 
 I didn't find how to add comments on your blog, so I post them here:
 
...


Dear Lee,

Thank you for your comments and corrections.  I have included all of them in the
new version of the article.
Best wishes,
Henry Laxen



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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Andrew Coppin

Thomas ten Cate wrote:

Out of curiosity, what are *you* using it for?
  


Centering things.

In you have an odd number of items, the middle one will be at position 
0, with the others at integer positions on either side. However, if you 
have an even number, the middle two will be at 0 +- 1/2, and so forth.


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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Andrew Coppin

Felipe Lessa wrote:

On Sun, Jun 28, 2009 at 02:24:30PM +0100, Andrew Coppin wrote:
  

Now, the question is... Is this useful enough to be worth putting on
Hackage?



Why not?  :)
  


Well, it *does* mean I'll have to figure out how Cabal actually works...

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


[Haskell-cafe] What is an expected type ...

2009-06-28 Thread michael rice
as opposed to an inferred type?

Michael



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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Martijn van Steenbergen

Hi Michael,

michael rice wrote:

as opposed to an inferred type?


Can you deduce from the following example?


Prelude let foo = () :: Int
interactive:1:10:
Couldn't match expected type `Int' against inferred type `()'
In the expression: () :: Int
In the definition of `foo': foo = () :: Int



Hope this helps!

Martijn.

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Joe Fredette
When Haskell runs it's type checker, it tries to guess the type of 
each function. Thats why you can write:


   map (+1)

and it knows that you're talking about a function of type:

   Num a = [a] - [a]

Another thing, called 'defaulting' resolves this, but you didn't ask 
about that, so I won't go into it.


An expected type is one that you provide to the compiler in the form of 
a type signature, this can be used to specialize a general type (like 
the one I showed) or
to resolve ambiguous types the compiler can't, or just for 
documentation/good practice. So when I write:


   foo :: Num a = [a] - [a]
   foo ls = map (+1) ls

The expected type for `foo` is `Num a = [a] - [a]`. I imagine you're 
asking this because you got an error which said your expected type 
doesn't match your inferred type. That might, for instance, happen if I 
wrote:


   bar :: String
   bar = 'a'

'a' has type `Char`, since `String` is not `Char`, the type checker 
infers that 'a' has type char, but _expects_ it to be type String. Two 
solutions are as follows:


   --- Method 1
   bar :: Char
   bar = 'a'
   --- Method 2
   bar :: String
   bar = a

Can you see why those two changes fix the problem?


Also, just as a matter of process, I forwarded this to the 
haskell-beginners list, as I imagine type errors like these come up a 
lot, and someone probably has a better explanation over there.


/Joe


michael rice wrote:

as opposed to an inferred type?

Michael




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  
begin:vcard
fn:Joseph Fredette
n:Fredette;Joseph
adr:Apartment #3;;6 Dean Street;Worcester;Massachusetts;01609;United States of America
email;internet:jfred...@gmail.com
tel;home:1-508-966-9889
tel;cell:1-508-254-9901
x-mozilla-html:FALSE
url:lowlymath.net, humbuggery.net
version:2.1
end:vcard

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Brandon S. Allbery KF8NH

On Jun 28, 2009, at 02:39 , Vasili I. Galchin wrote:

; case fmt of
N3- swishParseN3 fnam inp
otherwise -
do  { swishError (Unsupported file format: ++(show  
fmt)) 4

; return Nothing
}
}

I am receiving a shadow warning:

Swish/HaskellRDF/SwishCommands.hs:304:12:
Warning: Defined but not used: `otherwise'


1. otherwise isn't a keyword, it's a function (well, CAF).
2. if you use a variable in a case alternative, that variable is  
created and bound.  I think you wanted to use _ instead of  
otherwise there.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Brandon S. Allbery KF8NH

On Jun 28, 2009, at 12:02 , michael rice wrote:

dec2bin :: Integer - [Integer]
dec2bin n = dec2bin' n []
where dec2bin' n acc
| n == 0 = acc
| otherwise = let r = rem n 2
  m = div (n - r) 2
  in dec2bin' m (r : acc)

is there any way to assign a type signature to the helper function?



Same way you do for a top level binding:


dec2bin :: Integer - [Integer]
dec2bin n = dec2bin' n []
where dec2bin' :: Integer - [Integer] - [Integer]
  dec2bin' n acc
| n == 0 = acc
| otherwise = let r = rem n 2
  m = div (n - r) 2
  in dec2bin' m (r : acc)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Deniz Dogan
2009/6/28 Andrew Coppin andrewcop...@btinternet.com:
 Felipe Lessa wrote:

 On Sun, Jun 28, 2009 at 02:24:30PM +0100, Andrew Coppin wrote:


 Now, the question is... Is this useful enough to be worth putting on
 Hackage?


 Why not?  :)


 Well, it *does* mean I'll have to figure out how Cabal actually works...

Usually, it's pretty straight-forward and most options are
self-explanatory.
http://en.wikibooks.org/wiki/Haskell/Packaging#The_Cabal_file

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread michael rice
Hey Joe, all,

Got it. Thanks!

An associated question: In programming a local helper or auxilliary 
function such as dec2bin' in

dec2bin :: Integer - [Integer]
dec2bin n = dec2bin' n []
    where dec2bin' n acc
    | n == 0 = acc
    | otherwise = let r = rem n 2
  m = div (n - r) 2
  in dec2bin' m (r : acc)

is there any way to assign a type signature to the helper function?

Michael


--- On Sun, 6/28/09, Joe Fredette jfred...@gmail.com wrote:

From: Joe Fredette jfred...@gmail.com
Subject: Re: [Haskell-cafe] What is an expected type ...
To: michael rice nowg...@yahoo.com
Cc: Haskell Cafe mailing list haskell-cafe@haskell.org, 
beginn...@haskell.org
Date: Sunday, June 28, 2009, 11:29 AM

When Haskell runs it's type checker, it tries to guess the type of each 
function. Thats why you can write:

   map (+1)

and it knows that you're talking about a function of type:

   Num a = [a] - [a]

Another thing, called 'defaulting' resolves this, but you didn't ask about 
that, so I won't go into it.

An expected type is one that you provide to the compiler in the form of a type 
signature, this can be used to specialize a general type (like the one I 
showed) or
to resolve ambiguous types the compiler can't, or just for documentation/good 
practice. So when I write:

   foo :: Num a = [a] - [a]
   foo ls = map (+1) ls

The expected type for `foo` is `Num a = [a] - [a]`. I imagine you're asking 
this because you got an error which said your expected type doesn't match your 
inferred type. That might, for instance, happen if I wrote:

   bar :: String
   bar = 'a'

'a' has type `Char`, since `String` is not `Char`, the type checker infers that 
'a' has type char, but _expects_ it to be type String. Two solutions are as 
follows:

   --- Method 1
   bar :: Char
   bar = 'a'
   --- Method 2
   bar :: String
   bar = a

Can you see why those two changes fix the problem?


Also, just as a matter of process, I forwarded this to the haskell-beginners 
list, as I imagine type errors like these come up a lot, and someone probably 
has a better explanation over there.

/Joe


michael rice wrote:
 as opposed to an inferred type?
 
 Michael
 
 
 
 
 ___
 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] Half-integer

2009-06-28 Thread Andrew Coppin

Deniz Dogan wrote:

2009/6/28 Andrew Coppin andrewcop...@btinternet.com:
  

Felipe Lessa wrote:


On Sun, Jun 28, 2009 at 02:24:30PM +0100, Andrew Coppin wrote:

  

Now, the question is... Is this useful enough to be worth putting on
Hackage?



Why not?  :)

  

Well, it *does* mean I'll have to figure out how Cabal actually works...



Usually, it's pretty straight-forward and most options are
self-explanatory.
http://en.wikibooks.org/wiki/Haskell/Packaging#The_Cabal_file
  


Yes, one would *hope* that a 1-module library with no dependencies would 
be fairly trivial. ;-)


Also Haddock; I'm thinking some documentation might be nice...

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread michael rice
How else? ;-)

Thanks,

Michael

--- On Sun, 6/28/09, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S. Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] What is an expected type ...
To: michael rice nowg...@yahoo.com
Cc: Brandon S. Allbery KF8NH allb...@ece.cmu.edu, Joe Fredette 
jfred...@gmail.com, beginn...@haskell.org, Haskell Cafe mailing list 
haskell-cafe@haskell.org
Date: Sunday, June 28, 2009, 12:06 PM

On Jun 28, 2009, at 12:02 , michael rice wrote:dec2bin :: Integer - [Integer]
dec2bin n = dec2bin' n []
    where dec2bin' n acc
    | n == 0 = acc
    | otherwise = let r = rem n 2
  m = div (n - r) 2
  in dec2bin' m (r : acc)

is there any way to assign a type signature to the helper function?

Same way you do for a top level binding:
dec2bin :: Integer - [Integer]
dec2bin n = dec2bin' n []
    where dec2bin' :: Integer - [Integer] - [Integer]
                  dec2bin' n acc
    | n == 0 = acc
    | otherwise = let r = rem n 2
  m = div (n - r) 2
  in dec2bin' m (r : acc)
 -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] 
allb...@kf8nh.comsystem administrator [openafs,heimdal,too many hats] 
allb...@ece.cmu.eduelectrical and computer engineering, carnegie mellon 
university    KF8NH
 



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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Daniel Fischer
Am Sonntag 28 Juni 2009 18:06:52 schrieb Brandon S. Allbery KF8NH:
 On Jun 28, 2009, at 12:02 , michael rice wrote:
  dec2bin :: Integer - [Integer]
  dec2bin n = dec2bin' n []
  where dec2bin' n acc
 
  | n == 0 = acc
  | otherwise = let r = rem n 2
 
m = div (n - r) 2
in dec2bin' m (r : acc)
 
  is there any way to assign a type signature to the helper function?

 Same way you do for a top level binding:
  dec2bin :: Integer - [Integer]
  dec2bin n = dec2bin' n []
  where dec2bin' :: Integer - [Integer] - [Integer]
dec2bin' n acc
 
  | n == 0 = acc
  | otherwise = let r = rem n 2
 
m = div (n - r) 2
in dec2bin' m (r : acc)

But, to mention it before it bites, putting type signatures involving type 
variables on 
local helper functions is not entirely straightforward. Consider

inBase :: Integral a = a - a - [a]
0 `inBase` b = [0]
n `inBase` b = local n []
  where
local 0 acc = acc
local m acc = case m `divMod` b of
(q,r) - local q (r:acc)

Now try giving a type signature to local. You can't.
What is the type of local?
It's (type of b) - [type of b] - [type of b],
but type of b isn't available.
If you try 
local :: a - [a] - [a]
or
local :: Integral a = a - [a] - [a],
you are saying that local works for *every* type a (or for every type a which 
is an 
instance of Integral), because the 'a' from local's type signature is a new 
(implicitly 
forall'd) type variable.

To be able to give local a type signature, you must bring the type variable 'a' 
into 
scope:

{-# LANGUAGE ScopedTypeVariables #-}

inBase :: forall a. Integral a = a - a - [a]
0 `inBase` b = [0]
n `inBase` b = local n []
  where
local :: a - [a] - [a]-- now this a is the same a as the one above
local 0 acc = acc
local m acc = case m `divMod` b of
(q,r) - local q (r:acc)

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Thomas ten Cate
On Sun, Jun 28, 2009 at 17:14, michael ricenowg...@yahoo.com wrote:
 as opposed to an inferred type?

There was a thread on haskell-cafe about this a few weeks ago. Here it
is in the archives:
http://www.haskell.org/pipermail/haskell-cafe/2009-May/062012.html

Maybe some post in there might help. Maybe they will all confuse you... :)

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


[Haskell-cafe] ANNOUNCE: X Haskell Bindings 0.3

2009-06-28 Thread Antoine Latter
I'd like to announce the 0.3.* series release of the X Haskell
Bindings.  This release, like the prior 0.2.* series focuses on making
the API prettier. This release is based on the XCB protocol
descriptions version 1.5

This does mean that there's a good chance this is a
breaking release for any code compiled against 0.2.*.

The goal of XHB is to provide a Haskell implementation of the X11 wire
protocol, similar in spirit to the X protocol C-language Binding
(XCB).

On Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xhb
Source: darcs get http://community.haskell.org/~aslatter/code/xhb/

New this release:

 * In 0.2, a lot of the core protocol requests, events and replies
were updated to use prettier Haskell datatypes for the various enums
and bitmasks. Thanks to Peter Harris's work on the protocol
description XML files, these niceties have extended out to all of the
extension requests, events and replies and such.

 * Due to name clashes, I the type-names for events and errors now
include an Event or Error suffix. For example, the type Notify
has become NotifyEvent.

 * Now based on the protocol description version 1.5, from 1.4.

Related projects:

X protocol C-language Binding: http://xcb.freedesktop.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: X Haskell Bindings 0.3

2009-06-28 Thread Antoine Latter
On Sun, Jun 28, 2009 at 12:52 PM, Antoine Latteraslat...@gmail.com wrote:
 I'd like to announce the 0.3.* series release of the X Haskell
 Bindings.  This release, like the prior 0.2.* series focuses on making
 the API prettier. This release is based on the XCB protocol
 descriptions version 1.5


I'd also like to share my thoughts on where the XHB project is, and
where I see it going.

As an experiment to show that an X client library can be written in
Haskell, I feel like XHB has succeeded.

But to be truly useful as a library, I feel like it needs to be able
to inter-operate with xlib and libxcb, which XHB currently does not.

Conceptually, XHB can be thought of as two parts:

 - Haskell data types generated from the X protocol description, which
know how to serilaize/deserialize themselves to and from byte streams.

 - A runtime which knows how to open a connection to the X server, and
knows how to peek and poke stuff onto the connection to the X server
(this is where all of the networking and thread wrangling code lives).

So it seems to me that the path forward is to keep as much of the
first part as possible, and then replace the second part with haskell
bindings to XCB.

I've started the binding to libxcb here:
http://community.haskell.org/~aslatter/code/xcb-ffi/


There are still a few unknowns in my mind, such as
 - I've never made Haskell bindings to a multi-threaded C App. Is
there anything strange I have to worry about?

 - I have no idea how I'll map event and error codes to the function
to decode the bytes into a Haskell type. In XHB all of the information
needed lives in Haskell datatypes - once I start moving over to being
a wrapper around XCB, the extensions cache is held in libxcb and isn't
exposed publicly.

But presumably these problems have solutions.

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Dan Piponi
I really dislike this error message, and I think the terms are
ambiguous. I think the words 'expected' and 'inferred' apply equally
well to the term, and the context in which it has been found. Both of
the incompatible types were 'inferred', and 'unexpected' is a property
of the combination, not a property of one or the other.
--
Dan

On Sun, Jun 28, 2009 at 8:24 AM, Martijn van
Steenbergenmart...@van.steenbergen.nl wrote:
 Hi Michael,

 michael rice wrote:

 as opposed to an inferred type?

 Can you deduce from the following example?

 Prelude let foo = () :: Int
 interactive:1:10:
    Couldn't match expected type `Int' against inferred type `()'
    In the expression: () :: Int
    In the definition of `foo': foo = () :: Int


 Hope this helps!

 Martijn.

 ___
 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] Half-integer

2009-06-28 Thread Andrew Coppin

Andrew Coppin wrote:

Deniz Dogan wrote:
2009/6/28 Andrew Coppin andrewcop...@btinternet.com:
Well, it *does* mean I'll have to figure out how Cabal actually 
works...



Usually, it's pretty straight-forward and most options are
self-explanatory.
http://en.wikibooks.org/wiki/Haskell/Packaging#The_Cabal_file
  


Yes, one would *hope* that a 1-module library with no dependencies 
would be fairly trivial. ;-)


Ah, but it's not as easy as you'd think. The instructions above fail to 
mention several required or strongly recommended fields. (E.g., 
apparently Category and Synopsis are both required, Cabal-Version is 
strongly recommended, several fields are meant to be in the Library 
subsection...) And then of course there's the question of choosing a 
licence. But I think I'm nearly there now.


Oh, one last thing. I know I'm going to regret this for the rest of my 
life, but... which version of Base should it depend on?



Also Haddock; I'm thinking some documentation might be nice...


This at least *was* fairly trivial. ;-) [The only hard part being 
figuring out how to manually run Haddock...]


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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Antoine Latter
On Sun, Jun 28, 2009 at 2:13 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:

 Oh, one last thing. I know I'm going to regret this for the rest of my life,
 but... which version of Base should it depend on?


Which versions of base have you tested it with?  :-)

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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Andrew Coppin

Antoine Latter wrote:

On Sun, Jun 28, 2009 at 2:13 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
  

Oh, one last thing. I know I'm going to regret this for the rest of my life,
but... which version of Base should it depend on?




Which versions of base have you tested it with?  :-)
  


Whichever one GHC 6.10.3 ships with...

Frankly, I highly doubt it makes any difference either way. (Does 
anybody know how base3 differs from base4?) It only uses a few type 
classes from the Prelude...


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


Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Max Rabkin
On Sun, Jun 28, 2009 at 9:29 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
 Which versions of base have you tested it with?  :-)


 Whichever one GHC 6.10.3 ships with...

ghc-pkg list base will tell you which version you have installed.

 Frankly, I highly doubt it makes any difference either way. (Does anybody
 know how base3 differs from base4?) It only uses a few type classes from the
 Prelude...

If it *only* uses the prelude (i.e., does not include *any* modules),
then it should work with any version of base.

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


Re: [Haskell-cafe] shadowing keywords like otherwise

2009-06-28 Thread Kim-Ee Yeoh

Whoops, you're right.

Interestingly, the shadowing warnings vary between 
the 2 examples I gave, i.e. shadowing within 
'function definition' vs 'binding group'.



Felipe Lessa wrote:
 
 On Sun, Jun 28, 2009 at 12:49:12AM -0700, Kim-Ee Yeoh wrote:
 This isn't really a shadowing/redefinition issue. Here's
 a perfectly legitimate snippet that compiles fine:

 f 0 = 0
 f otherwise = 1+otherwise
 
 What?  It is a redefinition issue *as well*, but this kind of
 warning isn't active by default
 
 Prelude :s -Wall
 Prelude let f 0 = 0; f otherwise = 1 + otherwise
 
 interactive:1:15:
 Warning: This binding for `otherwise' shadows the existing binding
imported from Prelude
  In the definition of `f'
 
 --
 Felipe.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/%22shadowing%22-keywords-like-%22otherwise%22-tp24239153p24244760.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Kim-Ee Yeoh

Could you suggest a better word pair to describe the dichotomy then?
How about 'calculated' vs 'user-imposed' (or even, 'explicitly-
signatured')?



Dan Piponi-2 wrote:
 
 I really dislike this error message, and I think the terms are
 ambiguous. I think the words 'expected' and 'inferred' apply equally
 well to the term, and the context in which it has been found. Both of
 the incompatible types were 'inferred', and 'unexpected' is a property
 of the combination, not a property of one or the other.
 --
 Dan
 
 On Sun, Jun 28, 2009 at 8:24 AM, Martijn van
 Steenbergenmart...@van.steenbergen.nl wrote:
 Hi Michael,

 michael rice wrote:

 as opposed to an inferred type?

 Can you deduce from the following example?

 Prelude let foo = () :: Int
 interactive:1:10:
    Couldn't match expected type `Int' against inferred type `()'
    In the expression: () :: Int
    In the definition of `foo': foo = () :: Int


 Hope this helps!

 Martijn.

 ___
 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
 
 

-- 
View this message in context: 
http://www.nabble.com/What-is-an-%22expected-type%22-...-tp24242359p24244820.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re[2]: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Bulat Ziganshin
Hello Kim-Ee,

Sunday, June 28, 2009, 11:52:57 PM, you wrote:

we already had a *long* discussion on this topic. afaik, it's dichotomy
between type of term itself and type of position where it's used (f.e.
argument of some function)


 Could you suggest a better word pair to describe the dichotomy then?
 How about 'calculated' vs 'user-imposed' (or even, 'explicitly-
 signatured')?



 Dan Piponi-2 wrote:
 
 I really dislike this error message, and I think the terms are
 ambiguous. I think the words 'expected' and 'inferred' apply equally
 well to the term, and the context in which it has been found. Both of
 the incompatible types were 'inferred', and 'unexpected' is a property
 of the combination, not a property of one or the other.
 --
 Dan
 
 On Sun, Jun 28, 2009 at 8:24 AM, Martijn van
 Steenbergenmart...@van.steenbergen.nl wrote:
 Hi Michael,

 michael rice wrote:

 as opposed to an inferred type?

 Can you deduce from the following example?

 Prelude let foo = () :: Int
 interactive:1:10:
    Couldn't match expected type `Int' against inferred type `()'
    In the expression: () :: Int
    In the definition of `foo': foo = () :: Int


 Hope this helps!

 Martijn.

 ___
 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
 
 




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Cabal fun [Half-integer]

2009-06-28 Thread Andrew Coppin

Max Rabkin wrote:

On Sun, Jun 28, 2009 at 9:29 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
  

Which versions of base have you tested it with?  :-)

  

Whichever one GHC 6.10.3 ships with...



ghc-pkg list base will tell you which version you have installed.
  


Which tells me I have base-3.0.3.1 *and* base-4.1.0.0 ;-)


Frankly, I highly doubt it makes any difference either way. (Does anybody
know how base3 differs from base4?) It only uses a few type classes from the
Prelude...



If it *only* uses the prelude (i.e., does not include *any* modules),
then it should work with any version of base.
  


Yeah, that's what I figured...

Alrighty then, so how I just do Setup configure, and now Setup sdist, 
and then I can upload the result to Ha-- oh, don't be silly. That would 
simply be too easy. ;-)


E:\Haskell\AOC-HalfIntegerrunhaskell Setup sdist
Building source dist for AOC-HalfInteger-1.0...
Preprocessing library AOC-HalfInteger-1.0...
Setup: tar is required but it could not be found.

Time to go search the web and find out what the other 50 people who 
stumbled into this did... *sigh*



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


Re: [Haskell-cafe] What is an expected type ...

2009-06-28 Thread Arne Dehli Halvorsen

Bulat Ziganshin wrote:

Hello Kim-Ee,

Sunday, June 28, 2009, 11:52:57 PM, you wrote:

we already had a *long* discussion on this topic. afaik, it's dichotomy
between type of term itself and type of position where it's used (f.e.
argument of some function)


  

Could you suggest a better word pair to describe the dichotomy then?
How about 'calculated' vs 'user-imposed' (or even, 'explicitly-
signatured')?


How about 'Int' used in '()'-shaped hole?
'Int' from usage, '()' from definition of  'foo' could not be reconciled?

Arne D Halvorsen




  

Dan Piponi-2 wrote:


I really dislike this error message, and I think the terms are
ambiguous. I think the words 'expected' and 'inferred' apply equally
well to the term, and the context in which it has been found. Both of
the incompatible types were 'inferred', and 'unexpected' is a property
of the combination, not a property of one or the other.
--
Dan

On Sun, Jun 28, 2009 at 8:24 AM, Martijn van
Steenbergenmart...@van.steenbergen.nl wrote:
  

Hi Michael,

michael rice wrote:


as opposed to an inferred type?
  

Can you deduce from the following example?



Prelude let foo = () :: Int
interactive:1:10:
   Couldn't match expected type `Int' against inferred type `()'
   In the expression: () :: Int
   In the definition of `foo': foo = () :: Int

  

Hope this helps!

Martijn.

___
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


Re: [Haskell-cafe] Cabal fun [Half-integer]

2009-06-28 Thread Andrew Coppin

Andrew Coppin wrote:
Alrighty then, so how I just do Setup configure, and now Setup sdist, 
and then I can upload the result to Ha-- oh, don't be silly. That 
would simply be too easy. ;-)


E:\Haskell\AOC-HalfIntegerrunhaskell Setup sdist
Building source dist for AOC-HalfInteger-1.0...
Preprocessing library AOC-HalfInteger-1.0...
Setup: tar is required but it could not be found.

Time to go search the web and find out what the other 50 people who 
stumbled into this did... *sigh*


Ah. Apparently it's fixed:

http://hackage.haskell.org/trac/hackage/ticket/40

Except that it isn't fixed. Yay for me...

It seems that GHC provides ar but not tar. Looks like I might actually 
have to copy the entire directory tree to a Linux box just so I can run 
sdist... Nice to know this stuff is so easy. :-/


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


Re: [Haskell-cafe] Cabal fun [Half-integer]

2009-06-28 Thread Antoine Latter
On Sun, Jun 28, 2009 at 3:42 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
 Andrew Coppin wrote:

 Alrighty then, so how I just do Setup configure, and now Setup sdist, and
 then I can upload the result to Ha-- oh, don't be silly. That would simply
 be too easy. ;-)

 E:\Haskell\AOC-HalfIntegerrunhaskell Setup sdist
 Building source dist for AOC-HalfInteger-1.0...
 Preprocessing library AOC-HalfInteger-1.0...
 Setup: tar is required but it could not be found.

 Time to go search the web and find out what the other 50 people who
 stumbled into this did... *sigh*

 Ah. Apparently it's fixed:

 http://hackage.haskell.org/trac/hackage/ticket/40

 Except that it isn't fixed. Yay for me...

 It seems that GHC provides ar but not tar. Looks like I might actually have
 to copy the entire directory tree to a Linux box just so I can run sdist...
 Nice to know this stuff is so easy. :-/


I don't know anything that's gauranteed to work, as I've never tried
packaging from a Windows box, but:

 - Is 'htar' a good enough 'tar' replacement for cabal?
 - Does cabal-install also require an external tar? You could try cabal sdist

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


Re: [Haskell-cafe] Re: test-framework success

2009-06-28 Thread Felipe Lessa
On Sun, Jun 28, 2009 at 11:07:27AM +0100, Max Bolingbroke wrote:
 Awesome! I'm really glad to hear you are having success with the package!

BTW, thanks for fixing the spacing issue with nested tests! :)

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


[Haskell-cafe] C global vars local to threads

2009-06-28 Thread Maurí­cio

I would like to write a wrapper to C global
variable, but that variable is unique to each
thread. Is there some native support on that
in Haskell FFI?

(I imagine I probably should write a C function
to get its pointer as an 'IO (Ptr ...)', but I
would like to check if there's a more standard
way to do that.)

Thanks,
Maurício

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


[Haskell-cafe] parallel haskell

2009-06-28 Thread Kevin Smith
I'm interested in doing some research with parallel programming using
Haskell (both multi-core on one machine and clusters using multiple
machines) but in going through the various resources on the web (looking at
GPH and others), it is not clear to me what the current state is as many of
the resources/projects have out of date information in them.
Any pointers ?  What parallel extensions are available in the current
version 6.10.3 ?  Which parallel extensions support clustered networks ?
 Where to start ?

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


Re: [Haskell-cafe] Cabal fun [Half-integer]

2009-06-28 Thread Derek Elkins
On Sun, Jun 28, 2009 at 4:11 PM, Antoine Latteraslat...@gmail.com wrote:
 On Sun, Jun 28, 2009 at 3:42 PM, Andrew
 Coppinandrewcop...@btinternet.com wrote:
 Andrew Coppin wrote:

 Alrighty then, so how I just do Setup configure, and now Setup sdist, and
 then I can upload the result to Ha-- oh, don't be silly. That would simply
 be too easy. ;-)

 E:\Haskell\AOC-HalfIntegerrunhaskell Setup sdist
 Building source dist for AOC-HalfInteger-1.0...
 Preprocessing library AOC-HalfInteger-1.0...
 Setup: tar is required but it could not be found.

 Time to go search the web and find out what the other 50 people who
 stumbled into this did... *sigh*

 Ah. Apparently it's fixed:

 http://hackage.haskell.org/trac/hackage/ticket/40

 Except that it isn't fixed. Yay for me...

 It seems that GHC provides ar but not tar. Looks like I might actually have
 to copy the entire directory tree to a Linux box just so I can run sdist...
 Nice to know this stuff is so easy. :-/


 I don't know anything that's gauranteed to work, as I've never tried
 packaging from a Windows box, but:

  - Is 'htar' a good enough 'tar' replacement for cabal?
  - Does cabal-install also require an external tar? You could try cabal 
 sdist

If one actually reads the discussion in the ticket, it is clear that
the conclusion was to have cabal-install handle it and that
cabal-install uses it's own tar implementation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] List spine traversal

2009-06-28 Thread Tony Morris
Is there a canonical function for traversing the spine of a list?

I could use e.g. (seq . length) but this feels dirty, so I have foldl'
(const . const $ ()) () which still doesn't feel right. What's the
typical means of doing this?


-- 
Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] parallel haskell

2009-06-28 Thread Don Stewart
k2msmith:
 I'm interested in doing some research with parallel programming using Haskell
 (both multi-core on one machine and clusters using multiple machines) but in
 going through the various resources on the web (looking at GPH and others), it
 is not clear to me what the current state is as many of the resources/projects
 have out of date information in them.
 
 Any pointers ?  What parallel extensions are available in the current version
 6.10.3 ?  Which parallel extensions support clustered networks ?  Where to
 start ?

A broad overview of all the abstractions available:

 
http://haskell.org/haskellwiki/Applications_and_libraries/Concurrency_and_parallelism

Obviously, the most heavily used are those for shared-memory multicore
implemented and shipping with GHC (see e.g. the new rts papers). Things
like sparks, STM, MVars, and to some extent nested data parallelism, are
just there, out of the box.

A good paper on the rts support in GHC.


http://ghcmutterings.wordpress.com/2009/03/03/new-paper-runtime-support-for-multicore-haskell/

Followed by hackage libraries for different things (like actors).

Transparently distributed Haskell's are researchy, and someone else
should fill in the story there.

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


[Haskell-cafe] Haskell Platform + gtk2hs

2009-06-28 Thread John Van Enk
List,

Has any one managed to install gtk2hs on a Windows box running the
Haskell Platform? I've had no luck; it seems the gtk2hs installer is
unable to find the GHC installation.

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


[Haskell-cafe] How to convert CPid to Word32?

2009-06-28 Thread Magicloud Magiclouds
Hi,
  I am trying to use Data.Binary with ProcessID. Well, how to convert
between CPid and Word32?
  Thanks.

-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to convert CPid to Word32?

2009-06-28 Thread Thomas DuBuisson
fromIntegral should do the trick.

Thomas

On Sun, Jun 28, 2009 at 7:48 PM, Magicloud
Magicloudsmagicloud.magiclo...@gmail.com wrote:
 Hi,
  I am trying to use Data.Binary with ProcessID. Well, how to convert
 between CPid and Word32?
  Thanks.

 --
 竹密岂妨流水过
 山高哪阻野云飞

 ___
 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