[Haskell-cafe] Typing problem

Steffen Schuldenzucker sschuldenzucker at uni-bonn.de
Mon Jan 31 19:36:35 CET 2011


Michael,

just leaving out the type declaration for 'normalize', your module 
complies fine and ghc infers the following type:

normalize :: (Integral a, Floating a) => [a] -> a -> a

Note that the context (Integral a, Floating a) cannot be met by any of 
the standard types. (try in ghci: ":i Integral" and ":i Floating")
So we have to apply a conversion function like this: (I just replaced 
len by len' at all occurrences)

 > normalize l = let (total,len) = sumlen l
 >                  len' = fromIntegral len
 >                  avg = total/len'
 >                  stdev = sqrt $ ((/) (len'-1)) $ sum $ map ((** 2.0) 
. (subtract avg)) l
 >              in  ((/) stdev) . (subtract avg)

yielding a type of

normalize :: (Floating b) => [b] -> b -> b

You could save the conversion by allowing a more liberal type for 
'sumlen'. Without the type signature, it is inferred to

sumlen :: (Num t, Num t1) => [t] -> (t, t1)

-- Steffen

On 01/31/2011 06:29 PM, michael rice wrote:
> I'm mapping a function over a list of data, where the mapping function is
> determined from the data.
>
> g f l = map (g l) l
>
> So
>
> g serialize "prolog"  ->  [4,5,3,2,3,1]
>
> But I'm having typing problems trying to do a similar thing with a 
> function
> that statistically normalizes data.
>
> See:
> http://people.revoledu.com/kardi/tutorial/Similarity/Normalization.html#Statistic
>
> So
>
> g normalize [2,5,3,2]  ->  
> [-0.7071067811865475,1.414213562373095,0.0,-0.7071067811865475]
>
> Is my typing for normalize too loose. Should I be using Floating 
> rather than Num?
>
> Michael
>
> =======Code==============
> {-
> See Problem 42, pg. 63, Prolog by Example, Coelho & Cotta
>
> Generate a list of serial numbers for the items of a given list,
> the members of which are to be numbered in alphabetical order.
>
> *Main> serialize "prolog"
> [4,5,3,2,3,1]
> *Main> serialize "int.artificial"
> [5,7,9,1,2,8,9,5,4,5,3,5,2,6]
>
> *Main> ["prolog"] >>= serialize
> [4,5,3,2,3,1]
> *Main> ["int.artificial"] >>= serialize
> [5,7,9,1,2,8,9,5,4,5,3,5,2,6]
> -}
>
> import Data.Map hiding (map)
> import Data.List
>
> {-
> serialize :: [Char] -> [Int]
> serialize l = map (f l) l
>               where
>                 f = ((!) . fromList . ((flip zip) [1..]) . (sort . nub))
> -}
>
> serialize :: (Ord a, Integral b) => [a] -> a -> b
> serialize = ((!) . fromList . ((flip zip) [1..]) . (sort . nub))
>
> g f l = map (f l) l
>
> normalize :: (Num a, Num b) => [a] -> a -> b
> normalize l = let (total,len) = sumlen l
>                   avg = total/len
>                   stdev = sqrt $ ((/) (len-1)) $ sum $ map ((** 2.0) . 
> (subtract avg)) l
>               in  ((/) stdev) . (subtract avg)
>
> sumlen :: (Num a, Integral b) => [a] -> (a,b)
> sumlen l = sumlen' l 0 0
>            where sumlen' [] sum len = (sum,len)
>                  sumlen' (h:t) sum len = sumlen' t (sum+h) (len+1)
> =========================
>
> Prelude> :r
> [1 of 1] Compiling Main             ( serialize2.hs, interpreted )
>
> serialize2.hs:34:32:
>     Could not deduce (Integral a) from the context (Num a, Num b)
>       arising from a use of `sumlen' at serialize2.hs:34:32-39
>     Possible fix:
>       add (Integral a) to the context of
>         the type signature for `normalize'
>     In the expression: sumlen l
>     In a pattern binding: (total, len) = sumlen l
>     In the expression:
>         let
>           (total, len) = sumlen l
>           avg = total / len
>           stdev = sqrt
>                 $   ((/) (len - 1)) $ sum $ map ((** 2.0) . (subtract 
> avg)) l
>         in (/ stdev) . (subtract avg)
>
> serialize2.hs:36:61:
>     Could not deduce (Floating a) from the context (Num a, Num b)
>       arising from a use of `**' at serialize2.hs:36:61-66
>     Possible fix:
>       add (Floating a) to the context of
>         the type signature for `normalize'
>     In the first argument of `(.)', namely `(** 2.0)'
>     In the first argument of `map', namely
>         `((** 2.0) . (subtract avg))'
>     In the second argument of `($)', namely
>         `map ((** 2.0) . (subtract avg)) l'
>
> serialize2.hs:37:18:
>     Couldn't match expected type `b' against inferred type `a'
>       `b' is a rigid type variable bound by
>           the type signature for `normalize' at serialize2.hs:33:25
>       `a' is a rigid type variable bound by
>           the type signature for `normalize' at serialize2.hs:33:18
>     In the expression: (/ stdev) . (subtract avg)
>     In the expression:
>         let
>           (total, len) = sumlen l
>           avg = total / len
>           stdev = sqrt
>                 $   ((/) (len - 1)) $ sum $ map ((** 2.0) . (subtract 
> avg)) l
>         in (/ stdev) . (subtract avg)
>     In the definition of `normalize':
>         normalize l = let
>                         (total, len) = sumlen l
>                         avg = total / len
>                         ....
>                       in (/ stdev) . (subtract avg)
> Failed, modules loaded: none.
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>    

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110131/6b4b63fe/attachment.htm>


More information about the Haskell-Cafe mailing list