Re: [Haskell-cafe] Parsec float

2009-05-31 Thread wren ng thornton

Jason Dusek wrote:

2009/05/30 Bartosz Wójcik :

...reading RWH I could not memorize what those liftM funtions
meant.


  The basic one, `liftM`, means `fmap`, though specialized for
  functors that are monads.

Prelude Control.Monad> :t liftM
liftM :: forall a b (m :: * -> *). (Monad m) => (a -> b) -> m a -> m b
Prelude Control.Monad> :t fmap
fmap :: forall a b (f :: * -> *). (Functor f) => (a -> b) -> f a -> f b



Category theoretically, all the following are (or should be!) equal: 
fmap, (<$>), liftA, liftM.


Type theoretically, they differ in whether they require Functor, 
Applicative, or Monad. Unfortunately there's a clash between the current 
types and their CT backing. That is, Monad doesn't require Applicative 
(or Functor), so people will often use liftM to avoid extra type 
constraints.


Operationally, fmap and (<$>) are potentially more efficient. The liftA 
and liftM functions re-engineer fmap by using pure/(<*>) or return/ap, 
thanks to CT. The (<$>) function is just an alias for fmap. But the fmap 
function is part of a type class and so it may have a specific 
implementation which is more efficient than the generic one provided by CT.


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


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Derek Elkins
On Sat, May 30, 2009 at 1:12 PM, Jason Dusek  wrote:
> 2009/05/30 Bartosz Wójcik :
>> ...reading RWH I could not memorize what those liftM funtions
>> meant.
>
>  The basic one, `liftM`, means `fmap`, though specialized for
>  functors that are monads.
>
>    Prelude Control.Monad> :t liftM
>    liftM :: forall a b (m :: * -> *). (Monad m) => (a -> b) -> m a -> m b
>    Prelude Control.Monad> :t fmap
>    fmap :: forall a b (f :: * -> *). (Functor f) => (a -> b) -> f a -> f b
>
>  I think we have `liftM` either to help the inferencer or due
>  to the absence of a `(Functor m)` constraint in the definition
>  of the `Monad` typeclass.

It's the latter effectively.  liftM doesn't make anything easier for
the type checker.  liftM simply has a different type than fmap, not a
more specialized one, but even if Monad did have a Functor constraint,
liftM would still never lead to any ambiguity being resolved.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Jason Dusek
2009/05/30 Bartosz Wójcik :
> ...reading RWH I could not memorize what those liftM funtions
> meant.

  The basic one, `liftM`, means `fmap`, though specialized for
  functors that are monads.

Prelude Control.Monad> :t liftM
liftM :: forall a b (m :: * -> *). (Monad m) => (a -> b) -> m a -> m b
Prelude Control.Monad> :t fmap
fmap :: forall a b (f :: * -> *). (Functor f) => (a -> b) -> f a -> f b

  I think we have `liftM` either to help the inferencer or due
  to the absence of a `(Functor m)` constraint in the definition
  of the `Monad` typeclass.

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


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Bartosz Wójcik
On Saturday 30 May 2009 03:10:11 Bryan O'Sullivan wrote:
> On Fri, May 29, 2009 at 5:04 PM, Bartosz Wójcik  wrote:
> > I don't undersdand what is being missed.
>
> Brevity.
>
> > liftM f m1  = do { x1 <- m1; return (f x1) }
> > so
> > liftM fromIntegral integer
> > will result the same.
>
> Yes, and there's less code to read if you use liftM or <$>, hence fewer
> moving parts to understand.

OK, thats clear.  BTW: reading RWH I could not memorize what those liftM 
funtions meant. 
Best,
Bartek


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


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Bryan O'Sullivan
On Fri, May 29, 2009 at 5:04 PM, Bartosz Wójcik  wrote:


> I don't undersdand what is being missed.
>

Brevity.


> liftM f m1  = do { x1 <- m1; return (f x1) }
> so
> liftM fromIntegral integer
> will result the same.


Yes, and there's less code to read if you use liftM or <$>, hence fewer
moving parts to understand.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Derek Elkins
On Fri, May 29, 2009 at 4:02 AM, Tillmann Vogt
 wrote:
