[Haskell-cafe] ANN (2 Libs) -- hvac 0.1b, a lightweight web framework and HStringTemplate 0.3

2008-03-23 Thread Sterling Clover
1) hvac 0.1b: transactional, declarative framework for lightweight  
web applications.

2) HStringTemplate 0.3

1) hvac 0.1b

hvac (short for http view and controller) has been my project for the  
last little while, and is finally in a fairly usable state, so I'm  
opening up the repo (darcs get http://community.haskell.org/~sclv/ 
hvac/) for folks to play with and to get some feedback. While not  
quite yet ready for hackage, the package as provided should be fully  
cabal installable. Documentation is available at http:// 
community.haskell.org/~sclv/hvac/html_docs/hvac/


The aim of hvac is to provide an environment that makes the creation  
of lightweight fastcgi based web applications as simple as possible,  
with an emphasis on concise, declarative style code, correct  
concurrent transactional logic, and transparency in adding caching  
combinators.


There are two included example programs, naturally neither of which  
is feature complete. They share a common login module of about 50  
lines of code, excluding imports, templates, and database schema.


The first program is a classic, greenspun-style message board with  
basic login functionality. It totals roughly 40 lines and tends to  
use just under 4mb of resident memory on my system.


The second is a wiki based on Pandoc and the PandocWiki code. The  
code totals roughly 30 lines (rendering borrowed from PandocWiki  
aside) and uses about 5mb of memory.


hvac processes all requests in the STM monad, with some bells  
attached to properly interleave STM with session, database and  
filesystem operations such that they all conceptually occur together  
in a single transaction per request. Currently it is only fully  
tested with sqlite, but it should operate, modulo a few tweaks, with  
any database accessible via HDBC.


hvac is particularly designed to use the HStringTemplate library as  
an output layer, in a simple declarative fashion. As the  
StringTemplate grammar is explicitly sub-turing, this ensures a clean  
separation of program logic from presentation, while providing a  
nonetheless fairly powerful language to express typical display tasks.


The included cache combinators, still experimental, should allow a  
simple and fine-grained control over the level of caching of various  
disk-bound operations. Phantom types are used to ensure that no  
functions that modify state may be cached.


To give a flavor of hvac code, the following is the complete (twenty  
lines!) source of the wiki controller (due to sql statements, some  
lines are rather long):


wikiController tmpl =
 h |/ login * login_plug tmpl
 |
 (h |/ wiki |\\ \pageName -
h |// POST *
  withValidation [ (contents, return) ]
  (\ [contents] - do
 pageId - selectVal id from pages where name=? [toSql  
pageName]
 maybe (addErrors [(Login,must be logged in.)]   
continue)

(\user - case fromSql pageId of
Just (_::Int) -
  execStat insert into page_hist 
(pageId,contents,author) values(?,?,?) [pageId, toSql contents,  
toSql . userName $ user]

Nothing - do
  execStat insert into pages 
(name,locked) values(?,?) [toSql pageName, toSql (0::Int)]

  pid - selectVal max(id) from pages []
  execStat insert into page_hist 
(pageId,contents,author) values(?,?,?) [pid, toSql contents, toSql .  
userName $ user]) = getSes

 continue)
   | do
 pageId - selectVal id from pages where name=? [toSql  
pageName]

 (join $ renderf (tmpl showPage) (pageName, pageName)
  $ pageContents |= selectRow * from page_hist  
where pageId=? order by time desc limit 1 [pageId] ))

 | (redirect . ( ++ /wiki/Index) = scriptName)

Future directions for work on hvac include: Stress testing for  
correctness of transactional logic and benchmarks. Exploration of  
various efficiency tweaks. Unit tests. Further development of the  
cache combinator API. Improvement of the example apps and addition of  
a few others (a blog maybe). Expansion of the library of validator  
functions. Exploration of transferring hvac to the standard FastCGI  
bindings (currently it uses a custom modified version to work  
properly with STM). Improvement of the database layer, particularly  
with regards to common paging functions. Creation of a set of simple  
combinators for generating CRUD (create read update delete) pages.  
Creation of a minimal set of standard templates (maybe).


2) HStringTemplate 0.3.1

This release of HStringTemplate (up now at Hackage) fixes a number of  
bugs pointed out to me by its small but growing user base (thanks,  
cinema, elliottt!) ranging from the minor (a particular two-level  
iteration pattern wasn't working properly) to the truly irritating  
(poor handling of file groups). It's still unfortunately skimpy on  
the 

Re: [Haskell-cafe] compile error with FFI code

2008-03-23 Thread John Meacham
On Fri, Mar 21, 2008 at 11:21:26PM -0500, Galchin Vasili wrote:
 In my blah.hsc, I have allocbytes (#const (struct bozo)) .. where

you probably meant allocBytes (#const sizeof(struct bozo))

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: wxHaskell 0.10.3 rc1

2008-03-23 Thread Marc Weber
On Sat, Mar 22, 2008 at 08:48:20PM +0100, Peter Verswyvelen wrote:
 Amazing, I downloaded and installed this release for Windows and it works
 out of the box, just as a lazy Windows user expects! Woohoo! Great work.

I've had this success adding wxhaskell to nixos using the new distribution as 
well!

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


[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 55, Issue 30

2008-03-23 Thread Deng Chao
Hi Sebastian Sylvan,
  Thank you very much! I thick the last column return a string because
of the Haskell Show function, for when I made test, I got such an
error message: Show ([SqlValue] - IO [[SqlValue]]). Any way, thank you
very much!

Deng Chao

在 2008-03-22六的 13:55 [EMAIL PROTECTED]
 Send Haskell-Cafe mailing list submissions to
   haskell-cafe@haskell.org
 
 To subscribe or unsubscribe via the World Wide Web, visit
   http://www.haskell.org/mailman/listinfo/haskell-cafe
 or, via email, send a message with subject or body 'help' to
   [EMAIL PROTECTED]
 
 You can reach the person managing the list at
   [EMAIL PROTECTED]
 
 When replying, please edit your Subject line so it is more specific
 than Re: Contents of Haskell-Cafe digest...
 
 
 Today's Topics:
 
1. compile error with FFI code (Galchin Vasili)
2. doctest for haskell -- a good project? (Shaun Cutts)
3. Re: [GSoC] Plugins for GHC (Bulat Ziganshin)
4. Re: doctest for haskell -- a good project? (Roman Cheplyaka)
5. Re: doctest for haskell -- a good project? (Don Stewart)
6. Re: [GSoC] Plugins for GHC (Neil Mitchell)
7. Re: doctest for haskell -- a good project? (Neil Mitchell)
8. Re: An ugly zip3 problem.. (Michael Feathers)
9. Re: An ugly zip3 problem.. (Michael Feathers)
   10. How to program with sqlite? (Deng Chao)
   11. Re: doctest for haskell -- a good project? (Thomas Schilling)
   12. Re: How to program with sqlite? (Sebastian Sylvan)
   13. Re: doctest for haskell -- a good project? (Sebastian Sylvan)
   14. HXT and types in Control.Arrow.ArrowTree (Robert Vollmert)
   15. Opening Windows .lnk Files (Dominic Steinitz)
   16. RE: doctest for haskell -- a good project? (Shaun Cutts)
   17. Re: An ugly zip3 problem.. (Bryan O'Sullivan)
   18. Re: doctest for haskell -- a good project? (Paul Johnson)
   19. Re: AMQP framing layer: design help requested. (Paul Johnson)
   20. Re: Problem with OpenAL (Antoine Latter)
   21. Re: AMQP framing layer: design help requested. (Derek Elkins)
   22. Re: Opening Windows .lnk Files (Neil Mitchell)
   23. Re: doctest for haskell -- a good project? (Neil Mitchell)
   24. Re: Opening Windows .lnk Files (Dominic Steinitz)
   25. RE: doctest for haskell -- a good project? (Shaun Cutts)
 
 
 --
 
 Message: 1
 Date: Fri, 21 Mar 2008 23:21:26 -0500
 From: Galchin Vasili [EMAIL PROTECTED]
 Subject: [Haskell-cafe] compile error with FFI code
 To: Haskell-cafe haskell-cafe@haskell.org
 Cc: Galchin Vasili [EMAIL PROTECTED]
 Message-ID:
   [EMAIL PROTECTED]
 Content-Type: text/plain; charset=iso-8859-1
 
 Hello,
 
 In my blah.hsc, I have allocbytes (#const (struct bozo)) .. where
 
 struct bozo is a bunch of long int ,,, In the runhaskell Setup.hs build
 step I get a nasty error message about an incomplete type. I have look at
 many times but this error doesn't make sense to me. ??
 
 Kind regards, Vasili
 -- next part --
 An HTML attachment was scrubbed...
 URL: 
 http://www.haskell.org/pipermail/haskell-cafe/attachments/20080321/273d5ca0/attachment-0001.htm
 
 --
 
 Message: 2
 Date: Sat, 22 Mar 2008 02:20:38 -0400
 From: Shaun Cutts [EMAIL PROTECTED]
 Subject: [Haskell-cafe] doctest for haskell -- a good project?
 To: haskell-cafe@haskell.org
 Message-ID: [EMAIL PROTECTED]
 Content-Type: text/plain; charset=iso-8859-1
 
 Hello,
  
 I am an experienced programmer, currently learning Haskell. Currently I
 write many things in python. I use both the doctest and unittest modules
 extensively. As I write code, I simultaneously write doctest code in the doc
 strings to explain/set out the typical narrative of how the code is used.
 Then finishing off a module I write unittests for boundary conditions, more
 complex test cases, and generally code that would be annoying to write 
 read in doctests.
  
 I note that there is a unit testing framework for Haskell, but I don't see
 any doctest module. Might this be a good project?
  
 If so, suggestions as to resources would be greatly appreciated. I believe I
 can't just introspect Haskell modules to get at documentation/comments,
 like I can in python? (Why not? :)) I notice that there are a few
 documentation generators. Should I try to write an extension of one of
 these? Haddock, for instance? Are there any Haddock developers hanging out
 on this list, to encourage or dissuade me? :) (And where is the Haddock doc
 for Haddock?)
  
 In any case, thanks in advance for any comments  advice.
  
 - Shaun Cutts
 -- next part --
 An HTML attachment was scrubbed...
 URL: 
 http://www.haskell.org/pipermail/haskell-cafe/attachments/20080322/185fb821/attachment-0001.htm
 
 --
 
 Message: 3
 Date: Sat, 22 Mar 2008 10:08:50 +0300
 From: Bulat Ziganshin [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] [GSoC] Plugins for GHC
 To: Max Bolingbroke [EMAIL 

Re: [Haskell-cafe] Type constraints for class instances

2008-03-23 Thread Krzysztof Skrzętnicki
I fixed the code, see below. In fact, it works now for any listst of
type (YOrd a) = [a]. It works for things like
 ysort [[1..],[1..],[2..],[1..]]
Unfortunately, the performance of ysort is rather low. I belive that
it is impossible to create any sorting algorithm that uses ycmp
instead of compare, that is faster than O(n^2). In fact, ysort is
Theta(n^2), and it appears to be optimal. Why?
Well, consider the bubble sort algorithm. Then ycmp will be simply
sort of swap used there:

ycmp x y = case x `compare` y of
 LT - (x,y)
 EQ - (x,y)
 GT - (y,x)

And because it is the only possible operation here, it can't be
faster. (Though I may be wrong.)

Best regards,


Christopher Skrzętnicki.


---

--- http://hpaste.org/6536#a1

{-# OPTIONS_GHC -O2 #-}

module Data.YOrd (ysort, YOrd(..)) where

-- Well defined where Eq means equality, not only equivalence

class YOrd a where
ycmp :: a - a - (a,a)

instance (Ord a) = YOrd [a] where
ycmp = ycmpWith compare
where
  ycmpWith _ xs [] = ([],xs)
  ycmpWith _ [] xs = ([],xs)
  ycmpWith cmp (xs'@(x:xs)) (ys'@(y:ys)) = case x `cmp` y of
 LT - (xs',ys')
 GT - (ys',xs')
 EQ - let (sm,gt)
= xs `ycmp` ys in
   (x:sm,x:gt)
-- assumes that cmp is equality not equivalence relation here!


ycmpWrap cmp x y = case x `cmp` y of
 LT - (x,y)
 EQ - (x,y)
 GT - (y,x)


instance YOrd Integer where
ycmp = ycmpWrap compare
instance YOrd Char where
ycmp = ycmpWrap compare
instance YOrd Int where
ycmp = ycmpWrap compare


-- ysort : sorting in O(n^2)

ysort :: (YOrd a) = [a] - [a]

ysort = head . mergeAll . wrap

wrap xs = map (:[]) xs

mergeAll [] = []
mergeAll [x] = [x]
mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest))

merge xs [] = xs
merge [] xs = xs
merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in
  sm : (merge [gt] $ merge xs ys)




2008/3/21 Stephen Marsh [EMAIL PROTECTED]:
 Actually, infinite trees wouldn't work, for a similar reason to above. You
 can't decide sort order on the infinite left branches, so you could never
 choose the correct right branch.

 Stephen

  2008/3/21 Stephen Marsh [EMAIL PROTECTED]:


  There is a bug in the code:
 
  *Main ycmp [5,2] [2,5] :: ([Int], [Int])
  ([2,2],[5,5])
 
  I think it is impossible to define a working (YOrd a) = YOrd [a]
 instance. Consider:
 
  let (a, b) = ycmp [[1..], [2..]] [[1..],[1..]]
 
  head (b !! 1) -- would be nice if it was 2, but it is in fact _|_
 
  We take forever to decide if [1..] is greater or less than [1..], so can
 never decide if [1..] or [2..] comes next.
 
  However Ord a = YOrd [a] can be made to work, and that is absolutely
 awesome, esp. once you start thinking about things like Ord a = YOrd
 (InfiniteTree a). This really is very cool, Krzysztof.
 
  Stephen
 
 
  2008/3/20 Krzysztof Skrzętnicki [EMAIL PROTECTED]:
 
  
  
  
   Hello everyone,
  
   I'm working on a small module for comparing things incomparable with
 Ord.
   More precisely I want to be able to compare equal infinite lists like
 [1..].
   Obviously
  
   (1) compare [1..] [1..] = _|_
  
   It is perfectly reasonable for Ord to behave this way.
   Hovever, it doesn't have to be just this way. Consider this class
  
   class YOrd a where
  ycmp :: a - a - (a,a)
  
   In a way, it tells a limited version of ordering, since there is no
   way to get `==` out of this.
   Still it can be useful when Ord fails. Consider this code:
  
   (2) sort [ [1..], [2..], [3..] ]
  
   It is ok, because compare can decide between any elements in finite
 time.
   However, this one
  
   (3) sort [ [1..], [1..] ]
  
   will fail because of (1). Compare is simply unable to tell that two
   infinite list are equivalent.
   I solved this by producing partial results while comparing lists. If
   we compare lists
   (1:xs)
   (1:ys)
   we may not be able to tell xs  ys, but we do can tell that 1 will be
   the first element of both of smaller and greater one.
   You can see this idea in the code below.
  
  
   --- cut here ---
  
   {-# OPTIONS_GHC -O2 #-}
  
   module Data.YOrd where
  
   -- Well defined where Eq means equality, not only equivalence
  
   class YOrd a where
  ycmp :: a - a - (a,a)
  
  
   instance (YOrd a) = YOrd [a] where
  ycmp [] [] = ([],[])
  ycmp xs [] = ([],xs)
  ycmp [] xs = ([],xs)
  ycmp xs'@(x:xs) ys'@(y:ys) = let (sm,gt) = x `ycmp` y in
   let (smS,gtS) = xs `ycmp` ys in
   (sm:smS, gt:gtS)
  
  
   ycmpWrap x y = case x `compare` y of
   LT - (x,y)
   GT - (y,x)
   EQ - (x,y) -- biased - but we have to make 

Re: [Haskell-cafe] ANN (2 Libs) -- hvac 0.1b, a lightweight web framework and HStringTemplate 0.3

2008-03-23 Thread John Melesky

On Mar 23, 2008, at 1:21 AM, Sterling Clover wrote:
1) hvac 0.1b: transactional, declarative framework for lightweight  
web applications.

2) HStringTemplate 0.3


Excellent! Thanks for these.

-johnnn

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


Re: [Haskell-cafe] doctest for haskell -- a good project?

2008-03-23 Thread Marc Weber
Hi Shaun,

I've read the whole thread till now.
If you only look at the testing side Cabal is a possible target to run your 
tests.
(I think you've already met it?)

Adding documentation ficilities to ghci is nice,
however my experience is that documentation is not complete everywhere.
That's why I'm looking at source code directly (thus having doc strings if given
else I can have look at source directly).
One quick way to find the source location is using hasktags (comes with ghc).
It's still some work to create tags for each package (that's why 
I've automated it within the nix distribution system).
If you're interested send me a mail or contact me at #haskell.

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


Re: [Haskell-cafe] HXT and types in Control.Arrow.ArrowTree

2008-03-23 Thread Albert Y. C. Lai

Robert Vollmert wrote:
In short, I'm constantly running into what appear to be artificial type 
restrictions in Control.Arrow.ArrowTree. For example, the signature of 
deep is


deep :: (Tree t, ArrowTree a) = a (t b) (t b) - a (t b) (t b)

instead of the more general

deep :: (Tree t, ArrowTree a) = a (t b) c - a (t b) c


You are right, there is no harm generalizing deep, since a related 
combinator, multi, has the more general type.  Meanwhile, I don't think



deep (hasName a)  getLink


looks too bad. :)

Under suitable assumptions, you can use

multi getLink

if you want.

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


[Haskell-cafe] hoisting as well as lifting and returning

2008-03-23 Thread Matthew Pocock
Hi,

Happy Easter!

I've been using monad transformers for the first time in anger this week. They 
certainly do the job. However, there's an operation that I keep defining over 
and over again. It is sort of like lift and return in that it's glue to get 
operations and values into the monad from outside it. Here are two examples.

hoistList :: (Monad m) = [a] - ListT m a
hoistList = foldr (mplus . return) mzero

hoistMaybe :: (Monad m) = Maybe a - MaybeT m a
hoistMaybe = maybe mzero return

The general idea is that you have some legacy, non-transform operation in some 
monad MonadFoo, and you are writing an operation in MonadFooT. You want to 
get the monadFoo value into MonadFooT. So, you say something like:

do vInMFT - hoist vInMF

Is this a common enough operation on a monad transformer and it's 'raw' monad 
to warrant a class of its own? I have 'hoist' methods for several monad 
transformers, including RamdomMonadT, although I've probably defined them in 
ways that are overly eager or eat stack/heap, so I'd prefer knowledgable 
people to write them :)

There must be other operations that link the base monad with its transformed 
version, other than 'hoist' - the runFooT method for example.

Perhaps 'hoist' already exists and I'm re-inventing the wheel?

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


Re: [Haskell-cafe] doctest for haskell -- a good project?

2008-03-23 Thread Arnar Birgisson
On Sun, Mar 23, 2008 at 5:09 PM, Marc Weber [EMAIL PROTECTED] wrote:
  Adding documentation ficilities to ghci is nice,
  however my experience is that documentation is not complete everywhere.
  That's why I'm looking at source code directly (thus having doc strings if 
 given
  else I can have look at source directly).

This reminds me of a very handy feature in ipython (a custom python
repl) - you can type

name?

which prints the docstring associated with name (which can be a
function, module, class etc.) - but if you type

name??

you get the docstring _and_ the source code (colorized and all :). I
use it a lot when I'm experimenting in a interactive session. I could
see something similar for haskell being very useful, to me at least.

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


Re: [Haskell-cafe] hoisting as well as lifting and returning

2008-03-23 Thread Yitzchak Gale
Matthew Pocock wrote:
  I've been using monad transformers for the first time in anger this week.

I hope your enjoyment in using monads has helped your anger
to subside. :)

  ...there's an operation that I keep defining over
  and over again...
  hoistList :: (Monad m) = [a] - ListT m a
  hoistMaybe :: (Monad m) = Maybe a - MaybeT m a
  do vInMFT - hoist vInMF
  Perhaps 'hoist' already exists and I'm re-inventing the wheel?

You are correct. This is a fundamental operation. It exists
for just about every monad, but in a haphazard and
inconsistent way. In my opinion, its type needs to be
more polymorphic in a slightly different direction than what
you are suggesting.

Here's a sampling of what we have now:

State :: (s - (a, s)) - State s a
StateT . return :: Monad m = (s - (a, s)) - StateT s m a
liftList :: Monad m = [a] - ListT m a -- ListT_Done_Right
ErrorT . return :: Monad m = Either e a - ErrorT e a

You get the picture. Yes, it's a bit of a mess.

A general hoist function that would work for
disparate kinds of monads would require yet
an additional parameter to the MonadFoo class
for each monad. Or an additional MonadHoist
type class. (Or whatever the corresponding
additional complexity will be when we move to
associated types.) This would be needed to specify
what the underlying structure is that needs to be
hoisted from. I'm not sure that kind of polymorphism
would be worth the additional complexity - unless
someone can suggest a more beautiful way to capture
this generality. Otherwise, I think it would be enough
to have a hoist function for each monad, based on
the name of the monad.

What I do sorely feel the need for is a hoist for each pair
of base/transformer monads: i.e., polymorphic monad
constructors.

So, for example, if we had

mkState :: (st - (a, st)) - m a

as a member of the MonadState st m class,
then it would be so much easier to write functions

f :: MonadState st m = ...

that could be used without having to refactor it every time
the monad stack changes. In general, each monad
Foo would have a MonadFoo class (even the monads
that don't have one yet) containing (at least) a mkFoo
method that lifts the underlying structure polymorphically
either to Foo or to FooT.

btw, a variation on this is to provide only a hoist
or mkFoo for the transformer version of the monad, and
then use only transformers, basing every monad stack
at the Identity monad. This is what Iavor Diatchki does in
his monadlib library. I don't particularly like that approach,
though. In the most common simple case, I like being
able to specify whether my monad is a transformer or
not.

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


Re: [Haskell-cafe] Type checking of partial programs

2008-03-23 Thread ac
So a number of people responded with various ways this is already possible.
Of course GHC can already do this... it's type inference. The part I'm
interested in working on is exposing the functionality in GHC's API to make
this as easy as possible.

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


Re: [Haskell-cafe] hoisting as well as lifting and returning

2008-03-23 Thread Matthew Pocock
Hi Yitz,

I was thinking along the lines of a class linking the monad transformer with 
the base monad:

class (MonadTrans mt, Monad b) = MonadTForm mt b | mt - b
where 
  hoist :: (Monad m) = b a - mt m a

This is to restrict it directly between the base monad and the transformed 
version. If you wish to 'adapt' any other pair of monads, then I think that's 
another operation, just as lift is a different operation to hoist.

Matthew

On Sunday 23 March 2008, Yitzchak Gale wrote:
 You are correct. This is a fundamental operation. It exists
 for just about every monad, but in a haphazard and
 inconsistent way. In my opinion, its type needs to be
 more polymorphic in a slightly different direction than what
 you are suggesting.

...

 What I do sorely feel the need for is a hoist for each pair
 of base/transformer monads: i.e., polymorphic monad
 constructors.

 So, for example, if we had

 mkState :: (st - (a, st)) - m a

 as a member of the MonadState st m class,
 then it would be so much easier to write functions

 f :: MonadState st m = ...

 that could be used without having to refactor it every time
 the monad stack changes. In general, each monad
 Foo would have a MonadFoo class (even the monads
 that don't have one yet) containing (at least) a mkFoo
 method that lifts the underlying structure polymorphically
 either to Foo or to FooT.

...

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


[Haskell-cafe] Terminating GLUT/GLFW programs

2008-03-23 Thread hjgtuyl


L.S.,

I am trying GLUT and GLFW (on Windows XP, with GHC 6.8.2); the sample  
programs do not terminate when I close the window by clicking on the cross  
in the upper right corner of the window.


The sample program for GLUT is at
  
http://blog.mikael.johanssons.org/archive/2006/09/opengl-programming-in-haskell-a-tutorial-part-1/
the GLFW program:
  http://haskell.org/haskellwiki/GLFW

I tried in the GLUT program:
  close = exitWith ExitSuccess

  closeCallback $= Just close -- = User error (unknown GLUT call  
getCloseFunc, check for freeglut)


this needs freeglut (not documented); I downloaded freeglut.dll and placed  
it in the windows\system32 directory. The error message remained.


What is needed to let these programs terminate properly?

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--


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


[Haskell-cafe] more on FFI build error

2008-03-23 Thread Galchin Vasili
line #102 ...

   allocaBytes (#const sizeof(struct mq_attr)) $ \ p_attrs - do

definition of struct mq_attr on Linux ...

  struct mq_attr
{
  long int mq_flags;/* Message queue flags.  */
  long int mq_maxmsg;   /* Maximum number of messages.  */
  long int mq_msgsize;  /* Maximum message size.  */
  long int mq_curmsgs;  /* Number of messages currently queued.  */
  long int __pad[4];
};



build errors received 

[EMAIL PROTECTED]:~/FTP/Haskell/unix-2.2.0.0$ runhaskell Setup.hs build
Preprocessing library unix-2.2.0.0...
MQueue.hsc: In function 'main':

MQueue.hsc:102:0:
 error: invalid application of 'sizeof' to incomplete type 'struct
mq_attr'

MQueue.hsc:102:0:
 error: invalid application of 'sizeof' to incomplete type 'struct
mq_attr'

MQueue.hsc:102:0:
 error: invalid application of 'sizeof' to incomplete type 'struct
mq_attr'
compiling dist/build/System/Posix/MQueue_hsc_make.c failed
comma


???

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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-23 Thread Manuel M T Chakravarty

Claus Reinke:

type family F a :: * - *

..
We made the design choice that type functions with a higher-kinded  
result type must be injective with respect to the additional  
paramters. I.e. in your case:

F x y ~ F u v = F x ~ F u /\ y ~ v


i'm still trying to understand this remark:

- if we are talking about type functions, i should be allowed
  to replace a function application with its result, and if that
  result doesn't mention some parameters, they shouldn't
  play a role at any stage, right?

- if anything other than the function result matters, isn't it
  somewhat misleading to speak of type functions?


You will notice that I avoid calling them type functions.  In fact,  
the official term is type families.  That is what they are called in  
the spec http://haskell.org/haskellwiki/GHC/Type_families and GHC's  
option is -XTypeFamilies, too.  More precisely, they are type-indexed  
type families.


One difference between type families and (value-level) functions is  
that not all parameters of a type family are treated the same.  A type  
family has a fixed number of type indicies.  We call the number of  
type indicies the type family's arity and by convention, the type  
indicies come always before other type parameters.  In the example


  type family F a :: * - *

F has arity 1, whereas

  type family G a b :: *

has arity 2.  So, the number of named parameters given is the arity.   
(The overall kind is still F :: * - * - *; ie, the arity is not  
obvious from the kind, which I am somewhat unhappy about.)  In other  
words, in a type term like (F Int Bool), the two parameters Int and  
Bool are treated differently.  Int is treated like a parameter to a  
function (which is what you where expecting), whereas Bool is treated  
like a parameter to a vanilla data constructor (the part you did not  
expect).  To highlight this distinction, we call only Int a type  
index.  Generally, if a type family F has arity n, it's first n  
parameters are type indicies, the rest are treated like the parameters  
of any other type constructor.  Moreover, a type family of arity n,  
must always be applied to at least n parameters - ie, applications to  
type indicies cannot be partial.


This is not just an arbitrary design decision, it is necessary to stay  
compatible with Haskell's existing notion of higher-kinded unification  
(see, Mark Jones' paper about constructor classes), while keeping the  
type system sound.  To see why, consider that Haskell's higher-kinded  
type system, allows type terms, such as (c a), here c may be  
instantiated to be (F Int) or Maybe.  This is only sound if F treats  
parameters beyond its arity like any other type constructor.  A more  
formal discussion is in our TLDI paper about System F_C(X).


Manuel

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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-23 Thread Manuel M T Chakravarty

Tom Schrijvers:

could you please help me to clear up this confusion?-)


Let me summarize :-)

The current design for type functions with result kinds other than *
(e.g. * - *) has not gotten very far yet. We are currently  
stabilizing the ordinary * type functions, and writing the story up.  
When that's done we can properly focus on this issue and consider  
different design choices.


I don't quite agree.  The current story was pretty much settled in the  
paper on associated type synonyms already and further clarified in the  
FC paper.


Manuel

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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-23 Thread Manuel M T Chakravarty

Claus Reinke:

type family F a :: * - *

..
We made the design choice that type functions with a higher-kinded  
result type must be injective with respect to the additional  
paramters. I.e. in your case:

F x y ~ F u v = F x ~ F u /\ y ~ v


actually, i don't even understand the first part of that:-(

why would F x and F u have to be the same functions?
shouldn't it be sufficient for them to have the same result,
when applied to y and v, respectively?


Oh, yes, that is sufficient and exactly what is meant by F x ~ F u.   
It means, the two can be unified modulo any type instances and local  
given equalities.


Manuel

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