Re: Why cannot inferred type signatures restrict (potentially) ambiguous type variables?

2013-10-14 Thread Nicolas Frisby
An observation: on GHC 7.6.3, if I remove c2 entirely, then ghci cooperates. *Main :t \x - c (c x) \x - c (c x) :: (C a b, C a1 a) = a1 - b At first blush, I also expected the definition -- no signature, no ascriptions c2 x = c (c x) to type-check. Perhaps GHC adopted a trade-off giving

Re: TypeHoles behaviour

2013-08-27 Thread Nicolas Frisby
I also say +1, but I am concerned about always showing all the bindings. In my experiences over the years, the times when holes seem they would have been most helpful is when the bindings were numerous and had large and complicated types. Dumping all of the bindings in that sort of scenario would

Re: Marking type constructor arguments as nominal (e.g. Set)

2013-08-18 Thread Nicolas Frisby
Is the non-injectivity not an issue here because the type family application gets immediately simplified? On Sun, Aug 18, 2013 at 12:45 PM, Joachim Breitner m...@joachim-breitner.de wrote: Hi, now that roles are in HEAD, I could play around a bit with it. They were introduced to solve the

Re: Marking type constructor arguments as nominal (e.g. Set)

2013-08-18 Thread Nicolas Frisby
than is required to read it. :P On Sun, Aug 18, 2013 at 3:37 PM, Joachim Breitner m...@joachim-breitner.dewrote: Hi, not sure – where would injectivity be needed? Greetings, Joachim Am Sonntag, den 18.08.2013, 15:00 -0500 schrieb Nicolas Frisby: Is the non-injectivity not an issue here

[Haskell-cafe] abs minBound (0 :: Int) negate minBound == (minBound :: Int)

2013-08-18 Thread Nicolas Frisby
The docs at http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:gcd give a NB mentioning that (abs minBound == minBound) is possible for fixed-width types. This holds, for example, at Int. It is also the case that (negate minBound == minBound). Two questions: 1) This

Re: Exposing newtype coercions to Haskell

2013-07-03 Thread Nicolas Frisby
On Wed, Jul 3, 2013 at 5:33 AM, Joachim Breitner m...@joachim-breitner.dewrote: [snip] strange, why did I miss that? But I can’t get [the GlobalRdrEnv lookup] to work, even looking up an element that I took from the GRE itself returns []: let e' = head (head (occEnvElts env))

Re: Exposing newtype coercions to Haskell

2013-07-02 Thread Nicolas Frisby
This is an exciting effort! Just a quick reaction to Simon's comments on CoreM. On Tue, Jul 2, 2013 at 9:11 AM, Simon Peyton-Jones simo...@microsoft.comwrote: To your questions: ** **·**To do these kind of things, CoreM will need more reader stuff. In particular: **o

SpecConstr and GADTs

2012-12-10 Thread Nicolas Frisby
I suspect I've found a situation where, to a first approximation, I'd like SpecConstr to run more than once. I'm specializing on GADT constructors that contain coercions, so the constructor-specialized functions have RHSs with refined types. In my situation, those refined types enable

Re: Generating random type-level naturals

2012-11-16 Thread Nicolas Frisby
When wren's email moved this thread to the top of my inbox, I noticed that I never sent this draft I wrote. It gives some concrete code along the line of Wren's suggestion. - The included code uses a little of this (singleton types) and a little of that (implicit configurations).

Re: Unexpected ambiguity in a seemingly valid Haskell 2010 program

2012-11-09 Thread Nicolas Frisby
My GHC 7.6.1 (on a Mac) compiles this code without any warnings or errors. Do you have some other compilation flags in effect? On Fri, Nov 9, 2012 at 11:09 AM, Roman Cheplyaka r...@ro-che.info wrote: For this module module Test where import System.Random data RPS = Rock |

Re: Using DeepSeq for exception ordering

2012-11-08 Thread Nicolas Frisby
And the important observation is: all of them throw A if interpreted in ghci or compiled without -O, right? On Thu, Nov 8, 2012 at 11:24 AM, Albert Y. C. Lai tre...@vex.net wrote: On 12-11-08 07:12 AM, Simon Hengel wrote: I was just going to say that I can give at least one counterexample

Re: Kind refinement in type families with PolyKinds

2012-10-30 Thread Nicolas Frisby
I share an observation/workaround below. On Tue, Oct 30, 2012 at 8:49 AM, Andres Löh andres.l...@gmail.com wrote: This one looks strange to me: -- Stripping a type from all its arguments type family Strip (t :: *) :: k I'd be tempted to read this as saying that Strip :: forall k. * - k

Re: Proposal: EPHEMERAL pragma

2012-10-25 Thread Nicolas Frisby
The question of whether the warnings should come by default or not is a question of how serious the programmer is when they declare a type as EPHEMERAL. In Pedro's use cases, I would be very serious about it — as Ryan said, performance tends to tank otherwise. ### Proposal Extensions I think a

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-10-11 Thread Nicolas Frisby
On Wed, Sep 19, 2012 at 1:51 PM, Richard Eisenberg e...@cis.upenn.edu wrote: As for recovering kind classes and such once Any is made into a type family: I'm in favor of finding some way to do explicit kind instantiation, making the Any trick obsolete. I'm happy to leave it to others to

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-10-11 Thread Nicolas Frisby
On Thu, Oct 11, 2012 at 10:20 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: The to my trick key is to use the promotion of this data type. The key to my trick is to use the promotion of this data type. Wow — I have no idea what happened

Re: seemingly inconsistent behavior for kind-indexed type constraints in GHC 7.6

2012-10-08 Thread Nicolas Frisby
On Fri, Oct 5, 2012 at 9:25 PM, Richard Eisenberg e...@cis.upenn.edu wrote: For similar reasons, GHC does not bring the constraints on an instance into the context when an instance matches. So, even if GHC did select the instance you want, it would not bring ('[] ~ ps) into the context. Ah,

Re: seemingly inconsistent behavior for kind-indexed type constraints in GHC 7.6

2012-10-08 Thread Nicolas Frisby
for the noise/HTH in the future. On Mon, Oct 8, 2012 at 1:52 AM, Nicolas Frisby nicolas.fri...@gmail.com wrote: On Fri, Oct 5, 2012 at 9:25 PM, Richard Eisenberg e...@cis.upenn.edu wrote: For similar reasons, GHC does not bring the constraints on an instance into the context when an instance

Re: Constructing TH types

2012-10-07 Thread Nicolas Frisby
The issue you had with applications of the [] type seems to be more insidious than my last email made it out to be. This expression ( $(return $ ConE (mkName [])) :: $(return $ ConT (mkName []) `AppT` ConT ''Char) ) fails with [] is applied to too many arguments. I'm thinking that the []

Re: seemingly inconsistent behavior for kind-indexed type constraints in GHC 7.6

2012-10-06 Thread Nicolas Frisby
in the file, but I'm not sure. Thanks for posting! Richard On Oct 5, 2012, at 5:49 PM, Nicolas Frisby wrote: GHC 7.6 is rejecting some programs that I think ought to be well-typed. Details here https://gist.github.com/3842579 I find this behavior particularly odd because I can get GHC to deduce

Re: seemingly inconsistent behavior for kind-indexed type constraints in GHC 7.6

2012-10-06 Thread Nicolas Frisby
On Sat, Oct 6, 2012 at 12:46 PM, Gábor Lehel illiss...@gmail.com wrote: What do you use NLong for? I.e. where and how are you taking advantage of the knowledge that the list is N long? OK, some context. I'm experimenting with an augmentation of the generic-deriving generic programming approach.

Re: Comments on current TypeHoles implementation

2012-10-04 Thread Nicolas Frisby
tl;wr Variables and holes should have disparate syntax, so that code is easy to locally parse. Simon, your proposal is very crisp from the GHC implementor's perspective, but I think it might be harmful from the user's perspective. My premise is that free variables — which are normally fatal —

Re: Comments on current TypeHoles implementation

2012-10-04 Thread Nicolas Frisby
On Thu, Oct 4, 2012 at 4:28 PM, Roman Cheplyaka r...@ro-che.info wrote: I don't see why it is an issue. You should never encounter holes in the released code. The only source of holes should be stuff that you just wrote. With this proposal not only you get an error for the unbound variable (as

Re: Problem with default signatures

2012-08-23 Thread Nicolas Frisby
I've investigated this behavior a bit, and I have two things worth mentioning. (1) One of the ingredients in this behavior is the non-injectivity of type families. If we make the class parameter f accessible in the signature of emptyAlt, there are no more type errors. For example, if you can

Re: Request for comments on proposal for literate programming using markdown

2012-08-22 Thread Nicolas Frisby
On Wed, Aug 22, 2012 at 10:02 AM, Nicolas Frisby nicolas.fri...@gmail.com wrote: Maybe just try again in a separate thread? Perhaps under a pseudonym! :) Whoa, just realized once again that email is tone-deaf. I meant that 'pseudonym' thing cheekily: just to help differentiate the proposal

Re: faking universal quantification in constraints

