Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 2:31:28 pm Jeremy Yallop wrote:
> Why does compiling the following program give an error?
>
> > {-# LANGUAGE TypeFamilies, RankNTypes #-}
> >
> > type family TF a
> >
> > identity :: (forall a. TF a) -> (forall a. TF a)
> > identity x = x
>
> GHC 6.10.3 gives me:
>
>  Couldn't match expected type `TF a1' against inferred type `TF a'
>  In the expression: x
>  In the definition of `identity': identity x = x

It has to do with the way that type families are checked, and the fact that 
they aren't guaranteed to be injective. You can massage the type to look like:

  identity :: forall b. (forall a. TF a) -> TF b

Which means that the caller gives us a 'b' and a 'forall a. TF a', and wants 
us to return a 'TF b'. That sounds fine, but when GHC goes to check things, 
things go awry. It instantiates things something like...

  x :: TF c (for some fresh c)
  TF c ~ TF b (this constraint must be solved for the return type to work)

However, since type families aren't necessarily injective, it can't deduce

  c ~ b

since there might well be distinct 'b' and 'c' such that 'TF b ~ TF c'. So, it 
fails to come to the conclusion that:

  x :: TF b

which is what is actually needed for the function as a whole to type. Thus, 
checking fails. I think that's a reasonably accurate description of the 
process; if not someone will probably correct me.

One could imagine extensions to solve this. For instance, if you could 
(optionally) do something like:

  ident...@b x = x...@b

to specifically apply the type variables, the compiler might have an easier 
time accepting such things. You can fake it now by having non-family types fix 
the variable:

  data Witness a -- = W -- if you don't like empty types

  identity :: (forall a. Witness a -> TF a) -> (forall a. Witness a -> TF a)
  identity x w = x w

This will be accepted, because inference/checking for Witness provides enough 
information to deduce the 'c ~ b' above. But of course, it's somewhat less 
than ideal.

Hope that helps.

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


Re: [Haskell-cafe] Text.JSON, Speed and Bytestrings

2009-07-11 Thread Don Stewart
mxcantor:
> Hi Cafe,
>
> I am using the Text.JSON library to [un]marshall messages passed over  
> the network and was wondering if the speed would be significantly  
> improved by either changing the code or adding a module to implement the 
> same functionality using Bytestrings instead of classical strings?  If 
> the consensus is that it would be worth it, I'll look into adding that 
> code..
>

I think porting the parsec-based JSON parser in the json package
to attoparsec + bytestrings would be easy and useful.

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


Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Roman Cheplyaka
* Brandon S. Allbery KF8NH  [2009-07-11 17:01:35-0400]
> On Jul 11, 2009, at 14:31 , Jeremy Yallop wrote:
>> Why does compiling the following program give an error?
>>
>>> {-# LANGUAGE TypeFamilies, RankNTypes #-}
>>>
>>> type family TF a
>>>
>>> identity :: (forall a. TF a) -> (forall a. TF a)
>>> identity x = x
>
>
> The scope of each a is the surrounding parentheses, so the de facto type 
> is TF a -> TF b.  Or, put otherwise, you're saying that for *any* type (TF 
> a)

No, for any (forall a. TF a), which should make the difference.

> you can produce *any* type (TF a) (because of the delimited forall-s), 
> but then the code asserts that they are the same type.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
"Don't let school get in the way of your education." - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Brandon S. Allbery KF8NH

On Jul 11, 2009, at 14:31 , Jeremy Yallop wrote:

Why does compiling the following program give an error?


{-# LANGUAGE TypeFamilies, RankNTypes #-}

type family TF a

identity :: (forall a. TF a) -> (forall a. TF a)
identity x = x



The scope of each a is the surrounding parentheses, so the de facto  
type is TF a -> TF b.  Or, put otherwise, you're saying that for *any*  
type (TF a) you can produce *any* type (TF a) (because of the  
delimited forall-s), but then the code asserts that they are the same  
type.


--
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] About the return type

2009-07-11 Thread Brent Yorgey
On Thu, Jul 09, 2009 at 10:57:19AM -0400, xu zhang wrote:
> I have trouble in returning a list of Figures. I want return a type of m
> (Maybe [Figure IO]), but the type of dv_findFigure is :: a -> Point -> s
> (Maybe (Figure s)). How can change the code below to get a s (Maybe [Figure
> s])?
> Thank you in advance!
> 
>  dv_findFigure :: a -> Point -> s (Maybe (Figures))
>  fig_contains :: fig -> Point -> m Bool
>  anc :: Point
> do
>  fs <- dv_getSelFigs dv
>  fs' <- filterM (`fig_contains` anc) fs
>  f <- case fs' of
> [] -> dv_findFigure dv anc
> fig : _ -> return $ Just fig
>  case f of
>Just f' -> tool_dragtrack self f'
>Nothing -> dv_clearSel dv >> tool_areatrack self
> 
>   Couldn't match expected type `Figure m'
>against inferred type `[Figure IO]'
>   Expected type: m (Maybe (Figure m))
>   Inferred type: m (Maybe [Figure IO])
> In the expression: return $ Just fs
> In a case alternative: fig : _ -> return $ Just fs

I'm not sure what you're trying to do here, and the code you gave does
not match the error message (the error message cites the code 'fig : _
-> return $ Just fs', but the code you gave has a line 'fig : _ ->
return $ Just fig'.)  If you still need help, can you provide a more
detailed explanation of what this code is supposed to do, and an
up-to-date version of the code and error message?

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


Re: [Haskell-cafe] following up on space leak

2009-07-11 Thread Uwe Hollerbach
Hi, George, thanks for the pointer, it led me to some interesting
reading. Alas, the problem which it solves was already solved, and the
unsolved problem didn't yield any further...

At this point, I've concluded that my interpreter just simply isn't
tail-recursive enough: in the Collatz test case I had originally
looked at and mentioned, it seems that no matter what I do the memory
usage stays the same. Initially, a significant portion of the usage
showed up as one particular function in the interpreter which applies
binary numerical operators to a list of numbers. It's a moderately
complex function, as it deals with any number of operands, and it
takes care of type conversions as well: if I add two integers, I want
the result to be an integer; if I add in a float, the result will be a
float, etc.

In my particular usage in this test case, it was only getting used to
increment an integer; so I simplified that, I added an "incr" function
to my interpreter and called that instead... now exactly the same
amount of memory usage shows up in the cost center labeled "incr" as
was previously being used in the more-complex numeric-binary-operator
function. I've cut down the interpreter to about a quarter of its
original size, now I've got a version that really is only useful for
running this Collatz test case, and... it uses exactly the same amount
of memory as before.

The last thing I tried before giving up was to try and make a
more-strict bind operator, I think I wrote that as

(!>=) !m !k = m >>= k

with appropriate -XBangPatterns added to the compiler options. It
passed all the self-tests for the interpreter, so I'm pretty sure I
didn't do anything wrong, but it made no difference to the memory
usage. So for now I've shelved that problem, I'm looking instead at
adding proper continuations to the interpreter.

Uwe

On 7/7/09, George Pollard  wrote:
> I believe there might be an elegant solution for this using the `Last`
> monoid
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Colour tutorial (Was: AC-Vector, AC-Colour and AC-EasyRaster-GTK)

2009-07-11 Thread Derek Elkins
On Sat, Jul 11, 2009 at 12:54 PM, Derek Elkins wrote:
> On Fri, Jul 10, 2009 at 12:42 AM,  wrote:
>> On Thu, 9 Jul 2009, rocon...@theorem.ca wrote:
>>
>>> You can use by lib without worrying about the CIE.  You can use my library
>>> without ever importing or using the word CIE.  However, the CIE stuff is
>>> there for those who need it.
>>>
>>> Perhaps I (maybe with some help) need to make a tutorial on the haskell
>>> wiki to try to make it less intimidating.
>>
>> Okay, I threw together a quick introduction at
>> .  Any changes, comments,
>> corrections, and addtions are welcome.  It's a wiki!
>>
>> The word CIE does occur at all in the document.
>
> I read this and it irks me that opaque is not a monoid homomorphism
> despite being the natural injection of non-transparent colours into
> semi-transparent colours with pureColour being the projection back.
> [Incidentally, you have a typo in pureColour, ac `over` mempty should
> be ac `over` black or opaque black presumably, or even opaque mempty,
> which I think was what you were going for, illustrating my point.]
> It's like defining mappend on Integers as (+) and on Reals as (*);
> actually, I think this is very close to what is actually happening.

I'm mistaken about the typo in pureColour, but luckily the mistake
just further illustrates my point.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Jeremy Yallop

Why does compiling the following program give an error?


{-# LANGUAGE TypeFamilies, RankNTypes #-}

type family TF a

identity :: (forall a. TF a) -> (forall a. TF a)
identity x = x


GHC 6.10.3 gives me:

Couldn't match expected type `TF a1' against inferred type `TF a'
In the expression: x
In the definition of `identity': identity x = x


--
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

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


Re: [Haskell-cafe] Colour tutorial (Was: AC-Vector, AC-Colour and AC-EasyRaster-GTK)

2009-07-11 Thread Derek Elkins
On Fri, Jul 10, 2009 at 12:42 AM,  wrote:
> On Thu, 9 Jul 2009, rocon...@theorem.ca wrote:
>
>> You can use by lib without worrying about the CIE.  You can use my library
>> without ever importing or using the word CIE.  However, the CIE stuff is
>> there for those who need it.
>>
>> Perhaps I (maybe with some help) need to make a tutorial on the haskell
>> wiki to try to make it less intimidating.
>
> Okay, I threw together a quick introduction at
> .  Any changes, comments,
> corrections, and addtions are welcome.  It's a wiki!
>
> The word CIE does occur at all in the document.

I read this and it irks me that opaque is not a monoid homomorphism
despite being the natural injection of non-transparent colours into
semi-transparent colours with pureColour being the projection back.
[Incidentally, you have a typo in pureColour, ac `over` mempty should
be ac `over` black or opaque black presumably, or even opaque mempty,
which I think was what you were going for, illustrating my point.]
It's like defining mappend on Integers as (+) and on Reals as (*);
actually, I think this is very close to what is actually happening.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] get cabal info for self?

2009-07-11 Thread Keith Sheppard
That's perfect. Thanks!

On Sat, Jul 11, 2009 at 12:10 AM, Gwern Branwen wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA512
>
> On Fri, Jul 10, 2009 at 11:46 PM, Keith Sheppard wrote:
>> Is there a way for a cabalized program to get its own info. I'm
>> specifically interested in version info.
>>
>> Thanks
>> Keith
>>
>
> Sure, via the Paths_* mechanism. For your reference, here's what it
> looks like for xmonad:
>
> module Paths_xmonad (
>    version,
>    getBinDir, getLibDir, getDataDir, getLibexecDir,
>    getDataFileName
>  ) where
>
> import Data.Version (Version(..))
> import System.Environment (getEnv)
>
> version :: Version
> version = Version {versionBranch = [0,8,1], versionTags = []}
>
> bindir, libdir, datadir, libexecdir :: FilePath
>
> bindir     = "/home/gwern/bin/bin"
> libdir     = "/home/gwern/bin/lib/xmonad-0.8.1/ghc-6.10.2"
> datadir    = "/home/gwern/bin/share/xmonad-0.8.1"
> libexecdir = "/home/gwern/bin/libexec"
>
> getBinDir, getLibDir, getDataDir, getLibexecDir :: IO FilePath
> getBinDir = catch (getEnv "xmonad_bindir") (\_ -> return bindir)
> getLibDir = catch (getEnv "xmonad_libdir") (\_ -> return libdir)
> getDataDir = catch (getEnv "xmonad_datadir") (\_ -> return datadir)
> getLibexecDir = catch (getEnv "xmonad_libexecdir") (\_ -> return libexecdir)
>
> getDataFileName :: FilePath -> IO FilePath
> getDataFileName name = do
>  dir <- getDataDir
>  return (dir ++ "/" ++ name)
>
> So if you wanted the version number "081", you could do something like
> 'concatMap show $ versionBranch $ version'
>
> - --
> gwern
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.9 (GNU/Linux)
>
> iEYEAREKAAYFAkpYD98ACgkQvpDo5Pfl1oI6gACZATzqwtJgBFhAl/qo0ZPauqhg
> zBcAnRdHtv5nFzNAo2Z9ulHdW1DxiJBE
> =XyEM
> -END PGP SIGNATURE-
>



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


[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-11 Thread Heinrich Apfelmus
Matthias Görgens wrote:
> Thanks.  I heard about the hylo-, ana- and catamorphisms before, but
> never explicitly used them.  Time to get started.

You did use them explicitly :) , namely in

  treeSort = bootstrap partitionOnMedian
  bootstrap f = Fix . helper . f
  where helper = fmap (Fix . helper . f)

  partitionOnMedian :: (Ord a) => (S.Seq a) -> BTreeRaw a (S.Seq a)

since

  bootstrap f = ana f

In particular, we have this slight reformulation

  bootstrap f = helper'
 where
 helper  = fmap helper'
 helper' = Fix . helper . f

and hence

  bootstrap f = helper'
 where helper' = Fix . fmap helper' . f

and thus

  bootstrap f = Fix . fmap (bootstrap f) . f

which is the definition of  ana f .


> And yet another question: One can get the median in deterministic
> linear time.  For quicksort choosing the median as pivot keeps the O(n
> log n) average running time and brings down the expected worst case,
> too.  Do you know of a (natural) way to combine selecting the median
> and doing the quicksort, so that you don't compare unnecessarily?
>
> The way to de-randomize quickselect is to calculate medians of
> medians.  I.e. solve the problem for smaller instances first.  I
> suspect if we follow this strategy with the reified quicksort
> call-trees, the de-randomized quicksort will look a lot like
> mergesort.

Interesting question! (Of which I don't know the answer of. ;) )

I never understood the median of median method because I always thought
that it calculates an approximate median of approximate medians, which I
now realize is not the case. I concur that there should be something
better than "recursively wasting" comparisons in quickselect just for
finding the median pivot in quicksort, especially since both are the
same algorithm modulo lazy evaluation.

Concerning quicksort looking like mergesort, it seems like a good idea
to somehow merge the groups of 5 from the median-of-medians calculation.
However, there is an important difference between quicksort and
mergesort, namely lazy quicksort is able to produce the batch of the
first k smallest elements in

  O(n + k log k) total time [1]

while lazy mergesort needs

  O(n + k log n) total time [2]

There is something about quicksort that makes it "better" than mergesort.


[1] Proof goes like this: First, quicksort chooses a sublist of smallest
items recursively until a list of the smallest k items remains, this
takes O(n) time. Then the list consisting of the smallest k items is
sorted in Θ(k log k).

[2] Mergesort builds a tournament tree in Θ(n) time and then performs k
tournaments that take O(log n) time each, so the the second phase is O(k
log n).

I need to think about this.



Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Flipping *->*->* kinds, or monadic finally-tagless madness

2009-07-11 Thread Kim-Ee Yeoh

>Kim-Ee Yeoh wrote:
>> As for fixing the original bug, I've found that the real magic lies
>> in the incantation (Y . unY) inserted at the appropriate places.

>Aka unsafeCoerce, changing the phantom type |a|.

The type of (Y . unY) is 

(Y . unY) :: forall a b c. Y c a -> Y c b

so modulo (Y c), it is indeed unsafeCoerce.

>The need to do it is caused by wanting to erase the existential introduced 
>by Za/MkZa. 

That's not the primary reason. The earlier version of the code
in my original message doesn't use existentials. We still however,
need to "wobble" the type via (Y . unY) in order to typecheck.

>Depending on what the phantom type is supposed to represent, this may or 
>may not give the semantics/safety you're after.

If you're referring to the safety of the object/target language, then even
without any Symantics instances, only type-correct code can compile,
thanks to the finally-tagless embedding that "lifts" type-checking in
the meta-language (Haskell) into type-checking for the target language.

That safety isn't in the least bit compromised.

The pretty-printing Symantics instance in question actually 
type-checks fine without unsafeCoerce or its like when written out
without the additional Monad type-class abstraction and Y-Z 
isomorphism. Translating to the latter was entirely straightforward.

Thanks to all who responded.

-- 
View this message in context: 
http://www.nabble.com/Flipping-*-%3E*-%3E*-kinds%2C-or-monadic-finally-tagless-madness-tp24314553p24439023.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


[Haskell-cafe] Re: ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-11 Thread Jon Fairbairn
Wolfgang Jeltsch  writes:

> Am Freitag, 10. Juli 2009 05:26 schrieb rocon...@theorem.ca:
>> I find it amazing that you independently chose to spell colour with a `u'.
>> It makes me feel better about my choice.
>
> I have to admit that it makes me unhappy. :-( 
>
> Why do we use English for identifiers? Because English is the language
> of computer science. What English should we use? It’s tempting to say,
> we should use the original English, which is British English. But we
> should ask again what is the language of computer science. And the
> language of computer science is American English.

I don't buy that. And don't forget India.

> To my knowledge, most early developments in computer science had their roots 
> in the US.

Really? Manchester Mark I, EDSAC I, EDSAC II? Alan Turing, David
Wheeler, Maurice Wilkes? To mention a random selection of early ones
(leaving aside Konrad Zuse and colleagues and various Russian pioneers
on account of not speaking English).

> One consequence of this is that reserved words of programming 
> languages are typically in American English. PASCAL uses “program”,

The use of "program" rather than "programme" in programming was mandated
by the IFIP in what I regard as an attempt to act outwith their remit.
I've never accepted it.

> not “programme”, and BASIC uses “COLOR”, not “COLOUR”.

I'm not sure I would use BASIC as an authority for any aspect of
programming language design. Going back to the early developments
aspect, a high proportion of early work in functional programming was
done in Britain and elsewhere in Europe (at a time when Europeans
typically preferred British spellings), so perhaps one should recognise
that in choosing identifiers.

But anyway, where's the harm in a bit of variety? If someone who prefers
British spellings originates a package, why get het up about it if they
use them in identifiers? I have to put up with American spellings all
over the place, so a few British spellings might even up the balance a
bit.

-- 
Jón Fairbairn (British, but with a tendency to identify myself as
European)


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


Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Malcolm Wallace

Johan Tibell wrote:

[...]

I also think void is clearer than ignore.


So do I. Another point is, that it's familiar from other languages; a
function "void f(...)" doesn't return anything but may have an  
effect on

the environment.


+1.

Regards,
Malcolm

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


Re: [Haskell-cafe] [Haskell Cafe] Parsec: buildExpressionParser and parens typecheck problem

2009-07-11 Thread Bas van Gijzel
Hello Paul,

As far as I can see you're calling the parens accessor function of the
TokenParser record instead of supplying a parser. Here is a working example
grammar I made for my bachelor paper a while ago:

module ExpressionsWithLexer where
import Text.ParserCombinators.Parsec.Expr
import Text.ParserCombinators.Parsec
import qualified Text.ParserCombinators.Parsec.Token as P
import Text.ParserCombinators.Parsec.Language


{-
Leftassociative: +, -, *, /
Rightassociative: ^
Priority 1: +,-
Priority 2: *, /
Priority 3: ^

expr   ::= factor (op factor)*
factor ::= number | '(' expr ')'

op ::= '+' | '-' | '*' | '/' | '^'

number ::= ('0' | '1' | ... | '9')+
-}

lexer :: P.TokenParser ()
lexer = P.makeTokenParser
(emptyDef
{ reservedOpNames = ["*","/","+","-", "^"]
})

whiteSpace= P.whiteSpace lexer
natural = P.natural lexer
parens = P.parens lexer
reservedOp = P.reservedOp lexer

gram   = do  whiteSpace
 x <- expr
 eof
 return x

expr :: Parser Integer
expr = buildExpressionParser table factor
"expression"

-- Earlier in the list means a higher priority
table = [[op "^" (^) AssocRight]
,[op "*" (*) AssocLeft, op "/" div AssocLeft]
,[op "+" (+) AssocLeft, op "-" (-) AssocLeft]
]
   where op s f assoc = Infix (do{ reservedOp s; return f} 
"operator") assoc


factor = natural
 <|>
 (parens expr
   "factor")

run :: Show a => Parser a -> String -> IO ()
run p input
   = case (parse p "" input) of
   Left err -> do{ putStr "parse error at "
; print err
}
   Right x -> print x

exampleRun = run gram "(10 ^3 - (1 + 3))"


This grammar parses the EBNF like grammar included in the source.

As you can see parens is an accessor function of the TokenParser record. A
TokenParser record is thus produced by calling makeTokenParser and supplying
that function with a language definition. I used the emptyDef (empty
definition) as an argument for the makeTokenParser and only updated the
operatornames. After constructing a TokenParser parsers such as parens are
accessed by their accessor functions. For ease of use you can use a
qualified import for the token parser module and define the parens parser
and other parsers at toplevel like I did.

I only tested this with Parsec 2.1.0.1 but the idea should be the same. You
can read some more explanations and examples in my bachelor paper if you'd
like[1][2].

Good luck,

Bas van Gijzel

(server is currently down :( )
[1] Comparing Parser Construction Techniques:
http://referaat.cs.utwente.nl/new/papers.php?confid=12
[2] Parser Code:
http://fmt.cs.utwente.nl/~michaelw/projects/vgijzel/ParserCode.zip

On Sat, Jul 11, 2009 at 00:27, Paul Sujkov  wrote:

> Hi haskellers,
>
> I'm trying to use buildExpressionParser parser generator from ParsecExpr
> module of Parsec (
> http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#ParsecExpr). It
> works well, except for the "parens" token parser (
> http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#parens). This code
> (sample from Expressions part of the manual) typechecks fine:
>
> expr:: Parser Integer
> expr= buildExpressionParser table factor
>  "expression"
>
> table   = [[op "*" (*) AssocLeft, op "/" div AssocLeft]
>   ,[op "+" (+) AssocLeft, op "-" (-) AssocLeft]
>   ]
> where
>   op s f assoc
>  = Infix (do{ string s; return f}) assoc
>
>
> factor  = do{ char '('
> ; x <- expr
> ; char ')'
> ; return x
> }
> <|> number
>  "simple expression"
>
> but if I try to use parens:
>
> factor  = parens expr
> <|> number
>  "simple expression"
>
> it fails to typecheck:
>
> Couldn't match expected type `GenTokenParser s u m'
>against inferred type `Parser Integer'
> In the first argument of `parens', namely `expr'
> In the first argument of `(<|>)', namely `parens expr'
> In the first argument of `()', namely `parens expr <|> number'
> Failed, modules loaded: none.
>
> the type of expr infers to GenParser Char () Integer, and the expected type
> for the parens is GenTokenParser s u m (however, manual introduces it with
> the type CharParser st a expected)
>
> It seems pretty weird for me, as there are numerous examples of using
> parens with the buildExpressionParser (e.g.
> http://blog.moertel.com/articles/2005/08/27/power-parsing-with-haskell-and-parsec)
> and nobody comments such an error. I know I'm missing something very simple
> here, maybe someone could help me with it? Thanks in advace
>
> I'm using GHC 6.10.1 and Parsec 3.0.0
>
> --
> Regards, Paul Sujkov
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Stephan Friedrichs
Johan Tibell wrote:
> [...]
> 
> I also think void is clearer than ignore.

So do I. Another point is, that it's familiar from other languages; a
function "void f(...)" doesn't return anything but may have an effect on
the environment.

Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 3:35:27 am Jeff Wheeler wrote:
> On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote:
> >> ## Control.Monad.void m a -> m ()
> >> Don Stewart
> >> Iavor Diatchki
>
> For whatever it's worth, I prefer void as well, for the exact reason
> Don said. Indeed, 'ignore' indicates to me that the argument won't
> even be evaluated: it'll be ignored, and skipped. But it is, and only
> part --- the result --- is ignored.
>
> What about 'void' with functors?

Perhaps it should be noted that 'void' is sometimes associated with the type:

  data Void

the 'empty' type (which isn't empty in Haskell). In typical catamorphism 
style, void would be its eliminator:

  void :: forall a. Void -> a
  void _ = undefined
  -- if you're writing Agda
  -- void ()

This, doesn't see much use in Haskell, though, so perhaps it's irrelevant.

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


Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Johan Tibell
On Sat, Jul 11, 2009 at 9:35 AM, Jeff Wheeler  wrote:

> On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote:
>
> >> ## Control.Monad.void m a -> m ()
> >> Don Stewart
> >> Iavor Diatchki
>
> For whatever it's worth, I prefer void as well, for the exact reason
> Don said. Indeed, 'ignore' indicates to me that the argument won't
> even be evaluated: it'll be ignored, and skipped. But it is, and only
> part --- the result --- is ignored.
>

I also think void is clearer than ignore.

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


[Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Jeff Wheeler
On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote:

>> ## Control.Monad.void m a -> m ()
>> Don Stewart
>> Iavor Diatchki

For whatever it's worth, I prefer void as well, for the exact reason
Don said. Indeed, 'ignore' indicates to me that the argument won't
even be evaluated: it'll be ignored, and skipped. But it is, and only
part --- the result --- is ignored.

What about 'void' with functors?

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