Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Mark Carroll
On Mon, 3 Oct 2005, Joel Reymont wrote:

 On Oct 3, 2005, at 6:51 AM, Marc Ziegert wrote:
 
  data (Integral a) = BigEndian a = BigEndian a deriving  
  (Eq,Ord,Enum,...)
  be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff  
  `flip` 0) ) :: Bool
 
 Will this always correctly determine if the platform is big-endian?  
 How does it actually work?

I don't know, having not used things like peekByteOff, but my suspicion
would be that it's rather like,

  typedef char byte;

  char cChar = 1;
  int cInt = 1;
  int be = cChar != *(((byte*) cInt) + 0);

  printf(be = %i\n, be);

  return 0;

in C, so it's looking to see if the first byte of the int representation
of 1 isn't 1.

-- Mark

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


[Haskell-cafe] Re: [Haskell] pros and cons of static typing and side effects ?

2005-08-11 Thread Mark Carroll
The previous comments make sense to me. The lots-of-unit-tests aspect of
static typing I find really useful, far exceeding any BDSM cost. If I'm
engaging in exploratory programming, the type inference combined with the
ability to write 'error armadillo' in stubs for values I can't be
bothered to generate right now really works conveniently for me.

Although I agree that lots-of-lists is very handy in early prototyping, I
don't feel at all constrained by using homogeneous lists, although very
occasionally I may use existential types, and the way I write programmes
is exactly to think in advance and then write the code: to do otherwise
just wastes my time because then the code doesn't work in some confusing
way and I have to do that thinking I postponed to figure out why - or, if
it does work, I have to think about it to satisfy myself that appearances
aren't deceiving.

I'm not quite sure what macros would look like in Haskell, but I've not
missed those either. In Lisp I would tend to use them for things that
involved changing the values of variables, but that's not really a
Haskellish thing to be doing anyway. Mind you, I learned Lisp after
learning ML, so to some extent I was thinking in ML when writing in Lisp.
Alas, dead-tree versions of On Lisp are hard to come by affordably, but
I am now trying to learn more about what I might have missed about Lisp.

I find monads useful because I find it a helpful debugging aid for
functions to be quite clear about what side effects they may want to
have.

I posted this to Haskell-Cafe instead of the main Haskell list, because
I'm rambling a bit. Puzzled Haskell-Cafe readers may like to check
http://www.mail-archive.com/haskell@haskell.org/msg17009.html

-- Mark

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


Re: [Haskell-cafe] Word32 to Int converions

2005-07-20 Thread Mark Carroll
On Wed, 20 Jul 2005, yin wrote:

 Bernard Pope wrote:

 On Wed, 2005-07-20 at 11:43 +0200, yin wrote:
 
 
 how do I convert an Word32 (or WordXYZ) to Int, or Integer, or Float,
 ...? The Int conversion is the priority.
 
 
 fromIntegral to convert to an instance of Integral, such as Int, Integer
 etc
 
 Thank you, but how to Work32 - Int?

Note that this compiles:

foo :: Word32 - Int

foo = fromIntegral

fromIntegral really is what you want.

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


Re: [Haskell-cafe] Coin changing algorithm

2005-07-13 Thread Mark Carroll
On Wed, 13 Jul 2005, Dinh Tien Tuan Anh wrote:

(snip)
 eg: m = 75, k = 5
  =   [50, 20, 5]
  [50, 20, 1,2,2]
(snip)
 Is this problem suitable for functional programming language ?

Oh, what fun. I like this sort of thing. My quick attempt is:

module Coins where
import Data.Maybe

nextChange :: Num a = (Int, [a]) - [(Int, [a])]

nextChange (n, xs) = [ (n', increment n' xs) | n' - [ n .. length xs - 1 ] ]
where
increment 0 (x:xs) = x+1 : xs
increment n (x:xs) = x   : increment (n-1) xs

makeChange :: (Num a, Ord a) = [a] - a - a - [[a]]

makeChange coins total number =
helper (0, replicate (length coins) 0)
where
helper state@(_, change)
   | sum change  number = []   -- too many coins
   | otherwise =
   case compare (sum (zipWith (*) coins change)) total of
  EQ - [change]-- correct amount
  LT - concatMap helper (nextChange state) -- too little
  GT - []  -- too much

showResults :: Num a = [a] - [a] - [String]

showResults coins change =
mapMaybe showResult (zip coins change)
where
showResult (_,0) = Nothing
showResult (c,n) = Just (show n ++  x  ++ show c)

test =
let coins = [1,2,5,10,20,50,100,200]
printChange change = do mapM_ putStrLn (showResults coins change)
putChar '\n'
 in mapM_ printChange (makeChange coins 75 5)


I post it here because, whenever I do, someone else shows a much better
solution that's shorter and clearer! Especially, I don't see myself using
much real functional programming in the above, and I'd love to see a
better approach.

-- Mark

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


Re: [Haskell-cafe] About ($)

2005-06-02 Thread Mark Carroll
On Thu, 2 Jun 2005, Frank-Andre Riess wrote:

 name's Frank-Andre Riess. Nice to meet you m(_ _)m

Hello!

 So, well, my first question on this list is admittedly somewhat simple, but I
 managed to delay it long enough and now I think I should ask about it: Does
 ($) have any relevance at all except for being a somewhat handier version of
 parentheses?

Well, it's nice to be able to pass ($) as an argument, a higher order
function that does function application, so you can write things like,
foldr ($) 6 [(/5),(+3),(*2)] and hopefully more useful things too.

-- Mark

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


Re: [Haskell-cafe] List containing different types but all implementing the same class

2005-04-08 Thread Mark Carroll
On Fri, 8 Apr 2005, Bo Herlin wrote:
(snip)
 Is it possible to make this work?

This is an extension beyond the 1998 standard, but
http://haskell.org/hawiki/ExistentialTypes may be
interesting to you.

-- Mark

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


[Haskell-cafe] Linux device drivers

2005-03-20 Thread Mark Carroll
I was wondering about the possibility of using Haskell for developing
device drivers that would be kernel modules for Linux. If nothing else,
it would be quite an educational experience for me, as I've not yet
experimented with either the Linux kernel or Haskell FFI, nor have I
had to learn how to squeeze much performance out of my Haskell code.

Clearly, this application demands special things from the compiler and
the runtime. But, I'm not exactly sure what, nor how to achieve such
given current compilers. Does anyone have any thoughts?

Thanks,
Mark

-- 
Haskell vacancies in Columbus, Ohio, USA: see http://www.aetion.com/jobs.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] invalid character encoding

2005-03-19 Thread Mark Carroll
On Sat, 19 Mar 2005, David Roundy wrote:

 That's not true, there could be many filesystems, each of which uses a
 different encoding for the filenames.  In the case of removable media, this
 scenario isn't even unlikely.

The nearest desktop machine to me right now has in its directory structure
filesystems that use different encodings. So, yes, it's probably not all
that rare.

Mark.

-- 
Haskell vacancies in Columbus, Ohio, USA: see http://www.aetion.com/jobs.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Typeclasses and instances

2005-03-17 Thread Mark Carroll
   newtype Floating a = Vector a = Vector [a]

Okay, I now know a little more about this, with help from friends. The
obvious Functor instance seems not to work with GHC 6.2.2 but does work
with GHC 6.4. With 6.2.2 I can still use GHC's newtype-deriving extension
to derive an instance for Functor, I'm just not sure how I can get an
explicit instance past 6.2.2 without it complaining about my syntax or not
being able to deduce Floating a or b. This isn't a show stopper, I'm just
intrigued.

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


Re: [Haskell-cafe] Typeclasses and instances

2005-03-17 Thread Mark Carroll
Another note, with more help from friends:

It turns out that GHC 6.4 will let me do,

newtype Floating a = Test a = Test [a] deriving Show

x = Test [False, True]

but, if I change newtype to data, it then says,

No instance for (Floating Bool)

I'm not sure I quite understand what's going on.

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


[Haskell-cafe] Typeclasses and instances

2005-03-16 Thread Mark Carroll
If I have,

newtype Floating a = Vector a = Vector [a]

if I want to make it an instance of Functor (with the obvious meaning),
how do I write that?

Thanks,
Mark

-- 
Haskell vacancies in Columbus, Ohio, USA: see http://www.aetion.com/jobs.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parser question

2005-03-15 Thread Mark Carroll
On Tue, 15 Mar 2005, Nicola Whitehead wrote:
(snip)
 term :: Parser Int
 term = do f - factor
do symbol *
e - expr
return (f * t)
   +++ return f
(snip)

 symbol and natural are defined elsewhere and work fine, but when I compile it 
 I get the error
  
 ERROR C:/HUGS/Calculator.hs:66 - Undefined variable t
  
 I suspect I'm missing something obvious, but for the life of me I can't see 
 it. Any suggestions?
(snip)

You are missing something obvious. (-: t appears indeed to be undefined
in term. Did you mean return (f * e)? Variables (although why they're
called that in Haskell I'm not sure) defined with - in do are only in
scope later in that do, not anywhere else.

Mark

-- 
Haskell vacancies in Columbus, Ohio, USA: see http://www.aetion.com/jobs.html

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


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-12 Thread Mark Carroll
I had a go with things along this theme and came up with a couple of
options, with different type signatures. I use some functions from the
Data.List library.

If we know that, as with Ints, we are dealing with list members that are
instances of Ord, we can do:

howManyEqual :: (Eq a, Ord a) = [a] - Int

howManyEqual = maximum . (0 :) . map length . group . sort

Otherwise, we end up less efficient, with:

howManyEqual :: Eq a = [a] - Int

howManyEqual = countEach 0
where
countEach best [] = best
countEach best list@(x:_) =
let (xs, others) = partition (== x) list
 in countEach (max (length xs) best) others

-- Mark

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


[Haskell-cafe] Card trick

2005-03-10 Thread Mark Carroll
Having heard about an interesting card trick, I thought I'd try
implementing it in Haskell. With luck, I didn't make any mistakes.
I thought it was cool enough to be worth sharing with you guys.

-- Mark module CardTrick
 where
 import Data.List
 import Data.Maybe

This code is by Mark Carroll, based on a description by Chris Ball of some
aspects of the trick. A guest selects five cards at random from a standard
deck. The magician's assistant hands four of them to the magician, and the
magician reveals what the fifth was. offerToTrickster reveals the four
cards that are handed to the magician by their assistant. tricksterAnswers
reveals what the fifth card was, based on the order of the four. The two
functions are separate and outside any monad to make it clear that no
information is leaking between the two apart from the obvious. Note that
the necessary procedures are easy for people to learn and to perform. Chris
mentions that there is interesting further reading in an article by Michael
Kleber to be found at http://people.brandeis.edu/~kleber/Papers/card.pdf

Usage example:

let fiveCards = (Card Five Clubs, Card Five Spades, Card Jack Hearts, Card Ace 
Spades, Card Two Clubs)
let fourCards = offerToTrickster fiveCards
let fifthCard = tricksterAnswers fourCards
print fourCards  print fifthCard

First, we define the suits of the cards. They are in ascending order of
traditional superiority so that they work intuitively with Ord, and are thus
easy for a human to sort just as the computer does.

 data Suit = 
 Clubs | Diamonds | Hearts | Spades
 deriving (Eq, Ord, Read, Show)

Then, we define the ranks of the cards. Again, they are in intending order of
superiority, but one may prefer to make aces low instead of high.

 data Rank = 
 Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten |
 Jack | Queen | King | Ace 
 deriving (Bounded, Enum, Eq, Ord, Read, Show)

A card has a rank and a suit.

 data Card = 
 Card { rank :: Rank,
suit :: Suit } 
 deriving (Eq, Ord)

We can pretty-print cards.

 instance Show Card where
 show (Card rank suit) = show rank ++  of  ++ show suit

limitToRanks brings an integer into range such that it corresponds to one of
the card ranks. Out-of-bounds integers are considered to have been referring
to duplicate enumerations of ranks among which our canonical enumeration is
stacked.

 limitToRanks :: Int - Int

 limitToRanks = flip mod $ fromEnum (maxBound :: Rank) + 1

Now, we define the function offerToTrickster that embodies the activity of the
magician's assistant in handing the magician four of the five guest-picked
cards.

 offerToTrickster :: (Card, Card, Card, Card, Card) -
 (Card, Card, Card, Card)

 offerToTrickster (c1, c2, c3, c4, c5) =

We aggregrate the cards by suit, with the larger groups first. This allows us
to easily pluck out in w and x two cards (of the same suit) from the largest
group.

 let ((w : x : ys) : zs) = 
 sortBy compareLengths $ 
 groupBy suitsEqual $ 
 sortBy compareSuits [c1, c2, c3, c4, c5]

The remaining cards are in ys and zs. We collect them together and put them
into a predictable order by sorting them.

 remainder = sort (ys ++ concat zs)

Now, we find how many ranks we must step up in order to get from x's rank to
w's rank, and vice-versa. If we step past the highest rank, we wrap back down
to the lowest rank.

 xToW = limitToRanks (fromEnum (rank w) - fromEnum (rank x))
 wToX = limitToRanks (fromEnum (rank x) - fromEnum (rank w))

We are going to tell the magician the suit of the card we retain by keeping
one of w or x, which are of the same suit, and giving the magician the other
as the first card of the four. We choose which card is which by finding the
card such that if we step up from it, we can reach the retained card in six or
fewer steps. We note how many steps we must step up from this first suit
card to the retained card.

 (suitCard, distance) = if xToW  wToX then (x, xToW) else (w, wToX)

We encode the number of steps, the distance between the cards, as two numbers:
   (0, 0) = 1 steps
   (0, 1) = 2 steps
   (1, 0) = 3 steps
   (1, 1) = 4 steps
   (2, 0) = 5 steps
   (2, 1) = 6 steps

 (firstOfThree, swapLastTwo) = quotRem (distance - 1) 2

Now we have chosen a suit card from the four we can give to the magician, we
have three cards left in which to encode how many ranks must be stepped up
from the suit card to find the rank of the retained card.

Of those three (remember, they are ordered), we pluck out one of them to
indicate the first number in our encoding. This will be the next card we give
to the magician.

 firstCard = remainder !! firstOfThree

We find the remaining two cards.

 unswappedLastTwo = delete firstCard remainder

To encode a 1 as the second number in our encoding, we swap these last two
cards.

 lastTwo = (if swapLastTwo == 1

Re: [Haskell-cafe] State Monad

2005-03-04 Thread Mark Carroll
On Fri, 4 Mar 2005, Mark Carroll wrote:
(snip)
 Enclosed is a programme that asks for two ints from standard input, adds
(snip)

Let me try again. (-:

-- Markmodule StackMTest
where
import StackM
import Control.Monad
import Control.Monad.Trans
import System.IO
import System.Random

add :: Num a = StackM a IO ()

add =
do x - popM
   y - popM
   pushM (x + y)

throwTenDie :: StackM Int IO ()

throwTenDie = lift (getStdRandom (randomR (1, 10))) = pushM

stackMTest :: StackM Int IO Int

stackMTest =
do pushNumber
   pushNumber
   throwTenDie
   add
   add
   popM
where
pushNumber =
do text - lift $ getLine
   pushM (read text)

main :: IO ()

main = runStackM stackMTest = print
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State Monad

2005-03-02 Thread Mark Carroll
On Thu, 3 Mar 2005, Sam G. wrote:

 I need a Monad to represent an internal stack. I mean I've got a lot
 of functions which operates on lists and I would not like to pass the
 list as an argument everytime.
 
 Could you help me writing this monad? To start, I just need a +
 function which will return the sum of the 2 toppest elements of the
 stack.

I wrote one which is at,

http://www.aetion.com/src/Stack.hs
http://www.aetion.com/src/StackM.hs

Then,

add :: Num a = Stack a ()

add =
do x - pop
   y - pop
   push (x + y)

or whatever.

Of course, if you use Control.Monad.State where you store the stack as a
list then you can probably just do something like,

add = (x:y:z) - get
  put ((x+y):z)  

I hope that helps.

-- Mark

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


Re: [Haskell-cafe] Literate Haskell

2005-02-18 Thread Mark Carroll
On Fri, 18 Feb 2005, Dmitri Pissarenko wrote:

 I'm curious what experienced Haskellers think about using literate
 Haskell in daily work.

 It seems to me like a good idea, since during coding it often helps to
 write down one's thoughts (often, I find a solution to a complicated
 problem in this way).

 What are your experiences with using literate Haskell?

I used to use it - I also like to note things in among the code.
Now I tend to use Haddock documentation more.

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


Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Dmitri Pissarenko wrote:

 Is it possible (at least theoretically) to write a program in Haskell, then
 convert it into C and then compile the C program into an executable, which is
 optimized for the microcontroller?

I would guess so. Wasn't there someone mentioning here a little while ago
some project where they strip most of System.* from the libraries and get
something that might be suitable for embedded applications? What was that
called? Anyone remember?

-- Mark

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


Re: [Haskell-cafe] Parsing a string

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Dmitri Pissarenko wrote:
(snip)
 I need to read the height and width, then cut them from the string, create
 an array (or finite map) of Int's (for this I need to know the height and
 width), and then recursively process the pixel values (i. e. put them into the
 array).

The simple way is probably to use functions like lines and words and
map read. You can then use pattern-matching and recursive functions to
work your way through the file. For regular expressions you can use
Text.Regex in GHC.

However, for fancier parsing in GHC you can look at
Text.ParserCombinators.Parsec, and I recall that there was also talk on
this list of a nice regular expression library with syntax that goes
inline right into your Haskell code in a Perl-like way, but I also can't
immediately find any reference to that.

-- Mark

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


Re: [Haskell-cafe] File path programme

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Marcin 'Qrczak' Kowalczyk wrote:
(snip)
 If problems are in the implementation but the interface is right, then
 the module should be provided. It can be fixed later.
(snip)

A lot of the Haskell libraries are sufficiently poorly documented that I
work out what they do by experiment, or by resorting to reading the
source.

There is a risk that code will be developed that relies on the observed
broken behaviour, and is then broken when the implementation is fixed.

-- Mark

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


Re: [Haskell-cafe] wxFruit examples

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, John Peterson wrote:

 The wxFruit effort was a senior project that focused pretty much
 exclusively on the paddleball game.  It didn't really create any
 software that we intend to maintain and distribute.

Still, is wxFruit the best shot we have at being The Way Forward for
purely functional Haskell GUIs?

 I have a couple of students working on a continuation of this but I
 don't expect to release anything for a few more months. 
(snip)

Ah, great to hear it's still alive. We've been keeping a look out for
further developments. Thanks.

-- Mark

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


[Haskell-cafe] File path programme

2005-01-20 Thread Mark Carroll
I tried writing a little command-line utility to find the relative path of
one thing from another thing (with Unix-like systems in mind). For example,

$ ./pathfromof /etc/init.d/ /etc/X11/XF86Config-4
../X11/XF86Config-4
$ ./pathfromof /tmp/baz/ /tmp/foo/
.
$ ls -l /tmp/baz
lrwxr-xr-x  1 markc markc 8 2005-01-20 12:01 /tmp/baz - /tmp/foo

It turned out surprisingly complex, though, and doesn't feel very neat or
tidy at all, nor is it very portable given that I couldn't find generic
library functions for manipulating bits of filepaths. Anyhow, it's at
http://www.chiark.greenend.org.uk/~markc/PathFromOf.hs and may yet have
egregious bugs.

It seems to me like it could certainly be improved in various ways. If
anyone has any thoughts, as to how I could improve my style, make more use
of standard libraries, etc., I'd certainly appreciate them.

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


Re: [Haskell-cafe] Using Haskell as a database

2005-01-10 Thread Mark Carroll
On Mon, 10 Jan 2005, Dmitri Pissarenko wrote:
(snip)
 At the moment, I think that it makes more sense to store the data in form of
 facts (not tables as in relational database).
(snip)

A Haskell binding for something some of the stuff at
http://www.ai.sri.com/~gfp/ might be useful?

I'd often wondered about implementing something that
looked like GFP to the user, but had an ODBC backend.

-- Mark

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


Re: [Haskell-cafe] Re: Utility functions

2004-12-29 Thread Mark Carroll
On Wed, 29 Dec 2004, John Goerzen wrote:
(snip)
 I accept patches for things like this for MissingH.  You can send me
 code or diffs as you prefer.  I've been accepting code licensed under
 GPL, LGPL, or BSD, and will need a statement such as:
(snip)

Can you mix in BSD code with GPL, though, without making it also GPL?

-- Mark

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


[Haskell-cafe] Utility functions

2004-12-28 Thread Mark Carroll
I find myself writing things like,

splitListOn :: Eq a = a - [a] - [[a]]

splitListOn delimiter =
unfoldr splitter . (delimiter :)
where
splitter [] = Nothing
splitter xs = Just (span (/= delimiter) (tail xs))

This is a sort of intersperse-opposite, in that...

myId delimiter = concat . intersperse [delimiter] . splitListBy delimiter

...myId foo turns into a sort of id for lists of the correct type.

With this, and other things, I always have a feeling that it's probably in
the standard library somewhere but I didn't notice - maybe because it's
abstracted out of recognition, just like sequence does Cartesian
products for us, but not so that I noticed right away.

Is there a good place to put these things - little things that feel like
that maybe they're already in the standard library, and maybe they should
be? I'd hate to be unknowingly reinventing the wheel all the time. I don't
see an obviously-appropriate page for these on the Haskell Wiki, but maybe
I missed it, or maybe I should create one.

-- Mark

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


Re: [Haskell-cafe] Haskell IO and exceptions

2004-12-10 Thread Mark Carroll
On Sun, 5 Dec 2004, Scott Turner wrote:
(snip)
 Yes. Although Control.Monad.Error forces your error type to be in the Error
 class, that puts no constraints on what you save in the errors. If you thread
 your errors with the IO Monad then you would be using the monad:
ErrorT YourErrorType IO
 When you invoke runErrorT (within the plain IO monad) it returns an Either
 result which delivers your error type and it can be reported however you
 wish.
(snip)

Thanks very much! With the help of the StateT example I already had on the
Haskell Wiki I managed to figure out that, to have String errors in ErrorT
for code in the IO monad, I could just pass the strings to throwError,
change the IO Foo functions from which errors might propagate to ErrorT
String IO Foo functions, catch the error in the IO monad with runErrorT
(from the Either), and where I have a function that might throw an error
that uses the result of a normal IO monad function, I lift that result
into the ErrorT monad. And it all seems to work. (-:

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Non-technical Haskell question

2004-12-06 Thread Mark Carroll
On Mon, 6 Dec 2004 [EMAIL PROTECTED] wrote:

(snip)
 someone else wrote:
  gcc of course leaves .o files lying around, so this is no different than C.
(snip)
  When I use javac every file that is created is necessary for the
 application to run. This can't be said of the ghc compiler. Having an
 excuse that this is way the C compiler does it or that this is the way
 its always been done is to poor of a reason to even argue against. If a
 file isn't needed then it shouldn't be left there. 
(snip)

It can be useful to leave the .o files around. For instance, if you just
change some source files, but not all, then you can reuse some of the old
.o files instead of having to recompile everything. This gcc analogy also
applies to ghc.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell IO and exceptions

2004-12-04 Thread Mark Carroll
All this talk of IO and exceptions reminds me of a small issue I've been
having. I like Control.Monad.Error but often my stuff is threaded through
the IO monad so, AFAICT from the functional dependency stuff, that means
my errors have to be IOErrors. Is that right? And, then, I want control
over what's actually reported to the user, but if I make a userError than
the consequent message (where the details are presumably
platform-dependent) is wrapped up in extra text that I didn't want
appearing. Can I use Control.Monad.Error for IO monad stuff such that I
can control what string will appear when my error handler tries to show
my exception?

Admittedly, I'm still learning my way around this bit of the standard
libraries, so I may have missed something obvious.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Propagating Parsec errors

2004-12-04 Thread Mark Carroll
Is there a way in Parsec to, within a parser, throw an error generated 
by another parser? For instance, something of type

ParseError - GenParser tok st a

or whatever.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Better Exception Handling

2004-11-24 Thread Mark Carroll
On Tue, 23 Nov 2004, John Goerzen wrote:
(snip)
 I've been using Haskell for 1-2 months now, and feel fairly comfortable
(snip)
 catchJust :: (Exception - Maybe b) - (c - a) - c - (b - a) - a
(snip)

Yes, this was one of the first things that bothered me, too, when I
started actually writing much Haskell code: I wanted a non-monadic version
of try/catch. Because a pure function should always return the same value
given the same arguments, the behaviour of such a try/catch must be made
quite deterministic: for example, perhaps it should only return exceptions
generated in its own execution thread (to make it entirely synchronous),
and perhaps all the exceptions that could be generated in its evaluation
should be generated (so we don't learn anything about evaluation order -
after the first exception, we may need to carry on evaluating other parts
of the expression to find what other exceptions there are). I seem to have
learned to live with the lack of such non-monadic exceptions: often I use
monads for this sort of error propagation thing, but not the standard
try/catch in the IO monad because I avoid the IO monad wherever possible
because functions in the IO monad are so unconstrained by the type system
with regard to what effects they could have.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Job

2004-09-23 Thread Mark Carroll
The company I'm involved with - Aetion, a tiny defense contractor in
Columbus, Ohio - is now looking for an affordable Haskell programmer to
hire. So, on the offchance that any of you guys are interested, or know of
someone who might be, feel free to e-mail me for more information or to
supply your resume. Unfortunately, the nature of the work is such that US
citizenship or a security clearance would help, and telecommuting isn't
really an option. On the upside, the work should be varied and interesting
- more challenging than mundane. Given that fact, we are more interested
in aptitude than specific experience.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Functional Reactive Programming

2004-09-09 Thread Mark Carroll
I was wondering, how much active development is done on FRP frameworks
these days. What direction is it going in, and who are the users? I
haven't seen much new on Yampa lately so I wondered how that was doing, or
if it was thought largely finished and maybe something else was going on.
For instance, maybe more of the activity is in developing wxFruit or
suchlike?

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie problems

2004-07-05 Thread Mark Carroll
On Sat, 3 Jul 2004, paolo veronelli wrote:

 I'd like to have a simple definition of the meanings of 'type' and 'data'
 and maybe a clarifing example on their use.
(snip)

The way I see it, you use type for genuine synonyms where you don't care
about the distinction, newtype where you want to make a separate type
with a single constructor, and data where you want to make a separate
type with multiple constructors. My memory might be failing, though.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Mark Carroll
On Mon, 14 Jun 2004, Keith Wansbrough wrote:
(snip)
 to lose referential transparency.  What is the value of

 catchExcept (show (makeExcept E1 + makeExcept E2)) (\x - x)

 ?  Haskell wouldn't be purely functional any more.
(snip)

We've already had these issues raised on haskell-cafe when I've been
wanting non-monadic synchronous exceptions. (-: The answer is that you
evaluate all branches sufficiently to discover all the exceptions raised,
and maybe have an ordering on exceptions such that you can return
answers deterministically (as a list of ones that occurred or
something). I'll be happy to follow discussion of this on haskell-cafe but
will be reluctant to say much that I've already said (e.g. in December
2002's Error Handling) for fear of boring everyone silly.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Surprising bugs

2004-05-12 Thread Mark Carroll
I clearly don't understand Haskell very deeply yet because I dealt with a
couple of interesting types of bug this week.

One sort was where, if I have,

f :: SomeType - Stuff ...

f = whatever

g :: Stuff ...

g = f someValue

...then I can get an error that suggests that maybe I'm violating the
monomorphism restriction if I put in f's type but not g's. If I put both
in, it becomes happy.

Another sort was where, if I had an algebraic parametric type (is that the
name? Ord a = Foo a b c, etc.) then I couldn't have, say, a Maybe (Foo a
b c), where sometimes I called it with a (Just foo) and sometimes with a
Nothing, because with the Nothings it would complain about, erm, some
ambiguity to do with Ord a. However, it would be fixed if I made the Maybe
X argument into two arguments, Bool - X, the Bool indicating if the X was
meant to have been a Nothing or a Just X.

I hope both (or either!) of those made sense. I don't have the code
immediately to hand to reproduce the details, but I just thought I'd try
to recall what they were because I found these compiler complaints
interesting. I don't fully understand what's happening, and I'm sure a
newbie would be quite bewildered. (-:

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Data constructors

2004-04-25 Thread Mark Carroll
I keep running into annoyance in having to name data constructors
differently if they're for different types if they're in the same module
or something. I wish that something like some Type.Constructor syntax
worked in order to disambiguate. Or, better still, I have that problem
with function names too (e.g. Data.List.union, Data.Set.union, IIRC) and
it occurs to me that a lot of this can be resolved automatically because
the types only make sense with one of the choices.

I'm not really proposing any changes; more, I'm wondering what others'
thinking is about this sort of thing - what annoys them, how they get
around it, etc.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data constructors

2004-04-25 Thread Mark Carroll
On Sun, 25 Apr 2004, Scott Turner wrote:
(snip)
 Must function concepts such as 'union' can be made into type classes, to the
 extent that the concept can be described in the type system.
(snip)

Unfortunately, you still need the different names when you make the
instances, and you can't do things like foo { bar = baz } with the bar
as the name of the function in the class instead of the field name /
selector function that's used in the instance, AFAIK.

(Thanks for your other comments.)

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Haskell and Artificial Intelligence

2004-04-21 Thread Mark Carroll
On Wed, 21 Apr 2004, GAYLE, Orrett Orville wrote:

 I am having great difficulty finding resources with AI sysytems
 implemented in Haskell. If anyones knows of a book or site which covers
  AI techniques implemented using haskell, could you please help me.

Ask me in a year or two, if you're still interested. This summer my
company will start trying to implement stuff inspired by Josephson's
Abductive Inference (Cambridge University Press) in Haskell.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Haskell job (OH, USA)

2004-02-26 Thread Mark . Carroll
Aetion Technologies LLC seeks another high-quality programmer.
Development is mostly in Haskell, with some Java, mostly under Linux.
An ideal candidate is excellent at acquiring, applying, and writing
about new knowledge. Additional background in disciplines like
mathematics, science, engineering, etc. is also attractive.

Aetion's main customers are in defense and finance, so we prefer to
hire people who can likely get a security clearance, and who do not
object to developing military applications. Telecommuting isn't really
an option, but Columbus, Ohio is a nice enough city, and the work
tends to be varied and interesting - more challenging than mundane.
Although we work to build useful software, a lot of our activities are
at the leading edge of research, keeping us far ahead of competitors.

The vacancy has not yet been advertised more formally through the
usual HR channels. Aetion is most definitely an equal-opportunity
employer. It would be fine to direct questions and resumes directly to
me; I can pass them on to the right people where necessary.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Perl-ish =~ operator

2004-02-23 Thread Mark Carroll
On Tue, 24 Feb 2004 [EMAIL PROTECTED] wrote:

 In my effort to turn Haskell into a language more like Perl
 (muahaha)[1], I got a bit fed up and implemented something like Perl
 5's =~ binding operator (a.k.a. regex operator); I thought maybe
(snip)

This reminds me that one thing I do miss from the regex stuff I've found
so far in Haskell is Perl's ? operator for turning greedy matches into
minimally-short ones. I can still usually do what I need to with Parsec,
at least, but I just thought I'd mention the issue.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-ish =~ operator

2004-02-23 Thread Mark Carroll
On Mon, 23 Feb 2004, John Meacham wrote:
(snip)
 a standard pcre (pcre.org) binding would also be a cool thing to work on.
(snip)

Heh - maybe a Cambridge computer science student could do it, having both
PCRE's author and Haskell experts handy locally. (-:

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell overview

2004-02-04 Thread Mark Carroll
A colleague with a mathematics and Lisp background is wanting to learn
more about Haskell. The books he's looked at concentrate more on building
up from the basics and getting the syntax right, etc., whereas really he's
looking more of a top-down view that makes Haskell's features and behavior
clear and relates them to category theory, etc. Would anyone be able to
suggest some good references?

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple Maybe question

2004-01-27 Thread Mark Carroll
On Tue, 27 Jan 2004, Jim Lewis wrote:

 I'm new to Haskell and can't find an example to solve a trivial problem.

 I have code like this:
 findBlank :: [] - Int
 findBlank str = findIndex (==' ') str

 But interpreter complains elsewhere of mismatch of Int with Maybe Int. I want to 
 handle the maybe only here and nowhere else.
(snip)

This may somehow help,

findBlank' :: [Char] - Int
findBlank' str = fromJust (findIndex (==' ') str)

findBlank'' :: [Char] - Int
findBlank'' str = let Just index = findIndex (==' ') str in index

findBlank''' :: [Char] - Int
findBlank''' str = maybe (error Pigs flew) id (findIndex (==' ') str)

You may have to import Maybe to get some of those to work.

Matthew Walton's comments also look good.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: POpen, opening lots of processes

2004-01-10 Thread Mark Carroll
Tomasz,

   Your code looks great, but where do you find the library documentation,
like what the arguments for executeFile are all about? (I'd guessed the
Maybe thing was an environment, but what's the Bool?) I've been trying to
do similar stuff, but have been stumbling in the dark rather.

-- Mark
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Combining distinct-thread state monads?

2004-01-09 Thread Mark Carroll
Another bit of code that seems to work is:

convertState :: (s1 - s2)
 - (s2 - s1)
 - State s2 a
 - State s1 a

convertState fromState toState computation =
do oldState - get
   let (result, newState) =
   runState computation (fromState oldState)
   put (toState newState)
   return result

Buoyed by this apparent success, I had a go with a Parsec parser:

convertParser :: (s1 - s2)
  - (s2 - s1)
  - GenParser tok s2 a
  - GenParser tok s1 a

convertParser fromState toState parser =
do oldState - getState
   oldInput - getInput
   case runParser (wrapParser parser)
(fromState oldState)  oldInput of
  Left error -
  fail (show error)
  Right (result, newState, newInput) -
  do setState (toState newState)
 setInput newInput
 return result
where
wrapParser parser =
do result - parser
   state - getState
   input - getInput
   return (result, state, input)

However, this has problems, not least of which are that the source
filepath is lost in the handing down, and the ParseError can't be passed
upward easily without some extra housekeeping, so the resulting shown
error has multiple locations. So maybe composed monads are the way to go.

Is there a better way to do this - with lifting or whatever - *while
keeping the type signatures the same*? (If this has already been said in a
way that wasn't obvious to me the first time, just let me know who said it
and I'll hunt in the list archives.)

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: JVM bridge

2004-01-06 Thread Mark Carroll
I should add that I see things like -Wl -rpath /usr/lib/jvm-bridge/lib/ in
the verbose output which maybe should be
-Wl,-rpath,/usr/lib/jvm-bridge/lib/ instead.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Parsec question

2004-01-01 Thread Mark Carroll
Thanks to Tom for his interesting points. I am still developing an
inuition for how the error reporting goes. (-:

On Thu, 1 Jan 2004, Derek Elkins wrote:

(snip)
   testOr3 =   do{ try (string (a); char ')'; return (a) }
(snip)
 example both issues come up.  If we successfully parse the
 (a then the second alternative (b) can't possibly succeed and since
 it can't succeed there's no point in saving the input (a to be
 reparsed when backtracking since there's no point in backtracking.
(snip)

Ah, that makes sense - thanks! I think part of my problem might have been
the quoted and real brackets and braces - at least a couple of times, I
thought the char and the return were within the try. (-: I will try to
look more carefully next time.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Monads

2003-12-31 Thread Mark Carroll
Omitting the typeclass bit, I'm trying to write something like
(s1 - s2) - StateT s1 m () - StateT s2 m a - StateT s1 m a

That is, it sequences two StateT computations, providing a way to
translate from the first's state to the second to keep the chain
going.

I can easily write something for when s1 and s2 are the same, and my
understanding of much of Control.Monad.* remains tenuous at best, but if
it's easy for anyone to provide me with some tips, then I thought I should
mention that it'd certainly be helpful.

And Happy New Year, everyone!

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Parsec question

2003-12-31 Thread Mark Carroll
I tried posting this before but, from my point of view, it vanished. My
apologies if it's a duplicate.

In http://www.cs.uu.nl/~daan/download/parsec/parsec.html we read,

 testOr2 =   try (string (a))
 | string (b)

 or an even better version:

 testOr3 =   do{ try (string (a); char ')'; return (a) }
 | string (b)

Why is the latter better?

(BTW, I like Parsec. Thanks, Daan. (-:)

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Monads

2003-12-31 Thread Mark Carroll
On Wed, 31 Dec 2003, Ken Shan wrote:

 Don't you need a (s2 - s1) function as well, to translate the final
 state back into StateT s1?

Yes, you're right: the thing actually running the stateful computation
presumably expects to start it with a state of type s1 and to be able to
extract from it a state of type s1 when it's done.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Why are strings linked lists?

2003-11-29 Thread Mark Carroll
On Sat, 29 Nov 2003 [EMAIL PROTECTED] wrote:
(snip)
 Interesting that you mention this.  I've also been thinking about this
 lately in the context of the discussion on collections and the left-fold
 combinator both here and on LtU.  When people say I want String to be
 [Char], what I'm actually hearing is I want String to be a collection
 of Char.  I may be mishearing.

It did strike me that it would be interesting if you could make various
things instances of a List sort of class and then take, reverse, etc.
would work on them. How this relates to your comment, I'm not sure.
Things like map, of course, could work on unordered bags of things too,
but I suppose that's what Functors are for.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Why are strings linked lists?

2003-11-28 Thread Mark Carroll
(shifting to Haskell-Cafe)

On Fri, 28 Nov 2003, Donald Bruce Stewart wrote:

 ajb:
(snip)
  As a matter of pure speculation, how big an impact would it have if, in
  the next version of Haskell, Strings were represented as opaque types
  with appropriate functions to convert to and from [Char]?  Would there be
  rioting in the streets?

I'd be sad to lose some convenient list-based string type because I make a
lot of use of the fact that strings are lists in processing them.

 You could look at GHC's FastString representation (used internally).
 It is in $fptools/ghc/compiler/utils/FastString.lhs

It does make sense to have a rather faster form of string conveniently
available in /some/ form.

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Data representation, maybe reflection, laziness

2003-10-31 Thread Mark Carroll
People have been talking about transmitting Haskell values on the GHC
users' list, and I wanted to ask some more general stuff, partly out of
mild ignorance.

Ralf Hinze and Simon Peyton-Jones wrote an interesting paper on generic
programming and derivable type classes. It looked like maybe programmers
would be able to write their own deriving xml stuff and whatever, which
looked great because, if there's not already one out there, I'd love to
derive some read/show analogue automatically for data in some encoding
that's very efficient to write and parse (i.e. not XML (-:).

I was also wondering how the ability to write deriving stuff related to
what one might think of as being reflection - that is, for example, could
a definition of deepSeq be derived that automatically knows how to recurse
into and traverse data structures and make sure everything's evaluated?

This leads me to the point that little of the code I write needs laziness,
but many of my unpleasant performance surprises come from laziness. I do
find it hard to figure out where to put strictness annotations to actually
make things work - for instance, I think it's laziness things that are
causing my uses of Control.Exception.evaluate to actually work more by
trial and error. No doubt it'll all grow clearer in time. Maybe I need
laziness annotations instead. (-:

Still, I was wondering what current thinking and directions were with
regard to any of the above!

-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: force garbage collection?

2003-10-05 Thread Mark Carroll
On Sun, 5 Oct 2003, Abraham Egnor wrote:

 Is there any way to force collection of all unreachable data structures?

I would guess that System.Mem.performGC would be worth a try.

-- Mark
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type design question

2003-07-28 Thread Mark Carroll
On Mon, 28 Jul 2003, Konrad Hinsen wrote:

 What is the general attitude in the Haskell community towards
 compiler-specific extensions? My past experience with Fortran and C/C++ tells
 me to stay away from them. Portability is an important criterion for me.

It depends which ones. Some are implemented in multiple compilers in a
consistent way and widely liked and used, and are rather likely to make it
into the next standard version of Haskell in much their current form. (For
instance, portability is an important criterion for us, too, but we still
use multi-parameter typeclasses.) Others are still sufficiently
experimental that ideas really are just being played with. It would be
interesting to see a list of what people think will make it into Haskell 2
though.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Simple monads

2003-06-26 Thread Mark Carroll
Not really seeing why Unique is in the IO monad, not deeply understanding
the use of Haskell extensions in the State source, and wanting to try to
learn a bit more about monads, I thought I'd try to write my own monad for
the first time: something for producing a series of unique labels. This is
how it turned out:

==
module Label (Label, Labeller, newLabel)
where
import Monad

newtype Label = Label Int deriving (Eq, Ord)

newtype Labeller a = Labeller (Int - (Int, a))

instance Monad Labeller where
return r = Labeller (\n - (n, r))
(Labeller g) = y =
let f m = let (r, n) = g m
  Labeller h = y n
   in h r
 in Labeller f

newLabel :: Labeller Label

newLabel = Labeller (\n - (n + 1, Label n))

runLabeller :: Labeller a - a

runLabeller (Labeller l) = snd (l minBound)

labelTest :: Labeller [Int]

labelTest =
do Label a - newLabel
   Label b - newLabel
   Label c - newLabel
   Label d - newLabel
   return [a,b,c,d]

main = print (runLabeller labelTest)
==

I was thinking that maybe,

(a) People could point out to me where I'm still confused, as revealed by
my code. Is it needlessly complicated?

(b) My code may be instructive to someone else.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Assembling lists start-to-end

2003-06-21 Thread Mark Carroll
I am assembling a list from start to end. I can add elements to the end
with previous ++ [current] or I can add them with current : previous
and reverse it when I'm done. Or, maybe I should use some other data
structure. (I don't know the length in advance.) Any thoughts?

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: African money

2003-03-25 Thread Mark Carroll
On Tue, 25 Mar 2003, Jerzy Karczmarczuk wrote:
(snip)
 Anyway, I am willing to spend a part of this money on your behalf.
 If somebody has any idea how to empoison, strangle, shoot, electrocute
 or burn alive this annoying bastard who proposes regularly to everybody
 on Internet all that financial transactions with Nigeria, Congo, etc.,
 please contact me. You don't even need to do the dirty job. Just show
(snip)

Rich Kulawiec, on Dave Farber's Interesting People list, recently said
interesting things at http://tinyurl.com/84dm

Personally, I like SAUCE at http://tinyurl.com/84dp but it's not for
everyone, or even most people. (Needs to be attached to exim.)

ObHaskell: I have bought my own domain and have got to the point where
soon there will not be a public permanent e-mail address for me. I plan to
write software to help keep public addresses rolling over, keeping track
of which private addresses have been given to whom, what is whitelisted
and blacklisted, etc. I worry a bit about character IO being slow, but
maybe Haskell might be a good implementation language for this system.
Perhaps I'll have to look out for a library for parsing e-mail messages.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Question About lists

2002-12-30 Thread Mark Carroll
On Mon, 30 Dec 2002, Cesar Augusto Acosta Minoli wrote:

 Hello! I'm Working with Lists in Haskell, I´m a Beginner in Functional
 Programming and I would like to know if there is a way to write a more
 efficient function that return the length of a list, I wrote this one:

 long    ::  [a]-Int
 long p =  longitud p 0
    where
    longitud []   s=s
    longitud (x:xs) s=longitud xs (s+1)

 but I think that it have a lineal grow O(n).

Yes, it's O(n), but you can't do any better for calculating the length of
a list. Your second parameter seems to be an accumulator which is the sort
of thing you'd make explicit in an imperative approach but can often be
eliminated in functional code - e.g.,

long [] = 0
long (x:xs) = 1 + long xs

A decent optimizing compiler will probably turn that code into something
that uses an accumulator. This code probably isn't any more efficient than
yours, it's just shorter.

-- Mark

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Parsing date and time specifications

2002-12-20 Thread Mark Carroll
On 20 Dec 2002, Ketil Z. Malde wrote:
(snip)
 Since it's almost Christmas, I'd also like a way to specify things
 like first Tuesday of every month, or the day before (last Thursday
 of every month).  And a GHC target for my Palm Pilot :-)  We could
 build a really cool Cron replacement, and become rich and famous.
(snip)

That is the slippery end of the wedge - next we'll be wanting standard
library functions for calculating when Easter and Id-ul-Fitr are. (-: The
calendar source code I'd referred to before was indeed written to get all
this type of stuff into my m100 - I type calendar 2004 or whatever and
hand that to install-datebook. (Is all the world on a seven-day week? I
wonder how that came about.)

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Parsing date and time specifications

2002-12-19 Thread Mark Carroll
On 19 Dec 2002, Peter Simons wrote:
(snip)
 datatype. It appears that in order to construct one of those, I need
 _all_ the information it contains, including the weekday (Day) and the
 number of the day in the year.

 The problem now is that I do not have this information! Of course I
 could calculate these values by hand, but this is immensely
 complicated.
(snip)
 Any suggestions what I could do?

I have some calendar calculation code in Haskell from which I could easily
generate code to calculate the weekday (Day) and the number of the day in
the year, if it turns out you do end up needing it.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Random

2002-12-17 Thread Mark Carroll
On Tue, 17 Dec 2002, Filipe Santos wrote:

 I need some help to do a function so that I cant get 4 numbers between 1
 and 6, i tried to use random but i can't make it work well.

This might be useful,

import Random

dice :: (RandomGen g) = g - Int - (g, [Int])

dice rng number_rolls =
(iterate next_roll (rng, [])) !! number_rolls
where
next_roll (rng, rolls) =
let (random_number, new_rng) = next rng
in  (new_rng, (mod random_number 6 + 1) : rolls)

main = do rng - newStdGen -- (or getStdGen or something)
  print (snd (dice rng 4))

The dice function gives you back the new state of the rng which maybe
you should keep around to start the next set of rolls with. (main throws
it away with snd.) I'd certainly be interested to see how this could be
written more nicely. I avoided making the list of die rolls an infinitely
long lazy list in case we wanted to use the same RNG for other stuff too
and not have the same RNs reused, but I don't know much about how the RNG
stuff is exactly defined.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Random

2002-12-17 Thread Mark Carroll
On 17 Dec 2002, Ketil Z. Malde wrote:
(snip)
 dice :: Integer - StdGen - [Integer]
 dice n g = take n $ randomRs (1,6) g

Can we still do this concisely and get the new state of the rng back out
the other end after the die has been thrown a few times? Or are things
like newStdGen meant to be so cheap that it's fine to use lots of
different RNGs instead of one that you thread through everything?

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Random

2002-12-17 Thread Mark Carroll
On 17 Dec 2002, Ketil Z. Malde wrote:

 Mark Carroll [EMAIL PROTECTED] writes:
(snip)
  Can we still do this concisely and get the new state of the rng back out
  the other end after the die has been thrown a few times?

 Oops; I missed that part!

No problem - it wasn't exactly clearly part of the original problem
specification. (-: It was good to see what randomRs does, too.

  Or are things like newStdGen meant to be so cheap that it's fine to
  use lots of different RNGs instead of one that you thread through
  everything?

Also, I was wondering if I can or should use monads to thread the RNG
state through everything instead of always returning these two-tuples;
I've been peering at things like Control.Monad.Cont to try to see what
they're good for.

 I've no idea - I've always used StdGen's as if they were going out of
 style.  (You can, of course, `split` them and get two for the price of
 one)

Ah - I was never sure what to make of that - I normally just use the GHC
online Haddockised stuff which tells me no more than the type signatures,
but I suppose split must be more than (\x-(x,x))! (-: (I'll be happy to
help with adding documentation once I'm sure of the semantics myself.)

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Error Handling

2002-12-13 Thread Mark Carroll
On Fri, 13 Dec 2002, Fergus Henderson wrote:
(snip)
 and [slightly] reduced need to use Monads would be outweighed by the
 drawbacks mentioned above, i.e. code bloat and compiler complexity.)

Ah - that's the impression I got from your earlier reply, too.

(snip)
 time-outs or user interrupts.  But if `choose' is only catching
 exceptions raised by explicit calls to throw or error, then
 I think it would be semantically OK, wouldn't it?
(snip)

That would actually be fine - I hadn't been hoping to catch errors that
were things like user interrupts, which sound like they should be monadic
anyway - just things explicitly thrown as you suggest. Admittedly, that is
a rather important point that I should have made - I hadn't actually
thought about errors caused by other stuff going on in the system and I
completely agree that they should be wrapped in monads.

Basically I was just wanting to replace some of the nastiness I have in
code that passes two-tuples of (result, errors) around and has conditional
statements to deal with backing up the functional call chain to deal with
error conditions. What the code is doing can safely be done completely
without monads so I didn't want any monads to be in the top-level type
signature: all the errors involved are all things that were noticed in
normal computation by matching otherwise in a guard and whatever, not IO
or anything.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Error Handling

2002-12-10 Thread Mark Carroll
On 10 Dec 2002, Alastair Reid wrote:
(snip)
 To do this, we have to actually build the set of all exceptions that
 an expression could raise.  This could take quite a while to build

Why? I can see that, to do the ordering, you may want to know all the
exceptions that can arise somewhere in the program, not minding about a
few false positives. Then, at runtime, if an exception pops up, we just
evaluate the other parallel expressions to see what else happens. Even
if we do need the exact set of all exceptions that a particular expression
could raise, could that be found at compile time?

(snip)
 And even this wouldn't get rid of the monads since the problem monads
 deal with is present even if we can't observe the exceptions.  For
 example, a simple operation like this:

   choose :: a - a - a

 which returns its first argument if it can evaluate its argument to
 WHNF without raising an exception and returns its 2nd argument
 otherwise has severe semantic problems.

I don't understand why, I'm afraid. I'm not sure if I'm missing something
obvious or if we're somehow talking at cross-purposes. It probably doesn't
help that I can imagine what it means to evaluate the first argument
strictly but I'm having difficulty figuring out what Weak Head Normal Form
is in relation to what Haskell code might get up to. I seem to have a
problem understanding exactly how mathematical things shore up practical
computing things even when I understand each in isolation, though.

Of course, I am happy to suspend judgment until I understand your point
better, and I don't think that you have any obligation to bring my
education to the point where I can understand it!

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: AW: slide: useful function?

2002-12-02 Thread Mark Carroll
On Mon, 2 Dec 2002, David Bergman wrote:
(snip)
 Till then, we Haskellers will probably continue expressing our
 patterns either directly in Haskell or using highly formal language,
 with terms such as catamorphisms.

 The virtue, and weakness, of traditional design patterns is their
 vagueness and informal character, making them (1) comprehensible to the
 90% of the developer community not familiar with category theory but (2)
(snip)

If there are any good ways in which non-mathematicians can get to grips
with these terms from category theory, they would be well worth promoting.
For example, despite having a good computer science degree (in which I was
at least introduced to FP, proof, etc. and even learned to draw the dual
graph of hypercubes) I'm really not equipped to understand catamorphisms
in terms of algebras and homomorphisms, and don't currently have time to
take the math degree I fear I'd need in order to do so. Last time I was
looking at category theory books I think I came to the conclusion that
Lawvere and Schanuel cover things kindly but Pierce seemed to get the
syllabus right, so the right book wasn't quite out there.

My understanding of monads is already a matter of record. Does anyone know
of a friendly text that might help new Haskellers to understand functors,
etc. and what they mean for program design? I'm not averse to the formal
language per se if it can be easily acquired; right now, I worry that I'm
using Haskell suboptimally because, not only do I not know the terminology
well, but I fear that I'm not even cognisant of the concepts that these
terms represent.

In a nutshell: if these category theory concepts indeed have an important
impact in Haskell land, how to introduce them to working Haskell
programmers well enough that they can use them in engineering software
that's at least half as good as it could be?

(I'm making the assumption here that it would be good for Haskell to be
much more widely used - it shouldn't solely be for researchers.)

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: foldl' ?

2002-11-26 Thread Mark Carroll
On Fri, 22 Nov 2002, Hal Daume III wrote:

 Because List is the H98 module, Data.List is the extended one which
 contains foldl'.  Regardless of whether you say -package data or not,
 you're not going to get Data.List unless you ask for it explicitly:
(snip)

Thanks very much indeed! I finally have it working. (-:

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-22 Thread Mark Carroll
On Sat, 16 Nov 2002, Hal Daume III wrote:

 If it appears in Data.List then you need to import Data.List.  In order to
 do this, you will need a newer (=5.03) version of GHC, if I'm not
 mistaken.

I find it curious that I can do:

cicero:markc$ ghci -package data
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package lang ... linking ... done.
Loading package concurrent ... linking ... done.
Loading package posix ... linking ... done.
Loading package util ... linking ... done.
Loading package data ... linking ... done.
Prelude :type FiniteMap.lookupFM
forall key elt.
(Ord key) =
Data.FiniteMap.FiniteMap key elt - key - Maybe elt
Prelude :type List.isSuffixOf
forall a. (Eq a) = [a] - [a] - Bool
Prelude :type List.foldl'

interactive:1: Variable not in scope: `List.foldl''
Prelude


How come I can get at lookupFM and isSuffixOf but not foldl'? (-:

(Thanks to you and Richard for replies!)

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: re-opening a closed stdin?

2002-11-21 Thread Mark Carroll
On Wed, 20 Nov 2002, Volker Stolz wrote:
(snip)
 The other way involves opening /dev/stdin on hosts that support this
 (with the same limitation as above), including that that's currently
(snip)

Sometimes /dev/tty will work too.

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



foldl' ?

2002-11-16 Thread Mark Carroll
Where do I find foldl' in GHC? It's mentioned on
http://www.haskell.org/ghc/docs/latest/html/base/Data.List.html but
importing List and using -package data don't seem to make it appear. I'm
using GHC 5.02.2. I must be making some simple mistake.

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: deriving (was Re: storing to a file)

2002-11-15 Thread Mark Carroll
On Thu, 14 Nov 2002, matt hellige wrote:
(snip)
 well, here's one way it might work:
 http://research.microsoft.com/~simonpj/Papers/derive.htm

I'll take a look at that - thanks - it might answer a few of my generic
programming questions.

 although i'm not exactly sure what you mean by 'add your own
 deriving things'... :)

I was thinking that it might be nice to be able to write Haskell to add,
say, a deriving XML or deriving ASN1 feature whose instances provide
methods to convert between Haskell data structures and those formats,
instead of having to hack the compiler to achieve such automated method
writing.

BTW, those typed returns on sockets that Shawn mentioned sounded
interesting. IIRC Modula-3 also had some approach to worrying about data
exchange between older and newer versions of the same program.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: storing to a file

2002-11-14 Thread Mark Carroll
On 14 Nov 2002, Johan Steunenberg wrote:

 thanks for your advice, I guess it sweetens the situation, though I
 really would like to know how to store in a binary format.

http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne/haskell_libs/Binary.html
might be interesting for you. Actually, deriving binary would be a nice
thing to have in general - even more, a way to add your own deriving
things from within Haskell, although I have no idea how such a thing would
work.

http://www.pms.informatik.uni-muenchen.de/forschung/haskell-wish-list/items.php3?sort=pmono=y
seems to be a bit broken at the moment so I don't know if that relates to
any proposed extensions. Are there any pages that summarise what people
have learned from trying out already-implemented extensions, to help get
an idea what the next Haskell will be like, or what ideas to try next? For
instance, I expect to see some concurrency and exceptions, multi-parameter
type classes, etc. make it through.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Question about use of | in a class declaration

2002-08-21 Thread Mark Carroll

On Wed, 21 Aug 2002, Christian Sievers wrote:
(snip)
 It might not have become clear from the previous answers:
 this construction is not Haskell 98, but an extension.
 That's why it's not in the report.
(snip)

One issue we have here is that any Haskell we write is stuff we'll
probably want to keep using for a while so, although we've only just got
most of the bugs out of the H98 report, I'll certainly watch with interest
as people come to a consensus about multi-parameter typeclasses,
concurrency libraries, etc. and such things start to look very much like
they'll be fixed in the next round of standardisation. It's hard to know
which are experiments that ultimately will be shunned in favour of
something else, and which are just all-round good ideas. (-:

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Writing a counter function

2002-06-30 Thread Mark Carroll

On Sun, 30 Jun 2002, Jon Fairbairn wrote:
(snip)
 But there's the rub. It's not beautiful and it doesn't make
 much sense. I really wish we could get away from the How do
 I convert this imperative code snippet into Haskell
 questions into How do I solve this abstract problem?

The question as originally posed didn't seem like it particularly needed
something imperative though. For instance, the Perl isn't strongly
imperative - it's largely just a list of declarations and functions (some
anonymous) where you can think of the variables as being locally-declared
constants. For instance, the first bit is very similar to, say,

counter a = (a, \to_add - counter (a + to_add))

I think that's very different from asking people to translate into Haskell
things where variables have their value change and whatever. Jon Cast's
observation makes more sense to me - it's not a imperative/functional
issue so much as a weak or strong typing issue.

(snip)
 I guess that the last $next on the last line should have
 been $next3, but I'm not certain, and I certainly have no
 idea what the programme is /for/.

Yes, I'm sure you're right there.

Thanks very much for sharing the monadic approach - I was curious as to if
monads could be used to break the recursion, and I didn't see anyone else
mention that. I've certainly found Jon Cast's, John Hughes' and Andrew
Bromage's articles interesting - it seems like this is a well-known issue
and Haskell currently lies on an attractive point on the tradeoff between
making things awkward and opening cans of worms.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Writing a counter function

2002-06-29 Thread Mark Carroll

On Sat, 29 Jun 2002, Samuel E. Moelius III wrote:
(snip)
 Here's another not-exactly-what-you-wanted solution.  :)
(snip)

Do any of the experimental extensions to Haskell allow a what-he-wanted
solution? I couldn't arrange one in H98 without something having an
infinitely-recursive type signature. I'm sure it would have been easy in
Lisp, and he already gave a Perl equivalent, so I'm wondering if it could
be at all sane for Haskell to allow such stuff and if Haskell is somehow
keeping us on the straight and narrow by disallowing the exact counter
that was originally requested.

The beauty of his request was that it was so simple and seemed to make
sense; I went ahead and tried to fulfill it before realising I couldn't
do it either.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Constructing Cases

2002-05-24 Thread Mark Carroll

If you can live with f's domain being ordered, I'd probably use something
like f = lookupWithDefaultFM (listToFM list) (-1) importing FiniteMap from
ghc's libraries. HTH.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: SUGGESTION: haskell-announce mailing list

2002-05-11 Thread Mark Carroll

On Sat, 11 May 2002, Jorge Adriano wrote:
(snip)
 I like the actual haskell/haskell-cafe situation.

At least it seemed reasonable to me that many more people would be
interested in discussing proposed changes to the Haskell 98 spec. than
there are in wading through various newbie questions. I think the current
haskell/haskell-cafe distinction allows this quite well, separating
important discussion from other discussion.

-- Mark

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: finding ....

2002-03-20 Thread Mark Carroll

On Wed, 20 Mar 2002, Lennart Augustsson wrote:
(snip)
 examples you gave are broken.  Sometimes it doesn't matter much, but I'd
 hate to see that code like that, e.g., in the control software for an airplane.
 (Or in the kernel for that matter.)

...or, indeed, in any software that might be handling slightly-personal
data on a multi-user system.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Hiring and porting

2002-03-12 Thread Mark Carroll

Thanks, everyone, for your responses! It's all been very helpful. Some
things I should mention, then:

We're based in central Ohio, but are not currently hiring FPers. Whether
we will be in the future depends somewhat on this porting issue. However,
if we do decide to hire any Haskell programmers, I shall mention that
here.

Ideally, yes, we'd look to hire practising programmers who already know
Haskell and wish that they could be using it in their job, although I'd
fear that there may not be enough such people available to us.

The larger application is a simulation engine that involves parsing,
symbolic processing, etc. in which correctness in important and that will
require ongoing improvement and modification, so I was thinking that use
of Haskell would be appropriate. (Use of C++ would make it faster, though,
I expect. (-:)

However, I do fear that Ashley's correct in suggesting that you'd probably
need to rewrite everything to sensibly translate the Haskell to C or Java
or whatever, and it is both reasonable and plausible that some larger
clients will demand use of a more mainstream language in anything that we
deliver to them so that they don't rely on us for maintenance. So, first
we have to figure out if we should use Haskell at all, because a likely
need for a non-trivial port in the future could easily negate, in time and
cost, the initial productivity benefits we might gain from Haskell.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Hiring Haskell programmers

2002-03-11 Thread Mark Carroll

How easy is it to hire reasonable Haskell programmers? Of course, this may
mean, hiring people with the aptitude and interest to quickly learn
Haskell. Has anyone any experience of this that they can share?

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Hiring Haskell programmers

2002-03-11 Thread Mark Carroll

On Mon, 11 Mar 2002, Konst Sushenko wrote:

 I have always been wondering what exactly does quickly learn Haskell
 mean? Quickly learn Haskell syntax? Can one learn how to paint quickly?

Be able to modify or add to the code base within a few weeks, in such a
way that somebody doesn't have to come back later and repair your work.
(-: So, no, not just the syntax: much harder, in my opinion, is to learn
how to phrase even just simple algorithms in an efficient and functional
way. When I first learned Standard ML, after years of imperative
programming, my brain almost hurt for the first few weeks.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Help

2002-02-27 Thread Mark Carroll

On Wed, 27 Feb 2002, Juan M. Duran wrote:

 I got a function with type :: IO [[Double]], and what I want is write this
 output in a file, how can I do it... I mean, I cannot doit by just using
 writeFile
(snip)

Does something like this help at all?

myfn :: IO [[Double]]
myfn = return [[1.346, 4.144], [5.143, 2.453]]

format_doubles :: [[Double]] - String
format_doubles x = foldr (++)  (map format_line x)

format_line :: [Double] - String
format_line [] = \n
format_line x = foldr1 (\x y - x ++ ,  ++ y) (map show x) ++ \n

main = myfn = (\x - return $ format_doubles x) = putStr


Okay, it's not the most readable bit of code, but I'm guessing it covers
the bit that's confusing you.

All the best,
  Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: add something to a list

2002-02-17 Thread Mark Carroll

On Sun, 17 Feb 2002, Jay Cox wrote:
(snip)
 PS:  Anybody got any other suggestions for IO monad entry-level docs?
(snip)

Simon's Tackling the Awkward Squad paper was a revelation for me.

-- Mark

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: oops (was: Re: if-then-else inside a do)

2002-01-30 Thread Mark Carroll

On Wed, 30 Jan 2002, Kevin Glynn wrote:

 I think the Haskell Wiki was going to be the place to collect
 interesting code fragments.

 However,  I must add that these functions are already part of the
 Haskell 98 standard.  See the Monad module in the Library Report.

Ah, cool, both points sound good. Thanks. (-:

-- Mark (still figuring out the wiki)


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: oops (was: Re: if-then-else inside a do)

2002-01-29 Thread Mark Carroll

On Wed, 30 Jan 2002, Bernard James POPE wrote:
(snip)
 when :: (Monad m) = Bool - m () - m ()
 when p s  = if p then s else return ()

 unless   :: (Monad m) = Bool - m () - m ()
 unless p s= when (not p) s
(snip)

That's cute. People post all sorts of handy little code fragments here.
Does anyone collect them together into a sort of here's some useful stuff
that's worth looking at library?

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: reading from file

2002-01-22 Thread Mark Carroll

On Tue, 22 Jan 2002, S.D.Mechveliani wrote:

 Who would tell me, please, what is the simplest way to read a
 string from a file?
 Namely, what has one to set in place of `...' in the program

 main = putStr (...)

 to obtain instead of `...' a string contained in the file
 foo.txt ?

main = readFile foo.txt = putStr

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Integer to String Conversion?

2001-12-03 Thread Mark Carroll

On Tue, 4 Dec 2001, Chris wrote:

 is there a function that converts Integers to Strings and vice versa?

Prelude (reads 123 abc) :: [(Integer, String)]
[(123, abc)]
Prelude show 123
123

HTH. (-:

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: not naming modules Main

2001-11-16 Thread Mark Carroll

On Fri, 16 Nov 2001, Iavor S. Diatchki wrote:
(snip)
 having said all that, there seems to be a bug in ghc (or perhaps
 an implementation restriction), which requires that main is defined
 in the module Main.  the only other haskell implementation i have
(snip)

Actually, what would be nice in ghci is to be able to :load modules that
don't have main defined. Followups should probably go to one of the GHC
lists though, I guess.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: suggestion

2001-10-22 Thread Mark Carroll

On Tue, 23 Oct 2001, Andre W B Furtado wrote:

 What do you all think about activating the mechanism that automatically
 includes the name of the list before the subject of a mailing list email?

I like the idea.

 For example:
 [hugs-users] Installation problems or [haskell] newbie question. I think
 this would be a nice way to make massages more organized and help people who
 sign multiple lists. I heard somewhere that this is possible, isn't it
 Simon?

Yes, this list is run through mailman - one of the general list
configuration options should be the prefix for the subject line of list
postings.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: read-ing scientific notation

2001-10-12 Thread Mark Carroll

On Fri, 12 Oct 2001, Simon Peyton-Jones wrote:

 | GHC is oddly particular about decimal points in read-ing in 
 | of Doubles in scientific notation. It seems that read 
 | 3.0e-06 is acceptable but read 3e-06 is not (both read 
 | 3 and read 3.0 work fine as Doubles). It's the same in 
(snip)
 It's an unforced change and therefore to be regarded with
 deep suspicion. I'd be interested in people's views about this.

I was actually recently caught out by this - I'd assumed that 3e-06 would
work (as it does in Modula-3, etc.), and it didn't. Personally, my
preference would be for it to mean just the same as 3.0e-06 - it's
annoying having to go through my physical constants now adding the
rather-redundant .0's everywhere. (-: But, with the sort of parsing I'm
doing, terms are largely separated by whitespace anyway; maybe if they
weren't I'd want things different.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: help for exercise 4.10

2001-10-11 Thread Mark Carroll

On Fri, 12 Oct 2001, rock dwan wrote:

 Iam having some difficulties doing exercise 4.10 from craft of functional 
 programming book second edition ..is their a possible solution for this ?

How far have you got with it so far? I'm sure we'd prefer to help you
along instead of just giving a solution. Have you done exercise 4.9?

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Namespaces (was Re: GUI Library Task Force)

2001-10-10 Thread Mark Carroll

On Wed, 10 Oct 2001, Hal Daume III wrote:
(snip)
 least) is that the Java compiler knows how to interpret the .s and
 will use them to navigate directory structure.
(snip)

Yes, that's certainly an interesting idea. I'd like to fall short of
mandating anything about location of source files in any language spec,
though: although I can see that people probably find Java's imposed
semantics useful, personally I find them irritating and wouldn't want to
shackle everyone to them.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



= vs -

2001-10-09 Thread Mark Carroll

What is the rationale for when Haskell demands a = and when it demands 
a -? Ideas that occur to me are:

(a) The distinction helps the parser a lot

(b) There's a semantic difference that the language's grammar is trying 
to express that isn't obvious to me

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



newtype | data

2001-10-05 Thread Mark Carroll

Why does newtype exist, instead of letting people always use data and
still get maximum efficiency? After all, surely the implementation is an
implementation detail - a compiler could see the use of data with a
unary constructor and implement it as it does newtype, instead of making
the programmer worry about how things are actually represented?

I'm obviously missing something obvious here; I'm hoping to learn what.
(-:

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: newtype | data

2001-10-05 Thread Mark Carroll

On 5 Oct 2001, Marcin 'Qrczak' Kowalczyk wrote:
(snip)
 It could indeed be represented in the same way, but they behave
 differently in pattern matching: case undefined of T _ - ()
 is () in the case of newtype and undefined in the case of strict data.

Ah. I don't really use error or anything in code that may not need to be
evaluated, which is why I didn't think of (or care (-:) about that! I'm
assuming that other people do!

It's like Lisp, I guess - I rarely used eval, but everyone else seemed to.

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: RFC: GUI Library Task Force

2001-09-24 Thread Mark Carroll

On Mon, 24 Sep 2001, Ch. A. Herrmann wrote:
(snip)
 Many applications where GUIs are used require a canvas/scribble field
 with the following basic functionality:
(snip)

Absolutely. The only reason I've found Java usable is that I can make my
own Canvases and LayoutManagers and 'implement' many GUI components myself
- its standard offering is adequate for the sorts of thing you'd use
VisualBasic for, but not for wierder stuff. (-:

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: RFC: GUI Library Task Force

2001-09-24 Thread Mark Carroll

On Mon, 24 Sep 2001, Ashley Yakeley wrote:

 At 2001-09-24 05:44, Manuel M. T. Chakravarty wrote:
(snip)
 * The library focuses on graphical *user interfaces* (ie,
   buttons, menus, scrollbars, selection lists, etc) as
   opposed to drawing and animation routines.
 
 Java has APIs for both, I believe.

It does indeed, at least enough for my purposes.

(snip)
 * We will not design a purely functional GUI:
 
 Same.

Pity; the idea does sound intriguing. (-: (I know nothing about them
though, hence the smiley.)

 The Plan
 
 * Handling of state altered by both the application and by
   GUI widgets:
 
 I'm not sure what the issue is here.
(snip)

I guess the point is that the application needs to be able to drive GUI
events itself, and it also has to be able to respond to actions by the
user.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



let/where

2001-09-19 Thread Mark Carroll

There seem to be a few situations where it's not clear to me when to use
let and when where. For instance, in this little example I was playing
with to work out what syntax works,

main = putStr (show (if maybe_index == Nothing then DP_Unknown else DP_Number index) 
++ \n)
   where maybe_index = maybe_read word 
 (Just index) = maybe_index

or...

main = let maybe_index = maybe_read word 
   (Just index) = maybe_index
   in putStr (show (if maybe_index == Nothing then DP_Unknown else DP_Number 
index) ++ \n)

Does anyone care? At the moment I use where so that at a first glance
you get an overall idea of things, then you can read further for details
if you like.

I was disappointed to find that I don't seem to be able to write things
like,

main = let maybe_index = maybe_read word 
   in putStr (show (if maybe_index == Nothing then DP_Unknown else DP_Number 
index) ++ \n)
  where (Just index) = maybe_index

BTW, is the above a sane way of getting the 'index' 'out of' the Just?
I often seem to be using a where (Just foo) = bar type of idiom.

(Of course, there is that special let stuff for do notation too
which doesn't seem to use in.)

I hope all that was somewhat coherent, anyway, or at least sheds light on
some of the confusion of newcomers to Haskell!

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: let/where

2001-09-19 Thread Mark Carroll

Thanks very much everyone, especially for the notes about the differences
between let and where, and the uses of case and maybe! Someday it
would be interesting to try a programming assignment and comparing my
coding style with the useful idioms that everyone else uses to see how
much I still have to learn. (-:

-- Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



  1   2   >