> Bartosz Wójcik wrote:
>>
>> Hi Everybody (especially Parsec Creator),
>>
>> is there any reason why float parses only positive numbers?
>>
>> I find following defition:
>>
>> float           = lexeme floating    "float"
>>
>> floating        = do{ n <- decimal
>>                        ; fractExponent n
>>                        }
>>
>> If floating was defined like
>>
>> floating        = do{ n <- integer ...
>>
>> or
>>
>> floating        = do{ n <- int ...
>>
>> instead  then it would parse negative ones as well.
>>
>
> Hi Bartek,
>
> I had the same problem. Daan Leijen gave me a similar answer than Malcom
> Wallace just gave you:
>
> "Usually the minus sign is treated as an operator in the language and
> treated as a separate token"

There's a more pointed reason related to the ones given.  If the float
parser parses signed floats, what then do you do when you want to
parse unsigned floats?  It's trivial to go the one way, it's less
trivial to go the other way.

Incidentally, I'd probably write something like
((try $ negate <$ char '-') <|> pure id) <*> float -- untested
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread David Menendez
On Fri, May 29, 2009 at 8:04 PM, Bartosz Wójcik  wrote:
> On Friday 29 May 2009 22:10:51 Bryan O'Sullivan wrote:
>> > myFloat = try (symbol "-" >> float >>= return . negate)
>> >     <|>  try float
>> >     <|>  (integer >>= return . fromIntegral)
>>
>> Any time you see ">>= return .", something is being missed. Use liftM or
>> <$> instead, i.e. "fromIntegral <$> integer" instead of "integer >>= return
>> . fromIntegral".
>
> I don't undersdand what is being missed.
>
> liftM f m1              = do { x1 <- m1; return (f x1) }
> so
> liftM fromIntegral integer
> will result the same. Is it then not just a convenience?

For some monads, fmap (or <$>) has a more efficient definition than
liftM. Otherwise, it's just a style thing.

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Daniel Fischer
Am Samstag 30 Mai 2009 02:04:29 schrieb Bartosz Wójcik:
> On Friday 29 May 2009 22:10:51 Bryan O'Sullivan wrote:
> > > myFloat = try (symbol "-" >> float >>= return . negate)
> > > <|>  try float
> > > <|>  (integer >>= return . fromIntegral)
> >
> > Any time you see ">>= return .", something is being missed. Use liftM or
> > <$> instead, i.e. "fromIntegral <$> integer" instead of "integer >>=
> > return . fromIntegral".
>
> I don't undersdand what is being missed.
>
> liftM f m1  = do { x1 <- m1; return (f x1) }
> so
> liftM fromIntegral integer
> will result the same. Is it then not just a convenience?

Even, desugaring the definition of liftM, we get

liftM f m1 = m1 >>= return . f

or, eta-reducing,

liftM  f= (>>= return . f)

It's a matter of style and readability.
>
> Bartek

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


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Bartosz Wójcik
On Friday 29 May 2009 22:10:51 Bryan O'Sullivan wrote:
> > myFloat = try (symbol "-" >> float >>= return . negate)
> > <|>  try float
> > <|>  (integer >>= return . fromIntegral)
>
> Any time you see ">>= return .", something is being missed. Use liftM or
> <$> instead, i.e. "fromIntegral <$> integer" instead of "integer >>= return
> . fromIntegral".

I don't undersdand what is being missed.

liftM f m1  = do { x1 <- m1; return (f x1) }
so 
liftM fromIntegral integer 
will result the same. Is it then not just a convenience?

Bartek


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


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Bryan O'Sullivan
On Fri, May 29, 2009 at 3:38 PM, Bartosz Wójcik  wrote:

> Thank you, this is an easy and nice solution. I've made it a bit prettier
> optically:
>
> myFloat = try (symbol "-" >> float >>= return . negate)
> <|>  try float
> <|>  (integer >>= return . fromIntegral)
>

Any time you see ">>= return .", something is being missed. Use liftM or <$>
instead, i.e. "fromIntegral <$> integer" instead of "integer >>= return .
fromIntegral".
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Bartosz Wójcik
On Friday 29 May 2009 08:34:36 you wrote:
> myfloat = try (do{ symbol "-"; n <- float; return (negate n) }) <|>
>            try float <|>
>                do { i<-integer; return(fromIntegral i) }

Thank you, this is an easy and nice solution. I've made it a bit prettier 
optically:

myFloat = try (symbol "-" >> float >>= return . negate) 
 <|>  try float 
 <|>  (integer >>= return . fromIntegral)

Best regards,
Bartek


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


Re: [Haskell-cafe] Parsec float

2009-05-29 Thread Tillmann Vogt

Bartosz Wójcik wrote:

Hi Everybody (especially Parsec Creator),

is there any reason why float parses only positive numbers?

I find following defition:

float   = lexeme floating"float"

floating= do{ n <- decimal
; fractExponent n
}

If floating was defined like

floating= do{ n <- integer ...

or

floating= do{ n <- int ...

instead  then it would parse negative ones as well.  

  


Hi Bartek,

I had the same problem. Daan Leijen gave me a similar answer than Malcom 
Wallace just gave you:


"Usually the minus sign is treated as an operator in the language and treated as a 
separate token"

He also gave me a workaround which finally resulted in this:

myfloat = try (do{ symbol "-"; n <- float; return (negate n) }) <|>

 try float <|>

 do { i<-integer; return(fromIntegral i) } -- 0 is not 
recognized as a float, so recognize it as an integer and then convert it 
to float




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


[Haskell-cafe] Parsec float

2009-05-28 Thread Malcolm Wallace

is there any reason why float parses only positive numbers?


It is usual in parsing libraries to separate the recognition of a  
leading sign from recognition of the number itself: the sign-only  
parser can be reused in many contexts,  e.g. in the Haskell'98 Numeric  
library, there is


 readSigned :: Real a => ReadS a -> ReadS a

which takes a secondary parser as its argument.  You can instantiate  
that argument to any of


 readDec   :: Num a => ReadS a
 readHex   :: Num a => ReadS a
 readFloat :: Num a => ReadS a

etc.  I do not know if the equivalent of "readSigned" exists in  
Parsec, but it in polyparse's Text.Parse module, it is called  
"parseSigned", rather unsurprisingly.


Regards,
Malcolm

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


[Haskell-cafe] Parsec float

2009-05-28 Thread Bartosz Wójcik
Hi Everybody (especially Parsec Creator),

is there any reason why float parses only positive numbers?

I find following defition:

float   = lexeme floating"float"

floating= do{ n <- decimal
; fractExponent n
}

If floating was defined like

floating= do{ n <- integer ...

or

floating= do{ n <- int ...

instead  then it would parse negative ones as well.  

Best regards,
Bartek


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