Re[3]: [Haskell-cafe] Why Exotic Languages Are Not Mainstream

2006-08-12 Thread Bulat Ziganshin
Hello Nicolas,

Friday, August 11, 2006, 7:13:26 PM, you wrote:

 Thanks for the pointers, but I think I'm looking for type information
 specific to my program. The VisualHaskell feature of which I am

 And, of course, I'd like this functionality in a multi-platform editor.

besides of Visual Haskell, there is EclipseFP project. it's still in
very early stage and don't supports what you asked. but it's author
continuously enhances the product and seeks for the testers. wo shile
i can't figure something that solves your problems, i can suggest you
to join this effort in order to got good IDE in some future

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Exotic Languages Are Not Mainstream

2006-08-12 Thread Bulat Ziganshin
Hello Johan,

Friday, August 11, 2006, 4:43:27 PM, you wrote:

 Haskell was mentioned in an article called Why Exotic Languages Are
 Not Mainstream on the blog defmacro.org the other day and I thought
 maybe someone would be interested (i.e. is procrastinating at work and
 need an excuse to do something else). Any comments?

 http://www.defmacro.org/ramblings/not-ready.html

i'm 100% agree with this article. imho Haskell is not ready for
_application_ programming mainly because of 3 issues:

- lack of specialists (and this means lack of teaching, training,
books)
- lack of IDE/RAD tools (this includes debugging, visual construction
of GUI+DB part of program and so on)
- lack of variety of libraries (application programmers want to have
many libraries pre-written)

imvho, these issues are less important for system programming (such as
creating of web server or CMS system), so Haskell, with all its
features, now is a great tool for system programming. for example,
i've written zip-like tool with ghc


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Nested Monads Questions

2006-08-12 Thread Bulat Ziganshin
Hello Chris,

Saturday, August 12, 2006, 4:05:44 AM, you wrote:

 Nine Base Monads:
IO STM ST ST.Lazy GenParser [] Maybe Either (-)

 Seven MonadTrans:
ListT ContT ErrorT ReaderT StateT WriterT RWST

i'm not sure, but isn't Id monad also required for completeness?

at least it's included in MonadLib by Iavor S. Diatchki:
http://www.csee.ogi.edu/~diatchki/monadLib/monadLib-2.0.tar.gz

am i correctly understand that your module is update on Monad
transformers lib already included in GHC?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Nested Monads Questions

2006-08-12 Thread Dan Doel

On 8/11/06, Dan Doel [EMAIL PROTECTED] wrote:

The difference is in what the parameters to the classes MonadTrans and
MonadIO represent. MonadIO m means that m is a monad into which
IO-actions can be lifted. MonadTrans t means that (t m) is a monad
into which m-actions can be lifted. However, since the type class
doesn't know about m, it's impossible to exprss that composition of
two transformers is itself a transformer, whereas you can easily
declare that the result of transforming a MonadIO with a certain
transformer results in a MonadIO.

Apologies for replying to myself.

I played around a bit, and I was essentially able to express
composition of transformers without extra class parameters. Ideally,
it'd go something like this:

 type CombinatorT (t :: (* - *) - * - *)
  (u :: (* - *) - * - *)
  (m :: * - *)
  (a :: *) = t (u m) a

 instance (MonadTrans t, MonadTrans u) =
 MonadTrans (CombinatorT t u) where
 lift = lift . lift

This says that the combinator transformer is a monad transformer if t
and u are. However, since the combinator transformer is just a type
synonym, it would (I think) end up reducing to all combinations of
transformers being transformers.

However, partially applied type synonyms aren't allowed (for good
reasons, I hear; this example is particularly weird; is it possible to
write without using type synonym syntax? MonadTrans (forall m. t (u
m)) ?), so instead, you have to use a data declaration (maybe a
newtype? I don't know):

 data (MonadTrans t, MonadTrans u, Monad m) =
 CombinatorT t u m a = CombinatorT (m a)

 instance (MonadTrans t, MonadTrans u) =
 MonadTrans (CombinatorT t u) where
 lift = CombinatorT

However, that doesn't really give the types we want, and obviously
doesn't do the lift composition, so we need a way to get it out of the
container:

 unC :: (MonadTrans t, MonadTrans u, Monad m, Monad (u m)) =
 CombinatorT t u m a - t (u m) a
 unC (CombinatorT m)= lift (lift m)

And for less typing:

 liftC = unC . lift

And now an example, shamefully stolen from Mr. Kuklewicz

 type Foo a = (WriterT [Int] (ReaderT String [])) a

 foo :: Foo String
 foo = do
 x - liftC [1, 2, 3]
 s - ask
 tell [succ x]
 return (s ++ show x)

 test = runReaderT (runWriterT foo) hello

 *Transform test
 [(hello1,[2]),(hello2,[3]),(hello3,[4])]

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


[Haskell-cafe] Re: Nested Monads Questions

2006-08-12 Thread Dan Doel

On 8/12/06, Dan Doel [EMAIL PROTECTED] wrote:

Viola.

Egads!

In my haste, I failed to note that my mapping from the type synonym to
the data constructor only works for a single nested transformer. lift
will build arbitrarily nested CombinatorTs, but I'm not sure how to
extract them into the component transformers. Hardly ideal.

Perhaps someone more enterprising will fix my error, if it is indeed
possible to do so. Until then, my apologies for triple posting.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Nested Monads Questions

2006-08-12 Thread Chris Kuklewicz

Bulat Ziganshin wrote:

Hello Chris,

Saturday, August 12, 2006, 4:05:44 AM, you wrote:


Nine Base Monads:
   IO STM ST ST.Lazy GenParser [] Maybe Either (-)



Seven MonadTrans:
   ListT ContT ErrorT ReaderT StateT WriterT RWST


i'm not sure, but isn't Id monad also required for completeness?



Yes, Identity is required for completeness.  And I have added to 
http://haskell.org/haskellwiki/NewMonads#MonadBase this definition:



-- One can recover MonadIO and liftIO from MonadBase
class (MonadBase IO m) = MonadIO' m where
  liftIO' :: IO a - m a
  liftIO' = liftBase


Of course, the above is unneeded since you can always write liftBase instead of 
liftIO.


...

at least it's included in MonadLib by Iavor S. Diatchki:
http://www.csee.ogi.edu/~diatchki/monadLib/monadLib-2.0.tar.gz



Hah...I knew someone else had done this.  Also, there is 2.0.1 version of 
monadLib at http://www.cse.ogi.edu/~diatchki/monadLib/


His version is called BaseM, and uses a fundep:


-- | Provides means to execute a computation in the base of a tower of monads.
class (Monad m, Monad b) = BaseM m b | m - b where
  inBase   :: b a - m a

instance BaseM IO IOwhere inBase x = x
instance BaseM [] []where inBase x = x
instance BaseM Maybe Maybe  where inBase x = x



I am not sure I like the inBase name.  I think fromBase might be a better 
match to its type.  The inBase seems more like toBase which is backwards.


My small test did not need the fundep, and I wonder if there is some creative 
example that shows either that the fundep is useful or a counter example that 
shows something very very clever that would otherwise violate the fundep.


I *might* be able to imagine a transformer stack that pretends to have different 
base monads.



am i correctly understand that your module is update on Monad
transformers lib already included in GHC?


Essentially, that is exactly what it is.  It completely replaces MonadIO.

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


Re: [Haskell-cafe] cabal specify a tested version, ghci target?

2006-08-12 Thread Duncan Coutts
On Sat, 2006-08-12 at 03:52 +0200, Marc Weber wrote:
 1.)
   I know I can use
   Build-Depends:   lib == version, lib2  version, lib3 = 
 version
   and so on.
 
   Do you think it would be useful to introducue some notation to indicate
   a tested with ?
 
   Reason, purpose: I think its sometimes the case that a author/ mantainer
   is quite busy with other projects and misses that some dependencies
   break things.. If you want to try out you're left with some compiler
   errors and a dependency and have to try out which version works.
 
   I would propose using this syntax:
   lib-1.3 =1.1 
   to indicate that lib 1.1 is required at leeast and tested with up to
   1.3.. Cabal might then give a warning if you try to use 1.4 or greater
   using newer version than tested or similar..
 
   What do you think?
   Would this be useful?

Well there is actually already a tested-with: field that you can put
in a .cabal file, however at the moment it refers only to the Haskell
implementation, eg ghc-x.y, hugs-x.y etc not to versions of libraries.

Yes, I think it's a quite reasonable argument to extend this to include
exact versions of libraries that it has been tested with.

What do others think?

Duncan

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