Re: Who is afraid of arrows, was Re: [Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-12 Thread Gene A
 (m x)
has the
functions g and then h applied to the elements of the monad 'm'  inside of
the
functor f and then have that structure returned as:  f (m ((gf) x)).

Okay, I am totally done with that.. probably just muddied things up, but
maybe
make sense if you try using ghci after loading a dummy module that imports
Control.Monad, Control.Arrow and Control.Applicative.  I just think that one
is
missing out when not using ALL the computational tools.

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


Re: [Haskell-cafe] Re: Re-order type

2010-10-10 Thread Gene A
2010/10/9 André Batista Martins andre...@netcabo.pt Said:


 Might have not been clear, but i will try illustrate .

 f:: a- b - c - (b,(c,a))
 f1 ::  c - a - d

-



 I think I would attack this with glue consisting of:

comb f f1 a b c =  arr (\(a,b,c) - f a b c)  arr (\(b,(c,a))) -f1 c a)
$ (a,b,c)

and yes, have to agree that easier to roll your own if only a few functions
are like this..
but should be able to parse the type signatures of the functions involved
and write a program to automate this process.. using this format as a
template..

Actually if you just set it to take all the variables prior to last (-) in
sig you can put them
put them together in an uncurried format.. for instance the a - b - c
portion would become always \(a,b,c) - then the function so arr (\(a,b,c)
- f a b c) then the term (output) would be the last term in this case
(b,(c,a)  add that with a - between to give that to first part of another
lambda construction (\(c,a) - f1 c a) ... arrowizing the whole thing with
arr (first lambda)  arr (second lambda) $ and a tuple from all but the
last variables in all cases of first function ... so for f it would be
(a,b,c).  if for some odd reason it was a single it would just become ((a))
an added parenthesis, which would not hurt a thing for the case where it was
a sig like f :: a - b

So for your case it becomes as shown above:
comb f f1 a b c =  arr (\(a,b,c) - f a b c)  arr (\(b,(c,a))) -f1 c a)
$ (a,b,c)
and say for:

f :: a - (b,c)
f1:: b - d

(\(a) - f a)  (\(b,c) - f1 b) $ (a)   - it just harmlessly adds the '(
' and ')' around the 'a' even though it doesn't need it as the only
parameter prior to the last '-'.

This is probably clear as mud, on first look, but I think a way forward in
automating from
this is possible.. I am sure of it.. but it would be at the source code
level and a string parse and output from that ..

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


Re: [Haskell-cafe] Rewriting a famous library and using the same name: pros and cons

2010-06-08 Thread Gene A
On Tue, Jun 8, 2010 at 8:08 AM, Don Stewart d...@galois.com wrote:


 (... There have been a few cases of major API  / rewrites to famous old
 packages causing problems, including:

* QuickCheck 1 vs 2
* parsec 2 vs 3
* OpenGL
 ...)



 (...  * No additional breakages are introduced. ...)


Oh lord yes...  just call it fgl3  and leave the fgl package alone.
This is a source based community here... so you take a package that
has a dependency on another library and you go out and get that to cover the
dependency and the API is not the same!!!  AND especially if that might be
the
only thing you will ever use that lib for ... and you have to stop and
rewrite the
original.. and as someone else said with maybe documentation of that API
that
is not maybe finished or...  NO ... At that point the person will probably
just
DISCARD the compile on the lib or program that had the dependency.. rather
then put the effort in to learn an entire API that doesn't match up..
BAD IDEA!!

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


[Haskell-cafe] Shorthand method of enumerating a list a gotcha ... or is it just me?

2010-05-07 Thread Gene A
The problem I see is that in both:
 Version: September 2006 of hugs, which is the one that is current for
Ubuntu 9.10 release, and
ghci 6.10.4, they both exhibit a {I think} strange behaviour, in regards
to the shorthand way of calling out a list of enumerable values.  I will
explain the problem that I have run into with examples:

Hugs [3,7..22]
[3,7,11,15,19] - OK

Hugs map (* 1.0) [3,7,11,15,19]  - manual spec OK
[3.0,7.0,11.0,15.0,19.0]

Hugs map (* 1.0) [3,7..22]   - same spec as first but !!! when
mapped to with a (*1.0) to
coerce
them to reals:
[3.0,7.0,11.0,15.0,19.0,23.0]   - went one outside of range spec.


Exactly the same behaviour from ghci 6.10.4 :

Prelude [3,7..22]
[3,7,11,15,19]

Prelude map (* 1.0) [3,7..22]  - using a range
[3.0,7.0,11.0,15.0,19.0,23.0] - it screws up
 {at least it is not a
feature' to me}

Prelude map (* 1.0) [3,7,11,15,19]   - spelled out it acts right.
[3.0,7.0,11.0,15.0,19.0]

This seems like a possible bug? or at least a sure fire trap waiting to
be sprung ... one of those nasties that could really create havoc if
someone is not aware of this behaviour and buries a function that include
something that unwittingly coerces from an Integral to a Realfrac or
Fractional.  Is this a well known thing to watch out for..
or is it something that can be worked around, other then having to
enumerate every value in a list rather then use the handiness of
the range notation as shorthand?

cheers,

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


[Haskell-cafe] Re: Looking for pointfree version (Kim-Ee Yeoh) (02/12)

2009-02-19 Thread Gene Arthur
Kim-Ee Yeoh said:
On the same note, does anyone have ideas 
for the following snippet? Tried the pointfree 
package but the output was useless. 

pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)

First sorry for the delay in getting to this.. been behind on
projects so had some days of mail piled up.  Here is what 
I came up with, using one arrow operator,
so you would have to import: Control.Arrow ((***)) at minimum 
to use this solution:

pointfree :: 
forall t t1 c. (t - t1 - c) - (t, t1) - (t, t1) - (c, c)

pointfree op  = 
  curry $ (\(a,b) - a `op` b)  *** (\(a,b) - a `op` b)

examples of use, that were executed using:

ghci -fglasgow-exts -farrows Control.Arrow

*pointfree (*) (3,5) (12,12)
(15,144)

* pointfree (++) (This ,That) (Old, Man)
(This That,Old Man)

Hope that helps.
 
-- gene
==
website:  http://haskblog.cloud.prohosting.com
==
If Helen Keller is alone in a forest and falls,
does she make a sound?


Receive Notifications of Incoming Messages
Easily monitor multiple email accounts  access them with a click.
Visit http://www.inbox.com/notifier and check it out!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing Mathematica

2007-06-12 Thread Gene A

On 6/2/07, [EMAIL PROTECTED] 
[EMAIL PROTECTED] wrote:

(... and showing an example of a simple-minded simplifier

and symbolic differentiator. The unification was presented as a powerful
pattern-matcher, being able to instanciate logic variables, and test the
coherence within patterns sharing the same elements (which is not possible
in Haskell, and *much* less efficient than the Haskell pattern-matcher,
for formal reasons). It *WORKED*. ...)
(... A good deal of Prolog non-determinism can be efficiently and nicely
simulated in Haskell using the list Monad.



You have brought up prolog, unification, etc .. and knowing this is the
Haskell board, just wondering what anyones thoughts on the hybrid haskell
based language CURRY, for these kind of problems.  It seems that it's
development is stalled... and sorry ahead of time if I am wrong on that
point.  Just seems that if it were firing on all cylinders and had
implemented all of the type magic of the Haskell implementations ..it it
wouldn't be great for doing symbolic manipulations.. any comments on that??
or has anyone out there ever taken a look at Curry in any comprehensive
way.  Just seems really interesting and I have fired it up just enough to
see that it works, but I was only doing things with it to test and they were
ALL things that I brought over from Haskell...
 Sorry if this is sorta off topic, but...
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Gene A

On 2/21/07, Henning Thielemann [EMAIL PROTECTED] wrote:



On Tue, 20 Feb 2007 [EMAIL PROTECTED] wrote:

 Paul Moore wrote:
  I'm after a function, sort of equivalent to map, but rather than
  mapping a function over a list of arguments, I want to map a list of
  functions over the same argument.



Well this is not very sexy, no monads or anything, but I kinda believe in
Keep It Simple:

Prelude let revApply a f = f a
Prelude let rMap a fs = map (revApply a) fs
Prelude rMap 2 [(*4),(^2),(+12),(**0.5)]
[8.0,4.0,14.0,1.4142135623730951]

oh and I REALLY enjoyed the discussions that this spawned about things
monadic, as there was some really slick stuff in there... The little thing
about 'join' and etcetera... really good stuff.
cheers...
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Gene A

On 2/21/07, Jules Bean [EMAIL PROTECTED] wrote:


Gene A wrote:

 Prelude let revApply a f = f a
 Prelude let rMap a fs = map (revApply a) fs
 Prelude rMap 2 [(*4),(^2),(+12),(**0.5)]
 [8.0,4.0,14.0,1.4142135623730951]


Note that revApply here is precisely flip ($).

And ($a) is the same as flip ($) a.

So this reduces to one of the earlier examples rather quickly.

It is possible to argue 'it's nice to give revApply a name'. It's also
possible to argue 'taking a section of $ is even better than naming
revApply'.


-
jules,
.. right on... ran this through ghci...

let rMap a fs = map ($ a) fs
{ that is clean ... gotta admit.. }
Prelude rMap 2 [(*4),(^2),(+12),(**0.5)]
[8.0,4.0,14.0,1.4142135623730951]
Prelude :t rMap
rMap :: forall a b. a - [a - b] - [b]

About naming the secondary revApply function would agree and that would have
been in a where clause inside the definition of rMap had that been saved
to a file, but ghci doesn't really lend itself to multiline definitions so
that is why that was there, and it was also named in this case to show what
was going on... The functions as I originally defined them are probably
easier for someone new to Haskell to understand what was going on than the
rather stark ($ a) in the final factoring of the function... Though the
final resulting function is far the cleaner for that notation!

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


Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-20 Thread Gene A

On 2/10/07, Peter Berry [EMAIL PROTECTED] wrote:


Sigh, I seem to have done a reply to sender. Reposting to the list.

On 06/02/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 Hello,

 I would like to create a Haskell function that generates a truth table,
for
 all Boolean values, say, using the following and function :

 and :: Bool - Bool - Bool
 and a b = a  b





This is solution that I used with list comprehension.. combining some of the
other ideas on the thread such as a tuple to see the original values and
then the result.

Prelude putStrLn $ concatMap (flip (++)\n) $ map show $ [(x,y,() x y)
|x - [True,False],y - [True,False]]
(True,True,True)
(True,False,False)
(False,True,False)
(False,False,False)

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


Re: [Haskell-cafe] How to solve this problem?It's quite easy in PHP.

2007-02-15 Thread Gene A

On 2/13/07, keepbal [EMAIL PROTECTED] wrote:

For example,

(...

$arr['a']='1';
$arr['b']='2';
$arr['c']='3';

...) result:


a = 1
b = 2
c = 3

-
Haskell solution:
build the array of all lower case with corresponding numbers starting with 1

Prelude let lowerCaseTable = zip ['a'..'z'] [1..26]

A couple of functions:
Prelude let box a = a:[]
Prelude let formatTableItems (a,b) = (box a) ++  =  ++ (show b) ++ \n

Then to output the results:
putStrLn $ foldr (++) \n$ map formatTableItems lowerCaseTable
a = 1
b = 2
c = 3
d = 4
e = 5
f = 6
g = 7
h = 8
i = 9
j = 10
k = 11
l = 12
m = 13
n = 14
o = 15
p = 16
q = 17
r = 18
s = 19
t = 20
u = 21
v = 22
w = 23
x = 24
y = 25
z = 26

I think that is pretty simple...

Good cheer to all from the desert,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to solve this problem?It's quite easy in PHP.

2007-02-15 Thread Gene A

On 2/15/07, Gene A [EMAIL PROTECTED] wrote:


Haskell solution:
build the array of all lower case with corresponding numbers starting with 1

Prelude let lowerCaseTable = zip ['a'..'z'] [1..26]

A couple of functions:
Prelude let box a = a:[]
Prelude let formatTableItems (a,b) = (box a) ++  =  ++ (show b) ++ \n

Then to output the results:
 putStrLn $ foldr (++) \n$ map formatTableItems lowerCaseTable
a = 1
b = 2


That last output function group could have been simpler.. I sometimes
forget concatMap.. as I did there it should have been:

Prelude putStrLn $ concatMap formatTableItems lowerCaseTable
a = 1
b = 2
c = 3
etc
even simpler than the first.. where I used map and then foldr

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


Re: [Haskell-cafe] Writing Haskell For Dummies Or At Least For People Who Feel Like Dummies When They See The Word 'Monad'

2006-12-12 Thread Gene A

On 12/11/06, Andrew Wagner [EMAIL PROTECTED] wrote:

 I think there are some great ideas here, and it would be a fantastic
 project to do as a community, via a wikibook.
..
On 12/11/06, Kirsten Chevalier [EMAIL PROTECTED] wrote:

there's not really a way to get a publisher to publish something that's
already released under a free documentation license --
but correct me if I'm wrong.)


I have on my shelf, copies of SICP, Thinking Forth, The Icon
Programming Language, and Programming with Unicon, just to name the
ones that I can think of and all of them are available on line.  I
like someone at the beginning of the thread, said I just like the
feel of paper...no ink.  I read what I have to in online docs, but I
do like to have to sit back with a book.  There is, I believe a book
publishing entity on the net that will publish, on demand, so to
speak, any book submitted to them.  I can't for the life of me
remember the name of that resource, but it makes the idea of turning a
wikibook into a hard copy feasible... no matter what the topic.  I
would surmise that due to the somewhat limited audience of even the
already TOP Haskell books, such as Craft and Hudak's book {title
has slipped my mind}, that most high volume publishers would have
never picked even those up.  Getting rich by publishing any book on
Haskell is probably not a good motivation for writing it. But I do
believe that people like myself are out there, and ready to buy a good
book, especially about an at time dense subject, in hard copy.  I for
one just like to get away from the whine of the box fan, that is the
cooling device right now on my computing machine, sitting 22 from my
ear canal, and read a good book that is potentially this useful.

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


Re: [Haskell-cafe] How to get subset of a list?

2006-12-07 Thread Gene A

On 11/30/06, Huazhi (Hank) Gong [EMAIL PROTECTED] wrote:


Thanks, it make sense here.
However, like I want to choose s[1,3,6,10] or something like this. Are there
some straightforward function or operator for doing this job? The !!
operator in haskell seems does not support multiple indecies.


hI,
 Hadn't checked my mail in a few days but here goes:

helper function:

index' :: forall a. [a] - Int - [a]
index' xs i = take 1 $ drop (i-1) xs

The real deal:

index :: forall a. [a] - [Int] - [[a]]
index cs xs = map (index' cs) xs

simple example of use:

Prelude index ABCDEFGHIJKLMNOPQRSTUVWXYZ [2,5..26]
[B,E,H,K,N,Q,T,W,Z]

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


Re: Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-29 Thread Gene A

Nicolas Frisby said:
{}
The fact of the matter is it's a rare case when a programmer's lack of
mathematical background threatens lives. If my GUI crashes, I'm angry
but not injured. Programmers make a living without the math background
because the vast majority of employers don't seek it--their products
simply don't need it.

Note that I said rare case; I think there are plenty of safety
critical programs out there. Consider the shuttle, deep-sea equipment,
military or medical equipment, etc. Now if the programmer you're
worried about is on one of these projects, I most certainly share your
unease.
{...}

All those angry office workers with those crashing GUI's cost hundreds
of millions of dollars every year... arguably some billions perhaps..
And besides deep space probes and aircraft, there are many machines
out in industrial plants that have some pretty dangerous processes and
such running on computer instructions... right to a dryer that maybe
doesn't shut off the heating element when it should due to a glitch in
a program... and burns up.
 Now as to the need for EVERY programmer to know discreet mathematics
and know how to run a proof through a theorem prover, and understand
fully all the nuances of lambda calculus, and pi calculus, and all
those other calculuses and such.. well, I guess that is why I am happy
to be using tools like Haskell, or the ML family of languages, because
at least the tool is built by folks the like of  Wadler, Peyton
Jones, and many other out and out academics and highly skilled and
brilliant mathematicians.  That means that I benefit from the type
checking {and inference} that make my programs more likely to be
correct on the first go.  I have found that to be the case so far.
  I was able to build an equation solver in three variable and
basically unlimited number of terms in about 6 hours, that would have
taken probably weeks to complete in any language other than Haskell or
one of the other functionals that support higher order functions, and
the mapping and folding functions, and list comprehensions etc.
   I am just a happy camper that I have the ability to use such fine
tools, and not have to be lost in the catacombs of mediocrity: ie.
Java, C++, C, and C#.

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


Re: class [] proposal Re: [Haskell-cafe] One thought: Num to 0 as ? to list?

2006-08-22 Thread Gene A

Arie said:
{...  This is an instance of a general conflict: should we sacrifice nice
notation for ease of learning? You could make a similar case for list
comprehensions, for example: they complicate matters for newcomers (yet
another meaning of brackets and pipe) ...}


I have to totally agree with that statement, and surely hopeful that
no one takes away the list comprehensions, as a person new to Haskell
that was something that I got the hang of right away.  I've used other
languages for YEARS before I needed or used a given construct, and the
fact that it was there never bothered me much.. I JUST DIDN'T use it.
Now as to the whole namespace part of the argument made by Brian...
well that is another kettle of fish, and I will leave that to guys
with his knowledge.. to cipher out such things... somebody has been
doing a good job on this language so far!

happy day to all,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-22 Thread Gene A

John,
Thanks very much for that bit of insight.  I am not really writing
anything right now that is in more hurry than what Haskell can handle
nicely.  I was feeling a bit guilty as, Shao said, I use $ over (.)
and thought that my code could get some amount of ridicule as to
style... when it gets a look by guru types.. Now I can just say, Hey,
it is just my style!..   I have written things that involved lists,
where it was building and rebuilding lists of some length that took
lots of time.. but that had nothing to do, as you had said with the
syntax I chose to use. it would seem that the big ones are things like
ordering placements to take advantage of tail recursion and such are
more the issue.. and using more efficient data structures than a
straight list when appropriate.
  Since you know this sort of thing... Point Free, does that end up
being the exact same code after the compiler gets done with it.. I
assume it must, but ... ?? Does it cause the compiler less or more
work to get to that resultant code.. hmmm

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


[Haskell-cafe] Re: Haskell wiki: most popular pages

2006-08-22 Thread Gene A

Excerpt from Bulat Ziganshin :

i think that definitions with omitted arguments can be more hrd to
understand to newbie haskellers, especiallyones who not yet know the
language. as Tamas suggests, this page can be used to present to such
newbies taste of Haskell so listing all the parameters may allow to
omit unnecessary complications in this first look into language


Excerpt from Tamas K Papp

I think I learned to understand and appreciate omitted arguments from
Hal Daume's Yet Another Haskell Tutorial.  The exercises there are
just great.


Hi for what it's worth, having recently {still} trying to grasp all
the nuances of this wonderful Language and coming from an imperative
world where the Variable is King... It would be a really tough stretch
on first look, but as Tamas said, the Yet Another Haskell Tutorial
herein mentioned, was along with some other places that the whole
point free concept was put forth, were immediately adopted by me for
many uses... I think any introductory material, would do well to show
the conventional method with explicit arguments  and then followed
with a point free version if applicable.
 As to the base discussion, I feel that any and all string
manipulation functions that are missing would be a great thing to add.
I came from a backgound of using Icon and Unicon, which are offshoots
of the earlier language Snobol.  Snobol's pattern matching and such on
strings is still unequaled, but Icon/Unicon, both have a facility that
is called string scanning which makes many things that involve search
and replacement trivial.  It has some things that I have already
written using just high level haskell, no C or C++ foreign functions
with wrappers or anything, to emulate such things as the left, right,
and center functions that will give back the string padde to the left
or right, and the center function is merely padded to the left and
right  based on the total field width given.  Also on the same note,
currency functions to do the same with string representations of US
dollar amounts and such, rounding to to decimal places first and then
adding leading zero, and commas for the thousands..{I think I added
that in?? not sure}.
  The functions to quickly substitute one word for another are a
little more problematical, as the most intuitive first step is to use
the function words, but if things are using more than one space
between words that is lost in any easily built function that just
breaks up the words, makes the substitutions to the resulting list,
and then goes on to introduce the spaces back in.. as the original
count of spaces is lost.. would need to make a new function that
breaks up a stream into words that are made up of non-whitespace
chars, and also the subsequent whitespace ones.. so that when put back
together the spacing is the same... more trouble with that if the new
replacement word is longer or shorter.. if it is column oriented data
that would get messed up even worse.

okay done with the rambling,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-21 Thread Gene A

On 8/19/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:


Or you could use:
   putStrLn [head This and that]



Gotta say I really like this ... running the head function inside of the list...
Okay so I can really learn something here... what would that look like
in raw monadic notation?
using bind and such notation... =  etc..
hey, mention was made of lists being monads.. so 

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


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-21 Thread Gene A

Lennart and all,

On 8/19/06, Lennart Augustsson [EMAIL PROTECTED] wrote:

There are much better ways than storing strings on the stack.
Like using a data type with constructors for the different types that
you can store.

-- Lennart


Off topic, but  this is important info for me!
Okay then, by doing that you can define a new type that encodes the
other types.. such that you can actually end up storing the different
types such as Int, Integer,Real, String, etc into a list . using
this new type to so that even though you are in effect storing
differing types to a list.. they are actually of the same type and
thus legal... without doing an explicit bunch of read/show
combinations.. to actually convert..  like Num for example... and
being able to use +,* on any of the numeric types... but can you have
a list of type [Num] ?? I thought that it had to be the base types of
Int, Integer, Float, Double  etc..  No?

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


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-21 Thread Gene A

Hi All,
I got up this morning {after not much sleep} to find these very
helpful suggestions/comments:

from Scott Turner:
{... See:  http://www.haskell.org/hawiki/ExistentialTypes ...}


From Bulat Ziganshin:

{...
you can read recent discussion on this in this topic, or look at
http://haskell.org/haskellwiki/OOP_vs_type_classes
}


From Lennart Augustsson,

A wonderfully instructive code fragment:
{...
data Value = D Double | S String | B Bool
type Stack = [Value]
-- Add top stack elements
plus :: Stack - Stack
plus (D x : D y : vs) = D (x+y) : vs
plus (  _ :   _ :  _) = error Bad operands to plus
plus_ = error Not enough operands on stack
...}  see his post for the continuation...

With these suggestions I have plenty to study now.. and probably a whole
redesign of some of the things that I have already implemented.. with
most likely a great boost in speed of execution, and much cleaner
code.  I must admit that some of these concepts have not come as
easily to me as to some that have had formal education in these
matters... This list and the materials from Haskell.org, papers on
various websites, and documentation with GHC and it's libraries are my
entire exposure.. so when stuck, kind folks from the net community are
my, I guess mentors would be the word I am looking for... and for that
I am very greatful!
I am not in a real race... but I have to thank everyone that
participated in this spawned off of the main topic discussion... for
all their patience with my questions..

Thanks again to All for the clarification and links to more reading,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-21 Thread Gene A

hi,
Now, is there a speed or cleaness of code advantage to using the
function composition method using (.) :
  putStrLn . return . head $ This and that
over the application method...using ($):
  putStrLn $ return $ head this and that

some thoughts on that ... they both work.. but any advantage or disadvantage
to one over the other.. I find a lot of these kind of things in
Haskell, and it is purely wonderful.. but always go away wondering if
I am really using the most efficient, or most acceptable method..
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Gene A

Hi,
 Here is a little thing I came up with to simulate the construct for
x:= n1 to n2 and for x:=n1 to n2 by n3  from purely imperative
world to use in Haskell,  I call the functions fromto  and fromtoby..
they also take a function which consumes the x component and uses it
in the computation.   Just syntactic sugar.. best to wean off of this
way of doing things.. but that is one of the nice things about
Haskell, you CAN do this sort of thing easily.

The definitions:
fromto :: forall b a. Enum a = a - a - (a - b) - [b]
fromto a b f = map f [a..b]

-- --

fromtoby :: forall a b.
   (Num a, Enum a) =
   a - a - a - (a - b) - [b]

fromtoby a b c f = map f [a,a+c..b]

-- --
Some applications using ghci with enhancements turned on...

*Iteration fromto 10 25 id
[10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25]  --raw list using id
*Iteration fromto 10 25 (2*)
[20,22,24,26,28,30,32,34,36,38,40,42,44,46,48,50]  -- list times 2

*Iteration fromtoby 1 12 2 id -- using id to show what the base list is
[1,3,5,7,9,11]
*Iteration fromtoby 1 12 2 (flip (^) 3)  -- cubing of the base list above..
[1,27,125,343,729,1331]

*Iteration fromtoby 12 42 3  id
[12,15,18,21,24,27,30,33,36,39,42]   -- raw list gen'd by  id
*Iteration fromtoby 12 42 3  (flip (**) 0.33)
[2.2894284849170297, 2.4662120741078493,  -- approx. cube roots
2.6207413939563993,2.7589241761011336,
2.884499140309247,2.9670416,
3.1072325056015817,3.2075343296219874,
3.3019272485002094,3.391211442600036,
3.4760266444533747]

Greetings from the Yuma Desert,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Gene A

Hi Lennart,

 This morning when I posted..it was about 2:30am and had been up a
long time... bad habits.. I sent a message to Henk-Jan to that effect,
but didn't send to the entire list.. anyway thanks to both for the
followups... I still tend to sometimes do things the hard way in
Haskell.  Started trying to learn it starting in I think Nov-Dec. of
2005, so not too awfully long, but with a lot of other things soaking
up time, not as far along as I wished to be in even this amount of
time... Most interesting language I have used yet.

but yes not sure why not the precision.. but I think when I tried
that with the way I had the thing in the original, I used  (**) 1/3
and got an error message which I was too tired to even read,..and just
changed it to 0. or whatever  however many 3's , and just
got it posted.. I don't think that those functions are of much use,
the thing was that when I wrote them, not at 2AM in the morning, I
remember thinking just how easy it was to do pretty much anything you
want with this language.. Off topic, but one of my tests of a
language, old habit this, is as soon as I know enough to be dangerous,
I try writing a forth interpreter in it.  I have started such a thing,
a module I call Hforth, and it is operational, but do to the nature of
lists not holding homogeneos values in Haskell everything has to be
stored with String values.  This has the result of having to apply
show function to store numerics to the stack and then to use the read
function to convert back when popping the stack.. .. hmm still
tired... Anyway the upshot is that a very rudimentary interpreter is
up and running to do simple things with just builtins so far, but was
built in a matter of some fairly small number of hours.  Doesn't
support line editing yet, so really not too good, but does support
pushing strings and concatenation and some other things that are more
tedious to write as primatives in other languages..  The only other
language that was as easy to get to this stage with was scheme.

Sorry for the ramble,
gene

On 8/19/06, Lennart Augustsson [EMAIL PROTECTED] wrote:

On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:


 [...]
 *Iteration fromtoby 12 42 3  (flip (**) 0.33)

 fromtoby 12 42 3  (**0.33)

And why approximate so much?

fromtoby 12 42 3 (** (1/3))



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


[Haskell-cafe] Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-19 Thread Gene A

The thread on the use of show and print to display an Int value,
brought up a problem I had early on... the one of cleanly displaying a
Char value, on a line all by itself.. My first attempts:

This was just plain hard to read: with the character t being where it was:

Prelude putChar $ head this and that
tPrelude
---
So I tried this and of course ... type mismatch:

Prelude putStrLn $ head this and that
interactive:1:16:
   Couldn't match `String' against `Char'
 Expected type: [String]
 Inferred type: [Char]
   In the first argument of `head', namely `this and that'
   In the second argument of `($)', namely `head this and that'
--
So I did this... to manually turn it to a string and it does work, but
a little cumbersome to work into other function calls:
Prelude putStrLn $ (head this and that):[]
t
-
so the definition of putCharLn came to life {may be in some library already
and I just haven't found it yet.. but it is in my toolbox now}:

Prelude let putCharLn c = putStrLn (c:[])
Prelude
and an application of it:

Prelude putCharLn $ head this and that
t
---
now I also have the char to string conversion alone:

c2Str c = c:[]

Prelude let c2Str c = c:[]
Prelude c2Str 'A'
A
--
Now this is almost too trivial a thing to mention these gizmos...
what with all the monadic constructions that greater minds  toss
about on this list.. and I am trying to get understanding of that
still, but 
sometimes we just accept the unacceptable little irritants
rather than just code a solution, no matter how simple it is.
There are probably troves of simple workarounds out there
that seem too trivial to mention but hey, share 'em...
might hit a guy like me that says. now why didn't I think to do that?

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