On Wed, 13 Jul 2005, Alberto Ruiz wrote:
> But now I have two problems:
>
> 1) If I define
>
> foo :: Vector.T a -> Matrix.T a
>
> Haddock (version 0.6) shows just this:
>
> foo :: T a -> T a
>
> I don't know how to tell haddock that I want the full names in the signatures.
I don't know, too. I'
Hello! I have a few doubts concerning the LinearAlgebra library...
On Friday 08 July 2005 11:29, Henning Thielemann wrote:
>I would remove the 'matrix' portions of the function names, since this
>information is already contained in the module name. E.g. after importing
>LinearAlgebra.Matrix as Mat
Of course I can't be sure about speed. If you make a recursive call it
will need to check all the guarded cases, by computing the range of
quantity it is doing the same work one additional time to get most, but
then avoid the work of checking the final failing case that the other
solutions relied
it's because of the impreative approach. Seem more elegent than a functional
approach.
Where is the best place to find out about Monads. The book by Richard Bird
is pretty confusing.
From: Radu Grigore <[EMAIL PROTECTED]>
Reply-To: Radu Grigore <[EMAIL PROTECTED]>
To: Dinh Tien Tuan Anh
On 7/13/05, Dinh Tien Tuan Anh <[EMAIL PROTECTED]> wrote:
> i guess i have to learn Monads then, ^_^
That's probably a good idea. But what about this problem made you
think "monads"? Caching? The imperative solution you mentioned?
--
regards,
radu
http://rgrig.blogspot.com/
___
Thanks for all your solutions
It seems that recursion is the only way.
i thought it is a variation of the "integer parition" problem so that can be
solved linearly (by generating next solution in (anti)lexicographic order)
i guess i have to learn Monads then, ^_^
Cheers
From: Kurt <[EMAIL
Okay, I like Cale's extra guard short circuit so much I must add it to
my pseudo-example.
Cale's guard:
> amount `div` maximum coins > maxCoins = [] -- optimisation
Mine, updated.
>
> partition (x:xs) m k | x>m = partition xs m k-- x is too big
>
> parititon (x:_) m k | x*k < m = []
On 7/13/05, ChrisK <[EMAIL PROTECTED]> wrote:
> Sort the list of integers, highest at the front of the list.
> (And perhaps remove duplicates with nub)
The first time I wrote in the comments that 'partition' takes a
"decreasing list of integers..." and then I decided to drop
"decreasing". Weakest
Here's mine, which is similar to Cale's, although done before I saw his:
coins = reverse [1,5,10,25]
change' 0 = [[]]
change' amt =
concat $ map subchange $ filter (amt >=) coins
where
-- recursively make change
subchange c =
map (\l -> c:l) $ filter (canon c)
heh, just noticed that the (amount > 0) test in the last guard is
unnecessary (other cases added since then leave only that as a
possibility) and it can be replaced by "otherwise", not that it makes
too much of a difference:
> import Monad
> import List
>
> makeChange :: [Integer] -> Integer -> I
Well, I don't have time to do more than comment, but here are few
improvements:
Sort the list of integers, highest at the front of the list.
(And perhaps remove duplicates with nub)
When you pop the first element you can already compute the range of
quantity you will need, and can perhaps special
Here's my little recursive solution:
import Monad
import List
makeChange :: [Integer] -> Integer -> Integer -> [[Integer]]
makeChange coins amount maxCoins
| amount < 0 = []
| amount == 0 = [[]]
| null coins = []
| amount `div` maximum coins > maxCoins = [] -- optimisation
|
On 08 July 2005 18:22, Olaf Chitil wrote:
> In fact, unsafeInterleaveIO shows up limitations of the IO monad.
> Without this strange primitive (what is actually unsafe about it?)
Just picking up on this point: unsafeInterleaveIO is so named because it
lets you write programs that don't obey the u
On 7/13/05, Dinh Tien Tuan Anh <[EMAIL PROTECTED]> wrote:
> Any idea ?
This is the first thing I wrote when i read your problem:
=== begin integer_partition.lhs ===
This is a solution to a question asked on Haskell cafe. The problem
looks like a classical one.
You are given a list of positive in
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
Hi,
The problem is:
Given an amount of money m, and unlimited coins of value 1p, 2p, 5p, 10p,
20p, 50p, £1 and £2
List ALL (distinct) ways of change for m, using no greater than k coins
eg: m = 75, k = 5
=> [50, 20, 5]
[50, 20, 1,2,2]
..
..
16 matches
Mail list logo