Re: Pascal Line in Haskell

2003-08-22 Thread Andrew J Bromage
G'day all.

On Fri, Aug 22, 2003 at 09:40:12AM +1000, Job L. Napitupulu wrote:

 Can anyone help me how to make a function which takes an integer n  0 and
 returns the list of integers in Line of Pascal's Triangle. For examples,
 
 pascalLine 4 - [1,4,6,4,1]
 pascalLine 7 - [1,7,21,35,35,21,7,1]

This should do the trick.

Cheers,
Andrew Bromage

8---CUT HERE---8

type InfTable a = [(Integer, BinTree a)]
data BinTree a = Leaf a | Node Integer (BinTree a) (BinTree a)

swing :: Integer - Integer
swing n = rec n (\_ _ r - r)
  where
 rec :: Integer - (Integer - Integer - Integer - Integer) - Integer
 rec n k
   | n  2
 = k 1 1 1
   | otherwise
 = rec (n `div` 2) (\nn ff r - swing' n nn ff
 (\nn' ff' - k nn' ff' $! (r*r*ff')))

 swing' :: Integer - Integer - Integer -
 (Integer - Integer - Integer) - Integer
 swing' n nn ff k
   | nn `mod` 2 == 1 = swing_odd k nn ff
   | otherwise   = swing_even k nn ff
 where
 swing_odd k nn ff
   | nn = n   = swing_even k (nn+1) $! (ff*nn)
   | otherwise = k nn ff

 swing_even k nn ff
   | nn = n   = swing_odd k (nn+1) $! (ff*4 `div` nn)
   | otherwise = k nn ff

recProd :: Integer - Integer - Integer
recProd b n
  | n  5
= case n of
 0 - 1
 1 - b
 2 - b*(b+1)
 3 - b*(b+1)*(b+2)
 4 - (b*(b+1))*((b+2)*(b+3))
  | otherwise
= let n2 = n `div` 2
  in recProd b n2 * recProd (b+n2) (n-n2)

pascalLine :: Integer - [Integer]
pascalLine n
  | n = 0 = searchTable n table
  where
 table :: InfTable [Integer]
 table = buildInfTable 1 5

 buildInfTable n i
= (nextn, buildInfTable' n i) : buildInfTable nextn (i+1)
 where
 nextn = n + 2^i

 buildInfTable' base 0
 = Leaf [ c base k | k - [0..base] ]
 where
 c m n
| m  0  = 0
| n  0 || n  m = 0
| n  m `div` 2  = c' n (m-n)
| otherwise  = c' (m-n) n
 c' i j = recProd (i+1) j `div` swing j
 buildInfTable' base i
 = Node (base + midSize)
(buildInfTable' base (i-1))
(buildInfTable' (base + midSize) (i-1))
 where
 midSize = 2 ^ (i-1)

 searchTable x ((x',tree):ms)
 | x  x'= searchTree x tree
 | otherwise = searchTable x ms

 searchTree x (Leaf y) = y
 searchTree x (Node mid l r)
 | x  mid   = searchTree x l
 | otherwise = searchTree x r

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


Re: Homework

2003-08-22 Thread Frank Seaton Taylor
- I leave this morning for ICFP.

- My laptop is broken, so I can't work on code for this on the plane.

- The delights of Sweden will go less noticed, since the number 
theorist in me will not let me forget. (It's already saying, It's such 
a simple description, how hard can it be? Just give it some thought.)

This was cruel timing. ;-)

---Frank

On Friday, Aug 22, 2003, at 02:25 US/Eastern, Andrew J Bromage wrote:

G'day all.

On Fri, Aug 22, 2003 at 03:41:14PM +1000, [EMAIL PROTECTED] 
wrote:

Seeing as its thst time of year again and everyone is posting their
homework, has anyone got any good puzzles to do?
I wouldn't mind having a go at something a bit tricky.
OK, here's a tricky problem.

Take a list S.  Delete some elements from the list.  What you have
left is a subsequence of S. For example, [1,3,2] is a subsequence of
[2,1,2,1,3,2,1,3].
Consider the following list:

	[1,2,3,1,2,3,1]

This list contains all permutations of the list [1,2,3] as
subsequences.  It is also minimal, in the sense that there is no 
shorter
subsequence which will do (though there are potentially many minimal
subsequences).  We will call such a list a shortest supersequence
over the alphabet [1..3].

The challenge is multi-part.  You may answer as many or as few 
questions
as you want.

   1. Write a function sss :: Int - [Int] where sss n is a shortest
  supersequence over the alphabet [1..n].  Make this as efficient
  as possible.  Prove an upper-bound complexity on your function.
   2. Write a function sss_length :: Int - Int where sss_length n is
  the length of a shortest supersequence over the alphabet [1..n].
  Make this as efficient as possible.  Prove an upper-bound
  complexity on your function.
  If you can't solve this problem efficiently, write a function
  sss_length_bounds :: Int - (Int,Int) which returns the best
  upper and lower bounds that you can.
  (Hint: n is a trivial lower bound, n^2 is a trivial upper
  bound.  A tighter upper bound is n^2-n+1.  Prove this as an
  exercise.)
   3. Write a function sss_count :: Int - Int where sss_count n is
  the number of shortest supersequences over the alphabet [1..n].
  Make this as efficient as possible.  Prove an upper-bound
  complexity on your function.
  (Hint: sss_count n must be a multiple of n factorial.  Why?)

  If you can't solve this problem efficiently, write a function
  sss_count_bounds :: Int - (Int,Int) which returns the best
  upper and lower bounds that you can.
Incidentally, I don't have sub-exponential answers to any of these
questions.  You did ask for something a bit tricky.
Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Urgent business assistance

2003-08-22 Thread Ola Abiola
Monsieur/Madam,

Tout d’abord, je voudrais solliciter votre ultime
confidence pour cette
proposition. C’est par la vertu de la nature de la
transaction qu’il
est nécessaire d’être confidentiel et plus discret.
J’ai obtenu votre
adresse dans l’annuaire de votre pays . Je
suis Mr. Ola ABIOLA, le fils du chef BASHORUN MKO
ABIOLA qui était mort
en détention politique le 7 juillet 1998.

Mon père avait contesté l’élection présidentielle au
Nigeria du 12 juin
1993 qu’il avait gagné mais annulée. Il était empêché
du fauteuil
présidentiel par l’ancienne association du nord dans
le pays connue
populairement commeKADUNA MAFIA. Cette assoc
iation regroupe les anciens chefs d’Etats militaire et
la dernière
junte militaire Général SANI ABACHA qui est mort le 8
juin 1998. Ils ont
juré de ne pas abdiquer le fauteuil présidentiel à un
sudiste,
revendiquant que le fauteuil est pour les natifs du
nord. Pour se débarrasser de mon père, ils
raisonnaient que mon père
avait dépensé de l’argent pour gagner le mandat du
public, d’où
l’annulation de l’élection . La situation s’est
empyrée la veille du 12 juin,
Ier anniversaire(11 juin 1994) lorsque mon
père s’est déclaré président de la République Fédérale
du Nigeria. Pour
cette raison, la junte déclare que mon père est
recherché. Il fut arrêt
» et il n’était pas ni jugé ni libéré jusqu’à sa mort.

En outre, ma mère ALHADJA KUDIRAT ABIOLA qui luttait
pour la libération
de mon père fut assassiné par des inconnus armés le 4
juin 1996. Il
faut noter qu’avant la mort de ma mère, elle avait
déposée une somme de
35.300.000 US$(trente cinq million trois c
ent mille) de dollars Américains auprès d’une
compagnie de sécurité et
ceci appartenait à mon père. Mon père était un
polygame et depuis sa
mort il y a des problèmes à cause du partage de sa
richesse et mes
frères(de mère différente) faisaient tout pour
s’asseoir sur les biens de mon père, d’où ma décision
de transférer ce
fonds à un étranger qui m’aidera pour son
investissement dans une
affaire lucrative à mon profit et à celui de mon petit
frère, comme de même
père et de même mère et qui arrangera au
ssi ma résidence dans son pays.

Notez bien que ma famille n’est pas au courant de
cette transaction,
c’est uniquement vous et la compagnie de sécurité et
assurez-vous que
cette transaction ne sera jamais sue par ma grande
famille et les gens du
Nigeria. J’ai décidé d’exécuter cette aff
aire ici à Lomé-Togo d’où ma résidence temporaire,
pour des raisons de
sécurités.

Soyez informé que toutes les modalités nécessaire pour
le transfert de
ce fonds ont été parfaites et la transaction est à
100% de hors risque.
D’ailleurs, les militaires sont rentrés dans les
casernes et le Nigeria
a maintenant un gouvernement démocratiq
ue. Vous êtes libres de m’informer dans votre réponse
à cette lettre
votre commission en pourcentage sur le montant total
pour votre
assistance. Notez tout de même que les 5% de la somme
totale reste pour les
dépenses pouvant être contractées pour le pro
cessus de la transaction. Contactez- moi et je vous
donnerez l’image
complète de ce projet.

Dans l’attente de votre réponse rapide, veuillez
agréer l’__expression
de mes sentiments les plus sincers.

Ola ABIOLA



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


ML like pattern matching

2003-08-22 Thread Cagdas Ozgenc



Greetings,

How do I emulate the "when" clause in ML for 
pattern matching? In other words when a pattern is matched (from a list of 
patterns of a function)and to enforce additional predicates I use guards, 
but if the guard condition is not satisfied I want Haskell toget back 
totrying theremaining patterns.

Thanks




Re: ML like pattern matching

2003-08-22 Thread Jonas Ritter
Hi

Cagdas Ozgenc wrote:
Greetings,
 
How do I emulate the when clause in ML for pattern matching? In other 
words when a pattern is matched (from a list of patterns of a 
function) and to enforce additional predicates I use guards, but if the 
guard condition is not satisfied I want Haskell to get back to trying 
the remaining patterns.
 
Thanks
Maybe you hav to reorganize the list of patterns or you use
otherwise as the last case of your guard conditions to call the 
function with a more general parameters which matches an other pattern.
A litle example would be helpfull.

Jonas

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


FFI Ptr CFile problem

2003-08-22 Thread Christoph Flamm
hi,

my problem is as follows:

I have a c-function bla() which gets a stream for reading ( FILE *rx ).
Within bla() alternating a c-function getlineC() and a haskell-function
getlineHS() should read a line from stream rx and print it.

void bla ( FILE *rx ) {
 char *line

 for ( ;; ) {
  line = getlineC( rx );
  printf ( %s\n, line );
  free( line );

  line = getlineHs( rx );
  printf ( %s\n, line );
 }
}

How do i pass the stream FILE *rx to the haskell-function properly?

I tried to pass FILE *rx as a Ptr Cfile and converting it back into
something of type Handle in getlineHS,

\begin{code}
module Cfile ( getLineHs ) where

import IO
import Foreign ( Ptr )
import Foreign.C.Types ( CFile, CInt )
import Foreign.C.String ( CString, newCString )
import System.Posix.IO ( fdToHandle )

foreign export ccall getLineHs getLineHs :: Ptr CFile - IO (CString)
getLineHs :: Ptr CFile - IO (CString)
getLineHs file
= do
  hdl - getInStream file
  hGetLine hdl = newCString 

foreign import ccall stdio.h fileno cfileno :: Ptr CFile - IO CInt
getInStream :: Ptr CFile - IO (Handle)
getInStream f = cfileno f = fdToHandle . fromIntegral
\end{code}

but this doesn't work (i seem to lose the file position indicator)
and i get the following error:

Fail: end of file
Action: hGetLine
Handle: {loc=file descriptor: 3,type=readable,
 binary=True,buffering=block (8192)}
File: file descriptor: 3

If i pass the file position indicator explicitly as a double value between
c and haskell and use the functions hTell/hSeek, ftell/fseek to get/set the
file position indicator the whole thing works for files but doesn't work
for pipes.

Any help would be appreciated.

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


Re: ML like pattern matching

2003-08-22 Thread Ganesh Sittampalam
On Fri, 22 Aug 2003 15:49:15 +0300, Cagdas Ozgenc [EMAIL PROTECTED]
wrote:

How do I emulate the when clause in ML for pattern matching? In other 
words when a pattern is matched (from a list of patterns of a function) and 
to enforce additional predicates I use guards, but if the guard condition is 
not satisfied I want Haskell to get back to trying the remaining patterns.

I may be confused about what you're asking for, but Haskell does this by
default:

foo (Left x) | x3 = bar
foo _ = splat

Main foo (Left 5)
bar
Main foo (Left 1)
splat


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


Re: ML like pattern matching

2003-08-22 Thread Cagdas Ozgenc
Thanks.

I was reading some codes in ML, and it was commented this was the case. I
didn't know Haskell had the equivalent behavior. I always thought once the
pattern was matched there is no going back.

 I may be confused about what you're asking for, but Haskell does
 this by default:

 foo (Left x) | x3 = bar
 foo _ = splat

 Main foo (Left 5)
 bar
 Main foo (Left 1)
 splat


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


Re: Numbers again

2003-08-22 Thread Jon Fairbairn
On 2003-08-22 at 18:39+0200 Konrad Hinsen wrote:
 I am getting a bit worried about the usability of Haskell
 for numerical work.  The Haskell 98 report states that
 floating literals are represented as a conversion from
 Rational, which means that the literal is first converted
 to a Rational. I can't find anything in the Haskell report
 that states how this conversion should take place, and to
 what precision it should be correct. It could be made
 correct to any precision as Rationals are represented
 using Integers, but at least Hugs doesn't do that. By
 experimenting with some particular cases, I found that its
 internal Rational representation is even less accurate
 than the precision of Double permits, which means that it
 is impossible to specify literals to the full precision of
 Double. GHC behaved fine in my tests. But what can I
 safely assume from a Haskell implementation?

You can safely assume that (as it says in its documentation)
Hugs is not suitable for numeric work.  proper¹ Haskell
implementations ought to use conversions that give the best
possible accuracy for the final type.

 Jón

[1] not that Hugs isn't proper, but it's just not designed
for that.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Puzzle

2003-08-22 Thread Ralf Hinze
| Seeing as its thst time of year again and everyone is posting their
| homework, has anyone got any good puzzles to do?
| I wouldn't mind having a go at something a bit tricky.

Here is another one: figure out what `unknown' is.

 unknown   =  mysterious unknown

 mysterious ks =  0 : weird ks
 weird (k : ks)=  (k + 1) : mysterious ks

Cheers, Ralf

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


Re: Monads and Maybe

2003-08-22 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 C T McBride [EMAIL PROTECTED] wrote:

 My point, however, is not to use $ with that type, but the more general
 
   class Fun f where
 eta :: x - f x
 ($) :: f (s - t) - f s - f t
 
 Is there a better name for Fun? Is it ancient and venerable?

Ancient and venerable almost certainly, but not well-known. Lost 
Knowledge of Haskell, perhaps. People keep reinventing this class (which 
is a subclass of Functor btw).

In HBase I call it FunctorApplyReturn. My hierarchy looks more or less 
like this:

  class HasReturn f where
return :: a - f a -- eta

  class Functor f where
fmap :: (a - b) - f a - f b

  class (Functor f) = FunctorApply f where
fApply :: f (a - b) - f a - f b   -- ($)
fPassTo :: f a - f (a - b) - f b
() :: f a - f b - f b
fPassTo = liftF2 (\a ab - ab a)

  liftF2 func fa = fApply (fmap func fa)

  class (FunctorApply f,HasReturn f) = FunctorApplyReturn f

  instance (FunctorApply f,HasReturn f) = FunctorApplyReturn f

  class (FunctorApplyReturn f) = Monad f where
(=) :: f a - (a - f b) - f b
fail :: String - f a;
fail = error;
 
Certain functions that seem to require Monads actually work with any 
FunctorApplyReturn. For instance:

  class (Functor f) = ExtractableFunctor f where
fExtract :: (FunctorApplyReturn m) = f (m a) - m (f a)

  for :: (ExtractableFunctor f,FunctorApplyReturn m) =
(a - m b) - (f a - m (f b));
  for foo fa = fExtract (fmap foo fa)

All sorts of useful types such as [] and Maybe can be made 
ExtractableFunctors. And then 'for' can iterate on them.

IMO something like all this should be in the standard libraries. The 
downside is that people would have to make instances for HasReturn, 
Functor and FunctorApply with every Monad instance.

-- 
Ashley Yakeley, Seattle WA

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