[Haskell-cafe] Simple quirk in behavior of `mod`

2009-07-21 Thread Nathan Bloomfield
Hello haskell-cafe;

I'm fiddling with
this<http://cdsmith.wordpress.com/2009/07/20/calculating-multiplicative-inverses-in-modular-arithmetic/>blog
post about inverting elements of Z/(p), trying to write the inversion
function in pointfree style. This led me to try executing statements like

   n `mod` 0

which in the ring theoretic sense should be n, at least for integers*.
(MathWorld
agrees. <http://mathworld.wolfram.com/Congruence.html>) But Hugs gives a
division by zero error! I'm more of a recreational haskell user and not too
familiar with how the Prelude works. But I dug around a bit and saw
this inGHC.Real: (
link<http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-Real.html#mod>
)

>  a `mod` b
>   | b == 0 = divZeroError
>   | a == minBound && b == (-1) = overflowError
>   | otherwise  =  a `modInt` b

Is there a reason why n `mod` 0 is undefined in Haskell? Maybe this
has already been considered for Haskell' and I'm just unaware.
I did some digging in the archives and this discussion
<http://markmail.org/message/5dmehw4lhu56x4zw#query:haskell%20%22%60mod%60%200%22+page:1+mid:7alg3hdlndapyxg6+state:results>
<http://markmail.org/message/5dmehw4lhu56x4zw> from 2002 is the most
relevant one I could find; it is suggested there that n `mod` 0 should
be an error.

Thanks all-
Nathan Bloomfield

*- The mod function is defined in the Integral class, and I'm not even
sure how to interpret that. It looks kind of like a Euclidean domain.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Nathan Bloomfield
> This, to defend myself, was not how it was explained in high school.

No worries. I didn't realize this myself until college; most nonspecialist
teachers just don't know any better. Nor did, it appears, the original
authors of the Haskell Prelude. :)

BTW, this definition of gcd makes it possible to consider gcds in rings that
otherwise have no natural order- such as rings of polynomials in several
variables, group rings, et cetera.

Nathan Bloomfield

On Sun, May 3, 2009 at 11:16 AM, Achim Schneider  wrote:

> Nathan Bloomfield  wrote:
>
> > The "greatest" in gcd is not w.r.t. the canonical ordering on the
> > naturals; rather w.r.t. the partial order given by the divides
> > relation.
> >
> This, to defend myself, was not how it was explained in high school.
>
> --
> (c) this sig last receiving data processing entity. Inspect headers
> for copyright history. All rights reserved. Copying, hiring, renting,
> performance and/or quoting of this signature prohibited.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Nathan Bloomfield
Having gcd(0,0) = 0 doesn't mean that 0 is not divisible by any other
natural number. On the contrary, any natural trivially divides 0 since n*0 =
0. Perhaps the disagreement is over what is meant by "greatest". The
"greatest" in gcd is not w.r.t. the canonical ordering on the naturals;
rather w.r.t. the partial order given by the divides relation. Similarly for
the "least" in lcm.

Suppose gcd(0,0) = a. Then a|0, and if b|0 then b|a. (That's what it means
to be the gcd.) So what is a? Since every natural number divides zero, a
must be divisible by every natural number. The only natural number with this
property is 0, which can be proved using the essential uniqueness of prime
factorizations and infinitude of primes.

So having gcd(0,0) = 0 isn't just useful, it's the correct thing to do.

I hope that didn't use too many long words. :)

-Nathan Bloomfield
Grad Assistant, University of Arkansas, Fayetteville

On Sat, May 2, 2009 at 5:17 PM, Achim Schneider  wrote:

> Steve  wrote:
>
> > "It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then
> > the natural numbers become a complete distributive lattice with gcd
> > as meet and lcm as join operation. This extension of the definition
> > is also compatible with the generalization for commutative rings
> > given below."
> >
> Ouch. Speak of mathematicians annoying programmers by claiming that 0
> isn't divisible by any of [1..], and further implying that 0 is bigger
> than all of those, not to mention justifying all that with long words.
>
> Damn them buggers.
>
> --
> (c) this sig last receiving data processing entity. Inspect headers
> for copyright history. All rights reserved. Copying, hiring, renting,
> performance and/or quoting of this signature prohibited.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Grokking zippers

2009-03-20 Thread Nathan Bloomfield
Hello all-

I'm trying to understand the categorical guts underlying zippers. In the
Haskell wikibook (and other places) I've seen zippers described roughly as
the derivatives of functors. However, I haven't been able to find any
references that develop this idea rigorously. For instance, what exactly is
the "derivative" of a functor at an object, in the direction of some arrow?
I'm interested in studying this concept in more depth, but I can't find a
definition to start with.

Any pointers to good books or papers would be greatly appreciated. :)

Thank you all-

Nathan Bloomfield
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Improved documentation for Bool (Was: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt)

2009-01-18 Thread Nathan Bloomfield
That's a great start, but "coproduct" is still pretty scary. Why not refer
to it as OneOrTheOtherButNotBothDataConstructor?

-Nathan Bloomfield

On Sun, Jan 18, 2009 at 11:32 AM, Sterling Clover wrote:

> This is a great effort, but the root of the problem isn't just poor
> documentation, but an insistence on some obscure name. How about renaming
> Bool to YesOrNoDataVariable? I think this would help novice programmers a
> great deal.
>
> It would also make the documentation flow much more naturally:
>
> The Bool type is the coproduct of the terminal object with itself.
>
> --huh?
>
> The YesOrNoDataVariable is the coproduct of the terminal object with
> itself.
>
> --Oh! Of course!
>
> --S
>
>
> On Jan 18, 2009, at 12:17 PM, Benja Fallenstein wrote:
>
>  On Sun, Jan 18, 2009 at 5:48 PM,   wrote:
>>
>>> I noticed the Bool datatype isn't well documented.  Since Bool is not a
>>> common English word, I figured it could use some haddock to help clarify
>>> it
>>> for newcomers.
>>>
>>> -- |The Bool datatype is named after George Boole (1815-1864).
>>> -- The Bool type is the coproduct of the terminal object with itself.
>>>
>>
>> Russell, this does seem like it might be very helpful, but it might be
>> useful to include a note about what category you are working in.
>> People may sometimes naively assume that one is working in the
>> category of Haskell/Hugs/GHC data types and Haskell functions, in
>> which there are no terminal -- or initial -- objects ('undefined' and
>> 'const undefined' are distinct maps between any two objects X and Y),
>> or else in the similar category without lifted bottoms, in which the
>> empty type is terminal and the unit type isn't ('undefined' and 'const
>> ()' are both maps from any object X to the unit type). These niceties
>> will not confuse the advanced reader, but it may help the beginner if
>> you are more explicit.
>>
>> - Benja
>>
>>
>> P.S. :-)
>> ___
>> Libraries mailing list
>> librar...@haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OT: representations for graphs

2008-12-19 Thread Nathan Bloomfield
(Forgot to send to haskell-cafe- sorry Alistair!)

Martin Erwig wrote a paper [1] that defines an inductive graph type and
implements some common algorithms with it.

Also, it isn't very Haskellish but if you can label your nodes with an
instance of Ix you might be able to use an Array to get constant time
access.
I've never used Data.HashTable before, but that might also be useful.

[1] -
http://web.engr.oregonstate.edu/~erwig/papers/InductiveGraphs_JFP01.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Time for a new logo?

2008-12-16 Thread Nathan Bloomfield
On Tue, Dec 16, 2008 at 11:40 AM, Darrin Thompson wrote:

> My $0.02 us:
>
> Apologies for ascii art, and hopefully gmail doesn't munge this:
>
> 
> \\  \\
>  \\  \\  \|
>  \\  \\   ---
>   \\  \\
>   //  / \
>  //  /   \  \|
>  //  /   /\\   ---
> //  /   /  \\
>  
>
> --
> Darrin


I really like this idea. It incorporates two important ideas and is simple
enough to look good at different sizes; plus, it doesn't look like the
Half-life logo. My biggest concern is that to someone not already familiar
with Haskell syntax, it might be confusing. (That may or may not be an
actual problem.)

Nathan Bloomfield
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec and type level numerals

2008-12-13 Thread Nathan Bloomfield
Hello all. I've got a puzzling Parsec problem. Perhaps the collective wisdom
of haskell-cafe can point me in the right direction.

I want to be able to parse a string of digits to a type level numeral as
described in the Number parameterized
types<http://okmij.org/ftp/papers/number-parameterized-types.pdf>paper.
After fiddling with the problem for a while, I'm not convinced it's
possible- it seems as though one would need to know the type of the result
before parsing, but then we wouldn't need to parse in the first place. :) My
first (simplified) approximation is as follows:

> data Zero = Zero
> data Succ a = Succ a

> class Card t
> instance Card Zero
> instance (Card a) => Card (Succ a)

> parseP :: (Card a) => Parser a
> parseP = do { char '1'
> ; rest <- parseP
> ; return $ Succ rest
> }
>  <|> return Zero

I'd like for this to parse, for example, "111" into Succ Succ Succ Zero. Of
course this doesn't work because parseP is ill-typed, but I'm not sure how
to fix it. It seems that what I'm asking for is a function whose type is forall
a. (Card a) => String -> a, which is problematic.

Has anyone tried this before? I'm new to using Parsec and to parsing in
general, so I apologize if this is a silly question. (Parsec is very
impressive, by the way.)

Thanks-

Nathan Bloomfield
University of Arkansas, Fayetteville
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Origins of '$'

2008-12-08 Thread Nathan Bloomfield
>
>
>> In set theory, and sometimes in category theory, A^B is just another
> notation for Hom(B, A), and the latter might be given the alternate notation
> B -> A. And th reason is that for finite sets, computing cardinalities
> result in the usual power function of natural numbers - same as Church,
> then.
>
>  Hans