2012-04-17 Thread Nicolas Frisby
is kind of irrelevant ... Regarding impredicativity in GHC, we are still unfortunately on the whiteboard ... Hope this helps! d- -Original Message- From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- users-boun...@haskell.org] On Behalf Of Nicolas Frisby

Re: faking universal quantification in constraints

2012-04-17 Thread Nicolas Frisby
that the corresponding instances was totally polymorphic in the argument. That's bogus reasoning because of ~ (and hence fundeps, as you used). Thanks again. On Tue, Apr 17, 2012 at 2:14 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: Thanks! I'll analyze what you've done here. One thing that jumps out

Re: faking universal quantification in constraints

2012-04-17 Thread Nicolas Frisby
Great! I'll take a whack at it ;) On Tue, Apr 17, 2012 at 4:07 PM, Edward Kmett ekm...@gmail.com wrote: On Mon, Apr 16, 2012 at 6:57 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: I'm simulating skolem variables in order to fake universal quantification in constraints via unsafeCoerce

Re: faking universal quantification in constraints

2012-04-17 Thread Nicolas Frisby
is definitely trying to subvert it; so I vote trustworthy. I'm adopting Data.Constraints.Forall for my local experimentation. Thanks for pointing it out. On Tue, Apr 17, 2012 at 4:15 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: Great! I'll take a whack at it ;) On Tue, Apr 17, 2012 at 4:07

faking universal quantification in constraints

2012-04-16 Thread Nicolas Frisby
I'm simulating skolem variables in order to fake universal quantification in constraints via unsafeCoerce. http://hpaste.org/67121 I'm not familiar with various categories of types from the run-time's perspective, but I'd be surprised if there were NOT a way to use this code to create run-time

Re: How to declare polymorphic instances for higher-kinded types?

2012-03-16 Thread Nicolas Frisby
Here's another alternative. newtype Comp f g a = Comp {unComp :: f (g a)} instance Resolvable e = Resolvable (Maybe `Comp` e) where resolve db = fmap Comp . resolveMaybe db . unComp One disadvantage of this approach is that it requires you to pepper your types with explicit compositions of

packaged up polykinded types can't index type families?

2012-03-13 Thread Nicolas Frisby
I suspect I'm tripping on a gap in the PolyKinds support. I'm trying to package up a type-level generic view. It uses PolyKinds — and DataKinds, but I think it's the PolyKinds that matter. If I compile everything locally in the same build, it works fine. If I isolate the spine view declarations in

Re: ConstraintKinds and default associated empty constraints

2012-01-09 Thread Nicolas Frisby
Just a note: as section 6 of [1] notes, one way (possibly the only?) to satisfy a universally quantified constraint would be a suitably polymorphic instance — i.e. with a type variable in the head. I think this would mitigate the need for whole program analysis at least in some cases, including

Re: Records in Haskell

2012-01-03 Thread Nicolas Frisby
Disclaimer: this use case for type-level string ops is still hypothetical, so these are predictions. Shooting for the moon, I foresee writing a type-level string similarity metric. In my experience, that would involve nested traversals, sliding of sequence windows, etc. In that case, I would very

Re: Records in Haskell

2012-01-02 Thread Nicolas Frisby
I'm interested in type-level strings myself. I'm using an approximation in order to enrich the instant-generics-style reflection of data type declarations with a sensitivity to constructor names. For example, this lets me automatically convert between many the similarly-named constructors of

Superclass Cycle via Associated Type

2011-12-07 Thread Nicolas Frisby
(Sorry I'm so late to this dialogue.) In http://www.haskell.org/pipermail/glasgow-haskell-users/2011-July/020593.html, SPJ asks The superclasses are recursive but   a) They constrain only type variables   b) The variables in the superclass context are all       mentioned in the head.  In

Re: [Haskell-cafe] Template Haskell sometimes sees hidden constructors

2011-05-30 Thread Nicolas Frisby
but an alpha-equivalent type does exhibit it in my larger program. On Fri, May 27, 2011 at 12:04 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: With the three modules at the end of this email, I get some interesting results. Note that none of the constructors are exported, yet Template Haskell can

[Haskell-cafe] something between a QQ and Q Exp?

2011-05-30 Thread Nicolas Frisby
This message motivates adding support to Template Haskell for code that can be spliced but can no longer be intensionally analyzed. I'm trying to use the well-known technique of a hidden constructor in order to represent values that satisfy a particular predicate. module Safe (Safe(), safe,

[Haskell-cafe] Template Haskell sometimes sees hidden constructors

2011-05-27 Thread Nicolas Frisby
Whith the three modules at the end of this email, I get some interesting results. Note that none of the constructors are exported, yet Template Haskell can see (and splice in variable occurrences of!) T, C2, W1, and W4. If you load Dump into GHCi, you get to see the Info that TH provides when you

[Haskell-cafe] no time profiling on my MacBookPro8,1

2011-05-06 Thread Nicolas Frisby
For this vanilla program module Main where main = print $ fib 40 fib 0 = 1 fib 1 = 1 fib n = fib (n - 1) + fib (n - 2) with these commands $ ghc -prof -auto-all -rtsopts -O --make Main.hs -o Main $ ./Main +RTS -p all of the %time cells in the generated Main.prof file are 0.0, as is the

Re: [Haskell-cafe] no time profiling on my MacBookPro8,1

2011-05-06 Thread Nicolas Frisby
Whoops: I'm running Haskell Platform 2011.2.0.1. OS X 10.6.7 i686-apple-darwin10-gcc-4.2.1 (GCC) 4.2.1 (Apple Inc. build 5664) (if that matters?) Out of my depth here. On Fri, May 6, 2011 at 5:07 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: For this vanilla program module Main where

[Haskell-cafe] what are the safety conditions for unsafeIOToST

2010-04-06 Thread Nicolas Frisby
I haven't been able to find it via Google or Haddock. An old message suggests is was just a matter of exceptions? I only want to use the IO for generating Data.Uniques to pair with STRefs in order to make a map of them. I'm guessing this would be a safe use since it's exception free (... right?).

Re: [Haskell-cafe] explicit big lambdas

2010-03-18 Thread Nicolas Frisby
Alternatively: let f :: some type involving a f = ... f' :: a - some type involving a f' _ = f in f' (undefined :: Int) normal f arguments On Thu, Mar 18, 2010 at 12:10 PM, Max Bolingbroke batterseapo...@hotmail.com wrote: Hi Paul, You should be able to introduce \Lambda at the

[Haskell-cafe] idioms ... for using Control.Applicative.WrapMonad or Control.Arrow.Kleisli?

2010-03-01 Thread Nicolas Frisby
Each time I find myself needing to use the wrapping functions necessary for this embeddings, I grumble. Does anyone have a favorite use-pattern for ameliorating these quickly ubiquitous conversions? For runKleisli, I was considering something like okKleisli :: (Control.Arrow.Kleisli m a b -

Re: [Haskell-cafe] know a workaround for greedy context reduction?

2009-01-19 Thread Nicolas Frisby
thinking of exporting a MyLibrary.Main or MyLibrary.Instances module. Anyone have experience with this approach in a library design? Is it worth the user's extra import? Any pitfalls? On Sun, Dec 7, 2008 at 4:57 PM, Nicolas Frisby nicolas.fri...@gmail.com wrote: Seems I got ahead of myself

Re: [Haskell-cafe] Proposal for associated type synonyms in Template Haskell

2009-01-15 Thread Nicolas Frisby
Any movement on this? (I am actually just looking forward to generating kind ascriptions and having access to the kinds when processing TH.Dec, TH.Type, and such.) 2008/11/27 Simon Peyton-Jones simo...@microsoft.com: I've been away. I hope others will reply to this thread too; whatever you

Re: [Haskell-cafe] know a workaround for greedy context reduction?

2008-12-07 Thread Nicolas Frisby
a) away. So GHC must try that route. If it fails, you want it to back up to a notationally more convenient type, but GHC can't do that, I'm afraid Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:haskell-cafe- | [EMAIL PROTECTED] On Behalf Of Nicolas Frisby | Sent: 06

[Haskell-cafe] know a workaround for greedy context reduction?

2008-12-05 Thread Nicolas Frisby
With these three declarations {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} class C a where c :: a class C a = D a where d :: a instance C a = D a where d = c ghci exhibits this behavior: * :t d d :: (C a) = a Where I would prefer d :: (D a) = a. In my

[Haskell-cafe] Re: Could FDs help usurp an ATs syntactic restriction?

2008-12-05 Thread Nicolas Frisby
Perhaps this ticket is related? http://hackage.haskell.org/trac/ghc/ticket/714 On Thu, Dec 4, 2008 at 9:38 PM, Nicolas Frisby [EMAIL PROTECTED] wrote: From the error below, I'm inferring that the RHS of the associated type definition can only contain type variables from the instance head

[Haskell-cafe] two type-level programming questions

2008-12-04 Thread Nicolas Frisby
1) Type families, associated types, synonyms... can anything replace the use of TypeCast for explicit instance selection? Section 2, bullet 4 of http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap indicates a negative response. Any other ideas? 2) Any progress/options for kind polymorphism in

[Haskell-cafe] Could FDs help usurp an ATs syntactic restriction?

2008-12-04 Thread Nicolas Frisby
From the error below, I'm inferring that the RHS of the associated type definition can only contain type variables from the instance head, not the instance context. I didn't explicitly see this restriction when reading the GHC/Type_families entry. Could perhaps the a b - bn functional dependency

[Haskell-cafe] template haskell overly conservative during splicing?

2008-11-03 Thread Nicolas Frisby
When using template haskell (via Derive) to generate this (exact) instance: instance Foldable ((-) Int) = Foldable Data.Derivable.InterpreterLib.Test.List where foldMap f (Cons x0 x1) = (const mempty Cons `mappend` foldMap f x0) `mappend` foldMap f x1 foldMap f (Nil) = const

[Haskell-cafe] dangling symbolic links

2008-08-27 Thread Nicolas Frisby
I think I've exhausted my options without catching exceptions. If I have an invalid symbolic link, how can I identify that it exists? (Sorry about the line wrap.) tmp$ ls -l# no tricks up my sleeve, empty directory tmp$ touch foo tmp$ ln -s foo bar tmp$ ls -l total 8 lrwxr-xr-x 1

[Haskell-cafe] Re: dangling symbolic links

2008-08-27 Thread Nicolas Frisby
Ah the magic of using a mailing list... I just realized that using getDirectoryContents lists the entry. Still, a doesLinkExist function might be nice... On Wed, Aug 27, 2008 at 11:46 PM, Nicolas Frisby [EMAIL PROTECTED] wrote: I think I've exhausted my options without catching exceptions

[Haskell-cafe] cabal build command and package versions

2008-08-20 Thread Nicolas Frisby
I have a question about cabal's behavior for the build command. When using the build command on a cabalized project, any version changes for installed packages go unnoticed - the necessary modules in the project are not re-compiled. If however, you run the configure command (though the .cabal file

Re: [Haskell-cafe] Data Types a la Carte - automatic injections (help!)

2008-07-29 Thread Nicolas Frisby
I have accomplished this in two ways. Either drop the reflexive rule and introduce a void sentinel type or use TypeEq (... you said everything was fair game!) to explicitly specify the preference for the reflexive case over the inductive case. An advantage of TypeEq is that you can avoid

Re: [Haskell-cafe] MonadPlus

2008-05-09 Thread Nicolas Frisby
It sounds like the semantics of the MonadPlus methods are under-specified. I recall once writing a newtype wrapper to treat the same non-determinism monad with different mplus semantics, akin to cut versus backtracking. I think of MonadPlus as a less expressive version of msplit, from

Re: [Haskell-cafe] OT: Isorecursive types and type abstraction

2008-01-24 Thread Nicolas Frisby
This paper, with a pdf available at Patricia Johann's publications page http://crab.rutgers.edu/~pjohann/ seems to be related. Initial Algebra Semantics is Enough! Patricia Johann and Neil Ghani. Proceedings, Typed Lambda Calculus and Applications 2007 (TLCA'07) Hope that helps. On Jan

Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
Extensionality says that the only observable properties of functions are the outputs they give for particular inputs. Accepting extensionality as a Good Thing implies that enabling the user to define a function that can differentiate between f x = x + x and g x = 2 * x is a Bad Thing. Note that

Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
This is a fine warning you both point out, but I would suggest that it distracts from the OP's question. The previous, germane discussion holds if we assume that i) both f and g have type Integer - Integer, ii) the compiler writer is not out to get us, and iii) the GMP library, if used by that

Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Nicolas Frisby
It seems there is previous background here that I am unaware of. I'll chime in anyway. What you describe as the wrong semantics seems to me to be the more appropriate. I am inferring that your expected behavior is explained such that the first server match ought to fail (and fall through to the

Re: [Haskell-cafe] RFC: demanding lazy instances of Data.Binary

2007-11-19 Thread Nicolas Frisby
I've got a first draft with the newtype and just an instance for list. If you'd prefer fewer questions, please let me know ;) 0) I've cabalised it (lazy-binary), but I don't have anywhere to host it. Would it be appropriate to host on darcs.haskell.org or HackageDB (yet?). Suggestions? 1)

Re: [Haskell-cafe] RFC: demanding lazy instances of Data.Binary

2007-11-19 Thread Nicolas Frisby
In light of this discussion, I think the fully spine-strict list instance does more good than bad argument is starting to sound like a premature optimization. Consequently, using a newtype to treat the necessarily lazy instances as special cases is an inappropriate bandaid. My current opinion: If

Re: [Haskell-cafe] RFC: demanding lazy instances of Data.Binary

2007-11-19 Thread Nicolas Frisby
On Nov 19, 2007 4:16 PM, Duncan Coutts [EMAIL PROTECTED] wrote: On Mon, 2007-11-19 at 13:39 -0800, Don Stewart wrote: nicolas.frisby: *snip* 1) The fact that serialisation is fully strict for 32760 bytes but not for 32761 makes the direct application of strictCheck

[Haskell-cafe] cabal Main-Is restriction

2007-11-16 Thread Nicolas Frisby
It seems the meaning of the -main-is switch for GHC and the Main-Is build option for Cabal executables differ. With GHC, I can point to any function main in any module, but in Cabal I must point to a filename with precisely the module name Main. This is tying my hands with regard to organizing a

[Haskell-cafe] RFC: demanding lazy instances of Data.Binary

2007-11-16 Thread Nicolas Frisby
I've noticed a few posts on the cafe, including my own experience, where the spine-strictness of the Binary instance for lists caused some confusion. I'd like to suggest an approach to preventing this confusion in the future, or at least making it easier to resolve. Having decided that it is

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-17 Thread Nicolas Frisby
It is truly irresponsible to post such interesting links on a mailing list! :) I resent and thank you for the last couple hours. On 10/17/07, Dan Weston [EMAIL PROTECTED] wrote: I find the mathematics is more accurate on http://www.conservapedia.com Their facts get checked by the Almighty

Re: [Haskell-cafe] Primitive Recursive Algebraic Types

2007-08-02 Thread Nicolas Frisby
It seems you are confusing the notion of counting the number of operators in the expression with actually evaluating the expression. Your evalLength function does both. It may help to consider counting the number of operators in the expression to be the same as calculating the height of the

Re: [Haskell-cafe] Indentation woes

2007-07-26 Thread Nicolas Frisby
A bandaid suggestion: longFunctionName various and sundry arguments = f where f | guard1 = body1 f | guard2 = body2 | ... where declarations (Disclaimer: untested) As I understand it, there can be guards on the definition of f even if it takes no arguments. Those guards can reference your

Re: [Haskell-cafe] Re: advantages of using fix to define rcursive functions

2007-07-26 Thread Nicolas Frisby
in this way. On 7/26/07, Dan Piponi [EMAIL PROTECTED] wrote: On 7/26/07, Nicolas Frisby [EMAIL PROTECTED] wrote: Trying to summarize in one phrase: you can do interesting manipulations to functions before applying fix that you cannot do to functions after applying fix (conventional functions fall

Re: [Haskell-cafe] Indentation woes

2007-07-26 Thread Nicolas Frisby
Whoops, read too fast. Sorry for the noise. On 7/26/07, Stefan O'Rear [EMAIL PROTECTED] wrote: On Thu, Jul 26, 2007 at 02:58:21PM -0500, Nicolas Frisby wrote: A bandaid suggestion: longFunctionName various and sundry arguments = f where f | guard1 = body1 f | guard2 = body2

Re: [Haskell-cafe] Re: advantages of using fix to define rcursive functions

2007-07-26 Thread Nicolas Frisby
Just casting my vote for the helpfulness of this reference. Trying to summarize in one phrase: you can do interesting manipulations to functions before applying fix that you cannot do to functions after applying fix (conventional functions fall in this second category). On 7/26/07, Chung-chieh

Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Nicolas Frisby
Perhaps an information retrieval pipedream, but what if we attempted an automated FAQ answerer? I'm sure some keywords pop-up often enough in certain chunks of first posts (heterogenous lists, existential error messages, SOE and graphics, category functor monad, etc). It could respond with the

Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Nicolas Frisby
FYI, Gmail *can* kill threads, the Geniuses just deemed it unworthy of a UI presence. This is news to me and related to earlier comments in this thread. HTH http://mail.google.com/support/bin/answer.py?hl=enanswer=47787 On 7/13/07, Nicolas Frisby [EMAIL PROTECTED] wrote: Perhaps an information

Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Nicolas Frisby
This might be a feasible appropriation of the term destructor. On 7/10/07, Bruno Oliveira [EMAIL PROTECTED] wrote: On Tue, 10 Jul 2007 10:53:35 +0200 (MEST), Henning Thielemann wrote: On Tue, 10 Jul 2007, Tony Morris wrote: A foldr without recursion. I use such functions frequently in order to

[Haskell-cafe] advice: instantiating/duplicating modules

2007-06-29 Thread Nicolas Frisby
I wrote a combination reader/writer monad (a la the RWS monad in the mtl) and I find myself wanting to use multiple instances of it in the same stack of transformers. The functional dependencies prevent this from working out. The class is called MonadRW and the transformer is called RWT. I find

Re: [Haskell-cafe] Collections

2007-06-20 Thread Nicolas Frisby
Just a couple of examples: many non-trivial program analyses (like optimizations or type-inference) rely on viewing the AST as a graph. Graph reduction is an evaluation paradigm, and I'm guessing that a (specification-oriented) interpreter might use a graph. On 6/20/07, Andrew Coppin [EMAIL

Re: [Haskell-cafe] Collections

2007-06-19 Thread Nicolas Frisby
I don't know where you got the notion that such structures are not available in Haskell. There are many efficient data structures in the libraries. Lists are not magical, just popular, natural, and traditional. Specialized data structures are always important. Take a look at the Data.* modules

Re: [Haskell-cafe] Mysterious monads

2007-05-28 Thread Nicolas Frisby
On 5/27/07, Andrew Coppin [EMAIL PROTECTED] wrote: [snip] such that a Reader is created with an initial list, and the read function fetches 1 element out of that list. That is, the expression x - read will take the head element of the list and put it into x, keeping the tail to be read later.

Re: [Haskell-cafe] Currying: The Rationale

2007-05-23 Thread Nicolas Frisby
Disclaimer: I've not read the standard. Sections are de-sugared depending on which argument you supply: (x^) == (^) x (^x) == flip (^) x I think this is why they are considered special cases. Prelude map (^2) [1..10] [1,4,9,16,25,36,49,64,81,100] Prelude map (flip (^) 2) [1..10]

[Haskell-cafe] ambiguous type variables at MPTC

2007-05-12 Thread Nicolas Frisby
This is a question about some interesting behaviors in GHC's typechecker regarding MPTCs. The brief code is at the bottom of the message. By the way, the types can be inferred but not declared without the forall and ascription in the where clause. f1 below is illegal because we don't know what

Re: [Haskell-cafe] Obscure instances for Obscure types

2007-04-26 Thread Nicolas Frisby
I've had a similar question, which I think boiled down to a compilation issue. Consider packages A and B that can be defined independently. But, just as Neil pointed out, perhaps A and B could also interact beyond their basic definition. My naive idea is that A would compile the simple

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-18 Thread Nicolas Frisby
Here here. This reminds me of a recent discussion on the cafe. Thee OP amounted to: What are the monad laws good for?. The answer was: It means the monad doesn't do surprising things and its behavior is congruent with the basic intuitions of sequenced computation. In my eyes, proving nice

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-16 Thread Nicolas Frisby
One technique I find compelling is (ab)using the type class system for meta programming. Something from Lightweight Static Resources, Faking It, or Hinze's Full Circle slides might be really attractive. Perhaps Danvy's Haskell printf? The hook might be: Yeah, you've heard of strong static typing

Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Nicolas Frisby
[sorry for the double, ajb] Since there seemed to be a disconnect between the expectation and the previous answers, I thought an alternative suggestion might help out. This sort of thing (haha) usually isn't my cup o' tea, so please point out any blunders. RM, is this more like what you had in

Re: [Haskell-cafe] Re: k-minima in Haskell

2007-04-12 Thread Nicolas Frisby
Both Yitzchak's and my suggestions should run in constant space--some strictness annotation or switching to foldl' might be necessary. On 4/12/07, Mark T.B. Carroll [EMAIL PROTECTED] wrote: Dan Weston [EMAIL PROTECTED] writes: Ah, but which k elements? You won't know until you've drained your

Re: [Haskell-cafe] A convenient way to deal with conditional function composition?

2007-04-10 Thread Nicolas Frisby
Using the Endo newtype can avoid such ambiguities: http://darcs.haskell.org/packages/base/Data/Monoid.hs newtype Endo a = Endo { appEndo :: a - a } instance Monoid (Endo a) where mempty = Endo id Endo f `mappend` Endo g = Endo (f . g) Endo allows you to explicitly select the

Re: [Haskell-cafe] Keeping a symbol table with Parsec

2007-04-02 Thread Nicolas Frisby
Section 2.12 of the Parsec manual[1] discusses user state. It sounds like that is what you are after. Hope that helps, Nick [1] - http://www.cs.uu.nl/~daan/download/parsec/parsec.pdf On 4/2/07, Joel Reymont [EMAIL PROTECTED] wrote: Folks, Are there any examples of keeping a symbol table with

Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Nicolas Frisby
I don't think that aName = [ x , y , z ] can be beat for adaptability (i.e. adding/removing/reorganizing results or _especially_ renaming the declaration). Doesn't do so hot regarding vertical space though... On 3/28/07, Greg Buchholz [EMAIL PROTECTED] wrote: David House wrote: I see

Re: [Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-28 Thread Nicolas Frisby
A wee bit off topic... but bear with me. Oleg points out a distinction between declaring a class with functional dependencies and implementing a class with functional dependencies. Judging from my experience, it might behoove those wrestling with type classes and FDs to emphasize that the class

Re: [Haskell-cafe] Re: Why the Prelude must die

2007-03-27 Thread Nicolas Frisby
Gut feeling: the quick'n dirty script case occurs far less than the whole module case. Thus I think the benefit of automatically importing the Prelude if the module declaration is omitted should not happen: the Principle of Least Surprise out-weighs the small benefit to a rare case. Correct me

[Haskell-cafe] ghc warning Var/Type length mismatch

2007-03-22 Thread Nicolas Frisby
When I load my program, GHC spits these messages at me, but doesn't fail Any idea what might be causing this or how to figure that out? Var/Type length mismatch: [] [a{tv aGIf} [tau]] ... Var/Type length mismatch: [] [a{tv aGN8} [tv]] ... I found the responsible code in GHC's darcs,

Re: [Haskell-cafe] There can be only one fix? Pondering Bekic's lemma

2007-03-21 Thread Nicolas Frisby
Whooops. Thanks for the correction. On 3/20/07, Levent Erkok [EMAIL PROTECTED] wrote: On 3/19/07, Nicolas Frisby [EMAIL PROTECTED] wrote: Nope, but I believe the two are equipotent. This usage of believe is one of those I think I remember reading it somewhere usages. On 3/19/07, Henning

Re: [Haskell-cafe] Re: fix

2007-03-20 Thread Nicolas Frisby
In effect, this is a demonstration that Haskell supports recursive values and not just recursive functions. If the a in fix :: (a - a) - a were to be unified always with a function type, then that would imply that the language only supported recursive definitions for functions, which would be a

Re: [Haskell-cafe] There can be only one fix? Pondering Bekic's lemma

2007-03-19 Thread Nicolas Frisby
Nope, but I believe the two are equipotent. This usage of believe is one of those I think I remember reading it somewhere usages. On 3/19/07, Henning Thielemann [EMAIL PROTECTED] wrote: On Sat, 17 Mar 2007, Nicolas Frisby wrote: Bekic's lemma [1], allows us to transform nested fixed points

[Haskell-cafe] There can be only one fix? Pondering Bekic's lemma

2007-03-17 Thread Nicolas Frisby
Bekic's lemma [1], allows us to transform nested fixed points into a single fixed point, such as: fix (\x - fix (\y - f (x, y))) = fix f where f :: (a, a) - a This depends on having true products, though I'm not exactly sure what that means. Mutual recursion can also be described with

Re: [Haskell-cafe] N and R are categories, no?

2007-03-15 Thread Nicolas Frisby
That said, N and R are indeed categories; however, considering them as categories should be carefully interlaced with your intuitions about them as types. I haven't formally checked it, but I would bet that this endofunctor over N, called Sign, is a monad: Sign x = x + x Pos = injectLeft Neg

Re: [Haskell-cafe] N and R are categories, no?

2007-03-15 Thread Nicolas Frisby
Thanks for keeping me honest ;) On 3/15/07, Dominic Steinitz [EMAIL PROTECTED] wrote: I haven't formally checked it, but I would bet that this endofunctor over N, called Sign, is a monad: Just to be picky a functor isn't a monad. A monad is a triple consisting of a functor and 2 natural

Re: [Haskell-cafe] Re: Maybe and partial functions

2007-03-13 Thread Nicolas Frisby
It seems like we could refine the first parameter of carryPropagate just as the second: make an= type N1 that only admits values [1..]. Would not that suffice to prove that base is never 0 and not have to go beyond the type-checker for a proof? On 3/13/07, Neil Mitchell [EMAIL PROTECTED] wrote:

Re: [Haskell-cafe] Usage of . and $

2007-03-07 Thread Nicolas Frisby
Which is the longer way of saying you don't need to count to make sure you closed all the brackets you opened! ;-) Dougal Stanton 1) Emacs does the counting for me 2) parens don't surprise me if I happen to use rank-2 types. i was bit enough times when learning why $ and runST don't like

Re: [Haskell-cafe] Usage of . and $

2007-03-07 Thread Nicolas Frisby
I don't use rank-2 types that often and when I do I'm aware of the restriction on ($) and similar hofs. I tend to use ($) only when the right-hand side gets very messy; a multiple-line do or similar. For example: blah = fromMaybe $ do x - blah1 y - blah2 guard (x == f y) g x The closing

  1   2   >