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 c
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
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,
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.Ma
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 e
On Tue, 31 May 2005, Daniel Fischer wrote:
(snip)
> The module Set has undergone major changes - look at the code and admire, if
> you have it. Formerly sets were implemented as 'FiniteMap's, now as
> size-balanced trees. Formerly there was a function called 'mapSet', now
(snip)
I'm puzzled: wasn'
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@
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
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 structur
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 un
> 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 Fun
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
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 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]
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 c
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 :: Nu
On Fri, 4 Mar 2005, Sam G. wrote:
> Thaks a lot for your contribution, this helps me a lot, I see what I've got
> to do.
> However, I understand the first version (Stack.hs), but I can't get what
> StateM.hs is. Is
> it the same version but using state transformers, so as to be able to do IO
>
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 wi
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
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 fo
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 exp
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).
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
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 mar
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 wo
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, wi
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 =
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 I
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 a
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
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 wh
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
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 instanc
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
This raises for me the more general question of, what should I read so
that I can more easily get a handle on what Haskell's arrows and monads
have to do with similar category-theory concepts? I can find plenty about
Haskell's monads, and there seem to be plenty of computer science category
theory
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
m
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 thing
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
I have data objects where each component is a labelled field through which
I access or modify it. I have a hierarchy of these - many of the fields
are themselves such data objects, so I may need to apply a few selector
functions to get down to what I want (call these "deep").
For fairly flat thing
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
___
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 fr
On Sun, 8 Feb 2004, Justin Walsh wrote:
> Can anyone recommend a very thin Linux/Haskell setup for DHCP cable?
I'm not sure what the relevance of the "DHCP cable" is; I can't think of
an interpretation of it that would cause me to worry much about bandwidth
usage at all. Debian makes it easy to i
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
clea
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
> handl
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
On Wed, 7 Jan 2004, Peter Robinson wrote:
> information of "javavm" to /opt/ghc/lib/ghc-6.2/package.conf.
> After removing those options (-rpath,...) from "extra_ld_opts = []" in the
Thanks! This was of great help. It all works if I do what's illustrated here:
$ diff /usr/lib/ghc-6.2/package.con
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/listin
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
>
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
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")
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
(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 [
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 program
On Thu, 4 Sep 2003, Nick Name wrote:
> I am just curios to hear from people who do not use haskell for project
> releases, or just think it's not suitable for a mature project, what
> exactly they find bad in current haskell implementations, or perhaps in
> the standard.
We're not really there ye
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 impl
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
ho
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
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 financ
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, an
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
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
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 newStdGe
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 rn
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.
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 p
On Sun, 8 Dec 2002, John Meacham wrote:
(snip)
> throw (userException "foo") + throw (userException "bar")
>
> without defining an evaluation order you cannot know which exepction is
> to be thrown. catching the exception in the IO monad makes this 'okay'
(snip)
Would it help if you defined an ord
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
> vag
On Fri, 15 Nov 2002, George Russell wrote:
> The TimeExts library probably does most of what you want. I really ought to
>Haddockify
> the comments some time . . .
Heh - this reminds me that one problem I often have with the GHC online
library Haddock docs is that many library function definit
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 y
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,
The company I'm involved with - Aetion, a tiny defense contractor in
Columbus, Ohio - will likely be wanting to hire an affordable Haskell
programmer before the end of the year. So, on the offchance that any of
you guys are be interested, or know of someone who might be, feel free to
e-mail me for
On Wed, 30 Oct 2002, Andrew J Bromage wrote:
(snip)
> main = do foo <- bar
> return foo
> ^ offside error, Haskell interprets this as not being
> part of the do expression
Gosh, I find that unintuitive, given, say,
http://www.zvon.org/other/h
The Libraries and Tools For Haskell page has quite a list of things, but a
few broken links, and links to very many projects that seem to have
started off as interesting research projects that, as the page itself
says, were more proofs of concept and are no longer maintained.
We can't help but be
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
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 questio
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 signatur
On Sat, 29 Jun 2002, Shlomi Fish wrote:
(snip)
> counter n = (n,(counter (n+1)))
(snip)
This doesn't work because you seem to be defining an infinitely deep tuple
(1,(2,(3,(4,() which is naughty.
I'm not really sure what alternative to suggest beyond [n .. ] without
knowing more about wh
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/ma
On 17 May 2002, Jens Petersen wrote:
(snip)
> I don't have a strong opinion on this either way, however I
> agree with some of the earlier comments that it only really
> makes sense to have two different lists if their agenda are
> more clearly distinct. (IMHO "cafe" is too vague.)
"cafe" has th
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 han
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,
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
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
One criticism I've received of the suggestion that we use Haskell in our
business is that some particularly large clients will demand code in some
'standard' language that they know they can deal with, especially if they
end up stuck with the software and we stop supporting it.
How are others dea
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.
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:
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 so
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 o
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
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 solu
On 10 Oct 2001, Ketil Malde wrote:
(snip)
> function definitions. Perhaps one could have had a syntax like
>
> z a =
> | a == 1 -> 1
> | a == 2 -> 3
>
> instead, as it'd make it more consisten with the case, but I suppose
> there's a reason for it being the way it is
On Tue, 9 Oct 2001, Ashley Yakeley wrote:
> At 2001-10-09 11:55, Mark Carroll wrote:
>
> >What is the rationale for when Haskell demands a "=" and when it demands
> >a "->"?
>
> What? Example please...
e.g.
x :: Integer -> Integer
y :: Int
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
___
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 anythi
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 pr
On Tue, 2 Oct 2001, Cagdas Ozgenc wrote:
> Do I ALWAYS need to create a new instance if I want to modify the state of
> an instance? For example, if I design an index for a simple database with an
> recursive algebric Tree type, do I need to recreate the whole Tree if I
> insert or remove an elem
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 st
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
To multiply apply a function, I'm currently using:
multiplyApply f n a = (iterate f a) !! n
...is there a Prelude function I've missed that already does this?
Could I be doing this better?
-- Mark
___
Haskell-Cafe mailing list
[EMAIL PROTECT
On Sat, 15 Sep 2001, Ashley Yakeley wrote:
> At 2001-09-15 08:31, Mark Carroll wrote:
>
> >AFAICS a simple way to get
> >out of this is to only have one exception type that carries no information
> >instead of different ones so we can't distinguish one exceptio
1 - 100 of 111 matches
Mail list logo