Re: [Haskell-cafe] implementing try for RWST ?

2007-04-16 Thread tpledger
Jeremy Shaw wrote:
 :
 | However, I think this is buggy, because changes
 | to 's' and 'w' will be lost if 'm' raises an
 | exception.
 :


That's determined by the way you stack your monad
transformers when declaring the type: adding error handling
to a writer monad, or adding writing to an error handling
monad.  For a concrete example, see the result types in the
following.  The first has the Either inside the tuple, and
the second has the tuple inside the Either.

Prelude :t Control.Monad.Writer.runWriter .
Control.Monad.Error.runErrorT
Control.Monad.Writer.runWriter .
Control.Monad.Error.runErrorT :: Control.Monad.Error.ErrorT
e (Control.Monad.Writer.Writer w) a
- (Either e a, w)
Prelude :t either Left Right .
Control.Monad.Writer.runWriterT
either Left Right . Control.Monad.Writer.runWriterT ::
Control.Monad.Writer.WriterT w (Either a) a1 - Either a
(a1, w)


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


[Haskell-cafe] why can't you surround (+) in backticks and have it be infix?

2007-01-08 Thread tpledger
David House wrote:
 :
 | You can fake this:
 |
 | (-!) = ($)
 | (!-) = flip ($)
 |
 | foo -! liftM2 (,) !- bar
 |
 | Not perfect, but it's interesting nonetheless.
 |
 | And yes, this was a product of some #haskell
 | brainstorming and algorithm tennis. :)

:-)

Was anyone in that brainstorm thinking of Chung-chieh Shan's
-: and :-
(http://www.haskell.org/pipermail/haskell-cafe/2002-July/003215.html)
or was the similarity just a really cool coincidence?

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


[Haskell-cafe] Great language shootout: reloaded

2006-11-13 Thread tpledger
Donald Bruce Stewart wrote:
[...]
 While we're here we should fix:
   chameneos
 And anything else you want to take a
 look at.

 A community page has been set up to
 which you can submit improved entries:

http://www.haskell.org/haskellwiki/Great_language_shootout
[...]


Well, then!

I've put a new chameneos solution up on the wiki, and will
wait the recommended couple of days for Community Feedback.

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


[Haskell-cafe] collection monads

2006-10-08 Thread tpledger
Matthias Fischmann wrote:
  Do you expect the contained type x to change during a
  sequence of monadic actions?  e.g. would you ever use
(=)
  at the type 'Permutation Int - (Int - Permutation
Bool) -
  Permutation Bool'?

 no, i don't need that.  but aside from
 the fact that

  data Permutation k v =
  Permutation [(k, v)]
  instance (Ix k) =
  Monad (Permutation k)

 is redundant (i think of the permutation
 as a function applicable to arbitrary
 lists): how would that change anything?
 my definition of return still doesn't
 work.  or how would you redefine
 'return'?

Ah.  Yes, my approach falls over because it lacks two
things.  #1: a distinguished value of the Ix-constrained
type k, to pair off with return's argument.  #2: a purpose. 
I don't have a clear idea of what a do-block in a
permutation monad ought to mean.  Whoops!  font
color=red:-]/font

Regards,
Tom (crawling back under his rock)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] collection monads

2006-10-04 Thread tpledger
Matthias Fischmann wrote:
 another beginners question about monads: given the type

 | data (Ix x) = Permutation x = Permutation [x]

 i wanted to define

 | instance Monad Permutation where
 | return xs = Permutation xs

 but of course nothing about the monad class guarantees xs
to be of
 type list.  the monad class seems unsuitable for holding
collections,
 and i am inclined to not instantiate permutations.

 just to be sure: is there any easy way to do it that i
missed?

Do you expect the contained type x to change during a
sequence of monadic actions?  e.g. would you ever use (=)
at the type 'Permutation Int - (Int - Permutation Bool) -
Permutation Bool'?

If not, you could separate each permutation into keys and
values:

data Permutation k v = Permutation [(k, v)]
instance (Ix k) = Monad (Permutation k)

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


[Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread tpledger
Joel Koerwer wrote:
 Let's say I want to evaluate a function of type
 (a-a-...-a-a), taking the arguments from a
 list. If know the function ahead of time, I can
 simply wrap it:

 foo a b c d = ...
 wrapFoo (a:b:c:d:_) = foo a b c d

 But, as an exercise, I challenged myself to write
 a function, multApply :: (a-a-...-a-a) - [a]
 - a, that automatically does the wrapping for any
 such function.

This came up a while ago (but with a list of functions of
different arities, all being fed one argument).  I found
Scott Turner's pure Haskell 98 solution very illuminating:

   
http://www.haskell.org/pipermail/haskell-cafe/2000-November/001332.html

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


[Haskell-cafe] Greetings...

2006-10-01 Thread tpledger
Seth Gordon wrote:
 I thought I should check and see if anyone
 on this list has used Haskell to munge a
 ten-million-row database table, and if
 there are any particular gotchas I should
 watch out for.

Are you sure you want to target the data directly?  Another
approach, that might have a better chance of a quick win
within your time frame, is to use Haskell to generate SQL
code.  That could still reduce the amount of code you
maintain by hand.

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


[Haskell-cafe] Re: Why is type 'b' forced to be type 'm a' and not possibly 'm a - m a'

2006-10-01 Thread tpledger
Vivian McPhail wrote:
...
 I need the arg a to be evaluated before it gets
 passed to a1 and a2. This definition does the right thing
 when type 'a' is a function type, because it is not a
 value, but with something like 'm a - (m a - m a) - m
 a' with Forkable (a - b) the first arg gets evaluated
 twice, to be more concrete:

 With

 (and golden white) eggs

 I want the 'eggs' that is passed to 'golden' to be the
 same as the 'eggs' that is passed to 'white', i.e.
...

Could you reduce the need for Forkable instances, by
rewriting '(and golden white) eggs' as 'and golden white =
eggs'?  Or would the same piece of code also have to handle
combinations such as monadic 'and golden white' and
non-monadic eggs?

[BTW, thanks for giving me a pretext to use the phrase
non-monadic eggs!]

 Tom suggested that I might be able to use the Reader monad
 , but I'm not clear as to how I could do this.

Please ignore that.  I only mentioned it in case the sole
purpose of fork was to propagate a String, which you've now
explained is not so.

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


[Haskell-cafe] How would you replace a field in a CSV file?

2006-10-01 Thread tpledger
Hi Pete.

For such a small self-contained task, I don't think Haskell
is any better than Python.

Haskell would come into its own if you wanted some assurance
about type safety, and/or were taking on a task large enough
to warrant the use of records (and hence record update
notation).

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


[Haskell-cafe] Re: Why is type 'b' forced to be type 'm a' and not possibly 'm a - m a'

2006-09-20 Thread tpledger
Vivian McPhail wrote:
   class Forkable a where
   fork :: String - a - a - a

 What I would like to be able to do is
 differentiate between Forkable (m a -
 b) and Forkable (function type - b).

Have you tried this combination of instances?

instance Forkable (IO a) where ...
-- and similarly for all the concrete
-- monad types you will use fork with

instance (Forkable a, Forkable b) =
 Forkable (a - b) where ...

Alternatively, since the fork function seems to be all about
propagating a value (the String), would Control.Monad.Reader
serve your purpose?

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


Re: [Haskell-cafe] Weak pointers and referential transparency???

2006-09-13 Thread tpledger
Brian Hulley wrote:
 [EMAIL PROTECTED] wrote:
[...]
  My reading of the semantics
 
(http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#4)
  is that you can be sure the proxy *object* is gone.

 My problem is that I don't know what to make of the word
 object in the  context of Haskell ie when can I be sure
 that a value is actually being  represented as a pointer
 to a block of memory and not stored in registers or
 optimized out? Or is the compiler clever enough to
 preserve the concept of  object despite such
 optimizations? I had been designing my Model/Proxy  data
 types with the Java notion of everything is a pointer to
 an object  but is this always correct relative to Haskell
 as a language or is it just a  consequence of the current
 GHC implementation?

In the context of System.Mem.Weak, but not necessarily GHC,
we're concerned solely with garbage collection of heap
objects.  So yes, that's Java-like.  AFAIK.

An example of something outside that context is a GHC Int#
(unboxed Int).  It never inhabits the heap, and isn't
allowed to be passed to a function where a polymorphic
parameter is expected (such as mkWeak).

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


[Haskell-cafe] Optimization problem

2006-09-13 Thread tpledger
Magnus Jonsson wrote:
[...]
 but your example fails on infinite lists
[...]
 take 2 $ snd $ head $ splitStreams (map (\x - (0 ,x))
[1..])

Any approach, even sieving, will struggle with infinite
lists, won't it?

(take 2 . snd . head . splitStreams) [(i, i) | i -
[0..]]

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


[Haskell-cafe] Weak pointers and referential transparency???

2006-09-12 Thread tpledger
Brian Hulley wrote:
[...]
 Ref.write proxiesRef $! (weakProxy : proxies)

(This is nothing to do with your main question, but the
strict application looks unnecessary there.  Its right hand
side is already a constructor cell.)

[...]
 In other words, if the entry for the proxy
 in the table stored in the Model dies, can
 I be absolutely 100% sure that this means
 the proxy no longer exists in any shape or
 form in the running program?

My reading of the semantics
(http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#4)
is that you can be sure the proxy *object* is gone.

As for referential transparency...

Fan-in:
If you create equivalent proxies in different calls to
createProxy, it's possible that they'll end up referring to
the same object (e.g. if the compiler or RTS does something
fancy, or you use a memoised smart constructor).  So then a
single live proxy object *could* protect many elements of
your Weak Proxy list from scavenging.

Fan-out:
It would seem perverse to cry referential transparency!
and spontaneously clone one of your proxy objects.  That
*could* lead to deRefWeak returning Nothing while an
*equivalent* Proxy object is still alive.  Might you run
your program on an avant-garde distributed RTS?  ;-)

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


[Haskell-cafe] state and exception or types again...

2006-08-28 Thread tpledger
Andrea Rossato wrote:

 Now I'm trying to create a statefull evaluator, with
output and
 exception, but I'm facing a problem I seem not to be able
to
 conceptually solve.

If a computation fails in your monad, do you still want to
return a value of the result type?  I'd expect not, and
hence remove the 'a' from the 'Raise' constructor.

data Eval_SOI a
= Raise (State -(State, Output))
| SOIE  (State - (a, State, Output))

The above is very similar to using the monad foundation
classes:

import Control.Monad.Error
import Control.Monad.State hiding (State)
import Control.Monad.Writer

type Eval_SOI
= ErrorT String
  (StateT State (Writer Output))

...assuming that you're happy to send back a descriptive
String when a computation fails.

Have a look at the Control.Monad.Error source code, to see
how 'instance Error a = Monad (Either a)' is defined.  It's
the sort of thing you were trying to do in your 'instance
Monad Eval_SOI'.

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


[Haskell-cafe] Variants of a recursive data structure

2006-08-07 Thread tpledger
Klaus Ostermann wrote:
[...]
 data Exp e = Num Int | Add e e

 data Labelled a = L String a

 newtype Mu f = Mu (f (Mu f))

 type SimpleExp = Mu Exp

 type LabelledExp = Mu Labelled Exp

 The SimpleExp definition works fine,
 but the LabeledExp definition doesn't
 because I would need something like
 Mu (\a - Labeled (Exp a)) where \
 is a type-level lambda.

 However, I don't know how to do this in
 Haskell. I'd need something like the
 . operator on the type-level.

One way, that I haven't spotted in any of the replies so
far, is to declare a composition type

data BComp m n a = BC (m (n a))

as seen in
http://web.cecs.pdx.edu/~mpj/pubs/springschool.html , so
that

type LabelledExp = Mu (BComp Labelled Exp)

See
http://haskell.cs.yale.edu/pipermail/haskell/2001-May/003942.html
for more crafty tricks, including making Eq instances for
such Mu-based recursive structures.

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


[Haskell-cafe] trace function

2006-07-20 Thread tpledger
Alexander Vodomerov wrote:
 import Debug.Trace

 main = do
   putStrLn xxx
   return (trace yyy ())
   putStrLn zzz

 only xxx and zzz is displayed. yyy is missing.
 Why trace is not working?

Nothing uses the value of (trace yyy ()), so it is never
evaluated.

Try this instead, which uses the value for a pattern match:

() - return (trace yyy ())

Or this, which makes the trace part of the sequence of IO
actions:

trace yyy (return ())

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


[Haskell-cafe] REALLY simple STRef examples

2006-07-20 Thread tpledger
Chad Scherrer wrote:
 x = runST $ return 1

 y = runST $ do {r - newSTRef 1; readSTRef r}

 Neither of these works in ghci

x = runST (return 1)

y = runST (do {r - newSTRef 1; readSTRef r})

The escaping s is something to do with rank 2 polymorphism. 
(Search for rank in the ghc user guide, for example.)

The hassle is that runST must always be applied to an
argument (e.g. not passed to ($)), and a benefit is that
you're protected from using an STRef you created in the
context of one runST, in the context of another runST.

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


[Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-12 Thread tpledger
Jared Updike wrote:
  split is... unconcatIntersperse.

 How about separate?  (split or splitBy is better but
it is used
 all over the place in many libs)

 And for strings I definitely would use split :: [a] - [a]
- [[a]]  a
 lot, just like Python's split function. And words works
great for
 breaking on multiple spaces, so I would avoid trying to
fill that
 need...

FWIW my home-grown versions of these things are called
fields and unfields.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] closures with side effects

2006-06-28 Thread tpledger
dkarapet wrote:
 I have been trying to understand closures
 in haskell and how they relate
 to side effects. I have been looking
 around but all I find are trivial
 examples with no side effects. Please let
 me know if you know of any examples.

The side effects occur in the context that causes the
closure to be entered.

Here's a nigh-trivial example.

myClosure :: IO ()
myClosure = putStrLn Hello, world.
main  = myClosure  myClosure

When myClosure is defined, the side effect doesn't occur
yet.  We just have a *definition* of an IO action that
hasn't yet been bound into the program's sequence of
actions.

When main binds myClosure into the program's sequence of
actions (twice), the side effect occurs (twice).  Depending
on the implementation of putStrLn, it may be faster the
second time because the same closure has been entered
before.

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


[Haskell-cafe] Distributing monadic(?) functions across dyadic functions

2006-04-03 Thread tpledger
Nils Anders Danielsson wrote:
 A function like this has been suggested for the
 standard libraries a couple of times before.
 Someone suggested the name on, which I quite
 like:

   (*) `on` f = \x y - f x * f y


Thanks!  I always wanted to be someone.  :-)

Here's the link.

http://www.haskell.org//pipermail/haskell-cafe/2004-December/007917.html

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


[Haskell] Using MonadError within other Monads

2006-01-04 Thread tpledger
(In reply to
http://www.haskell.org/pipermail/haskell/2005-December/017109.html
)

One of the key things about those nested monads is that
*often* you
don't have to write things like

return $ throwError msg

but can simply write

throwError msg

because the nest has all the features of its components.

The IO monad doesn't participate fully in this, but the
liftIO
function (from the MonadIO class) serves as an adapter.

 import Control.Monad.Error
 f () = do n - liftIO readLn
   when (n == 2) (throwError 2-char string)
   sequence (replicate n (liftIO getChar))
   `catchError` (throwError . (g Error: ++))

(Pay no attention to the () parameter behind the curtain! 
I'm dodging
the monomorphism restriction, and don't want to give an
explicit type
signature.)

The inferred type is

f :: (MonadError [Char] m, MonadIO m) = () - m [Char]

i.e. it's usable for any nest of monads that provides the
MonadError String
and MonadIO features.

Now, how to run it?  Your type signatures of the form

IO (Either String String)

are very reminiscent of the ErrorT monad transformer

newtype ErrorT e m a
= ErrorT {runErrorT :: (m (Either e a))}

with IO as m and String as e and a.  So, let's test f in
ErrorT String IO.

*Main runErrorT (f ()) = print
0
Right 
*Main runErrorT (f ()) = print
2
Left I don't like strings with 2 characters.
*Main runErrorT (f ()) = print
4
Too
Right Too\n

Regards,
Tom
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Problem with continuations and typing

2005-12-04 Thread tpledger
Jerzy Karczmarczuk wrote:
 :
 | zeros fc sc = sc 0 zeros
 |
 | fails to compile as well. *I do not ask why, I know*.
 |
 | But I would like to continue this exercice along these
lines, without too much
 | exotism (no monads, yet...), for my students. Do you have
any simple work-around?
 | Introduce some algebraic constructors? Perhaps
higher-rank polymorphism could do
 | something (but then I would have to explain it to my
folk...)
 :


How about this for a non-exotic algebraic type?

 newtype G a b = G{ unG :: b - (a - G a b - b) - b }
 glist g   = unG g [] (\b g' - b : glist g')
 zeros = G (\no yes - yes 0 zeros)
 disj  g1 g2   = G (\no yes - unG g1 (unG g2 no yes)
  (\b g1' - yes b
(disj g1' g2)))

I haven't had much practice with continuations, so don't
know whether I've just lost some generality there.

But it does support *some* avoidance of higher-rank
polymorphism, through the use of good old partial
application.  For example, the type of the state variable s
doesn't leak into the result type of unfold:

 unfold f s= G (\no yes - case f s of
     Nothing  - no
     Just (s', b) - yes b (unfold f
s'))

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


[Haskell-cafe] Shortening if-then-else

2005-11-27 Thread tpledger
Arjan van IJzendoorn wrote:
 |  Is there a shorter way to write the if-then-else part
below?
 | if (cmdType cmd) /= (CmdSitError Server)
 |then return $ Just seat_num
 |else return Nothing
 |
 | return $ if cmdType cmd /= CmdSitError Serv
 |  then Just seat_num else Nothing


There's a subtle change in semantics when we move the 'if'
inside the 'return'.

The original code requires the condition to be evaluated as
part of the do-expression's monad's structure, but the
translated code defers it.

'return $! if ...' would be closer to the original.

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