Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-24 Thread Ozgur Akgun
Hi. On 23 August 2013 13:29, Nicolas Trangez nico...@incubaid.com wrote: Did anyone ever consider using type-level literals (strings) to 'name' effects (or transformer layers when using monad stacks)? Edwin Brady had this in his effects library in Idris.

Re: [Haskell-cafe] llvm on macos

2013-08-15 Thread Ozgur Akgun
Hi. On 15 August 2013 20:35, Carter Schonwald carter.schonw...@gmail.comwrote: Just brew install llvm should work fine. I wonder what makes you think this is the case. At this moment in time, `brew install llvm` will install llvm-3.3. Using llvm-3.3, I get warnings and errors. Using

Re: [Haskell-cafe] llvm on macos

2013-08-11 Thread Ozgur Akgun
. -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] llvm on macos

2013-08-10 Thread Ozgur Akgun
Hi. On 10 August 2013 18:20, Brandon Allbery allber...@gmail.com wrote: There may be some support for requesting specific versions from Homebrew. Try `brew versions llvm`. Then, you'll need to run the git checkout command in `brew --prefix` directory. I am using llvm 3.2 because I had a few

Re: [Haskell-cafe] Casting newtype to base type?

2013-07-06 Thread Ozgur Akgun
Hi Vlatko. On 2 July 2013 16:03, Vlatko Basic vlatko.ba...@gmail.com wrote: Is there a nicer way to extract the 'IO String' from 'IOS', without 'case' or without pattern matching the whole 'P'? You might enjoy the newtype package. http://hackage.haskell.org/package/newtype Hope this helps,

Re: [Haskell-cafe] TH clause Pat selection

2013-06-20 Thread Ozgur Akgun
Hi. On 19 June 2013 23:23, Brian Lewis br...@lorf.org wrote: The problem is, I don't know how to generate the function's clauses. foo 0 = ... seems to be a LitP pattern. But foo True = ... seems to be a ConP pattern. The appropriate pattern depends on type c. I've used haskell-src-meta for

Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ozgur Akgun
Hi, On 3 May 2013 11:43, Tobias Dammers tdamm...@gmail.com wrote: PS The proposal to fix Functor = Applicative = Monad has patches attached for GHC and base, but the backwards compatibility bogeyman always seems to trump something that will break a lot of code. This kind of breaks

Re: [Haskell-cafe] Haskell compilation errors break the complexity encapsulation on DSLs

2013-04-27 Thread Ozgur Akgun
Hi, On 27 April 2013 10:07, Alberto G. Corona agocor...@gmail.com wrote: I created a ticket for the feature request: Ticket #7870 Teachers, newbies and people working in Industry: Please push it! A link to the ticket may be helpful for the lazy.

[Haskell-cafe] cabal install choosing an older version

2013-01-25 Thread Ozgur Akgun
: HUnit-1.2.5.1 (new package) ansi-terminal-0.6 (new package) extensible-exceptions-0.1.1.4 (new package) random-1.0.1.1 (new package) QuickCheck-2.5 (new package) hspec-0.3.0 (new package) -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] cabal install choosing an older version

2013-01-25 Thread Ozgur Akgun
Aha! I think I know why this happens. The latest versions of ansi-terminal and hspec do not work together. Cabal picks the latest ansi-terminal (0.6) first, then the latest hspec that doesn't conflict with this choice is 0.3.0. I can confirm this by the following: $ cabal install hspec

Re: [Haskell-cafe] cabal install choosing an older version

2013-01-25 Thread Ozgur Akgun
Hi Max, On 25 January 2013 15:58, Max Bolingbroke batterseapo...@hotmail.comwrote: If this happens because the dependency bounds of ansi-terminal are too tight then please send me a patch. No, actually it happens because hspec depends on ansi-terminal-0.5.*. I am cc'ing Simon Hengel, the

Re: [Haskell-cafe] Quickcheck

2012-11-13 Thread Ozgur Akgun
, instead of generating and discarding some. hth, -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Is there a tool to see reduction steps?

2012-10-10 Thread Ozgur Akgun
Hi Daryoush, You could add another case to label, importing Debug.Trace: data Tree = Leaf | Node Tree Int Tree deriving Show *label t | trace (show $ label ++ show t) False = undefined* label (Node ln _ rn) ((h:r):rest) = (Node lr h rr, r:r2) where

Re: [Haskell-cafe] a parallel mapM?

2012-10-07 Thread Ozgur Akgun
Hi, On 3 October 2012 19:23, Ryan Newton rrnew...@gmail.com wrote: That said, I don't see a reason for not including a separate version of runParIO :: ParIO a - IO a for non-deterministic computations. It seems really useful! Exactly. I should have been more explicit but that's what I

Re: [Haskell-cafe] Discovery of unnecessary build-depends

2012-09-29 Thread Ozgur Akgun
On 28 September 2012 19:29, Jason Whittle ja...@funnelfire.com wrote: Is there a tool available that will tell me if the cabal file for my library or application has any unnecessary build-depends? FWIW, I felt the need for such a tool many times before too. The same tool can also report

Re: [Haskell-cafe] Printing call site for partial functions

2012-04-25 Thread Ozgur Akgun
Hi, On 25 April 2012 16:36, Michael Snoyman mich...@snoyman.com wrote: Prelude.head: empty list Recent versions of GHC actually generate a very helpful stack trace, if the program is compiled with profiling turned on and run with -xc. See:

Re: [Haskell-cafe] adding the elements of two lists

2012-03-29 Thread Ozgur Akgun
On 29 March 2012 04:34, Richard O'Keefe o...@cs.otago.ac.nz wrote: u f (PS x)= PS $ map f x b f (PS x) (PS y) = PS $ zipWith f x y to_ps x = PS (x : repeat 0) Also see: http://hackage.haskell.org/package/newtype -- Ozgur Akgun

Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-19 Thread Ozgur Akgun
Hi, If you are feeling adventurous enough, you can define a num instance for functions: {-# LANGUAGE FlexibleInstances #-} instance Num a = Num (a - a) where f + g = \ x - f x + g x f - g = \ x - f x - g x f * g = \ x - f x * g x abs f = abs . f signum f = signum . f

Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-19 Thread Ozgur Akgun
On 19 March 2012 17:43, David Thomas davidleotho...@gmail.com wrote: The 17 at the end should be 12, or the 2 passed into (f+g+2) should be 3. It was the latter :) Copy/paste error, sorry. Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-19 Thread Ozgur Akgun
Hi Chris, On 19 March 2012 17:58, Chris Smith cdsm...@gmail.com wrote: On Mar 19, 2012 11:40 AM, Ozgur Akgun ozgurak...@gmail.com wrote: {-# LANGUAGE FlexibleInstances #-} instance Num a = Num (a - a) where You don't want (a - a) there. You want (b - a). There is nothing about

[Haskell-cafe] cabal test-suite library recompilation

2012-03-13 Thread Ozgur Akgun
Hi all, I've recently started to move my tests to use the new cabal test-suite framework. Old setup: The cabal file compiles one library + a few executables. The library contains almost all of the code and exposes the necessary modules for use by the executables. The executables mainly consist

Re: [Haskell-cafe] cabal test-suite library recompilation

2012-03-13 Thread Ozgur Akgun
On 13 March 2012 16:22, Antoine Latter aslat...@gmail.com wrote: If your library code and test code are in separate sub-directories and you reference your library as a package dependency for your test then Cabal won't re-build your library. Yay! That was it. Thanks. Somehow I altered the

Re: [Haskell-cafe] Prettier pretty-printing of data types?

2012-03-13 Thread Ozgur Akgun
I prefer pretty-show rather than groom as it's output is hierarchical. http://hackage.haskell.org/package/pretty-show Ozgur On 13 March 2012 22:37, Austin Seipp mad@gmail.com wrote: It's not exactly hierarchical, but Groom most certainly should help with getting much prettier output:

Re: [Haskell-cafe] Finally, a pure iteratee library that deals with errors

2012-02-26 Thread Ozgur Akgun
I didn't really look into (enumerators/iteratees/conduits/etc)-land closely enough, but I can say one thing. The code you link to is very easy to understand and see what is going on. This must be a good thing. On 26 February 2012 10:50, Daniel Waterworth da.waterwo...@gmail.comwrote: There's

[Haskell-cafe] hackage down

2012-02-18 Thread Ozgur Akgun
Hackage seems to be down: http://www.downforeveryoneorjustme.com/http://hackage.haskell.org Best, Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] how to print out intermediate results in a recursive function?

2012-02-03 Thread Ozgur Akgun
Hi, There is also this nice trick to use Debug.Trace: merge xs ys | trace (show (xs,ys)) False = undefined -- add this as the first case to merge mergesort xs | trace (show xs) False = undefined -- and this as the first case to mergesort HTH, Ozgur

Re: [Haskell-cafe] ghc-api Static Semantics?

2012-01-23 Thread Ozgur Akgun
Hi, I don't know what you actually need, but if haskell-src-exts is an option, it is quite a bit easier to use (definitely easier to understand for me!). Especially when used together with Uniplate. For example, for a given piece of AST one can get all the identifiers used like so: [ x | Ident

Re: [Haskell-cafe] Idris

2012-01-20 Thread Ozgur Akgun
Just by looking at the hackage dependencies, it doesn't look like it has unix-only dependencies. Maybe the Boehm garbage collector? http://www.hpl.hp.com/personal/Hans_Boehm/gc/ Also, Idris has a mailing list, Edwin would be more likely to respond there: http://groups.google.com/group/idris-lang

Re: [Haskell-cafe] GHC exceeding command line length limit with split-objs - and a possible fix

2012-01-11 Thread Ozgur Akgun
Hi Eugene, I think I did run into this problem before, and had to turn of split-objs temporarily to work around it. I'd appreciate a fix. Best, Ozgur On 11 January 2012 14:14, Eugene Kirpichov ekirpic...@gmail.com wrote: Now my original question remains - is such a change a good idea? (I've

Re: [Haskell-cafe] DB vs read/show for persisting large data

2011-12-14 Thread Ozgur Akgun
On 14 December 2011 15:02, Yves Parès limestr...@gmail.com wrote: The 'derive' package? The problem is that it has a lot of dependencies you maybe don't need if you jut want serialization, plus it relies on TH so it grows both compilation time and executable size. Well you can use the stand

Re: [Haskell-cafe] How to get a file path to the program invoked?

2011-12-05 Thread Ozgur Akgun
Hi. On 5 December 2011 14:53, dokondr doko...@gmail.com wrote: Main System.Environment.Executable System.FilePath /abc / / / Instead of getting /abc/ I get /. What am I doing wrong? It thinks the second path is an absolute path. Combine two paths, if the second path isAbsolute, then it

Re: [Haskell-cafe] cabal install --hyperlink-source ?

2011-12-02 Thread Ozgur Akgun
On 2 December 2011 16:13, Johannes Waldmann waldm...@imn.htwk-leipzig.dewrote: but I don't see how to pass options from cabal install to cabal haddock (e.g., --hyperlink-source) As it seems, it is not possible.

Re: [Haskell-cafe] Using QuickCheck to test against a database

2011-12-01 Thread Ozgur Akgun
Hi! This looks cool indeed. On 2 December 2011 00:02, Oliver Charles haskell-c...@ocharles.org.ukwrote: [snip] You have to remember to apply all of the states of your arbitrary instances, which is a pain, and guaranteed to be missed. Why can't you define a helper function which runs the

Re: [Haskell-cafe] ANN: Netwire 2.0.0

2011-11-14 Thread Ozgur Akgun
Hi Ertugrul, Compilation problems here: cabal install netwire [ 7 of 22] Compiling Control.Wire.Prefab.Simple ( Control/Wire/Prefab/Simple.hs, dist/build/Control/Wire/Prefab/Simple.o ) Control/Wire/Prefab/Simple.hs:15:7: Ambiguous occurrence `force' It could refer to either

Re: [Haskell-cafe] ANN: Netwire 2.0.0

2011-11-14 Thread Ozgur Akgun
On 14 November 2011 16:33, Ertugrul Soeylemez e...@ertes.de wrote: It should be fixed now. Thanks for your report! Fixed indeed. Thanks. Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Libraries to compare trees?

2011-10-28 Thread Ozgur Akgun
Hi. On 27 October 2011 13:49, dokondr doko...@gmail.com wrote: Please advise on Haskell libraries to compare trees in textual representation. I need to compare both structure and node contents of two trees, find similar sub-trees, and need some metric to measure distance between two trees.

Re: [Haskell-cafe] Parsec and Text

2011-10-08 Thread Ozgur Akgun
Hi. See the following for the recent announcement: http://permalink.gmane.org/gmane.comp.lang.haskell.general/18972 On 8 October 2011 18:37, Yves Parès limestr...@gmail.com wrote: Is there a package that allows parsing Text with parsec, ... HTH, Ozgur

Re: [Haskell-cafe] Really Simple explanation of Continuations Needed

2011-10-01 Thread Ozgur Akgun
Hi. On 1 October 2011 11:55, Yves Parès limestr...@gmail.com wrote: BTW Heinrich, the evalState (sequence . repeat . State $ \s - (s,s+1)) 0 at the end doesn't work anymore. It should be replaced by : evalState (sequence . repeat . StateT $ \s - Identity (s,s+1)) 0 Or equivalently:

[Haskell-cafe] Fwd: problem with cabal install MissingH-1.1.1.0

2011-09-22 Thread Ozgur Akgun
Ooops, apparently I forgot to reply to the list. Sorry. -- Forwarded message -- From: Ozgur Akgun ozgurak...@gmail.com Date: 22 September 2011 16:49 Subject: Re: [Haskell-cafe] problem with cabal install MissingH-1.1.1.0 To: Mariano Cortesi mcort...@gmail.com Hi Mariano. On 22

[Haskell-cafe] cabal-install to produce a dependency tree

2011-09-14 Thread Ozgur Akgun
Dear Cafe, What would be the easiest way of generating the following output, given a package name optionally with additional constraints? $- foo X 3 X 3 depends on A-2.2, B-1.0, C-1.2 A-2.2 depends on D-1.2.3 ... I assume cabal-install internally does this anyway while creating the

[Haskell-cafe] type profiling not helpful

2011-09-02 Thread Ozgur Akgun
in advance, [1] http://www.haskell.org/ghc/docs/latest/html/users_guide/prof-heap.html#rts-options-heap-prof -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Unexpected Typeable behaviour; Prelude.undefined

2011-08-28 Thread Ozgur Akgun
Hi Philip, On 28 August 2011 23:44, Philip Holzenspies p...@st-andrews.ac.uk wrote: import Data.Typeable data MyADT m = MyADT (m ()) instance (Typeable1 m, Monad m) = Typeable (MyADT m) where typeOf t@(MyADT _) = mkTyCon MyADT `mkTyConApp` [typeOf1

Re: [Haskell-cafe] Haddock chokes on function arguments

2011-08-25 Thread Ozgur Akgun
Hi Arnaud, On 25 August 2011 15:44, Arnaud Bailly arnaud.oq...@gmail.com wrote: But then, why is it documented the other way ? It isn't, as far as I can see. Are we both looking at the same place, namely section 3.2.3? -- Ozgur Akgun ___ Haskell

[Haskell-cafe] haskell-src-exts should depend on happy

2011-08-25 Thread Ozgur Akgun
Hi, cabal installing haskell-src-exts fails, because of an unlisted dependency to the happy executable. The following succeeds: cabal install happy; cabal install haskell-src-exts Thanks, Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Ozgur Akgun
Evan, On 24 May 2011 19:57, Evan Laforge qdun...@gmail.com wrote: On the catMaybes thing, I have a function 'mapMaybe = Maybe.catMaybes . map'. I turns out I only ever used catMaybes after mapping a Maybe function, so I hardly ever use catMaybes anymore. I suppose it should have been

Re: [Haskell-cafe] Hash table constructors return table in IO Monad. Why?

2011-05-12 Thread Ozgur Akgun
On 12 May 2011 20:59, michael rice nowg...@yahoo.com wrote: HashTable doesn't do it. Neither does Map. Was I dreaming? I suppose you could implement this functionality on top of either. HTH, Ozgur ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Reformatter for Show

2011-05-02 Thread Ozgur Akgun
Hi Alexey, On 2 May 2011 21:01, Alexey Khudyakov alexey.sklad...@gmail.com wrote: My question is there any tool for reformatting result of show so it could be read by human beings? http://hackage.haskell.org/package/pretty-show Just use ppShow, instead of show. Hope this helps, Ozgur

Re: [Haskell-cafe] Trouble with currying and uncurrying...

2011-04-25 Thread Ozgur Akgun
On 25 April 2011 14:11, Angel de Vicente ang...@iac.es wrote: curry :: ((a,b) - c) - (a - b - c) is the same as: curry :: ((a,b) - c) - a - b - c HTH, Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] 64 bit generic link warning on every compile

2011-04-16 Thread Ozgur Akgun
___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Fucntion composing

2011-04-11 Thread Ozgur Akgun
? Ajschylos. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] parsec - source position information

2011-04-07 Thread Ozgur Akgun
Hi, Is there a way to get source position[1] information from parsec while defining a parser? It surely knows about source positions, as they are used while reporting a parsing error. data Identifier = Identifier String SourcePos pIdentifier :: Parser Identifier pIdentifier = do pos - ??

Re: [Haskell-cafe] parsec - source position information

2011-04-07 Thread Ozgur Akgun
Thanks! On 7 April 2011 16:27, Christopher Done chrisd...@googlemail.com wrote: On 7 April 2011 17:22, Ozgur Akgun ozgurak...@gmail.com wrote: Is there a way to get source position[1] information from parsec while defining a parser? It surely knows about source positions, as they are used

Re: [Haskell-cafe] Question on a common pattern

2011-03-14 Thread Ozgur Akgun
://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-04 Thread Ozgur Akgun
place where we have the lexicographic ordering by default. HTH, -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Ozgur Akgun
On 16 February 2011 09:19, Tako Schotanus t...@codejive.org wrote: I wondered if there was a way for a guard in a list comprehension to refer to the item being produced? I'm just wondering about this very specific case Then, the answer is no. As others have noted, let binding is the way

Re: [Haskell-cafe] combined parsing pretty-printing

2011-02-05 Thread Ozgur Akgun
constructors. To be precise, you handle the case for NormalC in the code, however you do not handle RecC. I don't think this will be a difficult thing to add. Is there any reason for you not to support RecC? Best, 2011/1/26 Tillmann Rendel ren...@informatik.uni-marburg.de Hi Ozgur, Ozgur Akgun

Re: [Haskell-cafe] combined parsing pretty-printing

2011-02-05 Thread Ozgur Akgun
Great! That was pretty fast :) Are you going to update invertible-syntax to use partial-isomorphisms-0.2? 2011/2/5 Tillmann Rendel tillm...@rendel.net Hi Ozgur, Ozgur Akgun wrote: I've already implemented a toy example and it worked great. Now I am trying to use your library in a more

Re: [Haskell-cafe] Inheritance and Wrappers

2011-02-03 Thread Ozgur Akgun
On 3 February 2011 02:35, Brandon Moore brandon_m_mo...@yahoo.com wrote: Here's one thing to consider: Can you write a function f :: (Data a) = a - String f x = termTag x It would seem the Data a = Term a instance justifies this function, and it will always use the default instance.

Re: [Haskell-cafe] Haskell Functions

2011-02-03 Thread Ozgur Akgun
On 3 February 2011 18:33, Manolache Andrei-Ionut andressocrate...@yahoo.com wrote: first this is the curent code :http://pastebin.com/UPATJ0r There is no code on that page. (It has expired, probably?) -- Ozgur Akgun ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Ozgur Akgun
On 3 February 2011 19:18, michael rice nowg...@yahoo.com wrote: but how do I get the constant a from the Reader monad? http://hackage.haskell.org/packages/archive/transformers/latest/doc/html/Control-Monad-Trans-Reader.html#v:ask You also need to change the type to use ReaderT. -- Ozgur

Re: [Haskell-cafe] Haskell Functions

2011-02-03 Thread Ozgur Akgun
(CCing haskell-cafe again) Is this an homework question? On 3 February 2011 20:30, Manolache Andrei-Ionut andressocrate...@yahoo.com wrote: http://pastebin.com/GxQBh3hx http://pastebin.com/GxQBh3hx --- On *Thu, 2/3/11, Ozgur Akgun ozgurak...@gmail.com* wrote: From: Ozgur Akgun ozgurak

Re: [Haskell-cafe] Inheritance and Wrappers

2011-02-01 Thread Ozgur Akgun
On 1 February 2011 11:41, John Lato jwl...@gmail.com wrote: The important point is that this declares an AbGroup instance for every type, not just types with Num instances. So, is there a way to declare an AbGroup instance for the types with num instances only? Thanks, Ozgur

Re: [Haskell-cafe] Inheritance and Wrappers

2011-02-01 Thread Ozgur Akgun
more interested in a discussion about why (if?) this would be considered a *design flaw*? Best, On 1 February 2011 12:18, Stephen Tetley stephen.tet...@gmail.com wrote: On 1 February 2011 11:47, Ozgur Akgun ozgurak...@gmail.com wrote: So, is there a way to declare an AbGroup instance

[Haskell-cafe] combined parsing pretty-printing

2011-01-26 Thread Ozgur Akgun
Dear Café, I working on a DSL represented by a algebraic data type with many constructors. I can write (separately) a parser and a pretty-printer for it, and I am doing so at the moment. However, this way it feels like repeating the same information twice. Is there any work to combine the two?

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ozgur Akgun
see also: http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state On 22 December 2010 20:02, Ryan Ingram ryani.s...@gmail.com wrote: Interesting. In that case, state f = StateT $ \s - Identity (f s) allows state to replace State in that code.

Re: [Haskell-cafe] the beginning of the end

2010-12-05 Thread Ozgur Akgun
the website, sort of. If a tweet is a reply to another one, there is a in reply to link right under the tweet. I guess other client applications (like tweetdeck) use this link to create a conversation view. I suppose, it is quite similar to what happens with e-mail. -- Ozgur Akgun

[Haskell-cafe] Hackage down?

2010-12-04 Thread Ozgur Akgun
http://downforeveryoneorjustme.com/http://hackage.haskell.org -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Offer to mirror Hackage

2010-12-04 Thread Ozgur Akgun
to me. -- Dan Knapp An infallible method of conciliating a tiger is to allow oneself to be devoured. (Konrad Adenauer) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Ozgur Akgun
On 11 November 2010 01:19, Richard O'Keefe o...@cs.otago.ac.nz wrote: I'm not sure that it is desirable to have many records in the same module in the first place. Amongst other reasons, http://www.haskell.org/haskellwiki/Mutually_recursive_modules -- Ozgur Akgun

[Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Ozgur Akgun
Café, Is there a way to make GHC dump the code for auto-derived type class instances, say for Show, Eq and such? Thanks, Ozgur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ghc dump the code for derived instances

2010-11-11 Thread Ozgur Akgun
Thanks! On 11 November 2010 14:52, Daniel Fischer daniel.is.fisc...@web.de wrote: On Thursday 11 November 2010 15:27:09, Ozgur Akgun wrote: Café, Is there a way to make GHC dump the code for auto-derived type class instances, say for Show, Eq and such? -ddump-deriv Thanks

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ozgur Akgun
-- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ozgur Akgun
On 10 November 2010 10:56, Ozgur Akgun ozgurak...@gmail.com wrote: Using TDNR, it will be possible to write the following code: data Foo = Foo { name :: String } data Bar = Bar { name :: String } getName :: Either Foo Bar - String getName (Left f) = name f getName (Right b) = name b

Re: [Haskell-Cafe] Parsing bytestream

2010-11-09 Thread Ozgur Akgun
If we change the code a bit, data MyAction = A1 Word8 | A2 Word16 a,b :: Get MyAction a = A1 $ getWord8 b = A2 $ getWord16be listOfActions :: [Get MyAction] listOfActions = [a,b,a] Now, we know how to execute the list of actions, and get the output as list. Using the following guys:

Re: [Haskell-cafe] Compiler constraints in cabal

2010-11-05 Thread Ozgur Akgun
://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Parsing workflow

2010-11-01 Thread Ozgur Akgun
On 1 November 2010 22:18, Andrew Coppin andrewcop...@btinternet.com wrote: I vaguely recall somebody mentioning a parser library on Hackage where try is the default behaviour and you turn it off explicitly, rather than turning it on explicitly. Apparently this is much more intuitive. But

Re: [Haskell-cafe] Parsing workflow

2010-10-31 Thread Ozgur Akgun
-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Parsing workflow

2010-10-31 Thread Ozgur Akgun
On 31 October 2010 16:15, Nils Schweinsberg m...@n-sch.de wrote: This is exactly what gives me headaches. It's hard to tell where you need try/lookAhead and where you don't need them. And I don't really feel comfortable wrapping everything into try blocks... I always thought this was an

[Haskell-cafe] Generic traversals for GADTs

2010-10-31 Thread Ozgur Akgun
Café, SYB-style libraries (and especially Uniplate) make it very easy to run generic traversals (queries/transformations) on ADTs. data Expr = ... x :: Expr f :: Expr - Expr transform :: (Expr - Expr) - Expr - Expr transform f x :: Expr -- applies f to x (and its children) in a bottom-up

Re: [Haskell-cafe] Decoupling type classes (e.g. Applicative)?

2010-10-29 Thread Ozgur Akgun
On 29 October 2010 14:35, Dominique Devriese dominique.devri...@cs.kuleuven.be wrote: I have a problem with the design of the Applicative type class Sorry for going a bit off-topic, but every-time I see someone complaining about such things, I remember this proposal:

Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Ozgur Akgun
Jonas, 2010/10/13 Jonas Almström Duregård jonas.dureg...@chalmers.se (++) :: Finite s1 a - Finite s2 a - Finite (S (Plus s1 s2)) a (++) (Finite a) (Finite b) = Finite $ a Prelude.++ b infixr 5 ++ Why do you have the S in the return type of Finite.++ ? Ozgur

[Haskell-cafe] ghci - always show types

2010-10-13 Thread Ozgur Akgun
Cafe, Just a quick question. Either I am hallucinating or there was a way of saying ghci to always show types. It was working as if you typed :t it after every line of input. Sorry, I searched but couldn't find the option via google. Hope someone here knows/remembers what I am talking about.

Re: [Haskell-cafe] ghci - always show types

2010-10-13 Thread Ozgur Akgun
On 13 October 2010 17:03, Christopher Done chrisd...@googlemail.com wrote: Options for ':set' and ':unset': +rrevert top-level expressions after each evaluation +sprint timing/memory stats after each evaluation +tprint type after evaluation See

Re: [Haskell-cafe] Re: Re-order type (flip map)

2010-10-10 Thread Ozgur Akgun
On 10 October 2010 22:32, Johannes Waldmann waldm...@imn.htwk-leipzig.dewrote: Oh, and while we're at it - are there standard notations for forward function composition and application? I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the ? While

Re: [Haskell-cafe] Re: Re-order type (flip map)

2010-10-10 Thread Ozgur Akgun
No, wrong. I am speaking nonsense here. Of course one also needs to define a *forward* function composition operator to get the effect you originally wanted. My point was: you need to find/define two operators, not just one. That still holds :) Best, On 10 October 2010 23:47, Ozgur Akgun

Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Ozgur Akgun
http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Haskell Helper

2010-10-04 Thread Ozgur Akgun
On 4 October 2010 23:10, c8h10n4o2 asaferibei...@ymail.com wrote: And why b - between (char ',') (char '=') (sepBy alphaNum (char ',') ) does not return [String] ? alphaNum :: Parser Char sepBy :: Parser a - Parser sep - Parser [a] sepBy alphaNum sepP :: Parser [Char] or Parser String but

Re: [Haskell-cafe] Re: Haskell Helper

2010-10-04 Thread Ozgur Akgun
On 4 October 2010 23:54, c8h10n4o2 asaferibei...@ymail.com wrote: By the way, there is a parser that returns [String] for my case? If you are trying to parse strings (of alphaNum's) separated by commas, you can use many alphaNum (or many1 alphaNum depending on what you want) instead of simply

Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-02 Thread Ozgur Akgun
On 2 October 2010 19:33, Henning Thielemann lemm...@henning-thielemann.dewrote: On Sat, 2 Oct 2010, Max Bolingbroke wrote: ... lambda-case/lambda-if ... Nice! Concerning if-then-else I would more like to see an according function to go to Data.Bool, then we won't need more syntactic sugar

Re: [Haskell-cafe] Inverse of HaskellDB

2010-09-29 Thread Ozgur Akgun
: On 28 sep 2010, at 17:33, Ozgur Akgun wrote: How do you define relationships between data types? Well, why is it any different from other fields? From one of your examples [1], I'd expect you to have a list of questions in the Quiz data type, and if necessary, a quiz field in the Question data

Re: [Haskell-cafe] Inverse of HaskellDB

2010-09-28 Thread Ozgur Akgun
://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] searching haskell-cafe ?

2010-09-19 Thread Ozgur Akgun
list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ghc in macports

2010-08-12 Thread Ozgur Akgun
sounds good to me. where can I find the list of packages (or whatever they call them in homebrew, formula?) available? On 12 August 2010 11:49, Benedict Eastaugh ionf...@gmail.com wrote: On 11 August 2010 15:49, Ozgur Akgun ozgurak...@gmail.com wrote: Personally, I'd like to use the macports

Re: [Haskell-cafe] ghc in macports

2010-08-12 Thread Ozgur Akgun
. -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ghc in macports

2010-08-11 Thread Ozgur Akgun
Dear Cafe, I wonder who is maintaining the ghc package in macports, and what the current stategy of doing things is? http://www.macports.org/ports.php?by=namesubstr=ghc (ghc 6.10.4) Personally, I'd like to use the macports version, if the ghc version there was resonably recent (having 2

Re: [Haskell-cafe] Preview the new haddock look and take a short survey

2010-08-04 Thread Ozgur Akgun
-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Ozgur Akgun
://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Ozgur Akgun
-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread Ozgur Akgun
://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Ozgur Akgun
' Nothing - False ...or indeed: eqTypeable x y = cast x == Just y ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ozgur Akgun ___ Haskell

  1   2   >