Slightly off topic, but the A^B notation for hom-sets also makes the natural
isomorphism we call currying expressable as A^(BxC) = (A^B)^C.

Nathan Bloomfield
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: universal algebra "support" in Haskell?

2008-10-23 Thread Nathan Bloomfield
This question is relevant to a project I'm working on. I've been putting
together an abstract algebra library for handling computations inside group
rings, polynomial rings, and rings with adjoined elements. Once I've got it
cleaned up a little I'll upload it to an appropriate place.

(I forgot to cc haskell-cafe- sorry DavidA!)

Nathan Bloomfield
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Nathan Bloomfield
At the risk of doing someone's homework...
A naive solution is to do trial division by all integers from 2 up to sqrt
n.

{-
isPrime :: Integer -> BoolisPrime n
 | n < 2 = False
 | otherwise = f 2 n
 where f k n
  = if k > isqrt
 then True
 else undefined -- exercise for the reader
-}

and where
isqrt n returns floor (sqrt n)

Here, f is the helper function, and is only in scope inside the definition
of isPrime. This is a common haskell idiom- a helper function that is not
quite general purpose enough to be made a standalone function can be defined
"on the fly" and doesn't need a name or type signature.

You could fancy this up to make it more efficient. I've also seen
probabilistic functions that can handle huge numbers, but I can't remember
if they are recursive.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Best book/tutorial on category theory and its applications

2008-07-30 Thread Nathan Bloomfield
If you want to see a human being explain some categorical ideas, there is a
nice (and growing) collection of video mini-tutorials on youtube by the
Catsters.

http://www.youtube.com/user/TheCatsters

-Nathan Bloomfield

(I first sent this just to Pierre by accident - sorry!)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FPers in Northwest Arkansas?

2008-07-25 Thread Nathan Bloomfield
Greetings, Haskell-cafe. I am interested in joining or starting a functional
programming interest group in my area. Are there any haskellers in the
Northwest Arkansas region?

Nathan Bloomfield
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A question about algebra and dependent typing

2008-07-14 Thread Nathan Bloomfield
There's something I want to do with Haskell, and after tinkering for a while
I think it's not possible. Before giving up entirely, I thought I'd try this
mailing list.

I'm working on an abstract algebra library, using the "types are sets"
strategy. For the algebraists out there, I'm trying to implement as much as
I can of "Abstract Algebra" by Dummit & Foote in Haskell. I've got a Ring
class definition that looks approximately like

> class Ring t where
>   (<+>) :: t -> t -> t
>  (<*>) :: t -> t -> t
>  neg :: t -> t
>  zero :: t

So, for example, we can say

>instance Ring Integer where
>  (<+>) = (+)
>  (<*>) = (*)
>  neg = negate
>  zero = 0

>From here I can subclass to domains, PIDs, EDs, UFDs, fields, et cetera, and
write some useful algorithms in great generality. The ring R[x] can be
modeled by the type [r], direct products are tuples, and fractions in the
domain r have type Fraction r. I can even model the set (i.e. type) of nxn
matrices over a ring using type-level integers as demonstrated in the paper
"Number-Parameterized Types" by Oleg Kiselyov [1]. All good stuff.

However, I'm running into problems modeling some other useful and
computationally interesting things, in particular adjoining an algebraic
element and taking a quotient by an ideal. For example, I've tried the
following (using GHC extensions):

>class (Ring r) => Ideal i r | i -> r
>
>data (Ring r) => FinGenIdeal r = Ideal [r]
>
>instance (Ring r) => Ideal (FinGenIdeal r) r
>
>data (Ring r, Ideal i r) => Coset r i = r :+: i

But of course I can't say

>instance (Ring r, Ideal i r) => Ring (Coset r i) where
>  (r :+: i) <+> (s :+: j) = (r <+> s) :+: i
>  zero = zero :+: ?
>  ...

It shouldn't make sense to add 2 :+: Ideal [3] and 3 :+: Ideal [5], for
example, and zero is ambiguous. This problem happems because Ideal [3] and
Ideal [5] have the same type, namely FinGenIdeal Integer.

I am pretty new to Haskell and type theory, but I think what I'm wanting is
dependent types. So, for instance, the type of Coset r i is parameterized by
an particular value in FinGenIdeal r. Is there another way around this? I'm
sure there is some sophisticated type-fu one could perform (similar to the
examples in [1]) to construct ideals of integers, tuples of integers, et
cetera, but this would quickly get unwieldy and sacrifices some generality.
I have heard lots of praise of GADT as an approximation to dependent types,
but I don't yet see how they could apply in this situation.

Has anyone else encountered a similar problem, and if so, how did you get
around it? Would I be better off working in a dependently-typed language
like Agda?

[1] - http://okmij.org/ftp/papers/number-parameterized-types.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe