Re: [Haskell-cafe] Deducing a type signature

2010-05-19 Thread Dan Weston
(i) strange f g = g (f g) Assume g :: a - b. Then f :: (a - b) - c. But since g :: a - b, f g :: a, so c = a. Therefore, f :: (a - b) - a, and g (f g) :: a. Therefore, strange :: ((a - b) - a) - (a - b) - a. Almost. The return type of strange is the same as the return type of g (the

Re: [Haskell-cafe] Type families vs. functional dependencies -- how to express something

2010-05-18 Thread Dan Weston
Unifying those two types by hand, I get: P (A t - B a) ~ P (B a) Maybe the problem is that type families (and associated types, their class cousins) are not injective: P x ~ P y does not imply that x ~ y. Maybe you need a data type (with appropriate wrapping and unwrapping) to ensure

Re: [Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Dan Weston
First of all, your function func (x,y) s dg =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg))) does NOT work for type (Float - Float), unless you mean that that is the type of the unused parameter s. Also, your desired type ((Float - Float) - Bool) itself looks suspicious. It must accept

Re: [Haskell-cafe] search Data.Tree.Zipper

2010-03-08 Thread Dan Weston
I think you want find :: Foldable t = (a - Bool) - t a - Maybe a Jian Fan wrote: Hi, There doesn't seem to be a function to search the tree so I come up with following function: searchTree :: (a - Bool) - TreeLoc a - Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc)

Re: [Haskell-cafe] foldl in terms of foldr

2010-01-26 Thread Dan Weston
f :: a - b - c is a function that takes an a, a b, and returns a c. g :: (a - b) - c takes one argument, which is expected to be a function from a to b. g returns a c. That stuff I mentioned before about variable binding and function application still applies. We can show that f and g

Re: [Haskell-cafe] Invertible functions list

2009-12-28 Thread Dan Weston
This might be pertinent: Alimarine et al, There and Back Again: Arrows for Invertible Programming http://www.cs.ru.nl/A.vanWeelden/bi-arrows/ Jonathan Fischoff wrote: Hi, I would to create a list of tuples (or something similar) of invertible functions [((a - b), (b - a)), ((b - c), (c -

Re: [Haskell-cafe] Restrictions on associated types for classes

2009-12-17 Thread Dan Weston
I think the denotational meanings are different. The instance also implies: For each Cl t there must exist a Cl u where u does not unify with [v] for some v. In other words, there must be a ground instance. For the class declaration, the existence of a ground instance can be inferred only by

Re: [Haskell-cafe] Restrictions on associated types for classes

2009-12-17 Thread Dan Weston
Oops, reverse that. The *instance* declaration allows for infinite types, the *class* declaration does not. Dan Weston wrote: I think the denotational meanings are different. The instance also implies: For each Cl t there must exist a Cl u where u does not unify with [v] for some v

Re: [Haskell-cafe] Why?

2009-12-11 Thread Dan Weston
Luke Palmer wrote: The idea being that any code that is pure could be evaluated anywhere with a very simple interpreter. If you have pure code, you can trace it back and evaluate it in a sandbox where you don't need a C runtime, a linker, or really anything but the simplest substitution engine.

Re: [Haskell-cafe] Zumkeller numbers

2009-12-09 Thread Dan Weston
Ouch. That's what happens when you let a machine do the translation. How about: Once your good name is trashed, you can live unabashed. David Virebayre wrote: On Wed, Dec 9, 2009 at 11:47 AM, Henning Thielemann lemm...@henning-thielemann.de wrote: Ist der Ruf erst ruiniert, lebt es sich

Re: [Haskell-cafe] forkSequence, runPar, parallelize

2009-12-09 Thread Dan Weston
It's a good thing then that forkExec and return are denotationally equal (though not operationally). Otherwise, I'd be worried. Matthew Brecknell wrote: Antoine Latter wrote: A similar function that I'm fond of: forkExec :: IO a - IO (IO a) It's cute that forkExec already has a dual

Re: [Haskell-cafe] Applicative but not Monad

2009-11-02 Thread Dan Weston
Obviously you know what your talking about and I don't, so this is a question purely out of ignorance. It seems to me that Tomorrow cannot be parametrically polymorphic, or else I could wrap it again (Tomorrow (Tomorrox x)). An unwrapping fixpoint operator needs to reflect the type to know

Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread Dan Weston
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 What am I missing? 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

Re: [Haskell-cafe] Time and space complexity of take k . sort

2009-10-22 Thread Dan Weston
Unless of course you use a GHC RULE to rewrite the RHS into the LHS, which should always be a valid transformation. Ketil Malde wrote: Paul Johnson p...@cogito.org.uk writes: takeLargest k = take k . sort But of equal practical interest is the space complexity. The optimum algorithm is

Re: [Haskell-cafe] Is there a null statement that does nothing?

2009-10-21 Thread Dan Weston
If you have a long if/else if/else chain, you might consider a trivial case statement with guards. Whether you think this is attractive is a matter of taste, but it has the fall-through semantics you want and ghc optimizes the _ pattern matching away: f x = case () of _| x == 2- 22 _|

Re: [Haskell-cafe] is proof by testing possible?

2009-10-12 Thread Dan Weston
Could that nice precise formulation simply be Scott continuity, which in turn preserves compactness through composition and under application? Dan Piponi wrote: On Mon, Oct 12, 2009 at 11:31 AM, Neil Brown nc...@kent.ac.uk wrote: swap = undefined Terminates and does not swap its arguments

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

2009-09-16 Thread Dan Weston
There is no magic here. This is merely explicit type specialization from the most general inferred type to something more specific. The denotational semantics of a function whose type is specialized does not change for those values belonging to the more specialized type. f :: forall a. (Num

Re: [Haskell-cafe] adding state in GUIs (qtHaskell)

2009-09-10 Thread Dan Weston
One simple solution is to leave the state in Qt. As of Qt 4.2, in C++ you can use bool QObject::setProperty(const char * name, const QVariant value) QVariant QObject::property(const char * name) const to set and get properties on any QObject (hence any QWidget). Since I believe these are

Re: [Haskell-cafe] forkM fails

2009-09-04 Thread Dan Weston
Try instead of `seq`. Alberto G. Corona wrote: Hi I need to execute a procedure not in the IO monad, but in an any monad: I defined: forkM :: Monad m= m a - IO ThreadId forkM proc=forkIO $ proc `seq` return() I assumed that seq will force the evaluation of proc and after, it will

Re: [Haskell-cafe] cannot build greencard

2009-09-02 Thread Dan Weston
Yet strangely, the last upload was Sun Apr 19 21:42:04 UTC 2009 and hackage claims it builds without failure with ghc-6.10. And in fact it builds just fine for me, so maybe it is worth finding out why it doesn't build for you. Are you using ghc-6.10.4 and the latest version of cabal? I get:

Re: [Haskell-cafe] Is logBase right?

2009-08-24 Thread Dan Weston
I don't know if anyone actually answered the question you didn't ask, but you can always improve an inaccurate guess when you need to. A limit will always exist, and should be unique (independent of the initial guess), assuming (+) and (*) are well-conditioned. In practice, a single

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

2009-08-20 Thread Dan Weston
Peter, I think you are right that there is no way in general to prevent a valid graph rewrite to remove a vacuous dependency. That is why seq is there. The funny business is visible right in the type signature of seq: seq :: forall a t. a - t - t If seq had nonstrict semantics, this would

Re: [Haskell-cafe] Type family signatures

2009-08-14 Thread Dan Weston
But presumably he can use a data family instead of a type family to restore injectivity, at the cost of adding an extra wrapped bottom value and one more layer of value constructor? David Menendez wrote: On Fri, Aug 14, 2009 at 11:06 AM, Thomas van Noorttho...@cs.ru.nl wrote: Hello, I have

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

2009-08-14 Thread Dan Weston
My intuition says the proper formalism is that undo is left adjoint to redo. They together form a monad in the category of redoable actions. return lifts doable actions to undoable ones by attaching an empty undo stack. join lowers (reflects) a first-class undoable action out of the undo

Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-06 Thread Dan Weston
than breaking the GenParser encapsulation 2009/8/6 Dan Weston weston...@imageworks.com mailto:weston...@imageworks.com Of course, since ParsecT s u m is a functor, feel free to use fmap instead of parsecMap. Then you don't need to import from Text.Parsec.Prim. And in hindsight

Re: [Haskell-cafe] Hugs faster and more reliable than GHC for large list monad 'do' block

2009-08-06 Thread Dan Weston
I assume for the return line, you meant to return a list, not a tuple. ghc doesn't support a 600-tuple. In any case, returning a list, I have verified that this problem exists in ghc 6.10.3, for -O0 and -O2. For -O0, it compiles and links fine, but gives this runtime message: z: internal

Re: [Haskell-cafe] Hugs faster and more reliable than GHC for large list monad 'do' block

2009-08-06 Thread Dan Weston
No, I am using the latest released ghc: ghc --version The Glorious Glasgow Haskell Compilation System, version 6.10.4 [ z.hs is attached ] time ghc -O0 --make z.hs [1 of 1] Compiling Main ( z.hs, z.o ) Linking z ... 14.422u 0.630s 0:15.10 99.6%0+0k 0+0io 0pf+0w time ./z z:

Re: [Haskell-cafe] Hugs faster and more reliable than GHC for large list monad 'do' block

2009-08-06 Thread Dan Weston
: Intel(R) Xeon(TM) CPU 3.40GHz x64 Clock Speed: 3400 MHZ OS: Linux 2.6.9-42.0.3.EL.spi OS-VERSION: CentOS release 4.4 (Final) OS-HW: x86_64 Dan Weston wrote: No, I am using the latest released ghc: ghc --version The Glorious Glasgow Haskell Compilation System, version 6.10.4 [ z.hs

Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-06 Thread Dan Weston
Is there any good extension? Yes, it's in Control.Applicative. Belka wrote: Hello, cafe visitors! :) This is a double topic: 1. Can't find any good informative resource with descriptions of Haskell extensions. Could anybody please share good one if it exists? The only good one I found:

Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-06 Thread Dan Weston
More specifically: sdtField3 sdt = f $ sdtField1 * sdtField2 You don't really need this inline in the record syntax, do you? Dan Weston wrote: Is there any good extension? Yes, it's in Control.Applicative. Belka wrote: Hello, cafe visitors! :) This is a double topic: 1. Can't find any

Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-06 Thread Dan Weston
the value grows exponentially with LOC (lines of code) count. :) Exponentially? Now I'm missing something... Your way has 156 chars: data SomeDataType = SomeDataType { sdtField1 :: SDT_Field1Type, sdtField2 :: SDT_Field2Type, sdtField3 :: SDT_Field2Type, sdtField3 = f sdtField1 sdtField2}

Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Dan Weston
I think parsecMap does the job here: --- import Text.ParserCombinators.Parsec hiding ((|)) import Text.Parsec.Prim(parsecMap) import Control.Applicative((|)) import Control.Arrow((|||),()) -- Tagged (:) () :: Either Char Char - Either String String - Either String String

Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Dan Weston
Of course, since ParsecT s u m is a functor, feel free to use fmap instead of parsecMap. Then you don't need to import from Text.Parsec.Prim. And in hindsight, I might prefer the name (:) or cons to () for the first function, but now I'm just obsessing. :) Dan Dan Weston wrote: I think

[Haskell-cafe] Importing Control.Arrow changes inferred type of (m = f) x in ghci

2009-07-27 Thread Dan Weston
The following inferred type has a constraint that can be trivially satisfied, but isn't: Control.Monad :t \ (m,f,x) - (m = f) x \ (m,f,x) - (m = f) x :: forall t a b. (Monad ((-) t)) = (t - a, a - t - b, t) - b -- In Control.Monad there is forall t. instance Monad ((-) t), -- so why is the

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Dan Weston
Bulat Ziganshin wrote: Hello Neil, Tuesday, July 21, 2009, 1:26:55 PM, you wrote: ++ [ -i | not (null (ghcOptSearchPath opts)) ] ++ [ -i, dir | dir - ghcOptSearchPath opts ] Following the discussions, I now support this extension too - I keep seeing more and more places in my code

Re: [Haskell-cafe] Why is there no Zippable class? Would this work?

2009-07-16 Thread Dan Weston
After rereading page 2 of McBride and Paterson's Functional Pearl, Applicative programming with effects, I think you are just reinventing Control.Applicative. The problem is that the default Applicative instance for [] is wrong, being a direct product rather than a direct sum. If [] were not

Re: [Haskell-cafe] Why is there no Zippable class? Would this work?

2009-07-16 Thread Dan Weston
Way cool. I have gained newfound respect for what I don't know. :) Can there ever be more than one (observably different) valid definition of pure for a given * that obeys all the laws? I would imagine that there could be at most one. Dan Ryan Ingram wrote: (I'm going to play fast and

Re: [Haskell-cafe] homomorphic encryption and monads?

2009-07-15 Thread Dan Weston
I think there may be a problem here. Homomorphic encryption is a form of encryption where one can perform a specific algebraic operation on the plaintext by performing a (possibly different) algebraic operation on the ciphertext. The word specific means that the functor is discrete, not

Re: [Haskell-cafe] Comonadic composition and the game Doublets

2009-06-08 Thread Dan Weston
I think the structure you are looking for is called a wedge sum [1], which is the coproduct in the category of the pointed spaces, each of which is (in this case) the group action of changing one letter to another in the ith position of a word of fixed length. One small tricky part is that,

Re: [Haskell-cafe] Comonadic composition and the game Doublets

2009-06-08 Thread Dan Weston
Oops. Make that: a list comprehension, which enumerates the product space *without* duplicates! Dan Weston wrote: I think the structure you are looking for is called a wedge sum [1], which is the coproduct in the category of the pointed spaces, each of which is (in this case) the group action

Re: [Haskell-cafe] Re: Non Empty List?

2009-06-04 Thread Dan Weston
Unless I'm missing something in your description, why not data Container a = Single a | Many a a [a] Dan GüŸnther Schmidt wrote: Hi Jake, Jake McArthur schrieb: GüŸnther Schmidt wrote: data Container a = Single a | Many a [a] but the problem above is that the data structure would

Re: [Haskell-cafe] Hugs vs. GHCi

2009-05-29 Thread Dan Weston
http://haskell.org/onlinereport/exps.html#sect3.12 Pattern bindings are matched lazily; an implicit ~ makes these patterns irrefutable. For example, let (x,y) = undefined in e does not cause an execution-time error until x or y is evaluated. So GHCi is correct. Dan Vladimir Reshetnikov

Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Dan Weston
I suspect your structure doesn't exist. A Kleisli algebra (a - m b) has a full subalgebra (() - m ()), but (() - m b) is not an algebra (it is not closed). I'm guessing that the largest proper subset of (a - m b) is just (() - m ()). Dan Tony Morris wrote: Michael Vanier wrote: I've

Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-23 Thread Dan Weston
Subject: Re: [Haskell-cafe] Overriding a Prelude function? To: michael rice nowg...@yahoo.com Cc: Ross Mellgren rmm-hask...@z.odi.ac, Dan Weston weston...@imageworks.com, haskell-cafe@haskell.org haskell-cafe@haskell.org Date: Wednesday, April 22, 2009, 5:02 PM On Wed

Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-22 Thread Dan Weston
Be aware that the do unsugars to (Prelude.), not your (), even if you hide (Prelude.): import Prelude hiding (()) m f = error Call me! main = putStrLn . show $ do [3,4] [5] The desugaring of the do { [3,4]; [5] } is (Prelude.) [3,4] [5] = [5,5], whereas you might

Re: [Haskell-cafe] Functor and Haskell

2009-04-21 Thread Dan Weston
You are on the right track. The usual construction is that Hask is the category (with types as objects and functions as morphisms). Functor F is then an endofunctor taking Hask to itself: a - F a f - fmap f So, for F = []: a - [a] f - map f Natural transformations are then any fully

Re: [Haskell-cafe] Functor and Haskell

2009-04-21 Thread Dan Weston
catagories. My problem is that I only have one functor between the Hask and List catagories. So where does the 2nd functor come into picture that also maps between the same C and D catagories? Thanks Daryoush On Tue, Apr 21, 2009 at 4:01 PM, Dan Weston weston...@imageworks.com mailto:weston

Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-16 Thread Dan Weston
Unless primesUpTo n goes from highest to lowest prime (ending in 2), I don't see how sharing is possible (in either space or time) between primesUpTo for different n. Is it intended that the primes should therefore be listed in descending order? a...@spamcop.net wrote: primes :: [Integer]

Re: [Haskell-cafe] abou the Godel Numbering for untyped lambda calculus

2009-03-31 Thread Dan Weston
have? any limitation? how capable they will be? Thanks alg On Tue, Mar 31, 2009 at 4:01 AM, Dan Weston weston...@imageworks.com mailto:weston...@imageworks.com wrote: I can't tell exactly what you're asking, but I'll give it a try! :) primes :: [Integer] primes

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

2009-03-31 Thread Dan Weston
What I've learned: Zippers are structured collections[1] with a focus. Through a Zipper you can O(1) change the value of the focused element: that's the fundamental property. In addition, you can change the focus through a series of moving functions. To clarify: there is no magic that turns

Re: [Haskell-cafe] abou the Godel Numbering for untyped lambda calculus

2009-03-30 Thread Dan Weston
I can't tell exactly what you're asking, but I'll give it a try! :) primes :: [Integer] primes = [2,3,5,7,11,13,17,19,23,29,31,undefined] godel :: String - Integer godel = product . zipWith (^) primes . map (toInteger . ord) -- Here is the identity function (note that double backslash is a

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

2009-03-25 Thread Dan Weston
So to be clear with the terminology: inductive = good consumer? coinductive = good producer? So fusion should be possible (automatically? or do I need a GHC rule?) with inductive . coinductive Or have I bungled it? Dan wren ng thornton wrote: Thomas Hartman wrote: sorry, wrong

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

2009-03-25 Thread Dan Weston
However, there is something to be said for code that just looks like a duck and quacks like a duck. It's less likely to surprise you. So... I insist... Easy for a beginner to read == better! All you have said is that one building a skyscraper will need scaffolding, blueprints, and a good

Re: [Haskell-cafe] Calculating with list comprehension

2009-03-05 Thread Dan Weston
Keep in mind this is a *lexical* rewrite. In the generator rule x and e are not independent: x is a pattern (which introduces a bind variable) and e is an expression (with free variables, one of which may be bound by x) After one application of the generator rule, we get (using a lambda

Re: [Haskell-cafe] Theory about uncurried functions

2009-03-03 Thread Dan Weston
Not a better programmer, just a better human being. Peter Verswyvelen wrote: Thank you all for this information. It was very enlightening. Too bad I don't know category theory, since I think it would give me a better view on the different forms and essence of computing. Maybe this raises a

Re: [Haskell-cafe] morphisms in IO

2009-02-05 Thread Dan Weston
I truly have no idea what you are saying (and probably not even what I am saying), but I suspect: a) You are calling IO the target category of applying the functor IO [taking a to IO a and (a-b) to (IO a - IO b)] to Hask. b) This category is hardly bereft, nor discrete. Its morphisms are IO

Re: [Haskell-cafe] Current research on overlapping/closed type families?

2009-01-23 Thread Dan Weston
Would this then also eventually work? data Zero data Succ a = Succ a type family IsFunction f type instances IsFunction (a - b) = Succ (IsFunction b) IsFunction c= Zero Simon Peyton-Jones wrote: Provided all the overlapping instances are supplied together, as you suggest, I

Re: [Haskell-cafe] Elevator pitch for functional programming

2009-01-20 Thread Dan Weston
One of the coolest things about Haskell is the ability to refer to values not yet calculated, without having to work out the timing yourself. You want Fibonacci numbers? Prelude let z = zipWith (+) (0:1:z) (0:z) in take 10 z [0,1,1,2,3,5,8,13,21,34] Try doing that in one line of C++. See

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

2009-01-15 Thread Dan Weston
Maybe you can explain that again? I see how the subset of Kleisli arrows (a - m a) forms a monoid (a, return . id, =), but what to do with (a - m b)? (=) is not closed under this larger set. Dan Miguel Mitrofanov wrote: Notice that monoid sounds almost *exactly* like monad. And yet, what

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

2009-01-15 Thread Dan Weston
Richard Feinman once said: if someone says he understands quantum mechanics, he doesn't understand quantum mechanics. But what did he know... Luke Palmer wrote: On Thu, Jan 15, 2009 at 7:02 PM, Michael Giagnocavo m...@giagnocavo.net mailto:m...@giagnocavo.net wrote: Your talk of

Re: [Haskell-cafe] Re: Updating doubly linked lists

2009-01-06 Thread Dan Weston
2 0) (Just C: X=2,Y=0,R=2,K=0), subForest = [] }] }]}, lefts = [], rights = [], parents = []}) Apfelmus, Heinrich wrote: Dan Weston wrote: For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm

Re: [Haskell-cafe] Infinite grid

2009-01-05 Thread Dan Weston
, with conversion to/from cartesian calculated on the fly (but may also be stored in label if speed is more important than time). Cyclic closed loop tests like your f below run in constant space for me. Dan Weston Martijn van Steenbergen wrote: Hello, I would like to construct an infinite two

Re: [Haskell-cafe] Re: Updating doubly linked lists

2009-01-05 Thread Dan Weston
For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point. Really? My

Re: [Haskell-cafe] Infinite grid

2008-12-29 Thread Dan Weston
I'm confused how this isn't just tantamount to using Data.Map (Integer,Integer) a. The essential problem is that you have an algebra acting on a topology. The algebra is easily rewritten to an efficient form, but a sequence of topological actions is not, because it is not sufficiently

Re: [Haskell-cafe] Rewrite thunk action rule?

2008-12-22 Thread Dan Weston
Peter Todd wrote: Not quite. If I have a thunk, at the low level somewhere it must refer to the transform function, the transform matrix, and the element that is to be transformed. If I apply another transform to that unevaluated thunk, my understanding is that haskell will represent it as such:

Re: [Haskell-cafe] Numerics implementing different instances of the same class

2008-12-12 Thread Dan Weston
What about something like data AddMult a b = AddMult a b class Monoid a where operation :: a - a - a identity :: a instance (Monoid a, Monoid b) = Monoid (AddMult a b) where operation (AddMult a1 m1) (AddMult a2 m2) = AddMult (operation a1 a2)

Re: [Haskell-cafe] Animated line art

2008-12-04 Thread Dan Weston
Andrew, I can think of several reasons why simple time-indexed animation may be a bad idea. Some important aspects of animation are usually: 1) A main use case is playback, where time change is continuous and monotonic. 2) Differential action is often much cheaper than time jumping (i.e.

Re: [Haskell-cafe] Bit Field Marshalling

2008-11-07 Thread Dan Weston
C standard allows padding and reorder of struct entries Almost. The ISO C standard does allow structs padding, but *not* reordering: http://www.open-std.org/JTC1/SC22/wg14/www/docs/n1124.pdf ISO/IEC 9899:1999 C Standard §6.7.2.1.13 Within a structure object, the non-bit-field members and the

Re: [Haskell-cafe] Re: A heretic question

2008-10-23 Thread Dan Weston
For the record, C++ (and a crippled scripting language call MEL that makes C look good) were used in the Maya 3D graphics software used for the Lord of the Rings movies [1]: Weta Digital utilized Maya® as the core 3D animation software technology throughout the process of creating digital

Re: [Haskell-cafe] Very silly

2008-10-16 Thread Dan Weston
Not that I want or need to defend C++ on this list, but reference-counted smart pointers (e.g. boost::shared_ptr), embedded inside copy-on-write proxy classes, largely simulates eager garbage collection. Targeted overriding of the new operator can make this lazier for efficiency. In other

Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Dan Weston
I suspect that more has been done since 1997. Isn't that pre-Oleg? Karl Mazurak wrote: Yitzchak Gale wrote: Derek Elkins wrote: In general, to encode OO... turns out all you needed was recursive bounded existential quantification. Do you have a reference for that? I'm not sure if this is

Re: [Haskell-cafe] List as input

2008-10-15 Thread Dan Weston
Google median order statistic. E.g. this is an interesting (and colorful) discussion: http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/6-046JFall-2005/60D030CD-081D-4192-9FB5-C220116E280D/0/lec6.pdf Toby Hutton wrote: On Wed, Oct 15, 2008 at 5:44 PM, leledumbo

Re: [Haskell-cafe] The container problem

2008-09-26 Thread Dan Weston
More specifically, although a set is a perfectly good (lowercase) functor, Set is not a (Haskell) Functor. Set's map has an Ord constraint, but the Functor type constructor is parametric over *all* types, not just that proper subset of them that have a total ordering. But see attempts to

Re: [Haskell-cafe] Is there already an abstraction for this?

2008-09-22 Thread Dan Weston
I can implement these with some 'sugar' as: identity (Sum (Lit 0) a)= a identity (Sum a (Lit 0))= a identity (Difference a (Lit 0)) = a identity (Product a (Lit 1))= a identity (Product (Lit 1) a)= a identity (Quotient a (Lit 1)) = a identity a

Re: [Haskell-cafe] Is there already an abstraction for this?

2008-09-22 Thread Dan Weston
Oops, never mind. This is just the shallow application you referred to. Too fast with that send button! Dan Weston wrote: I can implement these with some 'sugar' as: identity (Sum (Lit 0) a)= a identity (Sum a (Lit 0))= a identity (Difference a (Lit 0

Re: [Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-15 Thread Dan Weston
Take a look at http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap Tom Hawkins wrote: On Mon, Sep 15, 2008 at 3:11 PM, apfelmus [EMAIL PROTECTED] wrote: So, in other words, in order to test whether terms constructed with Equal are equal, you have to compare two terms of different type

Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-08-29 Thread Dan Weston
C++ faced this very issue by saying that with global data, uniqueness of initialization is guaranteed but order of evaluation is not. Assuming that the global data are merely thunk wrappers over some common data source, this means that at minimum, there can be no data dependencies between

Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-08-29 Thread Dan Weston
); } What is the value of D? Notice that this is never a problem with pure functions. The problem is that today() makes this an IO monad, and the swearing starts again. Dan Bryan O'Sullivan wrote: On Fri, Aug 29, 2008 at 4:33 PM, Dan Weston [EMAIL PROTECTED] wrote: C++ faced this very issue

Re: [Haskell-cafe] Haskell Propeganda

2008-08-27 Thread Dan Weston
Tim Docker wrote: David Roundy wrote: Which illustrates the point that it's not type safety that protects us from segfaults, so much as bounds checking, and that's got a non-trivial runtime cost. At least, most segfaults that *I've* caused (in C or C++) have been from overwriting the

Re: [Haskell-cafe] Last Call for the Italian Haskellers Summer Meeting

2008-08-07 Thread Dan Weston
Shouldn't that be posta elettronica (or posteletta along the lines of the Frence courriel)? Somehow I doubt that Dante would have approved of the word email. Titto Assini wrote: As usual we will now switch to Dante's bella lingua. Ottimissimi, mancano pochi giorni al primo incontro

Re: [Haskell-cafe] BLAS Solve Example

2008-07-23 Thread Dan Weston
A jedi master might stick with the existing double precision solver, then convert the results to best rational approximation [1], then do a forward solve on the rational versions of matrices, adjusting numerator and denominator to eliminate the residual error (with a heuristic to favor common

[Haskell-cafe] beginners mailing list should be beginner's choice

2008-07-21 Thread Dan Weston
Just to avoid any misunderstanding... I am certain that C.M. Brown meant to say CC'ed the Haskell-beginners mailing list instead of moved, but I think it's worth emphasizing that the new beginners list was ostensibly created for various discussed reasons, but all to provide a more tailored

Re: [Haskell-cafe] Galois Tech Talks: Stream Fusion for Haskell Arrays

2008-07-14 Thread Dan Weston
Slides, plus an audio recording of the talk would be great. With that, we could follow along easily. Johan Tibell wrote: On Sun, Jul 13, 2008 at 12:16 AM, Don Stewart [EMAIL PROTECTED] wrote: johan.tibell: On Sat, Jul 12, 2008 at 12:13 AM, Don Stewart [EMAIL PROTECTED] wrote: Any possibility

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

2008-07-11 Thread Dan Weston
Dmitri O.Kondratiev wrote: I need extendable array to store and count unique vectors. I have a file containing vectors presented as strings like: 10, 6, 80, 25, 6, 7 1, 2, 15, 17, 33, 22 21, 34, 56, 78, 91, 2 ... (BTW, what is the best library function to use to convert string of digits into a

Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Weston
I think the problem is here: getCatalog :: Catalog catalog = a - catalog This wants to constrain the result of getCatalog to be an instance of Catalog, but this only works for function arguments, not results. The following code does typecheck, though I have no idea what is does or if it

Re: [Haskell-cafe] type constructor confusion

2008-06-19 Thread Dan Weston
If it helps, feel free to use a different name for the data constructors and their data type until the difference is painfully clear to you (maybe suffix the constructor with a C or prefix by Mk). Data types and constructors live in different namespaces and can happily use the same

Re: [Haskell-cafe] A simple beginner question

2008-06-03 Thread Dan Weston
There's always one more way to do things in Haskell! :) Here's yet another way to get at the payloads in a list. You don't have to know how this works to use it: data SampleType = A | B Int | C String unA :: SampleType - [()] unA A = return () unA _ = fail Not an A unB :: SampleType

Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Dan Weston
than 50% of the monads in the standard libraries. I wonder what fraction of monads in real code the IO monad alone accounts for? 50% does not seem implausible to me. Dan Weston ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] Ubuntu and ghc

2008-05-21 Thread Dan Weston
Now you tell me! I also upgraded late last night and got the exact same problem. :( I just uninstalled the ghc from the Update Manager and was going to reinstall tonight. Are you saying that something else is screwed up because of this? Galchin, Vasili wrote: Hello,

Re: [Haskell-cafe] relational data representation in memory using haskell?

2008-05-21 Thread Dan Weston
Consider SQLite [1], which is a software library that implements a self-contained, serverless, zero-configuration, transactional SQL database engine. It is embeddable, can reside completely in memory (including the data), and can be saved and restored to disk when needed. It neatly fills the

Re: [Haskell-cafe] Re: Write Haskell as fast as C.

2008-05-16 Thread Dan Weston
Ketil Malde wrote: mkAnn :: ByteString - Annotation mkAnn = pick . B.words where pick (_db:up:rest) = pick' up $ getGo rest pick' up' (go:_:ev:_) = Ann (B.copy up') (read $ B.unpack go) (read $ B.unpack ev) getGo = dropWhile (not . B.isPrefixOf (pack GO:)) It seems at

Re: [Haskell-cafe] Re: Write Haskell as fast as C.

2008-05-16 Thread Dan Weston
Dan Weston wrote: Ketil Malde wrote: mkAnn :: ByteString - Annotation mkAnn = pick . B.words where pick (_db:up:rest) = pick' up $ getGo rest pick' up' (go:_:ev:_) = Ann (B.copy up') (read $ B.unpack go) (read $ B.unpack ev) getGo = dropWhile (not . B.isPrefixOf (pack

Re: [Haskell-cafe] Re: Endianess

2008-05-14 Thread Dan Weston
Henning Thielemann wrote: On Tue, 13 May 2008, Achim Schneider wrote: Jed Brown [EMAIL PROTECTED] wrote: It's not that simple with bits. They lack consistency just like the usual US date format and the way Germans read numbers. So you claim that you pronounce 14 tenty-four? In German

Re: [Haskell-cafe] Richer (than ascii) notation for haskell source?

2008-05-14 Thread Dan Weston
Richard A. O'Keefe wrote: At least to give editors a fighting chance of matching their concept of a word with Haskell tokens, it might be better to use nabla instead of lambda. Other old APL fans may understand why (:-). Alternatively, didn't Church really want to use a character rather like a

Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Dan Weston
Henning Thielemann wrote: On Thu, 8 May 2008, Madoc wrote: minValue = 0::Int maxValue = 1000::Int normalize a | a minValue = minValue | a maxValue = maxValue | otherwise = a normalize' = min maxValue . max minValue There is a curiosity here. The functions

Re: [Haskell-cafe] Induction (help!)

2008-05-07 Thread Dan Weston
only a masochist would be so verbose. But the induction hypothesis does after all require a first time! :) Dan Weston PR Stanley wrote: Hi One of you chaps mentioned the Nat data type data Nat = Zero | Succ Nat Let's have add :: Nat - Nat - Nat add Zero n = n add (Succ m)n = Succ (add m n

Re: [Haskell-cafe] Induction (help!)

2008-05-06 Thread Dan Weston
Ryan Ingram wrote: One point to remember is that structural induction fails to hold on infinite data structures: As I understand it, structural induction works even for infinite data structures if you remember that the base case is always _|_. [1] Let the initial algebra functor F = const

Re: [Haskell-cafe] unapplying function definitions?

2008-05-05 Thread Dan Weston
. And finally, if this is true for all x, then f = g. Note that Leibnitz allows for any argument, extensionality requires equality for every argument. Dan Weston [1] http://en.wikipedia.org/wiki/Identity_of_indiscernibles#Identity_and_indiscernibility [2] We know this because e.g. there is some

Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Dan Weston
I guess like minds think alike! See the very recent e-mail thread started by Ryan Ingram: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/39155/focus=39159 Take a look at the code referenced in Luke Palmer's reply:

Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Dan Weston
Freitag, den 25.04.2008, 11:49 -0700 schrieb Dan Weston: I guess like minds think alike! See the very recent e-mail thread started by Ryan Ingram: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/39155/focus=39159 Take a look at the code referenced in Luke Palmer's reply: http://luqui.org/git

  1   2   3   >