Re: [Haskell-cafe] A small (?) problem with type families

2009-11-13 Thread David Menendez
On Fri, Nov 13, 2009 at 4:00 PM, Daniel Fischer wrote: > Am Freitag 13 November 2009 21:36:59 schrieb David Menendez: >> >> I recall seeing a discussion of this in the GHC documentation, but I >> can't seem to locate it. > > Perhaps > http://www.haskel

Re: [Haskell-cafe] A small (?) problem with type families

2009-11-13 Thread David Menendez
On Fri, Nov 13, 2009 at 3:26 PM, Andy Gimblett wrote: > First a type family where the type Y is functionally dependent on > the type X, and we have a function from Y to (). > >> class X a where >>   type Y a >>   enact :: Y a -> () This is ambiguous. Type families are not injective (that is, Y a

Re: [Haskell-cafe] Long running Haskell program

2009-11-11 Thread David Menendez
On Wed, Nov 11, 2009 at 1:09 PM, Matthew Pocock wrote: > Is there a state monad that is strict on the state but lazy on the > computation? Of course, strictness in the state will force a portion of the > computation to be run, but there may be significant portions of it which are > not run. Would

Re: [Haskell-cafe] Are all arrows functors?

2009-11-05 Thread David Menendez
On Thu, Nov 5, 2009 at 4:34 PM, Andrew Coppin wrote: > Nicolas Pouillard wrote: >> >> Excerpts from Neil Brown's message of Tue Nov 03 13:45:42 +0100 2009: >> >>> >>> Hi, >>> >>> I was thinking about some of my code today, and I realised that where I >>> have an arrow in my code, A b c, the type (

Re: [Haskell-cafe] Re: Experiments with defunctionalization, church-encoding and CPS

2009-11-01 Thread David Menendez
On Sun, Nov 1, 2009 at 12:31 PM, Heinrich Apfelmus wrote: > David Menendez wrote: >> On Sun, Nov 1, 2009 at 7:12 AM, Heinrich Apfelmus >> wrote: >>> Even then, the results are mixed. The Church-encoding shines in GHCi as >>> it should, but loses its advantage w

Re: [Haskell-cafe] Applicative but not Monad

2009-11-01 Thread David Menendez
On Sun, Nov 1, 2009 at 11:20 AM, Conor McBride wrote: > On 31 Oct 2009, at 10:39, Conor McBride wrote: >> On 30 Oct 2009, at 16:14, Yusaku Hashimoto wrote: >> >>> Hello cafe, >>> Do you know any data-type which is Applicative but not Monad? >> >> [can resist anything but temptation] >> >> I have a

Re: [Haskell-cafe] Re: Experiments with defunctionalization, church-encoding and CPS

2009-11-01 Thread David Menendez
On Sun, Nov 1, 2009 at 7:12 AM, Heinrich Apfelmus wrote: > Even then, the results are mixed. The Church-encoding shines in GHCi as > it should, but loses its advantage when the code is being compiled. I > guess we have to look at the core if we want to know what exactly is > going on. What optimi

Re: [Haskell-cafe] Re: Newcomers question

2009-11-01 Thread David Menendez
On Sun, Nov 1, 2009 at 11:09 AM, b1g3ar5 wrote: > OK, I understand that now but I've got a supplimentary question. > > If I put: > > instance Eq b => Eq (a -> b) where >    (==) = liftA2 (Prelude.==) You don't need the "Prelude." here. > to do the Eq part I get another error: > >    Couldn't mat

Re: [Haskell-cafe] Re: Applicative but not Monad

2009-10-31 Thread David Menendez
On Sat, Oct 31, 2009 at 6:22 AM, Heinrich Apfelmus wrote: > Dan Weston wrote: >> Can you elaborate on why Const is not a monad? >> >> return x = Const x >> fmap f (Const x) = Const (f x) >> join (Const (Const x)) = Const x >> > > This is not  Const , this is the  Identity  monad. > > The real  Con

Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread David Menendez
On Fri, Oct 30, 2009 at 1:33 PM, Yusaku Hashimoto wrote: > Thanks for fast replies! Examples you gave explain why all > Applicatives are not Monads to me. > > And I tried to rewrite Bob's Monad instance for ZipList with (>>=). > > import Control.Applicative > > instance Monad ZipList where >  retu

Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread David Menendez
On Fri, Oct 30, 2009 at 12:59 PM, Luke Palmer wrote: > On Fri, Oct 30, 2009 at 10:39 AM, Tom Davie wrote: >> Of note, there is a sensible monad instance for zip lists which I *think* >> agrees with the Applicative one, I don't know why they're not monads: >> instance Monad (ZipList a) where >>   

Re: [Haskell-cafe] why cannot i get the value of a IORef variable ?

2009-10-22 Thread David Menendez
On Thu, Oct 22, 2009 at 2:23 AM, Gregory Crosswhite wrote: > For clarity, one trick that uses "unsafePerformIO" which you may have seen > posted on this list earlier today is the following way of creating a > globally visible IORef: > > import Data.IORef > import System.IO.Unsafe > > *** counter =

Re: [Haskell-cafe] Monadic correctness

2009-10-17 Thread David Menendez
On Sat, Oct 17, 2009 at 3:21 PM, Andrew Coppin wrote: > Suppose we have > >  newtype Foo x >  instance Monad Foo >  runFoo :: Foo x -> IO x > > What sort of things can I do to check that I actually implemented this > correctly? I mean, ignoring what makes Foo special for a moment, how can I > chec

Re: [Haskell-cafe] Different semantics in "identical" do statement?

2009-10-09 Thread David Menendez
On Fri, Oct 9, 2009 at 6:47 PM, staafmeister wrote: > > Daniel Peebles wrote: >> >> I vaguely remember on IRC someone pointing out that the Parsec monad >> broke one of the laws. I think return _|_ >> x === _|_ which could be >> causing your problem. I may be wrong though. >> >> > > Confirmed, wor

Re: [Haskell-cafe] CBN, CBV, Lazy in the same final tagless framework

2009-10-09 Thread David Menendez
On Fri, Oct 9, 2009 at 1:39 PM, Felipe Lessa wrote: > On Fri, Oct 09, 2009 at 01:27:57PM -0400, David Menendez wrote: >> On Fri, Oct 9, 2009 at 11:12 AM, Felipe Lessa wrote: >> > That's really nice, Oleg, thanks!  I just wanted to comment that >> > I'd pr

Re: [Haskell-cafe] CBN, CBV, Lazy in the same final tagless framework

2009-10-09 Thread David Menendez
On Fri, Oct 9, 2009 at 11:12 AM, Felipe Lessa wrote: > On Thu, Oct 08, 2009 at 12:54:14AM -0700, o...@okmij.org wrote: >> Actually it is possible to implement all three evaluation orders >> within the same final tagless framework, using the same interpretation >> of types and reusing most of the c

Re: [Haskell-cafe] Test.QuickCheck: generate

2009-10-07 Thread David Menendez
On Wed, Oct 7, 2009 at 8:29 PM, Michael Mossey wrote: > In Test.QuickCheck, the type of 'generate' is > > generate :: Int -> StdGen -> Gen a -> a > > I can't find docs that explain what the Int does. Some docs are here: > >

Re: [Haskell-cafe] Re: Num instances for 2-dimensional types

2009-10-07 Thread David Menendez
On Wed, Oct 7, 2009 at 12:08 PM, Ben Franksen wrote: > > More generally, any ring with multiplicative unit (let's call it 'one') will > do. Isn't that every ring? As I understand it, the multiplication in a ring is required to form a monoid. -- Dave Menendez _

Re: [Haskell-cafe] Snow Leopard, gtk2hs

2009-10-06 Thread David Menendez
On Tue, Oct 6, 2009 at 2:49 PM, Gregory Collins wrote: > Arne Dehli Halvorsen writes: > >> This may be a little off-topic, but if someone could help me, I'd be >> grateful. >> I am trying to get to a working gtk2hs environment in MacOSX Snow Leopard > > Have you patched: > >   /usr/bin/ghc >   /

Re: [Haskell-cafe] Generalizing IO

2009-10-05 Thread David Menendez
On Mon, Oct 5, 2009 at 11:54 PM, Floptical Logic wrote: >> Instead of specifying the monad implementation, specify the interface. >> That is, you are using state operations (from MonadState) and IO >> operations (from MonadIO). Try removing all the type signatures that >> mention PDState and see w

Re: [Haskell-cafe] Generalizing IO

2009-10-05 Thread David Menendez
On Mon, Oct 5, 2009 at 7:56 PM, Floptical Logic wrote: > The code below is a little interactive program that uses some state. > It uses StateT with IO to keep state.  My question is: what is the > best way to generalize this program to work with any IO-like > monad/medium?  For example, I would li

Re: [Haskell-cafe] Finally tagless - stuck with implementation of "lam"

2009-10-05 Thread David Menendez
2009/10/5 Robert Atkey : > Hi Günther, > > The underlying problem with the implementation of 'lam' is that > you have to pick an evaluation order for the side effects you want in > the semantics of your embedded language. The two obvious options are > call-by-name and call-by-value. I wonder how e

Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread David Menendez
2009/9/24 Iavor Diatchki : > I agree with Grzegorz.  Perhaps we should file a bug-report, if there > isn't one already? http://hackage.haskell.org/trac/ghc/ticket/2120 Apparently, it's fixed in GHC 6.12. -- Dave Menendez ___

Re: [Haskell-cafe] GHC will not let me install

2009-09-20 Thread David Menendez
On Sun, Sep 20, 2009 at 5:17 PM, Don Stewart wrote: > jmstephens: >> I am trying to install Xmonad on my Mac. I download GHC installer for mac the >> .dmg from Haskell.org and when I install it gets stuck here >> [img]http://www.jmstephens.99k.org/picture.png[/img] As you can see the >> install >

Re: Re[2]: [Haskell-cafe] How to understand the 'forall' ?

2009-09-16 Thread David Menendez
On Wed, Sep 16, 2009 at 4:18 AM, Bulat Ziganshin wrote: > Hello Cristiano, > > Wednesday, September 16, 2009, 12:04:48 PM, you wrote: > >> Yep, perhaps I used the wrong example. What about foo: (forall a. a) -> Int? > > it's a function that convert anything to integer. That would be forall a. a -

Re: [Haskell-cafe] Building a monoid, continuation-passing style

2009-09-15 Thread David Menendez
On Mon, Sep 14, 2009 at 11:25 AM, Martijn van Steenbergen wrote: > Inspired by Sean Leather's xformat package [1] I built a datatype with which > you can build a monoid with holes, yielding a function type to fill in these > holes, continuation-passing style. Neat! > I have a couple of questions

Re: [Haskell-cafe] Control.Exception base-3/base-4 woes

2009-09-11 Thread David Menendez
On Fri, Sep 11, 2009 at 11:26 AM, Neil Brown wrote: > > Can anyone tell me how to fix this?  I don't think that changing to always > use Control.Exception would fix this, because I need to give a different > type for catch in base-3 to base-4, so there's still the incompatibility to > be dealt wit

Re: [Haskell-cafe] Re: HList and Type signatures / synonyms

2009-09-07 Thread David Menendez
2009/9/6 Günther Schmidt : > > I keep reading in and processing data in an accumulating way, ie. lets say I > have a DB table (don't take this literally please, just an example), into > in-memory records of type > > data MyRecord = MyRecord { >        name :: String, >        birthDate :: LocalDate

Re: [Haskell-cafe] Re: Don't “accidentallyparallel ize”

2009-09-05 Thread David Menendez
On Sat, Sep 5, 2009 at 7:57 PM, Dan Doel wrote: > > I suppose technically, what foldl' has over foldl is that it is more readily > subject to optimization. Each recursive call is artificially made strict in > the accumulator, so it is legal for GHC to optimize the function by keeping > the accumula

Re: [Haskell-cafe] [Long] 'Fun' with types

2009-09-03 Thread David Menendez
On Thu, Sep 3, 2009 at 6:34 PM, Maciej Piechotka wrote: > I'm somehow experimenting with GADT. I'm implementing FRP system and I > get such error: >    Occurs check: cannot construct the infinite type: a = (a, b) >    In the pattern: CircuitSplit f g >    In the definition of `createChannel': >    

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 3:29 PM, Peter Verswyvelen wrote: > On Fri, Aug 21, 2009 at 6:53 PM, David Menendez wrote: >> >> Some people dislike seq because it lets you force strictness >> in cases where pattern matching cannot (like function arguments), but >> hardl

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 2:50 PM, Jason Dagit wrote: >> On Fri, Aug 21, 2009 at 2:03 PM, David Menendez wrote: >>> >>> The problem is that the parameter, n, is part of the input to toPeano, >>> but you need it to be part of the output. To rephrase slightly, you >

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 1:03 PM, Jason Dagit wrote: > > Even with a type class for our type level numbers I'm at a loss.  I > just don't understand how to convert an arbitrary int into an > arbitrary but fixed type.  Perhaps someone else on the list knows.  I > would like to know, if it's possible,

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 4:37 AM, Peter Verswyvelen wrote: > On Fri, Aug 21, 2009 at 5:03 AM, David Menendez wrote: >> >> I'm not sure I understand your question, but I think it's possible to >> use interact in the way you want. For example, this code behaves >

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 6:57 PM, Peter Verswyvelen wrote: > > On Thu, Aug 20, 2009 at 11:23 PM, David Menendez wrote: >> >> The important things to note are (1) getChar# depends on the token >> returned by putChar#, thus guaranteeing that putChar# gets executed >&g

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 4:41 PM, Peter Verswyvelen wrote: > But how does GHC implement the RealWorld internally? I guess this can't be > done using standard Haskell stuff? It feels to me that if I would implement > it, I would need seq again, or a strict field, or some incrementing "time" > value t

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelen wrote: > > Also doesn't Haskell's IO system uses a hidden RealWorld type that has no > value but which is passed from between monadics binds in a strict way to > make the ordering work? Haskell only describes how the IO monad behaves. GHC's implem

Re: [Haskell-cafe] Type family signatures

2009-08-14 Thread David Menendez
On Fri, Aug 14, 2009 at 11:06 AM, Thomas van Noort wrote: > Hello, > > I have a question regarding type family signatures. Consider the following > type family: > >  type family Fam a :: * > > Then I define a GADT that takes such a value and wraps it: > >  data GADT :: * -> * where >    GADT :: a -

Re: [Haskell-cafe] Announce: EnumMap-0.0.1

2009-08-12 Thread David Menendez
On Wed, Aug 12, 2009 at 12:07 PM, John Van Enk wrote: > On Wed, Aug 12, 2009 at 11:34 AM, David Menendez wrote: >> On Wed, Aug 12, 2009 at 9:16 AM, John Van Enk wrote: >>> On Wed, Aug 12, 2009 at 2:09 AM, Ketil Malde wrote: >>>> >>>> And perhaps also no

Re: [Haskell-cafe] Announce: EnumMap-0.0.1

2009-08-12 Thread David Menendez
On Wed, Aug 12, 2009 at 9:16 AM, John Van Enk wrote: > On Wed, Aug 12, 2009 at 2:09 AM, Ketil Malde wrote: >> >> And perhaps also note that you will get exceptions for values outside >> the Enum range. >> > > I'd think that part is obvious. That depends on what "outside the Enum range" means. You'

Re: DDC compiler and effects; better than Haskell? (was Re: [Haskell-cafe] unsafeDestructiveAssign?)

2009-08-12 Thread David Menendez
On Wed, Aug 12, 2009 at 9:34 AM, Derek Elkins wrote: > On Tue, Aug 11, 2009 at 3:51 PM, Robin Green wrote: >> On Wed, 12 Aug 2009 11:37:02 +0200 >> Peter Verswyvelen wrote: >> >>> Yes, sorry. >>> >>> But I think I already found the answer to my own question. >>> >>> DDC functions that are lazy don

Re: [Haskell-cafe] lifting restrictions on defining instances

2009-07-23 Thread David Menendez
On Thu, Jul 23, 2009 at 9:01 PM, wren ng thornton wrote: > John Lask wrote: >> >> Can anyone explain the theoretical reason for this limitation, ie other >> than it is a syntactical restriction, what would it take to lift this >> restriction ? > > There are a couple of theoretical concerns, mainly

Re: [Haskell-cafe] Alternative IO

2009-07-17 Thread David Menendez
On Fri, Jul 17, 2009 at 10:21 AM, Wolfgang Jeltsch wrote: > Am Freitag, 10. Juli 2009 23:41 schrieben Sie: > >> Additionally, the second equality you provide is just wrong. >> >> f *> empty = empty is no more true than f *> g = g, > > I don’t understand this. The equation f *> g = g is much more ge

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread David Menendez
In Wed, Jul 1, 2009 at 3:38 PM, Thomas Schilling wrote: > 2009/7/1 David Leimbach >> Just because the compiler can figure out what I mean because it has a great >> type system, I might not be able to figure out what I mean a year from now >> if I see ++ everywhere. > Yep, had the same experience.

Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread David Menendez
On Thu, Jun 25, 2009 at 12:17 PM, Wei Hu wrote: > Could you or anyone else briefly explain how mmtl solves the > combinatorical explosion problem? Reading the source code is not very > productive for newbies like me. Thanks! It's a good question, since from what I can tell mmtl does not solve the

Re: [Haskell-cafe] Type system trickery

2009-06-23 Thread David Menendez
On Tue, Jun 23, 2009 at 9:25 PM, Ross Mellgren wrote: > I'm no expert, but it seems like those constructors should return Foobar > NoZoo, unless you're nesting so there could be a Zoo, in which case the type > variable a should transit, for example: > > data Foobar a where >    Foo :: X -> Y -> Foo

Re: [Haskell-cafe] Type system trickery

2009-06-21 Thread David Menendez
On Sun, Jun 21, 2009 at 4:00 PM, Andrew Coppin wrote: > Niklas Broberg wrote: >> >> On Sun, Jun 21, 2009 at 9:24 PM, Andrew >> Coppin wrote: >> >>> I want the type system to track whether or not Zoo has been used in a >>> specific value. Sure, you can check for it at runtime, but I'd be happier >>>

Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-17 Thread David Menendez
On Wed, Jun 17, 2009 at 9:08 PM, Jon Strait wrote: > I use and love Haskell, but I just have this nagging concern, that maybe > someone can help me reason about.  If I'm missing something completely > obvious here and making the wrong assumptions, please be gentle.  :) > > I'm reading the third (bi

Re: [Haskell-cafe] Still having problems building a very simple "Executable" ....

2009-06-06 Thread David Menendez
On Sat, Jun 6, 2009 at 11:54 PM, Vasili I. Galchin wrote: > Hi David, > > I commented out "Hs-source-dirs" > > Executable QNameTest > --   Hs-source-dirs: Swish/ >    Main-Is:    HaskellUtils/QNameTest.hs Swish/HaskellUtils/QNameTest.hs >    Other-Modules:  HaskellUtils.QName S

Re: [Haskell-cafe] Still having problems building a very simple "Executable" ....

2009-06-06 Thread David Menendez
On Sat, Jun 6, 2009 at 7:45 PM, Vasili I. Galchin wrote: > Hello, > > I picked an exceedingly case to build an "Executable": > > Executable QNameTest >    Hs-source-dirs: Swish/ >    Main-Is:    HaskellUtils/QNameTest.hs >    Other-Modules:  HaskellUtils.QName > > Here are the res

Re: [Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread David Menendez
On Fri, Jun 5, 2009 at 7:25 AM, Claus Reinke wrote: > > If ProjectPackage actually depends on the existence of those orphan > instances, plan B is to delay instance resolution, from library to clients, > so instead of importing the orphan instances > > module ProjectPackage where import MyMonadT_P

Re: [Haskell-cafe] Missing a "Deriving"?

2009-05-30 Thread David Menendez
On Sat, May 30, 2009 at 9:00 PM, michael rice wrote: > That works. but it gives just a single solution [1,2,3] when there are > supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in > error. Works for me. *Main> searchAll g 1 3 :: [[Int]] [[1,2,3],[1,4,3]] *Main> searchAll g

Re: [Haskell-cafe] Parsec float

2009-05-29 Thread David Menendez
On Fri, May 29, 2009 at 8:04 PM, Bartosz Wójcik wrote: > On Friday 29 May 2009 22:10:51 Bryan O'Sullivan wrote: >> > myFloat = try (symbol "-" >> float >>= return . negate) >> >     <|>  try float >> >     <|>  (integer >>= return . fromIntegral) >> >> Any time you see ">>= return .", something is

Re: [Haskell-cafe] cabal option to specify the ghc version?

2009-05-27 Thread David Menendez
On Wed, May 27, 2009 at 5:25 PM, Johannes Waldmann wrote: > Hi. How can I tell cabal (= the executable from cabal-install) > to use a specific ghc version (and not the one that's > currently linked to "ghc")? - Thanks, J.W. According to

Re: [Haskell-cafe] Free theorems for dependent types?

2009-05-20 Thread David Menendez
On Sun, May 17, 2009 at 11:52 PM, Ryan Ingram wrote: > Free theorem's are theorems about functions that rely only on parametricity. > > For example, consider any function f with the type >   forall a. a -> a > > >From its type, I can tell you directly that this theorem holds: >  forall g :: A -> B

Re: [Haskell-cafe] old Hugs libraries?

2009-05-18 Thread David Menendez
On Mon, May 18, 2009 at 6:34 PM, Vasili I. Galchin wrote: > Hello, > >   Do newSTArray, readSTArray, writeSTArray, etc. belong to an old > deprecated Hugs library/module? If so, what is the Haskell 98 replacement? I don't know about Haskell 98, but I think the modern solution is to use newArr

Re: [Haskell-cafe] showing a user defined type

2009-05-18 Thread David Menendez
On Mon, May 18, 2009 at 10:02 PM, Ryan Ingram wrote: > Unfortunately, you can't derive Show on Chain as defined, because it > contains a function: Sure you can. I just tried the following, and it compiled without complaints. > import Text.Show.Functions > > data Chain = Link Int (Int -> Chain) d

Re: [Haskell-cafe] converting IOException to Either in ErrorT

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 6:36 PM, wrote: > I wrote this to make it a little nicer to catch IO exceptions and > convert them to ErrorT failure: > > onExceptionThrowError >  :: (Error ce) => >     IO a >  -> (String -> ce) >  -> ErrorT ce IO a > onExceptionThrowError a ce = >    liftIO (try a) >>= >

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 7:54 PM, Tobias Olausson wrote: > Would unsafeInterleaveST work just as unsafeInterleaveIO in the manner > that it returns immediately, and then is computed lazily? > The idea in the complete program is that one part representing > the CPU will produce a list lazily, which w

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 6:11 PM, Ryan Ingram wrote: > So, I don't know what is causing your problem, but foo will not do > what you want even with lazy ST. That depends on what he wants to do. As long as nothing subsequent to the call to foo tries to read a reference, then foo is fine. For exampl

Re: [Haskell-cafe] understanding typeable

2009-04-12 Thread David Menendez
On Mon, Apr 13, 2009 at 1:37 AM, Anatoly Yakovenko wrote: > any idea why this is True > > data Foo = FooC Int >         | BarC Int >         deriving (Data, Typeable, Show) > >> fromJust $ funResultTy (typeOf FooC) (typeOf (1::Int)) > Loading package syb ... linking ... done. > ParseG.Foo >> typeR

Re: [Haskell-cafe] Re: Monads from Functors

2009-04-08 Thread David Menendez
On Wed, Apr 8, 2009 at 5:20 PM, Ben Franksen wrote: > Sebastian Fischer wrote: >>  > {-# LANGUAGE Rank2Types #-} >> >> Dear Haskellers, >> >> I just realized that we get instances of `Monad` from pointed functors >> and instances of `MonadPlus` from alternative functors. >> >> Is this folklore? >>

Re: [Haskell-cafe] replicateM should be called mreplicate?

2009-04-06 Thread David Menendez
On Mon, Apr 6, 2009 at 1:46 PM, Luke Palmer wrote: > On Mon, Apr 6, 2009 at 11:42 AM, David Menendez wrote: >> >> Of course, this suggests that mfix should be fixM, so perhaps a better >> distinction is that mplus and mfix need to be defined per-monad, >> whereas

Re: [Haskell-cafe] replicateM should be called mreplicate?

2009-04-06 Thread David Menendez
On Mon, Apr 6, 2009 at 10:02 AM, Sjoerd Visscher wrote: > Considering these naming conventions: > http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#3 > > • A postfix 'M' always stands for a function in the Kleisli category: The > monad type constructor m is added to functio

Re: [Haskell-cafe] Type families and kind signatures

2009-04-02 Thread David Menendez
2009/4/2 Louis Wasserman : > Mkay.  One more quick thing -- the wiki demonstrates a place where the > original attempt worked, with a data family instead. (That is, replacing > 'type' with 'data' and adjusting the instance makes this program compile > immediately.) > a) Is there a type-hackery reas

Re: [Haskell-cafe] ZipList monad, anyone?

2009-04-01 Thread David Menendez
2009/4/1 Luke Palmer : > 2009/4/1 Patai Gergely >> >> Does ZipList have any useful monad instance? The thought came up while >> thinking about higher order dataflows and an ArrowApply interface for >> Yampa. As a ZipList can be thought of as a function with a discrete >> domain, I figured its mona

Re: [Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread David Menendez
On Mon, Mar 30, 2009 at 3:46 PM, Gü?nther Schmidt wrote: > Thanks Don, > > I followed some examples but have not yet seen anything that would show me > how, for instance, turn a nested Map like > > Map Int (Map Int (Map String Double) > > into a "zipped" version. > > That is presuming of course th

Re: [Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread David Menendez
On Tue, Mar 31, 2009 at 11:44 PM, wren ng thornton wrote: > Another tricky thing for this particular example is answering the question > of what you want to call the "focus". Usually zippered datastructures are > functors, so given F X we can pick one X to be the focus and then unzip the > F aroun

Re: [Haskell-cafe] Re: A bit of a shock - Memoizing functions

2009-03-27 Thread David Menendez
2009/3/27 Kirk Martinez : > It seems there is a very close correspondence between data structures and > functions in Haskell.  Your powersOfTwo function, since it gets memoized > automatically (is this the case for all functions of zero arguments?), seems > exactly like a data structure. That's be

Re: [Haskell-cafe] Really need some help understanding a solution

2009-03-26 Thread David Menendez
2009/3/26 Luke Palmer : > The spine of this trie is maximally lazy: this is key.  If the structure of > the spine depended on the input data (as it does for Data.Map), then we > wouldn't be able to process infinite data, because we can never get it all. > So even making a trie out of the list _|_ g

Re: [Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-25 Thread David Menendez
On Wed, Mar 25, 2009 at 11:32 AM, Simon Marlow wrote: > Jonathan Cast wrote: >> >> Define >> >>    swap (a, b) = (b, a) > > ew, that's far too crude.  I think you mean > >  swap = uncurry $ flip (,) On the theme of using monads where you might not expect, swap = liftA2 (,) snd fst -- Dave Mene

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread David Menendez
On Wed, Mar 18, 2009 at 5:15 AM, Ryan Ingram wrote: > newtype Lfix f = Lfix (forall x. (f x -> x) -> x) > > l_in :: Functor f => f (Lfix f) -> Lfix f > l_in fl = Lfix (\k -> k (fmap (\(Lfix j) -> j k) fl)) > -- derivation of l_in was complicated! I found l_in easiest to write in terms of cata and

Re: [Haskell-cafe] Type equality proof

2009-03-17 Thread David Menendez
2009/3/17 Luke Palmer : >> Here are the original definition and the proofs of comm and trans. >> Compiles >> fine with GHC 6.10.1. >> >>    data (a :=: a') where >> >>        Refl :: a :=: a >> >>    comm :: (a :=: a') -> (a' :=: a) >>    comm Refl = Refl >> >>    trans :: (a :=: a') -> (a' :=: a''

Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-13 Thread David Menendez
2009/3/13 Marcin Kosiba : > > Threading the state is not the problem. Maybe this will help: > what I have now: > > fsm world state = case state of >  first -> >    do_stuff_one >    (move_up, succ state) >  second -> >    do_stuff_two >    (move_left, succ state) >  third -> >     do_stuff_three >

Re: [Haskell-cafe] monadic MapReduce

2009-03-03 Thread David Menendez
On Mon, Mar 2, 2009 at 6:57 PM, Anish Muttreja wrote: > How about this. Is there a reason why I can't > replace the variables b and c in the type signature of mapReduce with with > (IO b') > and (IO c'). b and c  can be any types. > > mapReduce :: Strategy (IO b')    -- evaluation strategy for ma

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

2009-02-28 Thread David Menendez
On Fri, Feb 27, 2009 at 11:10 PM, Ryan Ingram wrote: > It's obvious that anything that accesses the STT constructor will > potentially not be typesafe; the question I have is that whether you > can construct something that isn't typesafe just via the use of runSTT > & lift. To my surprise, it tur

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

2009-02-27 Thread David Menendez
On Fri, Feb 27, 2009 at 1:28 PM, Ryan Ingram wrote: > Then it comes down to, within a session, is there some way for an > STTRef to "mingle" and break the type-safety rule.  I can think of two > potential ways this might happen.  First, if the underlying monad is > something like List or Logic, th

Re: [Haskell-cafe] Stacking StateTs

2009-02-22 Thread David Menendez
On Sun, Feb 22, 2009 at 9:20 AM, Luis O'Shea wrote: >> test3 :: MonadState Integer m => String -> m String > > Good point. It's interesting that this allows the signature of test5b to > become MonadState Integer m => m Integer (instead of (Monad m) => StateT > Integer (StateT String m) Integer) w

Re: [Haskell-cafe] Stacking StateTs

2009-02-21 Thread David Menendez
On Sat, Feb 21, 2009 at 3:33 PM, Luis O'Shea wrote: > I've been experimenting with the state monad and with StateT, and have some > questions about how to combine one state with another. >> test3 :: Monad m => String -> StateT Integer m String >> test3 s = do >> modify (+ 1) >> a <- get >>

Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread David Menendez
On Fri, Feb 13, 2009 at 1:29 PM, John A. De Goes wrote: > On Feb 13, 2009, at 11:23 AM, Jonathan Cast wrote: >> >> Usually `when no ambiguity can arise', no? Plenty of mathematical >> practice rests on imprecision and the expectation that the human reader >> will understand what you mean. Haskel

Re: [Haskell-cafe] Race condition possible?

2009-02-12 Thread David Menendez
On Thu, Feb 12, 2009 at 6:26 PM, Don Stewart wrote: > bugfact: >> Consider the following code >> >> stamp v x = do >> t <- getCurrentTime >> putMVar v (x,t) >> >> Is it possible - with GHC - that a thread switch happens after the t <- >> getCurrentTime and the putMVar v (x,t)? > > Yes. if 't'

Re: [Haskell-cafe] evaluation semantics of bind

2009-02-09 Thread David Menendez
2009/2/9 Gregg Reynolds : > On Mon, Feb 9, 2009 at 11:06 AM, Tillmann Rendel wrote: >> >> Gregg Reynolds wrote:: >>> >>> My original question was motivated by the observation that a human reader >>> of >>> an expression of the form "e >>= f" , on seeing that f is constant, may >>> pull >>> the con

Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread David Menendez
2009/2/9 Gregg Reynolds : > > Right; "implementation of IO" means also an implementation for >>=, not just > the IO operators. I hadn't thought about that but it's hugely important for > the exposition of monads and IO. > > "The IO Char indicates that getChar, when invoked, performs some action >

Re: [Haskell-cafe] evaluation semantics of bind

2009-02-09 Thread David Menendez
2009/2/9 Gregg Reynolds : > On Sun, Feb 8, 2009 at 6:25 PM, Richard O'Keefe wrote: >> >> On 6 Feb 2009, at 4:20 am, Gregg Reynolds wrote: >>> >>> However, consider: >>> >>>getChar >>= \x -> getChar >>> >>> An optimizer can see that the result of the first getChar is discarded >>> and replace

Re: [Haskell-cafe] type metaphysics

2009-02-02 Thread David Menendez
On Mon, Feb 2, 2009 at 3:25 PM, Ketil Malde wrote: > Gregg Reynolds writes: > >> Just shorthand for something like "data Tcon a = Dcon a", applied to Int. >> Any data constructor expression using an Int will yield a value of type Tcon >> Int. > > Right. But then the set of values is isomorphic t

Re: [Haskell-cafe] type and data constructors in CT

2009-02-02 Thread David Menendez
On Sun, Feb 1, 2009 at 12:36 PM, Gregg Reynolds wrote: > On Sat, Jan 31, 2009 at 3:14 PM, David Menendez wrote: >> >> There's a paper about defining catamorphisms for GADTs and nested >> recursive types that models type constructors that way. > > If you recall

Re: [Haskell-cafe] type and data constructors in CT

2009-01-31 Thread David Menendez
On Sat, Jan 31, 2009 at 12:00 PM, Gregg Reynolds wrote: > I think I've finally figured out what a monad is, but there's one > thing I haven't seen addressed in category theory stuff I've found > online. That is the relation between type constructors and data > constructors. What sort of relatio

Re: [Haskell-cafe] Re: Laws and partial values

2009-01-24 Thread David Menendez
2009/1/24 Conal Elliott : > Incorrect *if* the semantics distinguishes between () and _|_ (as apparently > is the choice in Haskell). In case there was any question, section 3.17.3 of the Haskell 98 Report states, case _|_ of { K x1 ... xn -> e; _ -> e' } = _|_ where K is a data construct

Re: [Haskell-cafe] Re: Laws and partial values

2009-01-24 Thread David Menendez
On Sat, Jan 24, 2009 at 4:31 PM, Thomas Davie wrote: > > On 24 Jan 2009, at 22:19, Henning Thielemann wrote: > >> >> On Sat, 24 Jan 2009, Thomas Davie wrote: >> >>> On 24 Jan 2009, at 21:31, Dan Doel wrote: >>> For integers, is _|_ equal to 0? 1? 2? ... >>> >>> Hypothetically (as it's already

Re: [Haskell-cafe] How to define an operation in terms of itself (but of different type)?

2009-01-24 Thread David Menendez
2009/1/24 Luke Palmer : > > And also, I wonder, what are you going and adding scalars to vectors for!? > (I've heard of multiplying scalars by vectors -- that's in the definition of > a vector space, but adding...?) You can do that in geometric algebra. The result is a multivector. But in that ca

Re: [Haskell-cafe] Monoids and newtypes

2009-01-22 Thread David Menendez
On Thu, Jan 22, 2009 at 10:11 AM, Ketil Malde wrote: > > I was just wondering if not phantom types might serve here as an > alternative way to go about that. Here's a small example illustrating > it: ... > *Monoids> mconcat [1,2::Foo Additive] > Foo 3 > *Monoids> mconcat [1,2::Foo Multiplicative]

Re: [Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-20 Thread David Menendez
On Tue, Jan 20, 2009 at 2:51 PM, Mauricio wrote: >>> But how is this: >>> data SomeNum = forall a. SN a >>> different from: >>> data SomeNum = SN (forall a. a) > >> At a glance they look the same to me — but only the first is accepted by >> ghc. > > Following the link you pointed in the last > mes

Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread David Menendez
On Mon, Jan 19, 2009 at 7:22 PM, wrote: > > And perhaps more to the point, "Boolean" is an adjective, not a noun. > Therefore, it would be better reserved for a typeclass. There's also John Meacham's Boolean package. > class (Heyting a) => Boolean a

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread David Menendez
On Fri, Jan 16, 2009 at 12:19 PM, Ross Paterson wrote: > On Fri, Jan 16, 2009 at 12:00:40PM -0500, David Menendez wrote: >> It would be nice to explain what operations have been chosen for the >> Monoid instances of Prelude data types. (Maybe this belongs in the >> Prelude do

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread David Menendez
On Fri, Jan 16, 2009 at 8:39 AM, Duncan Coutts wrote: > Ross just updated the documentation for the Monoid module. Here is how > it reads now: > > The module header now reads simply: > >A class for monoids (types with an associative binary operation >that has an identity) with var

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-15 Thread David Menendez
On Thu, Jan 15, 2009 at 5:32 PM, Andrew Coppin wrote: > > As an aside, the integers form two different monoids. Haskell can't [easily] > handle that. Does anybody know of a language that can? Some of the ML-derived languages can do that. Essentially, your code takes another module which implement

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-15 Thread David Menendez
On Thu, Jan 15, 2009 at 5:27 PM, Duncan Coutts wrote: > On Thu, 2009-01-15 at 21:21 +, Andrew Coppin wrote: > >> OK, well then my next question would be "in what say is defining >> configuration files as a monoid superior to, uh, not defining them as a >> monoid?" What does it allow you to do

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-15 Thread David Menendez
On Thu, Jan 15, 2009 at 11:46 AM, Ross Mellgren wrote: > > Usually when encountering something like "Monoid" (if I didn't already know > it), I'd look it up in the library docs. The problem I've had with this > tactic is twofold: > > First, the docs for the typeclass usually don't give any practic

Re: [Haskell-cafe] Multiple State Monads

2009-01-13 Thread David Menendez
On Tue, Jan 13, 2009 at 5:29 PM, Phil wrote: > Many thanks for the replies. > > Using 'modify' cleans the syntax up nicely. > > With regard to using 'iterate' as shown by David here: > >>> mcSimulate :: Double -> Double -> Word64 -> [Double] >>> mcSimulate startStock endTime seedForSeed = fst expi

Re: [Haskell-cafe] Multiple State Monads

2009-01-12 Thread David Menendez
On Mon, Jan 12, 2009 at 8:34 PM, Phil wrote: > Thanks Minh - I've updated my code as you suggested. This looks better than > my first attempt! > > Is it possible to clean this up any more? I find: > > ( (), (Double, Word64) ) > > a bit odd syntactically, although I understand this is just to fit

<    1   2   3   4   >