Re: [Haskell-cafe] type families and type signatures
On Mon, 7 Apr 2008, Manuel M T Chakravarty wrote: Ganesh Sittampalam: The following program doesn't compile in latest GHC HEAD, although it does if I remove the signature on foo'. Is this expected? Yes, unfortunately, this is expected, although it is very unintuitive. This is for the following reason. Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a -> Id a foo' :: forall b. Id b -> Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family, it would *not* be valid to derive (a ~ b) from this. After all, Id could have the same result for different argument types. (That's not the case for your one instance, but maybe in another module, there are additional instances for Id, where that is the case.) Can't it derive (Id a ~ Id b), though? Now, as GHC cannot show that a and b are the same, it can also not show that (Id a) and (Id b) are the same. It does look odd when you use the same type variable in both signatures, especially as Haskell allows you to leave out the quantifiers, but the 'a' in the signature of foo and the 'a' in the signatures of foo' are not the same thing; they just happen to have the same name. Sure, but forall a . Id a ~ Id a is the same thing as forall b . Id b ~ Id b. Thanks for the explanation, anyway. I'll need to have another think about what I'm actually trying to do (which roughly speaking is to specialise a general function over type families using a signature which I think I need for other reasons). Generally speaking, is there any way to give a signature to foo'? Given that this is a confusing issue, I am wondering whether we could improve matters by giving a better error message, or an additional hint in the message. Do you have any suggestion regarding what sort of message might have helped you? I can't think of anything good. Perhaps printing out the (type classes + equalities) context would have helped me to see that it was empty and understand why, but probably not. Cheers, Ganesh ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] type families and type signatures
On Sun, 6 Apr 2008, Thomas M. DuBuisson wrote: Id is an operation over types yielding a type, as such it doesn't make much sense to me to have (Id a -> Id a) but rather something like (a -> Id a). One could make this compile by adding the obvious instance: type instance Id a = a Curiously, is this a reduction from a real world use of families? I just can't think of how a (Fam a -> Fam a) function would be of use. Yes, it's cut down from an example where (I think) I really need the type signature to specialise a general function that does do something useful. The generalised intstance above wouldn't be valid or sensible in that context. Cheers, Ganesh ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] type families and type signatures
Ganesh Sittampalam: The following program doesn't compile in latest GHC HEAD, although it does if I remove the signature on foo'. Is this expected? Yes, unfortunately, this is expected, although it is very unintuitive. This is for the following reason. Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a -> Id a foo' :: forall b. Id b -> Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family, it would *not* be valid to derive (a ~ b) from this. After all, Id could have the same result for different argument types. (That's not the case for your one instance, but maybe in another module, there are additional instances for Id, where that is the case.) Now, as GHC cannot show that a and b are the same, it can also not show that (Id a) and (Id b) are the same. It does look odd when you use the same type variable in both signatures, especially as Haskell allows you to leave out the quantifiers, but the 'a' in the signature of foo and the 'a' in the signatures of foo' are not the same thing; they just happen to have the same name. BTW, here is the equivalent problem using FDs: class IdC a b | a -> b instance IdC Int Int bar :: IdC a b => b -> b bar = id bar' :: IdC a b => b -> b bar' = bar Given that this is a confusing issue, I am wondering whether we could improve matters by giving a better error message, or an additional hint in the message. Do you have any suggestion regarding what sort of message might have helped you? Manuel {-# LANGUAGE TypeFamilies #-} module Test7 where type family Id a type instance Id Int = Int foo :: Id a -> Id a foo = id foo' :: Id a -> Id a foo' = foo ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]
On Sun, Apr 06, 2008 at 11:30:20AM -0300, Felipe Lessa wrote: > On Sun, Apr 6, 2008 at 11:12 AM, John Meacham <[EMAIL PROTECTED]> wrote: > > I implemented this efficient lazy natural class once upon a time. it > > even has things like lazy multiplication: > [...] > > instance Num Nat where > > Zero + y = y > > Sum x n1 + y = Sum x (y + n1) > > --x + Zero = x > > --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) > [...] > > May I ask you why the last line above was commented out? Notice it flips the order of the arguments with each iteration. This allows it to avoid space leaks in some cases, for instance if you have infinity + (space wasting thunk), the space wasting thunk will never be deallocated even though it isn't used. It also means that the strictness properties are more symmetric than they would be otherwise as people expect of (+). 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: Well-Typed LLP - The Haskell Consultants
On Mon, 2008-04-07 at 02:57 +0400, Bulat Ziganshin wrote: > Hello Ian, > > Monday, April 7, 2008, 2:50:02 AM, you wrote: > > > We (Bjorn Bringert, Duncan Coutts and Ian Lynagh) are pleased to > > announce that we have recently set up a Haskell consultancy company, > > Well-Typed LLP (http://www.well-typed.com/). > > my congrats! Thank you. > seems you are first in this business :) Actually there are and have been a number of other individual consultants. So far as I know we're the first group specialising in Haskell consulting. The consultants page on the Haskell wiki lists some others and of course Alastair Reid did full time consulting for several years. Indeed he collected a list of other part time consultants. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] REMINDER: Next Hackathon (Hac4) starts in 4 days
Hi Haskell Hackers! There are only 4 days left until the fourth Hackathon (http:// www.haskell.org/haskellwiki/Hac4) at Chalmers University in Gothenburg, Sweden. If you haven't registered, yet, please do so now! Registration deadline: Tuesday, April 8, 2008 To register, go to http://www.haskell.org/haskellwiki/Hac4/Register and follow the steps. For all those already registered, here's a short (not nearly complete) checklist: * Make sure you have an account on code.haskell.org. (See http:// www.haskell.org/haskellwiki/Hac4/Projects for how to do that.) * Decide what to work on if you haven't yet. (See http:// www.haskell.org/haskellwiki/Hac4/Projects for ideas.) * Make sure your laptop is working and that you take all required extra equipment. (If your wireless driver sucks, we can probably find some cables and a switch here.) * It would be good to have all the code you want to work on already on your computer. Also make sure it builds with your compiler version. If your distro doesn't have binaries, maybe install some software in advance, like Gobby or profiled versions of GHC, newest version of gtk2hs or whatever seems appropriate. It would just be a shame to waste hours of precious hacking time. * Make a backup. Just in case. ;) * Many hostels want a confirmation a few days before arrival, don't forget. * If you need some phone numbers of locals, check the wiki site, if you need some more help from us locals, you can ask us at our IRC channel #haskell-hac4. We're looking forward to a fun weekend! / The Hac4 Team ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: Well-Typed LLP - The Haskell Consultants
Hello Ian, Monday, April 7, 2008, 2:50:02 AM, you wrote: > We (Bjorn Bringert, Duncan Coutts and Ian Lynagh) are pleased to > announce that we have recently set up a Haskell consultancy company, > Well-Typed LLP (http://www.well-typed.com/). my congrats! seems you are first in this business :) -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] ANNOUNCE: Well-Typed LLP - The Haskell Consultants
Fellow Haskellers, We (Björn Bringert, Duncan Coutts and Ian Lynagh) are pleased to announce that we have recently set up a Haskell consultancy company, Well-Typed LLP (http://www.well-typed.com/). Our services include application development, library and tool maintenance, project advice, and training. Please see our website or drop us an e-mail for more details. We look forward to hearing from you in the future! -- Björn Bringert, Duncan Coutts, Ian Lynagh http://www.well-typed.com/ [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] type families and type signatures
Id is an operation over types yielding a type, as such it doesn't make much sense to me to have (Id a -> Id a) but rather something like (a -> Id a). One could make this compile by adding the obvious instance: > type instance Id a = a Curiously, is this a reduction from a real world use of families? I just can't think of how a (Fam a -> Fam a) function would be of use. Cheers, Thomas Ganesh Sittampalam wrote: > The following program doesn't compile in latest GHC HEAD, although it does > if I remove the signature on foo'. Is this expected? > > Cheers, > > Ganesh > > {-# LANGUAGE TypeFamilies #-} > module Test7 where > > type family Id a > > type instance Id Int = Int > > foo :: Id a -> Id a > foo = id > > foo' :: Id a -> Id a > foo' = foo > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] problems building hpodder
I'm trying to build hpodder 1.1.2 with ghc 6.8.2. I successfully downloaded, built, and installed (the latest versions of) all its dependencies, but when building hpodder itself, I get FeedParser.hs:146:26: `Content' is not applied to enough type arguments Expected kind `??', but `Content' has kind `* -> *' In the type `Content -> Either String String' In the type `String -> Content -> Either String String' In the type signature for `strof_either': strof_either :: String -> Content -> Either String String I don't know enough Haskell to even determine what kind of problem this is -- wrong version of some dependency? Wrong version of ghc? Help appreciated. :-) ( FWIW, the hackage auto-builder thingie seems to have the exact same problem I have: http://hackage.haskell.org/packages/archive/hpodder/1.1.2/logs/failure/ghc-6.8 ) -- Karl Hasselström, [EMAIL PROTECTED] www.treskal.com/kalle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: [Haskell] ANN: Hayoo! beta 0.1
> I'm not sure if this is documented or not, but for those interested in > creating a search template for Firefox, Quicksilver and the like, it > is possible to use a URL such as this to enter a search term: > > http://holumbus.fh-wedel.de/hayoo/hayoo.html?query=catmaybes Well, it is not really documented, but if you visit the Hayoo! page using Firefox, it is possible to add Hayoo! as search engine to the small search box in the upper right corner using the drop down menu. Timo ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
t.h: > Hello, > > we are pleased to announce the first beta release of Hayoo!, a Haskell API > search engine providing advanced features like suggestions, find-as-you-type, > fuzzy queries and much more. > > Visit Hayoo! here: http://holumbus.fh-wedel.de/hayoo > > Please bear in mind that this is still a beta release and we are continuously > working on further improvements. Our plans for the future include: > > - Covering all documentation available at Hackage. > - Compatibility with non-JavaScript enabled browsers. > - Providing a web interface where people can point Hayoo! to an URI linking > to Haddock documentation which will be automatically included in Hayoo!. > > Hayoo! was developed as a use-case for the Holumbus framework, which aims to > help at the creation of very flexible and highly specialized search engines. > > Although Holumbus is still under heavy development and we have no official > release yet, some informations and a Darcs repository are available at the > Holumbus homepage: http://holumbus.fh-wedel.de Also, I see you have the QuickCheck and cabal badges, but your HPC use also qualifies for: http://projects.unsafeperformio.com/hpc/hpcbadge.jpg I'd argue :) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: [Haskell] ANN: Hayoo! beta 0.1
On 06/04/2008, Timo B. Hübel <[EMAIL PROTECTED]> wrote: > Hello, > > we are pleased to announce the first beta release of Hayoo!, a Haskell API > search engine providing advanced features like suggestions, find-as-you-type, > fuzzy queries and much more. Very nice! I'm not sure if this is documented or not, but for those interested in creating a search template for Firefox, Quicksilver and the like, it is possible to use a URL such as this to enter a search term: http://holumbus.fh-wedel.de/hayoo/hayoo.html?query=catmaybes Cheers, Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
On Sunday 06 April 2008 20:31:09 you wrote: > Overall feedback: Cool! So far, I like Hayoo!, and I'm therefore > interested in Holumbus. Is there some technical overview available? Currently, only what you can find on http://holumbus.fh-wedel.de but we will try to extend the site in the near future. > transcript of my short test of hayoo, including nitty-picky feedback: > [...] Thanks for this extensive feedback, some of these are known issues we're already working on which will be fixed soon. The others are on my TODO list now :) Regards, Timo ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] type families and type signatures
Hi, The following program doesn't compile in latest GHC HEAD, although it does if I remove the signature on foo'. Is this expected? Cheers, Ganesh {-# LANGUAGE TypeFamilies #-} module Test7 where type family Id a type instance Id Int = Int foo :: Id a -> Id a foo = id foo' :: Id a -> Id a foo' = foo ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
t.h: > Hello, > > we are pleased to announce the first beta release of Hayoo!, a Haskell API > search engine providing advanced features like suggestions, find-as-you-type, > fuzzy queries and much more. > > Visit Hayoo! here: http://holumbus.fh-wedel.de/hayoo > > Please bear in mind that this is still a beta release and we are continuously > working on further improvements. Our plans for the future include: > > - Covering all documentation available at Hackage. > - Compatibility with non-JavaScript enabled browsers. > - Providing a web interface where people can point Hayoo! to an URI linking > to Haddock documentation which will be automatically included in Hayoo!. > > Hayoo! was developed as a use-case for the Holumbus framework, which aims to > help at the creation of very flexible and highly specialized search engines. > > Although Holumbus is still under heavy development and we have no official > release yet, some informations and a Darcs repository are available at the > Holumbus homepage: http://holumbus.fh-wedel.de > > Any suggestions and feedback is highly welcomed. > Very very nice! And with HPC coverage details! http://holumbus.fh-wedel.de/coverage/hpc_index.html Excellent work guys. -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
Timo B. Hübel wrote: On Sunday 06 April 2008 16:38:03 Richard Kelsall wrote: Little detail : After visiting a page that appears in the search results then doing a back button the search I did is no longer there. (On my eccentric Firefox setup anyway.) Hm, that's strange. I know about this problem when using Konqueror, but my Firefox (Linux, 2.0.0.13) keeps the results even after visiting the documentation and hitting the back button. Which Firefox version do you use? I'm still on the old Firefox 1.5.0.5 : Mozilla/5.0 (X11; U; OpenBSD i386; en-US; rv:1.8.0.5) Gecko/20060902 Firefox/1.5.0.5 I expect most people have upgraded to by now so I wouldn't worry about it if it works in the new version. I just tried again switching off my Adblock and switching on Java and Javascript, but couldn't seem to get anything except a blank search page after clicking the back button. Maybe just my strange setup. Richard. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
On Sun, Apr 6, 2008 at 1:24 PM, Timo B. Hübel <[EMAIL PROTECTED]> wrote: > Hm, that's strange. I know about this problem when using Konqueror, but my > Firefox (Linux, 2.0.0.13) keeps the results even after visiting the > documentation and hitting the back button. My Epiphany works fine. Anyway, I can't use back and forward to navigate between my searches (i.e. while on Hayoo!, pressing Back takes me to the page I was before going to Hayoo! instead of the page inside Hayoo! I was before reaching that point). It would be very nice if it was a history-friendly site. Keep up the good work! =) Thanks, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
On Sunday 06 April 2008 16:38:03 Richard Kelsall wrote: > Little detail : After visiting a page that appears in the search results > then doing a back button the search I did is no longer there. (On my > eccentric Firefox setup anyway.) Hm, that's strange. I know about this problem when using Konqueror, but my Firefox (Linux, 2.0.0.13) keeps the results even after visiting the documentation and hitting the back button. Which Firefox version do you use? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: Hayoo! beta 0.1
Timo B. Hübel wrote: Hello, we are pleased to announce the first beta release of Hayoo!, a Haskell API search engine providing advanced features like suggestions, find-as-you-type, fuzzy queries and much more. Visit Hayoo! here: http://holumbus.fh-wedel.de/hayoo Please bear in mind that this is still a beta release and we are continuously working on further improvements. Our plans for the future include: - Covering all documentation available at Hackage. - Compatibility with non-JavaScript enabled browsers. Yes please. - Providing a web interface where people can point Hayoo! to an URI linking to Haddock documentation which will be automatically included in Hayoo!. Hayoo! was developed as a use-case for the Holumbus framework, which aims to help at the creation of very flexible and highly specialized search engines. Although Holumbus is still under heavy development and we have no official release yet, some informations and a Darcs repository are available at the Holumbus homepage: http://holumbus.fh-wedel.de Any suggestions and feedback is highly welcomed. Really like it. Looks very smart. Thank you! Little detail : After visiting a page that appears in the search results then doing a back button the search I did is no longer there. (On my eccentric Firefox setup anyway.) Cheers, Timo B. Hübel & Sebastian M. Schlatt ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]
On Sun, Apr 6, 2008 at 11:12 AM, John Meacham <[EMAIL PROTECTED]> wrote: > I implemented this efficient lazy natural class once upon a time. it > even has things like lazy multiplication: [...] > instance Num Nat where > Zero + y = y > Sum x n1 + y = Sum x (y + n1) > --x + Zero = x > --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) [...] May I ask you why the last line above was commented out? Thanks! -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]
On Fri, Apr 04, 2008 at 04:46:22PM +0100, Neil Mitchell wrote: > Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the > Int's aren't equal, since we don't have proper lazy naturals. If we > did, it would take 2 steps. > > Read this: http://citeseer.ist.psu.edu/45669.html - it argues the > point I am trying to make, but much better. I implemented this efficient lazy natural class once upon a time. it even has things like lazy multiplication: -- Copyright (c) 2007 John Meacham (john at repetae dot net) -- -- Permission is hereby granted, free of charge, to any person obtaining a -- copy of this software and associated documentation files (the -- "Software"), to deal in the Software without restriction, including -- without limitation the rights to use, copy, modify, merge, publish, -- distribute, sublicense, and/or sell copies of the Software, and to -- permit persons to whom the Software is furnished to do so, subject to -- the following conditions: -- -- The above copyright notice and this permission notice shall be included -- in all copies or substantial portions of the Software. -- -- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS -- OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -- IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -- CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -- TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -- SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -- efficient lazy naturals module Util.LazyNum where -- Nat data type is eqivalant to a type restricted lazy list that is strict in -- its elements. -- -- Invarients: (Sum x _) => x > 0 -- in particular (Sum 0 _) is _not_ valid and must not occur. data Nat = Sum !Integer Nat | Zero deriving(Show) instance Eq Nat where Zero == Zero = True Zero == _ = False _ == Zero = False Sum x nx == Sum y ny = case compare x y of EQ -> nx == ny LT -> nx == Sum (y - x) ny GT -> Sum (x - y) nx == ny instance Ord Nat where Zero <= _ = True _ <= Zero = False Sum x nx <= Sum y ny = case compare x y of EQ -> nx <= ny LT -> nx <= Sum (y - x) ny GT -> Sum (x - y) nx <= ny Zero `compare` Zero = EQ Zero `compare` _ = LT _`compare` Zero = GT Sum x nx `compare` Sum y ny = case compare x y of EQ -> nx `compare` ny LT -> nx `compare` Sum (y - x) ny GT -> Sum (x - y) nx `compare` ny x < y = not (x >= y) x >= y = y <= x x > y = y < x instance Num Nat where Zero + y = y Sum x n1 + y = Sum x (y + n1) --x + Zero = x --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) Zero - _ = zero x - Zero = x Sum x n1 - Sum y n2 = case compare x y of GT -> Sum (x - y) n1 - n2 EQ -> n1 - n2 LT -> n1 - Sum (y - x) n2 negate _ = zero abs x = x signum Zero = zero signum _ = one fromInteger x = if x <= 0 then zero else Sum x Zero Zero * _ = Zero _ * Zero = Zero (Sum x nx) * (Sum y ny) = Sum (x*y) ((f x ny) + (nx * (fint y + ny))) where f y Zero = Zero f y (Sum x n) = Sum (x*y) (f y n) instance Real Nat where toRational n = toRational (toInteger n) instance Enum Nat where succ x = Sum 1 x pred Zero = Zero pred (Sum n x) = if n == 1 then x else Sum (n - 1) x enumFrom x = x:[ Sum n x | n <- [1 ..]] enumFromThen x y = x:y:f (y + z) where z = y - x f x = x:f (x + z) toEnum = fromIntegral fromEnum = fromIntegral -- d > 0 doDiv :: Nat -> Integer -> Nat doDiv n d = f 0 n where f _ Zero = 0 f cm (Sum x nx) = sum d (f m nx) where (d,m) = (x + cm) `quotRem` d sum 0 x = x sum n x = Sum n x doMod :: Nat -> Integer -> Nat doMod n d = f 0 n where f 0 Zero = Zero f r Zero = fint r f r (Sum x nx) = f ((r + x) `rem` d) nx instance Integral Nat where _ `div` Zero = infinity n1 `div` n2 | n1 < n2 = 0 | otherwise = doDiv n1 (toInteger n2) n1 `mod` Zero = n1 -- XXX n1 `mod` n2 | n1 < n2 = n1 | otherwise = doMod n1 (toInteger n2) n `divMod` Zero = (infinity,n) n `divMod` d | n < d = (0,n) | otherwise = let d' = toInteger d in (doDiv n d',doMod n d') quotRem = divMod quot = div rem = mod toInteger n = f 0 n where f n _ | n `seq` False = undefined f n Zero = n f n (Sum x n1) = let nx = n + x in nx `seq` f nx n1 -- convert to integer unless it is too big, in which case Nothing is returned natToInteger :: Integer -> Nat -> Maybe Integer natToInteger limit n = f 0 n where f n _ | n > limit = Nothing f n Zero = Just n f n (Sum x n1) = let nx = n + x in nx `seq` f nx n1 natShow :: Nat -> String natShow n = case natToInteger bigNum n of Nothing -
[Haskell-cafe] ANN: Hayoo! beta 0.1
Hello, we are pleased to announce the first beta release of Hayoo!, a Haskell API search engine providing advanced features like suggestions, find-as-you-type, fuzzy queries and much more. Visit Hayoo! here: http://holumbus.fh-wedel.de/hayoo Please bear in mind that this is still a beta release and we are continuously working on further improvements. Our plans for the future include: - Covering all documentation available at Hackage. - Compatibility with non-JavaScript enabled browsers. - Providing a web interface where people can point Hayoo! to an URI linking to Haddock documentation which will be automatically included in Hayoo!. Hayoo! was developed as a use-case for the Holumbus framework, which aims to help at the creation of very flexible and highly specialized search engines. Although Holumbus is still under heavy development and we have no official release yet, some informations and a Darcs repository are available at the Holumbus homepage: http://holumbus.fh-wedel.de Any suggestions and feedback is highly welcomed. Cheers, Timo B. Hübel & Sebastian M. Schlatt ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Role based access control via monads or arrows or... something
Any help you can offer for my aching cranium will be _much_ appreciated. You might also be interested in the paper Edwin Brady and Kevin Hammond just submitted to ICFP: http://www.cs.st-andrews.ac.uk/~eb/drafts/icfp08.pdf It describes how to manage resources, in particular locks, in a dependently-typed language. You didn't explicitly mention that it needed to be in Haskell, so it might be worth having a look. Best of luck, Wouter ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Role based access control via monads or arrows or... something
David Roundy wrote: apfelmus wrote: David Roundy wrote: porrifolius wrote: (7) ideally required permissions would appear (and accumulate) in type signatures via inference so application code knows which are required and type checker can reject static/dynamic role constraint violations In other words, I fail to see how this GADT example is different from a normal phantom type (modulo different naming) The difference is that I can inspect at runtime what permissions I have. I see that I didn't demonstrate this. You can introduce a function checkPerms :: HavePermission p -> HavePermission p' -> EqCheck checkPerms HaveAPerm HaveAPerm = IsEq checkPerms HaveBPerm HaveBPerm = IsEq checkPerms _ _ = NotEq data EqCheck a b where IsEq :: EqCheck a a NotEq :: EqCheck a b which allows you to compare permissions at runtime and make use of them. Ah, so you are able to use case expressions casePerm :: (Permission Low -> a) -> (Permission High -> a) -> Permission any -> a which is not possible with a plain phantom type approach. One example use would be foo :: Permission p -> Either String Bar foo = casePerm (const $ Left "foo: permission too low") (\p -> readRestricted p ... ) Of course, you may not export HaveAPerm and HaveBPerm (at least not for construction, only for pattern matching), so you probably need such a special function casePerm anyway. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe