Re: [Haskell-cafe] Monad transformer, liftIO

2009-04-03 Thread Michael Roth
Creighton Hogg schrieb:

> Okay, so I think what you want is
>
>  [...]

Yes. Your solution works. Thank you. But:

>   a <- msum . map return $ [1,2,3]

Why Do I need this "msum . map return" thing?

The "map return" part is somewhat clear. But not entirely. Which
type of monad is created here?

The msum-part ist totally confusing me: First we create a list
with some monads (?) and then msum them? What is going on there?


> first, that you tried to use literal list syntax in
> do notation which I believe only works in the actual [] monad.

Is the "x <- xs" in the list monad a form of syntactic sugar?


>  Second, you didn't have the runListT acting on
> the foobar, which is how you go from a ListT IO Int to a IO [Int].

Ah, yes. This point I understood now. Thank you again.


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


[Haskell-cafe] Monad transformer, liftIO

2009-04-03 Thread Michael Roth
Hello list,

maybe I'm just stupid, I'm trying to do something like this:


import Control.Monad
import Control.Monad.Trans
import Control.Monad.List

foobar = do
a <- [1,2,3]
b <- [4,5,6]
liftIO $ putStrLn $ (show a) ++ " " ++ (show b)
return (a+b)

main = do
sums <- foobar
print sums


But this apparently doesn't work... I'm total clueless how
to achieve the correct solution. Maybe my mental image
on the monad transformer thing is totally wrong?


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


[Haskell-cafe] Field updates in a state monad

2008-01-10 Thread Michael Roth
Hello list,

still playing with monads and states, I have the following question:

Given:

import Control.Monad.State.Lazy

data MyData = MyData { content :: String }

foobar :: State MyData String
foobar = do
  gets content

Ok, that looks nice and tidy. But:

foobar2 :: State MyData ()
foobar2 = do
  modify $ \x -> x { content = "hello haskell"}

...looks not so nice.


Exists there a way to write this cleaner without writing countless
"set_xyz" helper functions?


Michael


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


Re: [Haskell-cafe] Problem with own written monad

2008-01-07 Thread Michael Roth
Jules Bean schrieb:

> data Stack a b = Stack { run :: [a] -> (b, [a]) }

Thank you, that does the trick.


> The correct types for the other functions are:
>
> push :: a -> Stack a ()
> pop :: Stack a a
> top :: Stack a a
>
> With those clues I think you will be able to write >>= and return more
> successfully!

Yes, this was the missing link. Because I thought "Stack a a" could be
abbreviated using "Stack a" I run into these problems. This was also the
cause that "push" echoed back the pushed value.


> There are some other interesting combinators to consider, like:
>
> isolate :: Stack b x -> Stack a x
> -- runs the computation with an empty stack, therefore
> -- guaranteeing it does more pushes than pops

Did you mean:

isolate :: Stack s1 a -> Stack s2 a
isolate stack = Stack f where f xs = ( fst $ run stack [], xs)

> and so on.

Yes, I have done: push, pop, top, nop, count, clear, isolate and binop.
All pretty easy, once I understand that "Stack a b" thing.



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


Re: [Haskell-cafe] Problem with own written monad

2008-01-07 Thread Michael Roth
Miguel Mitrofanov schrieb:

> May be you can explain what do you want to do with this "monad"?

Pure educational purpose, just "learning by doing".


> What kind of code would you write if it would be such monad?

Useless stuff like:

s2 = do
  push 11
  push 17
  count >>= push
  binop (+)
  binop (*)
  pop


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


[Haskell-cafe] Problem with own written monad

2008-01-07 Thread Michael Roth
Hello list,

while trying to learn the secrets of monads, I decided to write a simply
monand for pure educational purpose. But it turned out that it isn't as
easy as I thought... I circumnavigate quite a number of hurdles but now
I reached a point where I'm at a loss. :-(


The source:

#! /usr/bin/env ghc

data Stack a = Stack { run :: [a] -> (a, [a]) }

push :: a -> Stack a
push x = Stack f where f xs = ( x, x:xs )

pop :: Stack a
pop = Stack f where f (x:xs) = ( x, xs )

top :: Stack a
top = Stack f where f (x:xs) = ( x, x:xs )

instance Monad Stack where
  return x = Stack f where f xs = ( x, xs )
  (>>=) stack g = Stack f where
f s0 = (x2, s2) where
  (x1, s1) = run stack s0
  (x2, s2) = run (g x1) s1

The errors:

./mymonad.hs:16:24:
Couldn't match expected type `b' (a rigid variable)
   against inferred type `a' (a rigid variable)
  `b' is bound by the type signature for `>>=' at 
  `a' is bound by the type signature for `>>=' at 
  Expected type: [b] -> (b, [b])
  Inferred type: [a] -> (b, [b])
In the first argument of `Stack', namely `f'
In the expression: Stack f

./mymonad.hs:19:28:
Couldn't match expected type `b' (a rigid variable)
   against inferred type `a' (a rigid variable)
  `b' is bound by the type signature for `>>=' at 
  `a' is bound by the type signature for `>>=' at 
  Expected type: [b]
  Inferred type: [a]
In the second argument of `run', namely `s1'
In the expression: run (g x1) s1


I think the problem is that my operator (>>=) is of type:

  Stack a -> (a -> Stack a) -> Stack a

but should be:

  Stack a -> (a -> Stack b) -> Stack b


But, I have simply no clue how to fix that. :-(
Can anybody give my a hint?


Thank you in advance.


Michael Roth



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


[Haskell-cafe] How to write elegant Haskell programms? (long posting)

2007-01-29 Thread Michael Roth
Hello list,

I'm new to Haskell and I'm trying to learn how to write elegant code
using Haskell.

I decided to convert the following small tool, written in ruby:

===
#! /usr/bin/env ruby

require 'pathname'

BASENAMES   = %w{ mail.log thttpd.log }
ARCHIVEDIR  = Pathname.new '/var/log/archive'
LOGDIR  = Pathname.new '/var/log'

class Pathname
  def glob glob_pattern
Pathname.glob self.join(glob_pattern)
  end
  def timestamp
stat.mtime.strftime '%Y%m%d'
  end
end

for basename in BASENAMES
  for oldname in LOGDIR.glob "#{basename}.*.gz"
newname = ARCHIVEDIR.join "#{basename}.#{oldname.timestamp}.gz"
puts "mv #{oldname} #{newname}"
File.rename oldname, newname
  end
end
===


My solution in Haskell is:

===
import System.Directory   (getDirectoryContents, getModificationTime,
renameFile)
import System.Locale  (defaultTimeLocale)
import System.Time(ClockTime, toUTCTime, formatCalendarTime)
import Text.Regex (mkRegex, matchRegex)
import Maybe
import Control.Monad

logdir, archivedir :: String
logfiles :: [String]

logfiles= [ "mail.log", "thttpd.log" ]
logdir  = "/var/log"
archivedir  = "/var/log/archive"

basename :: String -> String
basename filename = head . fromMaybe [""] $ matchRegex rx filename where
  rx = mkRegex "^(.+)(\\.[0-9]+\\.gz)$"

isLogfile :: String -> Bool
isLogfile filename = basename filename `elem` logfiles

timestamp :: ClockTime -> String
timestamp time =
  formatCalendarTime defaultTimeLocale "%Y%m%d" (toUTCTime time)

makeOldname :: String -> String
makeOldname fn = logdir ++ '/' : fn

makeNewname :: String -> String -> String
makeNewname bn ts = archivedir ++ '/' : bn ++ '.' : ts ++ ".gz"

move :: String -> String -> IO ()
move oldname newname = do
  putStrLn $ "mv " ++ oldname ++ ' ' : newname
  renameFile oldname newname

main :: IO ()
main = do
  files <- liftM (filter isLogfile) (getDirectoryContents logdir)
  let oldnames = map makeOldname files
  times <- mapM getModificationTime oldnames
  let newnames = zipWith makeNewname (map basename files) (map timestamp
times)
  zipWithM_ move oldnames newnames
===


Ok, the tool written in Haskell works. But, to me, the source doesn't
look very nice and even it is larger than the ruby solution, and more
imporant, the programm flow feels (at least to me) not very clear.

Are there any libraries available to make writing such tools easier?
How can I made the haskell source looking more beautiful?


Michael Roth




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