Re: [Haskell-cafe] function arithmetic?

2013-09-01 Thread Christopher Howard

On 08/31/2013 09:27 PM, Charlie Paul wrote:

I believe that this is what you want:
http://www.haskell.org/haskellwiki/Num_instance_for_functions

On Sat, Aug 31, 2013 at 10:01 PM, Christopher Howard
christopher.how...@frigidcode.com wrote:


The author seemed to be subtly mocking the idea. It seemed to be 
suggesting that a Num instance for functions would imply the need for 
constant number functions, which leads to difficulties. But I don't see 
why one would have to take it that far.


In any case, I just tried the NumInstances package from Hackage and it 
seems to work great.


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


[Haskell-cafe] function arithmetic?

2013-08-31 Thread Christopher Howard
Hi. I was just curious about something. In one of my math textbooks I 
see expressions like this


f + g

or

(f + g)(a)

where f and g are functions. What is meant is

f(a) + g(a)

Is there a way in Haskell you can make use of syntax like that (i.e., 
expressions like f + g and f * g to create a new function), perhaps by 
loading a module or something?


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


[Haskell-cafe] continuations and monads

2013-08-17 Thread Christopher Howard
Q: Are the continuations in Scheme related to the monads from 
Haskell? If so, could someone elaborate on that?


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


[Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
When I previously asked about memoization, I got the impression that
memoization is not something that just happens magically in Haskell.
Yet, on a Haskell wiki page about Memoization
http://www.haskell.org/haskellwiki/Memoization#Memoization_with_recursion,
an example given is

memoized_fib :: Int - Integer
memoized_fib = (map fib [0 ..] !!)
   where fib 0 = 0
 fib 1 = 1
 fib n = memoized_fib (n-2) + memoized_fib (n-1)


I guess this works because, for example, I tried memoized_fib 1
and the interpreter took three or four seconds to calculate. But every
subsequent call to memoized_fib 1 returns instantaneously (as does
memoized_fib 10001).

Could someone explain the technical details of why this works? Why is
map fib [0 ..] not recalculated every time I call memoized_fib?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/21/2013 11:19 PM, KC wrote:
 Have you tried the compiler?

No. Would that work differently some how?

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/21/2013 11:52 PM, Chris Wong wrote:
 [.. snipped ..]

 A binding is memoized if, ignoring everything after the equals sign,
 it looks like a constant.

 In other words, these are memoized:

 x = 2

 Just x = blah

 (x, y) = blah

 f = \x - x + 1
 -- f = ...

 and these are not:

 f x = x + 1

 f (Just x, y) = x + y

 If you remove the right-hand side of memoized_fib, you get:

 memoized_fib = ...

 This looks like a constant. So the value (map fib [0..] !!) is memoized.

 If you change that line to

 memoized_fib x = map fib [0..] !! x

 GHC no longer memoizes it, and it runs much more slowly.

 --
 Chris Wong, fixpoint conjurer
   e: lambda.fa...@gmail.com
   w: http://lfairy.github.io/

Thanks. That's very helpful to know. Yet, it seems rather strange and
arbitrary that f x = ... and f = \x - ... would be treated in such
a dramatically different manner.

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/22/2013 06:16 AM, Andreas Abel wrote:
 On 22.07.2013 09:52, Chris Wong wrote:

 True, but the essential thing to be memoized is not memoized_fib,
 which is a function, but the subexpression

   map fib [0..]

 which is an infinite list, i.e., a value.

 The rule must be like in

   let x = e

 if e is purely applicative, then its subexpressions are memoized.
 For instance, the following is also not memoizing:

 fib3 :: Int - Integer
 fib3 = \ x - map fib [0 ..] !! x
where fib 0 = 0
  fib 1 = 1
  fib n = fib3 (n-2) + fib3 (n-1)

 In general, I would not trust such compiler magic, but just let-bind
 anything I want memoized myself:

 memoized_fib :: Int - Integer
 memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)

 The eta-expansions do not matter.

 Cheers,
 Andreas


Is this behavior codified somewhere? (I can't seem to find it in the GHC
user guide.)

The memoize package from hackage, interestingly enough, states that
[Our memoization technique] relies on implementation assumptions that,
while not guaranteed by the semantics of Haskell, appear to be true.

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/22/2013 03:41 PM, David Thomas wrote:
 I, for one, would love to have a compiler do (a) based on (b), my
 specification of (c), and the ability to pin particular things...



The reason it is a big deal to me is it sometimes the more
natural-looking (read, declarative) way of writing a function is only
reasonably efficient if certain parts are memoized. Otherwise I end up
having to pass around extra arguments or data structures representing
the data I don't want to be recalculated.

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


[Haskell-cafe] partially indeterminate?

2013-07-15 Thread Christopher Howard
Hi. For learning, I was doing the phone words problem, where a
function translates the digits of a phone number into all possible
words. I am trying to connect this idea to the idea of list
comprehensions / list monads (sort of the same thing, yes?)

I know it is easy to do this:

w = do two - ABC

   three - DEF

   four - GHI

   -- and the other digits

   [[two, three, two, four]] -- for example

But what if you don't know in advance what the digits will be? I'm not
sure how to insert that deterministic component into this idea. So far,
I have a framework like so:

p dx = do undefined

  where m = map (\d - case d of

2 - ABC

3 - DEF

4 - GHI

5 - JKL

6 - MNO

7 - PRS

8 - TUV

9 - WXY

otherwise - show d) dx


I would appreciate any guidance.

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


[Haskell-cafe] Roman Numeral Problem

2013-06-24 Thread Christopher Howard
Hi. I am working on some practice programming problems, and one is the
Roman numeral problem: write a program that converts Roman numerals into
their (arabic) numeral equivalent. I imagine I could hack something
together, but I was trying to think about the problem a bit more deeply.
I don't know much about parsing, but I was wondering if this problem
matched up with some kind of parsing or grammar or other generic
approach to thinking about the problem. (I once read something about
Context Free Grammars, which was rather interesting.) I can do more of
my own research if I can get some initial guidance.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
I'm working through some beginner-level keyboard problems I found at
users.csc.calpoly.edu. One problem is the Saddle Points problem:

quote:

Write a program to search for the saddle points in a 5 by 5 array of
integers. A saddle point is a cell whose value is greater than or equal
to any in its row, and less than or equal to any in its column. There
may be more than one saddle point in the array. Print out the
coordinates of any saddle points your program finds. Print out No
saddle points if there are none.


Let's say I use a simple list grid like so:

code:

array = Grid 5 [ [1,5,3,6,4]
   , [8,2,6,3,8]
   , [3,8,7,2,9]
   , [0,3,7,1,2]
   , [7,2,7,4,5] ]

data Grid = Grid Int [[Int]]


And let's say I take a brute force approach, moving through each cell,
checking to see if it is the greatest in its row and the least in its
column. And say I have functions like so for getting rows and columns:

code:

row (Grid s l) n = if (n = s) then [] else l !! n

col g@(Grid s l) n = if (n = s) then [] else col_ g n 0
where col_ (Grid s l) n i = if (i = s) then [] else (head l !! n) :
col_ (Grid s (tail l)) n (i + 1)


My question: With the way Haskell works (thunks, lazy evaluation, and
all that mystery), is it actually worth the trouble of /precalculating/
the maximum row values and minimum column values, to compare cell values
against? Or will, for example, something like (smallest_list_value (col
array 1)) definitely only evaluate once?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 
 There's not enough context to answer the specific question,
 but lazy evaluation isn't magic and the answer is probably no.
 
 Tommy
 

Perhaps to simplify the question somewhat with a simpler example.
Suppose you have

code:

let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)


After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
etc. calculated anymore?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
On 06/15/2013 05:02 PM, Christopher Howard wrote:
 On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 Perhaps to simplify the question somewhat with a simpler example.
 Suppose you have
 
 code:
 
 let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)
 
 
 After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
 etc. calculated anymore?

That might have been ambiguous. What I meant was:

code:

let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)


If I calculate (f 0), and the cycle repeats after four values, are sin,
cos, etc. calculated anymore?


-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simplest way to learn FRP through use

2013-06-01 Thread Christopher Howard
On 05/31/2013 07:47 PM, Tikhon Jelvis wrote:
 My favorite mini app is John Conway's game of life. I implemented a
 version with reactive banana and found it perfect for learning the ideas.
 
 I have a simple version of the code up on GitHub if you ever want a nice
 example to read. I tried to make the code neat rather than worrying
 about performance or features.
 

Would you be willing to give a URL for that? (To save posterity from the
trouble of putting your name in a GitHub search box.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Simplest way to learn FRP through use

2013-05-31 Thread Christopher Howard
I want to learn FRP but am having trouble wading through all the theory
about how FRP is implemented and how it /could/ be used for various
applications. What is the simplest, easiest-to-learn module or system
allowing you to quickly make something interesting (if not very
impressive) in an FRP style? Say, a simple simulation of some physical
phenomena outputting its state to the terminal; or an object moving on
the screen; or some other toy application that I could create and play with.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rip in the class-abstraction continuum

2013-05-20 Thread Christopher Howard
On 05/19/2013 10:10 PM, Tillmann Rendel wrote:
 
 This is not easily possible. If you could just put the constraint into
 the instance, there would be a problem when youc all toXy in a
 polymorphic context, where a is not known. Example:
 
   class XyConv a where
 toXy :: a b - [Xy b]
 
   shouldBeFine :: XyConv a = a String - [Xy String]
   shouldBeFine = toXy
 
 This code compiles fine, because the type of shouldBeFine is an instance
 of the type of toXy. The type checker figures out that here, b needs to
 be String, and since there is no class constraint visible anywhere that
 suggests a problem with b = String, the code is accepted.
 
 The correctness of this reasoning relies on the fact that whatever
 instances you add in other parts of your program, they can never
 constrain b so that it cannot be String anymore. Such an instance would
 invalidate the above program, but that would be unfair: How would the
 type checker have known in advance whether or not you'll eventually
 write this constraining instance.
 
 So this is why in Haskell, the type of a method in an instance
 declaration has to be as general as the declared type of that method in
 the corresponding class declaration.
 
 
 Now, there is a way out using some of the more recent additions to the
 language: You can declare, in the class, that each instance can choose
 its own constraints for b. This is possible by combining constraint
 kinds and associated type families.
 
   {-# LANGUAGE ConstraintKinds, TypeFamilies #-}
   import GHC.Exts
 
 The idea is to add a constraint type to the class declaration:
 
   class XyConv a where
 type C a :: * - Constraint
 toXy :: C a b = a b - [Xy b]
 
 Now it is clear to the type checker that calling toXy requires that b
 satisfies a constraint that is only known when a is known, so the
 following is not accepted.
 
   noLongerAccepted :: XyConv a = a String - [Xy String]
   noLongerAccepted = toXy
 
 The type checker complains that it cannot deduce an instance of (C a
 [Char]) from (XyConv a). If you want to write this function, you have to
 explicitly state that the caller has to provide the (C a String)
 instance, whatever (C a) will be:
 
   haveToWriteThis :: (XyConv a, C a String) = a String - [Xy String]
   haveToWriteThis = toXy
 
 So with associated type families and constraint kinds, the class
 declaration can explicitly say that instances can require constraints.
 The type checker will then be aware of it, and require appropriate
 instances of as-yet-unknown classes to be available. I think this is
 extremely cool and powerful, but maybe more often than not, we don't
 actually need this power, and can provide a less generic but much
 simpler API.
 
   Tillmann

Thank you for the quick and thorough response. To be honest though, I
had some difficulty following your explanation of the constraints
problem. I had an even more difficult time when I tried to read up on
what Type Families are -- ended up at some wiki page trying to explain
Type Families by illustrating them with Generic Finite Maps (a.k.a.,
Generic Prefix Trees). The rough equivalent of learning German through a
Latin-German dictionary. :|

Anyway, I played around with my code some more - and it seems like what
I am trying to do can be done with multi-parameter type classes:

code:

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

class XyConv a b where

  toXy :: a b - [Xy b]

instance (Integral a, Floating b) = XyConv (CircAppr a) b where

  toXy (CircAppr divns ang rad) =
  let dAng = 2 * pi / (fromIntegral divns) in
  let angles = map ((+ ang) . (* dAng) . fromIntegral) [0..divns] in
  map (\a - am2xy a rad) angles


Seems to work okay:

code:

h toXy (CircAppr 4 0.0 1.0)
[Xy 1.0 0.0,Xy 6.123233995736766e-17 1.0,Xy (-1.0)
1.2246467991473532e-16,Xy (-1.8369701987210297e-16) (-1.0),Xy 1.0
(-2.4492935982947064e-16)]
h :t toXy (CircAppr 4 0.0 1.0)
toXy (CircAppr 4 0.0 1.0) :: Floating b = [Xy b]


Is there anything bad about this approach?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] rip in the class-abstraction continuum

2013-05-19 Thread Christopher Howard
Hi. I won't pretend to be an advanced Haskell programmer. However, I
have a strong interest in abstraction, and I have been playing around
with programming as abstractly as possible. Naturally, I find classes to
be quite attractive and useful.

However, something is bothering me. Lately I keep running into this
situation where I have to cut across abstraction layers in order to make
the code work. More specifically, I keep finding that I have to add
constraints to a class definition, because eventually I find some
instance of that class which needs those constraints to compile.

For example, I wanted to create a class which represents all things that
can be converted into X,Y coordinates. Naturally, I would like to do
something like this:

code:

class XyConv a where

  toXy :: a b - [Xy b]


This leaves me free in the future to use any number type conceivable in
the Xy coordinates - Floating or Integral types, or whatever. (Doesn't
even have to be numbers, actually!)

However the first instance I create, requires me to use operators in the
function definition which require at least a Floating type. (The error
will say Fractional, but there are other components that also require
Floating.)

code:

data CircAppr a b = CircAppr a b b -- number of points, rotation angle,
radius
deriving (Show)

instance Integral a = XyConv (CircAppr a) where

  toXy (CircAppr divns ang rad) =
  let dAng = 2 * pi / (fromIntegral divns) in
  let angles = map ((+ ang) . (* dAng) . fromIntegral) [0..divns] in
  map (\a - am2xy a rad) angles


This gives me the error

code:

Could not deduce (Fractional b) arising from a use of `/'
from the context (Integral a)
  bound by the instance declaration
  at /scratch/cmhoward/pulse-spin/pulse-spin.hs:51:10-42
Possible fix:
  add (Fractional b) to the context of
the type signature for toXy :: CircAppr a b - [Xy b]
or the instance declaration
In the expression: 2 * pi / (fromIntegral divns)
In an equation for `dAng': dAng = 2 * pi / (fromIntegral divns)
In the expression:
  let dAng = 2 * pi / (fromIntegral divns) in
  let angles = map ((+ ang) . (* dAng) . fromIntegral) [0 .. divns]
  in map (\ a - am2xy a rad) angles


I can get a quick fix by adding Floating to the context of the /class/
definition:

code:

class XyConv a where

  toXy :: Floating b = a b - [Xy b]


But what I really want is to put Floating in the context of the
/instance/ declaration. But I don't know how to do that syntactically.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] fromIntegral not enough?

2013-05-13 Thread Christopher Howard
This is probably a haskell-beginners sort of question, but I usually get
about 4x as many responses from cafe, about 10x as fast.

I have code like so:

code:

data Xy a = Xy a a

class Coord2 a where

  coords2 :: Fractional b = a b - Xy b

data CircAppr a b = CircAppr a b b -- number of points, rotation angle,
radius
deriving (Show)

instance Integral a = Coord2 (CircAppr a) where

  coords2 (CircAppr divns ang rad) =
  let dAng = 2 * pi / (fromIntegral divns) in
  let angles = map (* dAng) [0..divns] in
  undefined -- To be coded...


In the instance definition divns is an integral trying to divide a
fractional. I hoped wrapping it in fromIntegral would coerce, but
apparently not:

quote:

Could not deduce (Fractional a) arising from a use of `/'
from the context (Integral a)
  bound by the instance declaration
  at /scratch/cmhoward/pulse-spin/pulse-spin.hs:34:10-42
or from (Fractional b)
  bound by the type signature for
 coords2 :: Fractional b = CircAppr a b - Xy b
  at /scratch/cmhoward/pulse-spin/pulse-spin.hs:(36,3)-(39,15)
Possible fix:
  add (Fractional a) to the context of
the type signature for
  coords2 :: Fractional b = CircAppr a b - Xy b
or the instance declaration
In the expression: 2 * pi / (fromIntegral divns)
In an equation for `dAng': dAng = 2 * pi / (fromIntegral divns)
In the expression:
  let dAng = 2 * pi / (fromIntegral divns) in
  let angles = map (* dAng) [0 .. divns] in undefined


So, I'm wondering how I can do what I'm trying to do here, while still
keeping my types as generic as possible.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] fromIntegral not enough?

2013-05-13 Thread Christopher Howard
On 05/13/2013 02:53 PM, Tom Ellis wrote:
 On Mon, May 13, 2013 at 11:43:41PM +0100, Tom Ellis wrote:
 
 You probably want
 
 let angles = map ((* dAng) . fromInteger) [0..divns] in
 ...
 
 instead.
 

Ah, that works. Thanks all.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Flip around type parameters?

2013-05-09 Thread Christopher Howard
Hi. Does Haskell allow you to flip around type parameters somehow? I was
playing around with toy code (still learning the fundamentals) and I
came up with a class like this:

code:

class Rotatable2D a where

rotate :: (Num b) = (a b) - b - (a b)


It was easy to make an instance of a generic single-parameter type:

code:

data Angle a = Angle a
deriving (Show)

instance Rotatable2D Angle where

rotate (Angle a) b = Angle (a + b)


But let's say I have something a little more complicated:

code:

data CircAppr a b = CircAppr a a b -- radius, rotation angle, number of
points


I think I need something like so:

instance Rotatable2D (\x - CircAppr x a) where

rotate (CircAppr a b c) d = CircAppr a (b + d) c


But I tried that and it isn't valid syntax.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GPGPU

2013-05-04 Thread Christopher Howard
Has anybody on the list been playing around with OpenCL at all? I'm just
starting to look into it - need to get a newer Radeon card, I think -
but I'm strongly interested in GPGPU programming.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal / cabal-install: special installation

2013-05-02 Thread Christopher Howard
Hi. This question dovetails off my previous thread. I described how I
got ghc-7.6.3 installed from source onto an old RHEL5 machine.

Naturally, I want to get cabal-install installed and start building
great Hackage software. However, I have this quirk: I installed GHC to a
special directory using ./configure --prefix=/specialdirectory/local. It
is in my path, and works just fine. But when I try to build
cabal-install, it claims it can't find Base, Cabal, and a few other
things I know are installed. I know they are installed because I can see
where they are installed and I can import stuff from them within GHCI.

The result is the same whether I use the boot script, or whether I use
runhaskell Setup configure (with or without a --prefix option). Is there
another environment variable I need to set or something like that?

(I need to emphasize that I do not want to install anything to $HOME,
because my $HOME directory is shared across multiple systems.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for portable Haskell or Haskell like language

2013-05-01 Thread Christopher Howard
On 05/01/2013 12:21 AM, Gabor Greif wrote:
 Am 27. April 2013 um 07:21 schrieb Christopher Howard
 christopher.how...@frigidcode.com:
 
  
 I can feel your pain... Here is a blog post I have written some time ago
 http://heisenbug.blogspot.de/2011/09/ghc-704-on-centos.html
 about how to bridge the gap. This was actually a RHEL5 system,
 but did not want to admit it :-)
 
 My writeup may be useful to you.
 
 Cheers,
 
 Gabor
 
 

For posterity's sake: I actually got this figured out already. First, I
downloaded the binary version of GHC 6.8.3 and installed it without
issues. Then I used it to build the sources of GHC 6.10.4 and install
them. Then I used 6.10.4 to build and install 6.12.3. Then 7.0.4, then
7.2.2, then 7.4.2, and finally 7.6.3.

Had no problems doing it that way, except for the optimization flags
issue in the 7.* series which I mentioned in my other thread. That was
easily fixed by setting the build.mk to the quick build profile.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghc-7 -fPIC error

2013-04-29 Thread Christopher Howard
Hey guys, this probably isn't the official GHC mailing list, but I've
been trying to build and install a new GHC on an old RHEL5 system, as
mentioned in my previous Cafe thread. I was able to make some good
headway: I installed a ghc-6.8 binary, and then used that to build
ghc-6.10 source, and then used that to build ghc-6.12 source. The idea
is to keep going until I get to ghc-7.6.

However, when I get to 7.0, my builds all eventually die with this error:

quote:

/usr/bin/ld: rts/dist/build/RtsStartup.dyn_o: relocation R_X86_64_PC32
against `StgRun' can not be used when making a shared object; recompile
with -fPIC
/usr/bin/ld: final link failed: Bad value
collect2: ld returned 1 exit status


After this failed the first time, I tried adding -fPIC to SRC_HC_OPTS,
GhcStage1HcOpts, and so forth in build.mk. But ultimately I get the same
error.

I tried skipping a version and building ghc-7.2 instead, but the same
error pops up.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for portable Haskell or Haskell like language

2013-04-27 Thread Christopher Howard
On 04/27/2013 08:36 AM, Jerzy Karczmarczuk wrote:
 Christopher Howard:
 Is the portability which worries you, or the age of your system?
 

Actually getting a successful build and installation would be great.
Also, there are multiple systems I work with, both of which have ancient
software, but unfortunately are not the same configuration. I often find
software that builds on one, but not the other.

 Hugs (and Gofer before) are simply sufficiently old... I used them on
 Red Hat in one of my previous lives.
 Do you really need to compile your system from sources?
 

I guess not, if I can get one to install successfully to a local
(non-root) user account. As mentioned, GHC Linux binaries failed me
here, because apparently the gnu libc version is too old. With most
software, I generally have had more success installing from source than
trying to work with pre-built.

 There are binaries everywhere. If you want a *simpler* language, perhaps
 try Miranda? Also a quite ancient language...
 
 Or, perhaps a newer one, in some aspects simpler than Haskell (but far
 from any simplicity): Clean.
 

To be clearer, I do not really want any language other than Haskell. I
just imagined that a simpler language might have a simpler and more
portable compiler.

 Perhaps it might help to know what do you need it for...
 

In brief, I have access to some large super computer systems. Sadly,
nobody in my academic or work circles seems to have the slightest
interest in applying functional languages to parallel computing problems
(C and Fortran seem to be the languages of choice.) So, I've been poking
around with some functional languages, trying to see what I could get
installed (without any admin assistance whatsoever) and how I might be
able to use them with the MPI or even GPGPU infrastructure we have. But
I keep running into problems, because the software infrastructure is
quite ancient (for compatibility purposes, I'm told), or there are other
mysterious configuration issues.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Looking for portable Haskell or Haskell like language

2013-04-26 Thread Christopher Howard
Hi. I've got this work situation where I've got to do all my work on
/ancient/ RHEL5 systems, with funky software configurations, and no root
privileges. I wanted to install GHC in my local account, but the gnu
libc version is so old (2.5!) that I can't even get the binary packages
to install.

I've had success installing some other simple functional languages (like
CLISP) on these same systems, so I was wondering if there was perhaps
another language very similar to Haskell (but presumably simpler) with a
super portable compiler easily built from source, which I could try.

I'll admit -- I haven't tried the HUGS compiler for Haskell. The quick
description didn't make it sound much more portable than GHC, but I
guess I could try it if I heard some good reasons to think it would be
more portable.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad fold

2013-04-16 Thread Christopher Howard
So, I'm doing something like this

foldl (=) someA list :: Monad m = m a

where
  list :: Monad m = [a - m a],
  someA :: Monad m = m a

Is there a more concise way to write this? I don't think foldM is what I
want -- or is it?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fwd: [Haskell-beginners] Monad instances and type synonyms

2013-04-13 Thread Christopher Howard

I asked this question in Haskell-beginners, but I haven't heard anything
yet, so I'm forwarding to Cafe.

 Original Message 
Subject: [Haskell-beginners] Monad instances and type synonyms
Date: Sat, 13 Apr 2013 17:03:57 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Reply-To: The Haskell-Beginners Mailing List - Discussion of primarily
beginner-level topics related to Haskell beginn...@haskell.org
To: Haskell Beginners beginn...@haskell.org

I am playing around with some trivial code (for learning purposes) I
wanted to take

code:

-- SaleVariables a concrete type defined early

-- `Adjustment' represents adjustment in a price calculation
-- Allows functions of type (a - Adjustment a) to be composed
-- with an appropriate composition function
type Adjustment a = SaleVariables - a


And put it into

code:

instance Monad Adjustment where

  (=) = ...
  return = ...


If I try this, I get

code:

Type synonym `Adjustment' should have 1 argument, but has been given none
In the instance declaration for `Monad Adjustment'


But if I give an argument, then it doesn't compile either (it becomes a
* kind). And I didn't want to make the type with a regular data
declaration either, because then I have to give it a constructor, which
doesn't fit with what I want the type to do.

-- 
frigidcode.com




___
Beginners mailing list
beginn...@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exp implementation

2013-04-11 Thread Christopher Howard
On 04/11/2013 06:37 AM, Brandon Allbery wrote:
 On Thu, Apr 11, 2013 at 1:38 AM, Christopher Howard
 christopher.how...@frigidcode.com
 mailto:christopher.how...@frigidcode.com wrote:
 
 Hi. For my own learning, I wanted to see how the exp function is
 implemented in GHC. I have GHC 7.4.1 source code open, but I'm having
 trouble figuring out which file the actual function definition is
 in. I see
 
  expFloat(F# x) = F# (expFloat# x)
 
 
 expFloat# is likely a primop; good luck Primops aka primitive
 operations are generally implemented in the compiler backend as assembly
 language or Cmm code. Untangling that part of ghc makes my head swim. .
 
 -- 
 brandon s allbery kf8nh   sine nomine associates
 allber...@gmail.com mailto:allber...@gmail.com
  ballb...@sinenomine.net mailto:ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net

I traced it down some more: I think it eventually goes into the
compiler/nativeGen section where it is translated into the platform's
native version of the function. On my platform, I think this is the expf
function from math.h. (See EXP(3)).

I find that to be interesting, because it means you could change the
output of your programs by altering your standard library. But I guess
there are a lot of things you could change by altering your standard
library!

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exp implementation

2013-04-11 Thread Christopher Howard
On 04/11/2013 07:12 AM, Christopher Howard wrote:
 On 04/11/2013 06:37 AM, Brandon Allbery wrote:
 
 I traced it down some more: I think it eventually goes into the
 compiler/nativeGen section where it is translated into the platform's
 native version of the function. On my platform, I think this is the expf
 function from math.h. (See EXP(3)).
 
 I find that to be interesting, because it means you could change the
 output of your programs by altering your standard library. But I guess
 there are a lot of things you could change by altering your standard
 library!
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

In glibc, it eventual comes down to this approximation, I think (from
./sysdeps/ieee754/flt-32/e_expf.c):

code:

  /* Compute ex2 = 2^n e^(t/512+delta[t]).  */
  ex2_u.d = __exp_atable[tval+177];
  ex2_u.ieee.exponent += (int) n;

  /* Approximate e^(dx+delta) - 1, using a second-degree polynomial,
 with maximum error in [-2^-10-2^-28,2^-10+2^-28]
 less than 5e-11.  */
  x22 = (0.500496709180453 * dx + 1.001192102037084) * dx +
delta;

/* ... snip ... */

  result = x22 * ex2_u.d + ex2_u.d;



-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] exp implementation

2013-04-10 Thread Christopher Howard
Hi. For my own learning, I wanted to see how the exp function is
implemented in GHC. I have GHC 7.4.1 source code open, but I'm having
trouble figuring out which file the actual function definition is in. I see

 expFloat(F# x) = F# (expFloat# x)

in libraries/base/GHC/Float.lhs.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] nice pattern from simple converging series

2013-03-28 Thread Christopher Howard
I made a nice little pattern from just a few lines of Haskell (mostly
code comments) using gloss. It is very kindergarten in terms of
mathematical art, but the idea was to illustrate that in a pretty short
amount of time, and a small amount code, you could easily translate
simple math concepts into geometry on your screen.

http://frigidcode.com/code/haskell-series-circles/

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] translating recursively defined sequence

2013-03-04 Thread Christopher Howard
Hi. My Haskell is (sadly) getting a bit rusty. I was wondering what
would be the most straightforward and easily followed procedure for
translating a recursively defined sequence into a Haskell function. For
example, this one from a homework assignment.

quote:

a_1 = 10
a_(k+1) = (1/5) * (a_k)**2


(The underscore is meant to represent subscripting what follows it.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] translating recursively defined sequence

2013-03-04 Thread Christopher Howard
On 03/04/2013 08:36 PM, Bob Ippolito wrote:
 I suppose it depends on your definition of straightforward but you can
 use the iterate function from Data.List to quickly define sequences like
 this.
 
 a = iterate (\x - (1/5) * (x**2)) 10
 
 
 On Mon, Mar 4, 2013 at 9:19 PM, Christopher Howard
 christopher.how...@frigidcode.com
 mailto:christopher.how...@frigidcode.com wrote:
 
 Hi. My Haskell is (sadly) getting a bit rusty. I was wondering what
 would be the most straightforward and easily followed procedure for
 translating a recursively defined sequence into a Haskell function. For
 example, this one from a homework assignment.
 
 quote:
 
 a_1 = 10
 a_(k+1) = (1/5) * (a_k)**2
 
 
 (The underscore is meant to represent subscripting what follows it.)
 
 --
 frigidcode.com http://frigidcode.com
 
 

Very cool! Thanks!

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] derivatives and integrals

2013-02-26 Thread Christopher Howard
Hi. The scope of this question is likely bigger that Haskell, but this
seems like the right crowd to ask. I'm in Calc II right now, and I'm
looking for a FOSS desktop application (I use Gnu/Linux) to replace the
functionality of my TI-98 in finding derivatives and integrals. (It's
very convenient for double checking my own solutions.) I've heard of
some software like Octave, but the manuals are usually very large, and
I'm not sure what is the best one to start with. I was wondering if
there is anyone on this list who uses free software to do that sort of
simpler Calc stuff, and what it is that they use.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Where is the convergence point between Category Theory and Haskell?

2013-01-13 Thread Christopher Howard
On 01/13/2013 03:15 AM, Alfredo Di Napoli wrote:
 Morning Cafe,
 
 I'm planning to do a series of write-ups about Category Theory, to
 publish them on the company's blog I'm currently employed.
 I'm not a CT expert, but since the best way to learn something is to
 explain it to others, I want to take a shot :)
 In my mind I will structure the posts following Awodey's book, but I'm
 wondering how can I make my posts a little more real world.
 I always read about the Hask category, which seems to be the
 bootstrap of the whole logic behind Haskell. Can you please give my
 materials/papers/links/blogs to the Hask category and briefly explain me
 how it relates to Category Theory and Haskell itself?
 
 I hope my question is clear enough, in case is not, I'll restate :P
 
 Cheers,
 A.
 
 

You want to give us the link to that blog?

If you can keep your explanations reasonably illustrative and easy to
understand, you'll get a regular reader out of me.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ln, e

2013-01-05 Thread Christopher Howard
Hi. Are natural log and Euler's constant defined somewhere in base, or a
convenience math module somewhere? I'm having trouble finding them with
hayoo or system documentation.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proving programs

2013-01-01 Thread Christopher Howard
I'm working through a video lecture describing how to prove programs
correct, by first translating the program into a control flow
representation and then using propositional logic. In the control flow
section, the speaker described how the program should be understood in
terms of an input vector (X, the inputs to the program), a program
vector (Y, the storage variables), and an output vector (Z, the outputs
of the program), with X mapping into Y, Y being affected by execution,
and X and Y mapping into Z.

However, only part way into the video, two practical questions come to mind:

1. Does this approach need to be adjusted for a functional language, in
which computation is (at least idealistically) distinct from control flow?

2. How do we approach this for programs that have an input loop (or
recursion)? E.g., I have an application that reads one line for stdin,
modifies said line, outputs to stdout, and repeats this process until
EOF? Should I be thinking of every iteration as a separate program?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monoid pair of monoids?

2012-12-21 Thread Christopher Howard
On 12/20/2012 08:54 PM, Daniel Feltey wrote:
 You were only missing the restriction that both types a and b must be
 instances of Monoid in order to make Socket a b into an instance of Monoid.
 
 
 
 Dan Feltey

Thank you for your help. An additional question, if I might: For the
sake of elegance and simplicity, I modified the class and instances to
avoid the tuple aspect:

code:

data Socket2 a b = Socket2 a b
  deriving (Show)

instance (Monoid a, Monoid b) = Monoid (Socket2 a b) where
mempty = Socket2 mempty mempty
Socket2 a b `mappend` Socket2 w x = Socket2 (a `mappend` w) (b
`mappend` x)


Of course, I thought it would be likely I would want other classes and
instances with additional numbers of types:

code:

data Socket3 a b c = Socket3 a b c
  deriving (Show)

instance (Monoid a, Monoid b, Monoid c) = Monoid (Socket3 a b c) where
mempty = Socket3 mempty mempty mempty
Socket3 a b c `mappend` Socket3 w x y =
Socket3 (a `mappend` w) (b `mappend` x) (c `mappend` y)

data Socket4 a b c d = Socket4 a b c d
  deriving (Show)

instance (Monoid a, Monoid b, Monoid c, Monoid d) = Monoid (Socket4 a b
c d) where
mempty = Socket4 mempty mempty mempty mempty
Socket4 a b c d `mappend` Socket4 w x y z =
Socket4 (a `mappend` w) (b `mappend` x) (c `mappend` y) (d
`mappend` z)

data Socket 5 a b c d e... et cetera


Seeing as the pattern here is so rigid and obvious, I was wondering: is
it possible to abstract this even more? So I could, for instance, just
specify that I want a Socket with 8 types, and poof, it would be there?
Or is this as meta as we get? (I.e., without going to something like
Template Haskell.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Layer on a layer of record syntax in the type synonym?

2012-12-21 Thread Christopher Howard
Using a simple type I gave earlier from my monadic type question...

code:

data Socket3 a b c = Socket3 a b c
  deriving (Show)


Is it possible somehow to layer on record syntax onto a synonym of the type?

The idea would be something like this...

code:

type SpaceShip =
  Socket3 { engine :: Last Engine
  , hull :: Last Hull
  , guns :: [Guns]
  }


...purely for the convenience. But this doesn't seem to work with type
as it assumes you are referring to already made constructors, and
evidently newtype only allows use of a single record. I could wrap it
in a normal data declaration but that would add an extra layer of
complexity I think.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Layer on a layer of record syntax in the type synonym?

2012-12-21 Thread Christopher Howard
On 12/21/2012 04:52 AM, Daniel Trstenjak wrote:
 
 Why having a Socket3 in the first place, what's the point of it?
 

The idea was to have some generic structures (Sockets) which were
already instanced into the Monoids-within-Monoids abstraction, yet could
still be made concrete into anything more specific.

So, I have...

code:

data Socket3 a b c = Socket3 a b c
  deriving (Show)

instance (Monoid a, Monoid b, Monoid c) = Monoid (Socket3 a b c) where
mempty = Socket3 mempty mempty mempty
Socket3 a b c `mappend` Socket3 w x y =
Socket3 (a  w) (b  x) (c  y)

nullSocket3 :: (Monoid a, Monoid b, Monoid c) = Socket3 a b c
nullSocket3 = Socket3 mempty mempty mempty


...which allows me to have...

code:

type ShipSys = Socket3 (Last Engine) (Last RotThruster) [LinThruster]

nullShipSys :: ShipSys
nullShipSys = nullSocket3

setEngineSocket (Socket3 a b c) x = Socket3 x b c

engineSys :: Engine - ShipSys
engineSys a = setEngineSocket nullShipSys (Last (Just a))

mk1Engine = engineSys (Engine 100 1 Mark I)

-- etc.


And so, with each individual component being wrapped as a generic
ShipSys (ship system), I can make a complete system simply by composition:

code:

h :t mk1Engine
mk1Engine :: ShipSys
h :t stdRearThruster
stdRearThruster :: ShipSys
h :t stdFrontThruster
stdFrontThruster :: ShipSys
h :t stdRotThruster
stdRotThruster :: Power - ShipSys
h mk1Engine  stdRearThruster  stdFrontThruster  stdRotThruster 10
Socket3 (Last {getLast = Just (Engine 100.0 1.0 Mark I)}) (Last
{getLast = Just (RotThruster 10.0)}) [LinThruster 3.1415927
1.0,LinThruster 0.0 0.5]


This seems to work well enough so far. But the issue I was concerned
about is: if I can't layer record syntax onto the type synonym, then I
have to rewrite a whole bunch of getters / setters each time I want to
add an attribute (e.g., requiring a switch from a Socket3 to a Socket4.)
If this is the case, then perhaps it would be better just to define the
ShipSys type directly, and directly instance it into the monoid abstraction.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Categories (cont.)

2012-12-20 Thread Christopher Howard
I've perhaps been trying everyones patiences with my noobish CT
questions, but if you'll bear with me a little longer: I happened to
notice that there is in fact a Category class in Haskell base, in
Control.Category:

quote:

class Category cat where

A class for categories. id and (.) must form a monoid.

Methods

id :: cat a a

the identity morphism

(.) :: cat b c - cat a b - cat a c

morphism composition


However, the documentation lists only two instances of Category,
functions (-) and Kleisli Monad. For instruction purposes, could
someone show me an example or two of how to make instances of this
class, perhaps for a few of the common types? My initial thoughts were
something like so:

code:

instance Category Integer where

  id = 1

  (.) = (*)

-- and

instance Category [a] where

  id = []
  (.) = (++)
---

But these lead to kind mis-matches.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Categories (cont.)

2012-12-20 Thread Christopher Howard
On 12/20/2012 03:59 AM, wren ng thornton wrote:
 On 12/20/12 6:42 AM, Christopher Howard wrote:
 
 As mentioned in my other email (just posted) the kind mismatch is
 because categories are actually monoid-oids[1] not monoids. That is:
 
 class Monoid (a :: *) where
 mempty  :: a
 mappend :: a - a - a
 
 class Category (a :: * - * - *) where
 id  :: a i j
 (.) :: a j k - a i j - a i k
 
 Theoretically speaking, every monoid can be considered as a category
 with only one object. Since there's only one object/index, the types for
 id and (.) basically degenerate into the types for mempty and mappend.
 Notably, from this perspective, each of the elements of the carrier set
 of the monoid becomes a morphism in the category--- which some people
 find odd at first.
 
 In order to fake this theory in Haskell we can do:
 
 newtype MonoidCategory a i j = MC a
 
 instance Monoid a = Category (MonoidCategory a) where
 id  = MC mempty
 MC f . MC g = MC (f `mappend` g)
 
 This is a fake because technically (MonoidCategory A X Y) is a different
 type than (MonoidCategory A P Q), but since the indices are phantom
 types, we (the programmers) know they're isomorphic. From the category
 theory side of things, we have K*K many copies of the monoid where K is
 the cardinality of the kind *. We can capture this isomorphism if we
 like:
 
 castMC :: MonoidCategory a i j - MonoidCategory a k l
 castMC (MC a) = MC a
 
 but Haskell won't automatically insert this coercion for us; we gotta do
 it manually. In more recent versions of GHC we can use data kinds in
 order to declare a kind like:
 
 MonoidCategory :: * - () - () - *
 
 which would then ensure that we can only talk about (MonoidCategory a ()
 ()). Unfortunately, this would mean we can't use the Control.Category
 type class, since this kind is more restrictive than (* - * - * - *).
 But perhaps in the future that can be fixed by using kind polymorphism...
 
 
 [1] The -oid part just means the indexing. We don't use the term
 monoidoid because it's horrific, but we do use a bunch of similar
 terms like semigroupoid, groupoid, etc.
 

Finally... I actually made some measurable progress, using these
phantom types you mentioned:

code:

import Control.Category

newtype Product i j = Product Integer

  deriving (Show)

instance Category Product where

  id = Product 1

  Product a . Product b = Product (a * b)


I can do composition, illustrate identity, and illustrate associativity:

code:

h Product 5  Product 2
Product 10

h Control.Category.id (Product 3)
Product 3

h Control.Category.id  Product 3
Product 3
h Product 3  Control.Category.id
Product 3

h (Product 2  Product 3)  Product 5
Product 30
h Product 2  (Product 3  Product 5)
Product 30


-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] monoid pair of monoids?

2012-12-20 Thread Christopher Howard
In my current pondering of the compose-able objects them, I was thinking
it would be useful to have the follow abstractions: Monoids, which were
themselves tuples of Monoids. The idea was something like so:

code:

import Data.Monoid

instance Monoid (Socket2 a b) where

  mempty = Socket2 (mempty, mempty)

  Socket2 (a, b) `mappend` Socket2 (w, x) = Socket2 (a `mappend` w, b
`mappend` x)

data Socket2 a b = Socket2 (a, b)


However, this does not compile because of errors like so:

code:

Sockets.hs:9:21:
No instance for (Monoid a)
  arising from a use of `mempty'
In the expression: mempty
In the first argument of `Socket2', namely `(mempty, mempty)'
In the expression: Socket2 (mempty, mempty)


This makes sense, but I haven't figured out a way to rewrite this to
make it work. One approach I tried was to encode Monoid constraints into
the data declaration (which I heard was a bad idea) but this didn't
work, even using forall. Also I tried to encode it into the instance
declaration, but the compiler kept complaining about errant or illegal
syntax.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Christopher Howard
On 12/17/2012 06:30 PM, Richard O'Keefe wrote:
 
 On 18/12/2012, at 3:45 PM, Christopher Howard wrote:
 
 It's basically the very old idea that an Abstract Data Type
 should be a nice algebra: things that look as though they
 ought to fit together should just work, and rearrangements
 of things ought not to change the semantics in surprising
 ways (i.e., Don't Be SQL).
 
 
 
 Categories contain two things:
 objects
 and arrows that connect objects.  Some important things about arrows:
  - for any object x there must be an identity idx : x - x
  - any two compatible arrows must compose in one and only one way:
f : x - y  g : y - z  =  g . f : x - z
  - composition must be associative (f . g) . h = f . (g . h)
when the arrows fit together.
 
 Of course for any category there is a dual category,
 so what I'm about to say doesn't really make sense,
 but there's sense in it somewhere:  the things you are
 trying to hook together with your . operator seem to me more
 like objects than arrows, and it does not seem as if
 they hook together in one and only one way, so it's not so
 much _associativity_ being broken, as the idea of . being
 a composition in the first place.
 
 

Since I received the two responses to my question, I've been trying to
think deeply about this subject, and go back and understand the core
ideas. I think the problem is that I really don't have a clear
understanding of the basics of category theory, and even less clear idea
of the connection to Haskell programming. I have been reading every link
I can find, but I'm still finding the ideas of objects and especially
morphisms to be quite vague.

The original link I gave
http://www.haskellforall.com/2012_08_01_archive.html purposely skipped
over any discussion of objects, morphisms, domains, and codomains. The
author stated, in his first example, that Haskell functions are a
category, and proceeded to describe function composition. But here I am
confused: If functions are a category, this would seem to imply (by
the phrasing) that functions are the objects of the category. However,
since we compose functions, and only morphisms are composed, it would
follow that functions are actually morphisms. So, in the function
category, are functions objects or morphisms? If they are morphisms,
then what are the objects of the category?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] efficient data structure: column with repeating values

2012-12-18 Thread Christopher Howard
Is there some good data type out there that basically provides a simple
table, but with optimization for repeating values on one column?
Something like:

Data Table a b

...where it assumes that 'a' values will usually be unique, while 'b'
values will usually be repeated from a small set? (But not needing to be
fixed beforehand.)

Like in...

client | patron
---
Bob| Tom
Sarah  | Tom
Dick   | Tom
George | Harry
Moe| Harry

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Christopher Howard
On 12/18/2012 08:02 PM, Gershom Bazerman wrote:
 On 12/17/12 9:45 PM, Christopher Howard wrote:
 
 I don't think you're describing a Category in the sense of the Haskell
 Category typeclass. But that's ok! Just because some things are
 categories and are nice doesn't mean that we can't have other nice
 things that aren't necessarily categories. My first thought was
 something with multiple inputs and one output is often an Operad
 (http://en.wikipedia.org/wiki/Operad_theory) but associativity is still
 an issue. Also bear in mind that operads and categories are both
 *directional* whereas your notion of coupling doesn't seem to be (which
 has something to do with associativity failing, I'd imagine).

I think the example I gave was pretty messed up anyway, because I was
trying to compose objects rather than morphisms. But that directional
aspect you mentioned does seem significant... so I guess my main
question is how that things that are more complex (like a
multi-directional system built from pluggable components) could be
represented in the Categorical manner. I'm looking for the Grand
Unifying Theory to follow, if you will; I really like the idea that all
parts of my program could be cleanly and systematically composed from
smaller pieces, in some beautiful design patter. Many of the problems in
my practical programming, however, are not like the examples I have seen
(nice pipes or unidirectional calculations) but rather complex fitting
together of components. E.g., space ships are made up of guns + engines
+ shields + ammo. Different kinds of space ships may use the same kind
of guns (reusable components) but some wont. Some will have many guns,
some will have none. And such like issues.

Soylemez seems to have answered this issue directly in his reply.
Unfortunately, I didn't understand most of what he wrote. :|

 
 I also don't understand, e.g., what happens if I couple a thing with two
 connectors and one connector -- which connector from the first gets
 used, or are they interchangeable?
 

The example I gave was hastily put together and not well thought out. I
was Just trying to come up with something that would convey the general
idea. But perhaps each component would have a list of connectors, and
the first ones in the list would be used first. When a new component was
created from other components, the new list would be taken from the
leftover connectors (if any). In real world use I would probably have
multiple types of connectors, but I haven't thought that far ahead.

 Going back even further, you've suggested a Fail to represent when the
 connectors don't match. Why not start with encoding connectors in types
 to begin with, so that it is a type error to not have matching
 connectors? Follow the logic of your idea, shape your types to match
 your representable states, and then see what algebraic structures
 naturally emerge.
 
 Cheers,
 Gershom
 

Sounds good. Of course, I still haven't figured out what design pattern
to fit said types into. :(


-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskell-like scripting language

2012-12-17 Thread Christopher Howard
I gave Shelly a try. Pretty cool - using it for some of the scripts on
my system. Has me wondering though: is anyone working on creating a
actual Haskell-like scripting language and engine?

Shelly is cool, as I said, but I imagine it would be more valuable to
have another language that is actually separate from Haskell, with an
interpreter that is more lightweight and changes much less frequently
(than GHC). Something that could be nearly as portable as Bash or Perl.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] category design approach for inconvenient concepts

2012-12-17 Thread Christopher Howard
Recently I read this article I happened across, about the categorical
design pattern:

http://www.haskellforall.com/2012/08/the-category-design-pattern.html

Barely understood it, of course, but it was a rather intriguing concept.
So now I'm looking at all my programming problems trying to make types
that can be composed and that seem to fit the idea of a category.

However, what I'm wondering about is ideas that can be composed but
that don't seem to fit the idea of category, because they don't obey
the associativity law. To give a specific example (pseudo code like,
without any idea here of implementation or proper syntax):

Say you created a type called Component (C for short), the idea being
to compose Components out of other Components. Every C has zero or more
connectors on it. Two Cs can be connected to form a new C using some
kind of composition operator (say, .), provided there are enough
connectors (one on each). Presumably you would need a Fail constructor
of some kind to represent the situation when there is not enough connectors.

Say you had a C (coupler) with two connectors, a C (thing) with one
connector, and a C (gadget) with one connector.

So you could have...

(coupler . thing) . gadget

Because the coupler and the thing would combine to create a component
with one spare connector. This would then combine with the gadget to
make the final component. However, if you did...

coupler . (thing . gadget)

Then thing and gadget combine to make a component with no spare
connectors. And so the new component and the coupler then fail to
combine. Associativity law broken.

So, can I adjust my idea to fit the category concept? Or is it just
not applicable here? Or am I just misunderstanding the whole concept?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] edge: compile testing

2012-12-14 Thread Christopher Howard
Hey guys, to teach myself Haskell I wrote a little arcade game called
The Edge, built on gloss. It is in hackage under the package name
edge. Are there a few kind souls who would be willing to compile it on
their machines and let me know if there are any problems at the
compiling level? In the past, I've had issues with Haskell code
compiling fine on my development system but not on others (due to
dependency-related issues). I want to double check this before I try to
make any distro-specific packages.

I developed with GHC 7.4 and cabal-install 1.16.0.2 on a Gentoo system.
Requires OpenGL and OpenAL (for sound).

cabal update  cabal install edge

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] edge: compile testing

2012-12-14 Thread Christopher Howard
On 12/14/2012 07:05 PM, Clark Gaebel wrote:
 Unacceptable argument type in foreign declaration

Thanks for giving it a try. Could you send off a bug report to the
OpenAL Haskell module maintainer? sven.pa...@aedion.de

(I might offer to do it, but I tried to e-mail him once about a
different issue and never heard back. Probably didn't make it through
his spam filter.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] containers license issue

2012-12-13 Thread Christopher Howard
On 12/13/2012 08:34 AM, Clint Adams wrote:
 On Wed, Dec 12, 2012 at 11:11:28PM -0800, Chris Smith wrote:
 
 That's true.  However, haskell.org's fiscal sponsor receives pro bono
 legal services.
 
 
 I may have been conflating threads, though the response to what I assume
 was just a lawyer asking a question seems excessive too.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

Just thought I'd mention: It is possible for anyone involved in a FOSS
project to get pro bono legal advice from the SFLC, from actual lawyers
who are highly familiar with the legal aspects of FOSS licenses:

https://www.softwarefreedom.org

quote:

If you are involved in a Free, Libre and Open Source Software (FLOSS)
project in need of legal advice, please email h...@softwarefreedom.org.
When seeking legal advice, please use only this address to contact us
(unless you are already a client).


I'm not sure if they are willing to help those who are trying to /avoid/
making a free software product, but they would likely be willing to
answer any generic questions about applicability of the GPLs, derived
works, etc.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] containers license issue

2012-12-13 Thread Christopher Howard
On 12/13/2012 05:54 PM, Richard O'Keefe wrote:
 
 On 14/12/2012, at 7:45 AM, Christopher Howard wrote:
 
 Intimately familiar with New Zealand law, are they?
 

I couldn't say anything about that, specifically. However, SFLC has an
international outreach. From 2011 SFLC news:

quote:

We are proud to announce a new position at the Software Freedom Law
Center: Director of International Programs. Over the past few years SFLC
has become an increasingly International organization, working with the
European Commission, launching SFLC India, and consulting with
governments around the world on issues of free software licensing,
policy, and use. Mishi Choudhary, counsel at SFLC and head of SFLC
India, has always been at the heart of this work so it is only fitting
that she is stepping up to fill the new position. Congratulations to Ms.
Choudhary and we all look forward to a stronger international presence
ahead.
-

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] education or experience?

2012-12-08 Thread Christopher Howard
I'm at something of a crossroads, and I'm hoping to get a bit of free
career advice. I really enjoy programming with Haskell (and a few other
exotic languages), and was hoping I could eventually make a living in
that sort of field. Not rich and famous, necessarily, just enough to get
by comfortably. I'm trying to decide, however; should I go back to
school, finish my B.S. and pursue a Masters in CompSci? Or would the
time (and money) be better spent aggressively pursuing volunteer work
for companies, hoping to eventually get the experience and contacts that
lead to a paying job?

To be honest, I don't really want to go back to school, because I learn
a lot faster (and more economically) on my own. However, I'm not sure
which path is the fastest, and safest, approach to an actual paycheck.

(Also, I'm something of a die-hard FOSS purist, if that affects the
discussion at all.)

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] sequential logic

2012-12-05 Thread Christopher Howard
Hi. I was wondering what the various (and especially most simple)
approaches one could take for working with (simulating or calculating)
sequential logic in Haskell. By sequential logic, I mean like wikipedia
describes, where a system is made up of logic gates, whose output is
dependent not only on the logic operation of the gate, but on the
previous state of the gate. (Like in electronics where the system can be
driven by a clock signal or have memory.)

Does one have to get into FRP for that sort of thing? Or use some kind
of FSM framework? Or is there some kind of fancy state monad suitable
for that? Or...?

I'm no electronic or digital engineer, but for learning purposes I've
been trying to see if I could build an (extremely simple) virtual
processor or calculator in Haskell, using only the Bool type and a few
of the boolean operators (and functions composed of the aforementioned),
reproducing things like half adders and full adders as functions in the
program. Of course, I quickly ran into the stateful aspect of the
problem, in subjects like clock signal and flip flops.

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe