[Haskell-cafe] Numeric Class Problem

Dennis Buchmann dBuchmann at gmx.net
Sun Jan 28 13:01:48 EST 2007


I've got a little problem i don't understand.
I need to calculate an index for a list (by use of !!).
It should look like this:
	floor(j * (n / p2n))
where j is an Integer, n is the length of a list, therefore Integer too,
and p2n is 2^n.

When i use the former line in my Haskell code (pasted at the end of  
this mail),
i get the following error message:

qc.lhs:464:16:
     No instance for (RealFrac Int)
       arising from use of `floor' at qc.lhs:464:16-36
     Possible fix: add an instance declaration for (RealFrac Int)
     In the expression: floor (j * (n / p2n))
     In the definition of `i': i = floor (j * (n / p2n))
     In the definition of `genUf'':
         genUf' f j n
                  | j == p2n = []
                  | otherwise
                  = [(replicate (j + (y1 - y0)) 0)
                   ++
                     ([1] ++ (replicate (p2n - ((j + (y1 - y0)) + 1))  
0))]
                  ++
                    (genUf' f (j + 1) n)
                  where
                      y0 = mod j 2
                      y1 = xor y0 (f !! i)
                      xor a b = mod (a + b) 2
                      p2n = (2 ^ n)
                      i = floor (j * (n / p2n))
Failed, modules loaded: none.

------------------------------------------------------------------------

genUf :: [Int] -> QOp
genUf f = (QOp(genUf' f 0 (length f)))
    where p2n = 2 ^ (length f) {- ok -}
genUf' f j n
    | j == p2n = [] {- ok -}
    | otherwise =
       [(replicate (j+(y1-y0)) 0)
       ++ [1] ++
       (replicate (p2n-(j+(y1-y0)+1)) 0)]
       ++ (genUf' f (j+1) n)
       where y0 = mod j 2
             y1 = xor y0 (f!!i)
             xor a b = mod (a+b) 2
             p2n = (2 ^ n)
             i = floor (j * (n / p2n))



More information about the Haskell-Cafe mailing list