Re: [Haskell-cafe] Best way to instance Fix?

2010-05-23 Thread Reid Barton
ml {-# LANGUAGE StandaloneDeriving, FlexibleContexts, UndecidableInstances #-} data Greet x = AlloAllo x x | AuRevoir deriving Show newtype Fix f = In { out :: f (Fix f) } deriving instance Show (f (Fix f)) => Show (Fix f) Regards, Reid Barton ___ H

Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Reid Barton
ression "show (3 + 4)" must be in a module for this demonstration.) There is no provision for extending the defaulting mechanism to your own type classes. Arguably this is a good thing, since defaulting can sometimes behave surprisingly already under GHCi's rules, as anyone who

Re: [Haskell-cafe] Simple game: a monad for each player

2010-04-14 Thread Reid Barton
s.blogspot.com/2010/03/bruno-oliveira-and-i-are-working-on.html (click the link "draft") Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] searching a function by providing examples of input/ouput pairs

2010-03-18 Thread Reid Barton
ecent release on Hackage. http://nautilus.cs.miyazaki-u.ac.jp/~skata/MagicHaskeller.html http://hackage.haskell.org/package/MagicHaskeller Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] classes with types which are wrapped in

2010-01-22 Thread Reid Barton
ere push :: b -> a -> a ? The second one might help you with your subsequent problem (although I didn't understand quite what you were trying to do there). Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ghc -e

2010-01-06 Thread Reid Barton
ot;, and then run ghc -e "forM [[1,2,3]] reverse" imports.hs I use this method in a short shell script "interact" so that I can apply Haskell functions to files from the command line and don't have to type the full qualified na

Re: [Haskell-cafe] Why can't we make an instance declaration on a type synonym?

2010-01-04 Thread Reid Barton
; (String, String)`. In Haskell, these just don't unify because there are no type-level lambdas. Even if there were, how is the typechecker supposed to know that we want the solution `m a = String -> (a, String)` and not `m a = a -> (a, a)` or many other possibilites? The purpose of th

Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Reid Barton
M -> E M type Expr = E M type AExpr = E Blah -- The same simplify function we would write for the original Expr, -- with a different type simplify :: E a -> E a simplify (Const x) = Const x simplify (Add (simplify -> a) (simplify -> b)) = case (a, b) of (Const 0, _) -> b (_, Const 0) -> a _ -> Add a b simplify (Mul (simplify -> a) (simplify -> b)) = case (a, b) of (Const 1, _) -> b (_, Const 1) -> a _ -> Mul a b Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-02 Thread Reid Barton
hand B could export TH descriptions of multiple instance corresponding to different versions of A.Foo, relying on the importer to select the one which matches its selected version of A. Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Reid Barton
ling for "opposite monoid" and "dual monoid" to see the standard usage for yourself. There is no standard meaning for the phrase "dual monoid", but I would venture that it is never used to mean "opposite monoid" in the mathematical literature. (Sorry for the r

Re: [Haskell-cafe] Re: A 3 line program --> Mauricio

2009-10-24 Thread Reid Barton
This problem is solved! Especially in the upcoming GHC 6.12.1! Just use UTF-8 everywhere! Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A 3-line program that does not work

2009-10-24 Thread Reid Barton
m? Her editor probably saved the file in a text encoding other than UTF-8, such as ISO-8859-1. By definition a Haskell program is a Unicode text document. runhaskell is encountering an invalid UTF-8 sequence E7 61 while decoding your program file. The other responses will be relevant to

Re: [Haskell-cafe] Sharing Subexpressions: Memoization of Fibonacci sequence

2009-10-12 Thread Reid Barton
an exercise, tracing the evaluation of memoized_fib using each of these desugarings, and then trying them out in ghci. Then you'll be able to tell which desugaring ghc is using. (It's not the one used in the Report! In principle this is a bug since we can distinguish them using seq.) Reg

Re: [Haskell-cafe] Type-level naturals & multiplication

2009-10-12 Thread Reid Barton
skell.org/pipermail/haskell-cafe/2009-June/062452.html If you prefer to use EmptyDataDecls, you can replace the first four lines by data Z data S n data Id :: * -> * data (:.) :: (* -> *) -> (* -> *) -> (* -> *) And I still don

Re: split (was Re: [Haskell-cafe] Simple program. Simple problem?)

2009-10-11 Thread Reid Barton
On Sun, Oct 11, 2009 at 08:17:48PM -0400, Reid Barton wrote: > It seems that the definition of split in System.Random is not really > satisfactory. For the curious, the reason for the asymmetry between fst . split and snd . split is that the RNG states produced by mkStdGen have varying

split (was Re: [Haskell-cafe] Simple program. Simple problem?)

2009-10-11 Thread Reid Barton
t sequences. Now let's look at the left side: GHCi> length $ nub [ take 30 . map (fst . random) . iterate (fst . split) $ mkStdGen i :: [Bool] | i <- take 1 . randoms $ mkStdGen 0 ] 8 This doesn't seem good. Michael's code (below) is effectively doing iterate (fst . split

Re: [Haskell-cafe] memoization

2009-09-05 Thread Reid Barton
On Sat, Sep 05, 2009 at 02:52:50AM -0700, staafmeister wrote: > How would experienced haskellers solve this problem? You could just memoize using an array, like in C. import Data.Array occurrences :: Num a => String -> String -> a occurrences key buf = grid ! (0, 0) -- grid ! (i, j) = occurrenc

Re: [Haskell-cafe] Need some help with an infinite list

2009-06-16 Thread Reid Barton
On Wed, Jun 17, 2009 at 02:28:55AM +0200, Gü?nther Schmidt wrote: > Hi guys, > > I'd like to generate an infinite list, like > > ["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. > "bz", "ca" ...] I'm surprised everyone is giving clever recursive solutions rather than concatM

Re: [Haskell-cafe] Is it possible to do type-level arithmetic without UndeciableInstances?

2009-06-05 Thread Reid Barton
On Fri, Jun 05, 2009 at 01:58:33PM -0700, Ryan Ingram wrote: > I tried several different implementations for Times but I was unable > to come up with one that passed the type family termination checker. > Is there a way to do so? Here is a solution. I don't understand exactly why this works while

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Reid Barton
On Sun, Feb 15, 2009 at 09:59:28PM -, Sittampalam, Ganesh wrote: > > Stateful-mtl provides an ST monad transformer, > > Is this safe? e.g. does it work correctly on [], Maybe etc? > > If not this should be flagged very prominently in the documentation. It is not safe: it has the same proble

Re: [Haskell-cafe] type metaphysics

2009-02-02 Thread Reid Barton
On Mon, Feb 02, 2009 at 02:41:36PM -0800, Dan Piponi wrote: > 2009/2/2 Luke Palmer : > > > But Nat ~> Bool is computably uncountable, meaning there is no injective > > (surjective?) > > function Nat ~> (Nat ~> Bool), by the diagonal argument above. > > Given that the Haskell functions Nat -> Boo

Re: [Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-16 Thread Reid Barton
On Thu, Oct 16, 2008 at 12:57:05PM -0700, Simon Michael wrote: >> Basically it has a more accurate haskell parser, and it has a simpler >> way of cycling through possible indentations: TAB moves to the right >> and BACKSPACE to the left. > > Unfortunately, it can sometimes fail to parse what's i

Re: [Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread Reid Barton
he author of ListT has not forgotten to write a MonadPlus instance). Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-06 Thread Reid Barton
hich error* should you return if there's more than one Left? Do you really want to check whether every run s1 y is a (Right whatever)? In that case you are not gaining much from the laziness of ResultSet and might as well use ResultSet'. Until you decide the answer to questions

Re: [Haskell-cafe] Stacking monads

2008-10-02 Thread Reid Barton
nce for n. Then you can write join :: m (n (m (n a))) -> m (n a) as m (n (m (n a))) --- fmap sequence ---> m (m (n (n a))) -- join -> m (n (n a)) -- join -> m (n a). Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Newbie: Appending arrays?

2008-07-11 Thread Reid Barton
ctors at different index in unique > array later. Then once you've finished constructing the list, turn it into an array with listArray and use random access into that. Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http:

Re: [Haskell-cafe] Lazy IO

2008-07-10 Thread Reid Barton
Nothing -> return [] xs <- go print xs The unsafeInterleaveIO is now hidden inside getChanContents. (I have an outMVar rather than an outChan just in case accumulator could produce lots of output before consuming much of its input.) Regards, Reid Barton ___

Re: [Haskell-cafe] Error in configure script for GHC

2008-06-27 Thread Reid Barton
e to break with a similar message, since I have a 32-bit system. If I delete utils/pwd/pwd, the configure script automatically rebuilds it and then completes successfully. Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ghc-HEAD: build succeeds, but install fails with linker errors?

2008-06-25 Thread Reid Barton
*** [install] Error 1 Have I got some of the steps wrong? Regards, Reid Barton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe