
I was doing the following: do status <- mapM PF.getFileStatus filenames let times = map PF.modificationTime status let sorted = sortBy (\(_, t1) (_,t2) -> compare t1 t2) (zip filenames times) and I thought, surely I can combine the status and times definitions into one line, only I can't. Hint ? Thanks, Brian

On 6 May 2010 15:01,
I was doing the following:
do status <- mapM PF.getFileStatus filenames let times = map PF.modificationTime status let sorted = sortBy (\(_, t1) (_,t2) -> compare t1 t2) (zip filenames times)
times <- mapM (liftM PF.modificationTime . PF.getFileStatus) filenames However, I'd be tempted to leave it as is (and hope/assume that fusion does its magic). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Thu, 6 May 2010 15:07:30 +1000
Ivan Miljenovic
On 6 May 2010 15:01,
wrote: I was doing the following:
do status <- mapM PF.getFileStatus filenames let times = map PF.modificationTime status let sorted = sortBy (\(_, t1) (_,t2) -> compare t1 t2) (zip filenames times)
times <- mapM (liftM PF.modificationTime . PF.getFileStatus) filenames
However, I'd be tempted to leave it as is (and hope/assume that fusion does its magic).
well now it's obvious :-) I did have liftM in there, but just couldn't quite figure out how to tie things together. to be completely clear : liftM takes modificationTime from Status -> EpochTime to IO Status -> IO EpochTime so now it can operate on the results of getFileStatus, which returns `IO Status`. mapM gathers the [IO EpochTime] into `IO [EpochTime]` and then <- gives [EpochTime]. It's a little more clear in the verbose form, isn't it ? Thanks ! Brian

On 6 May 2010 15:20,
well now it's obvious :-) I did have liftM in there, but just couldn't quite figure out how to tie things together.
to be completely clear : liftM takes modificationTime from
Status -> EpochTime
to
IO Status -> IO EpochTime
You can see it that way, yes (of course, liftM works on all monads, not just IO).
so now it can operate on the results of getFileStatus, which returns `IO Status`.
Operate directly on the returned values; you could always use something like "(return . modificationTime) =<< getFileStatus file" as well.
mapM gathers the [IO EpochTime] into `IO [EpochTime]` and then <- gives [EpochTime].
No, it's the sequence function that does that (but mapM f = sequence . map f). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like
other IO functions (getLine, putStrLn), it returns an IO action but accepts
a pure value (the modification time)
Also, I like this style:
import Control.Applicative ((<$>))
blah = do
times <- mapM (PF.modificationTime <$> PF.getFileStatus) filenames
...
The <$> operator evaluates to fmap so it's a cleaner way to apply a pure
function to an IO value.
On Thu, May 6, 2010 at 1:20 AM,
On Thu, 6 May 2010 15:07:30 +1000 Ivan Miljenovic
wrote: On 6 May 2010 15:01,
wrote: I was doing the following:
do status <- mapM PF.getFileStatus filenames let times = map PF.modificationTime status let sorted = sortBy (\(_, t1) (_,t2) -> compare t1 t2) (zip filenames times)
times <- mapM (liftM PF.modificationTime . PF.getFileStatus) filenames
However, I'd be tempted to leave it as is (and hope/assume that fusion does its magic).
well now it's obvious :-) I did have liftM in there, but just couldn't quite figure out how to tie things together.
to be completely clear : liftM takes modificationTime from
Status -> EpochTime
to
IO Status -> IO EpochTime
so now it can operate on the results of getFileStatus, which returns `IO Status`.
mapM gathers the [IO EpochTime] into `IO [EpochTime]` and then <- gives [EpochTime].
It's a little more clear in the verbose form, isn't it ?
Thanks !
Brian _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Bill Atkins wrote:
Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time)
Also, I like this style:
import Control.Applicative ((<$>))
blah = do times <- mapM (PF.modificationTime <$> PF.getFileStatus) filenames ...
The <$> operator evaluates to fmap so it's a cleaner way to apply a pure function to an IO value. That won't type-check (unless I've missed some crafty trick with the types?!); you have two functions you want to compose, but the <$> operator (i.e. fmap) applies a function on the left to a functor-value on the right. You would instead need:
times <- mapM ((PF.modificationTime <$>) . PF.getFileStatus) filenames At which point I prefer Ivan's liftM version rather than the above section (or worse: using (<$>) prefix). The original request is a relatively common thing to want to do, so I was slightly surprised that hoogling for: (b -> c) -> (a -> f b) -> a -> f c didn't turn up any relevant results. This function is a lot like (<=<) but with a pure rather than side-effecting function on the left-hand side. Thanks, Neil.

Yep, you and Ben are both correct. Mea culpa and sorry for the bad answer.
Just curious: why does getModificationTime take an IO FileStatus rather than
a FileStatus?
On Thu, May 6, 2010 at 7:00 AM, Neil Brown
Bill Atkins wrote:
Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time)
Also, I like this style:
import Control.Applicative ((<$>))
blah = do times <- mapM (PF.modificationTime <$> PF.getFileStatus) filenames ...
The <$> operator evaluates to fmap so it's a cleaner way to apply a pure function to an IO value.
That won't type-check (unless I've missed some crafty trick with the types?!); you have two functions you want to compose, but the <$> operator (i.e. fmap) applies a function on the left to a functor-value on the right. You would instead need:
times <- mapM ((PF.modificationTime <$>) . PF.getFileStatus) filenames
At which point I prefer Ivan's liftM version rather than the above section (or worse: using (<$>) prefix). The original request is a relatively common thing to want to do, so I was slightly surprised that hoogling for:
(b -> c) -> (a -> f b) -> a -> f c
didn't turn up any relevant results. This function is a lot like (<=<) but with a pure rather than side-effecting function on the left-hand side.
Thanks,
Neil.

On Thu, May 6, 2010 at 12:37 PM, Bill Atkins
Just curious: why does getModificationTime take an IO FileStatus rather than a FileStatus?
It doesn't. getModificationTime is a pure function (think of it like a record accessor). liftM makes it take IO FileStatus because that is what liftM is for :)

On Thu, 06 May 2010 12:00:01 +0100
Neil Brown
At which point I prefer Ivan's liftM version rather than the above section (or worse: using (<$>) prefix). The original request is a relatively common thing to want to do, so I was slightly surprised that hoogling for:
(b -> c) -> (a -> f b) -> a -> f c
didn't turn up any relevant results. This function is a lot like (<=<) but with a pure rather than side-effecting function on the left-hand side.
ha ! I had actually remembered to hoogle :-) and didn't get anything either, only I wasn't sure I put the signature in correctly. Brian

On Thu, May 6, 2010 at 11:51 AM, Bill Atkins
Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time)
ghci> :m +Control.Monad System.Posix.Files ghci> :t liftM modificationTime liftM modificationTime :: (Monad m) => m FileStatus -> m System.Posix.Types.EpochTime where m = IO in this case.
Also, I like this style: import Control.Applicative ((<$>)) blah = do times <- mapM (PF.modificationTime <$> PF.getFileStatus) filenames ... The <$> operator evaluates to fmap so it's a cleaner way to apply a pure function to an IO value.
Usually I'd agree but in fact PF.getFileStatus is not an IO value, but an IO function, so you need to map over its result: mapM ((PF.modificationTime <$>) . PF.getFileStatus) filenames but then you lose the convenience of the <$> as an infix operator, so mapM (liftM PF.modificationTime . PF.getFileStatus) filenames is probably clearer in this case. Or, if you're feeling particularly silly: mapM (fmap fmap fmap modificationTime getFileStatus) filenames

On Thu, 2010-05-06 at 12:09 +0100, Ben Millwood wrote:
On Thu, May 6, 2010 at 11:51 AM, Bill Atkins
wrote: Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time)
ghci> :m +Control.Monad System.Posix.Files ghci> :t liftM modificationTime liftM modificationTime :: (Monad m) => m FileStatus -> m System.Posix.Types.EpochTime
where m = IO in this case.
Also, I like this style: import Control.Applicative ((<$>)) blah = do times <- mapM (PF.modificationTime <$> PF.getFileStatus) filenames ... The <$> operator evaluates to fmap so it's a cleaner way to apply a pure function to an IO value.
Usually I'd agree but in fact PF.getFileStatus is not an IO value, but an IO function, so you need to map over its result:
mapM ((PF.modificationTime <$>) . PF.getFileStatus) filenames
but then you lose the convenience of the <$> as an infix operator, so
mapM (liftM PF.modificationTime . PF.getFileStatus) filenames
is probably clearer in this case. Or, if you're feeling particularly silly:
mapM (fmap fmap fmap modificationTime getFileStatus) filenames
I usually use <.> (IMHO should be in Control.Applicative next to <$>) which is the same to <$> as . is to $: g <.> f = fmap g . f :: Functor f => (b -> c) -> (a -> f b) -> a -> f c times <- mapM (PF.modificationTime <.> PF.getFileStatus) filenames Regards

This way :
do
times<-mapM PF.getFileStatus filenames >>= return.(map PF.modificationTime)
Or also :
do
times<-mapM (PF.getFileStatus >>= (return.(PF.modificationTime))) filenames
let sorted=...
I do not know exactly how ghc compiles the IO monad, but it seems to me that the latter would allocate a little less.
Cheers,
PE
El 06/05/2010, a las 01:01,
I was doing the following:
do status <- mapM PF.getFileStatus filenames let times = map PF.modificationTime status let sorted = sortBy (\(_, t1) (_,t2) -> compare t1 t2) (zip filenames times)
and I thought, surely I can combine the status and times definitions into one line, only I can't.
Hint ?
Thanks,
Brian _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Pierre-Etienne Meunier
This way :
do times<-mapM PF.getFileStatus filenames >>= return.(map PF.modificationTime)
Or also :
do times<-mapM (PF.getFileStatus >>= (return.(PF.modificationTime))) filenames let sorted=...
I do not know exactly how ghc compiles the IO monad, but it seems to me that the latter would allocate a little less.
List fusion probably converts them to the same core (you can always use ghc-core to verify this if you care). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Pierre-Etienne Meunier wrote:
This way :
do times<-mapM PF.getFileStatus filenames >>= return.(map PF.modificationTime)
Or also :
do times<-mapM (PF.getFileStatus >>= (return.(PF.modificationTime))) filenames let sorted=...
I do not know exactly how ghc compiles the IO monad, but it seems to me that the latter would allocate a little less.
FWIW, (a >>= (return . f)) == (liftM f a) ~= (fmap f a) Where available, the fmap version is the most efficient. The liftM function can be less efficient since it's defined generically (namely with the bind/return definition above), whereas fmap can take advantage of knowing the specific monad it's working on. But then, not everyone defines Functor instances for their monads... -- Live well, ~wren

On May 9, 2010, at 07:18 , wren ng thornton wrote:
Where available, the fmap version is the most efficient. The liftM function can be less efficient since it's defined generically (namely with the bind/return definition above), whereas fmap can take advantage of knowing the specific monad it's working on. But then, not everyone defines Functor instances for their monads...
Arguably that deserves a bug report, as logically a Monad is an Applicative is a Functor (or read "is a" as "subset of" for pedantry). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (10)
-
Ben Millwood
-
Bill Atkins
-
Brandon S. Allbery KF8NH
-
briand@aracnet.com
-
Ivan Lazar Miljenovic
-
Ivan Miljenovic
-
Maciej Piechotka
-
Neil Brown
-
Pierre-Etienne Meunier
-
wren ng thornton