Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Hutton 2nd ed, ex 7.6 (Theodore Lief Gannon)
   2.  Runtime error “Could not deduce (Integral Float) arising
      from a use of..” (Jack Vice)
   3. Re:  Runtime error “Could not deduce (Integral Float)
      arising from a use of..” (Kyle Murphy)


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

Message: 1
Date: Wed, 22 Aug 2018 15:23:11 -0700
From: Theodore Lief Gannon <tan...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Hutton 2nd ed, ex 7.6
Message-ID:
        <CAJoPsuDGSEyAqwoiFTQBV=bjxan99meuemvhysouwv9o3u2...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I'm not familiar with Hutton, and I agree that unless one of the book's
exercises was "read the Prelude docs" it shouldn't be expecting you to use
functions it hasn't introduced. In all fairness, though, both null and
const have in-line expansions that you probably could have come up with. In
fact, you DID come up with null, just in the wrong context: specialized to
lists, it's (==[]). And you can write (const False) as a lambda: (\_ ->
False)

On Wed, Aug 22, 2018, 5:36 AM David McBride <toa...@gmail.com> wrote:

> It sounds to me like you are just lacking a familiarity with the standard
> library.  All of the list functions (such as null) are detailed on hackage (
> http://hackage.haskell.org/package/base/docs/Data-List.html) with
> reasonable examples.
>
> There is also hoogle https://www.haskell.org/hoogle/, which allows you to
> search both for function names as well as types and operators like (.), all
> of which link to the documentation.
>
> As for unfold's type signature, the first thing any haskell programmer
> would have done is load it into ghci, and type :t unfold.  I could get it
> from his description of the function, and perhaps that would have been good
> practice, but there's no need to turn to google for that.
> :t unfold
> unfold :: (t -> Bool) -> (t -> a) -> (t -> t) -> t -> [a]
>
> Haskell's a pretty different language from most of the mainstream
> languages.  I wouldn't feel bad because your previous experience barely
> applies and also these exercises are not the easiest I've ever seen.
> Unfold is not a standard function in haskell and so being able to derive
> standard functions from it is more of an algorithmic problem than a
> learning haskell problem.  In any case, I think based on what you've
> written that you are doing just fine.
>
> On Wed, Aug 22, 2018 at 7:00 AM, trent shipley <trent.ship...@gmail.com>
> wrote:
>
>> 1. I got through the problem without getting so stuck I had to ask this
>> list.  But, I am disappointed in how much I had to cheat by looking up
>> solutions on Google after making my best attempt.  This higher order
>> functions chapter is giving more trouble than any chapter so far.
>>
>> 2. Since getting tutoring on how to read function declarations, I'm doing
>> better at deciphering simple declarations, but writing them myself is
>> beyond me more often than not.
>>
>> 3. I feel like Hutton introduces concepts well, but with more brevity and
>> fewer examples than would be best for me.  Unfortunately, he leaves out
>> almost all the ancillary pragmatics as exemplified by the need for "null"
>> and "const" below.  My bet is that when Hutton 2nd ed is used as a textbook
>> in college those practical lacks get covered in lecture, problem sessions,
>> and in mutual aid between students.
>>
>> Does anyone have any idea on how I might improve my performance.  I am
>> not used to having difficulty learning a computer language.  (Prolog and
>> Java Swing being exceptions.)
>>
>>
>> {--
>>
>> 6. A higher-order function unfold that encapsulates a simple pattern of
>> recursion for producing a list can be defined as follows:
>>
>> unfold p h t x | p x = []
>>                | otherwise = h x : unfold p h t (t x)
>>
>> That is, the function unfold p h t produces the empty list if the
>> predicate p is true of the argument value, and otherwise produces a
>> non-empty list by applying the function h to this value to give the head,
>> and the function t to generate another argument that is recursively
>> processed in the same way to produce the tail of the list. For example, the
>> function int2bin can be rewritten more compactly using unfold as follows:
>>
>> int2bin = unfold (==0) (‘mod‘ 2) (‘div‘ 2)
>>
>> Redefine the functions chop8, map f and iterate f using unfold.
>>
>> Hutton, Graham. Programming in Haskell (Kindle Locations 2830-2842).
>> Cambridge University Press. Kindle Edition.
>>
>> Basically, what you do to develop and test this question is to copy and
>> paste extended example 7.6 Binary String Transmittter from the chapter into
>> your text editor.  Then you alter large chunks of it to use the unfold
>> function.
>>
>> --}
>>
>> import Data.Char
>> import Prelude hiding (iterate, map)
>>
>> type Bit = Int
>>
>>
>> -- I had to crib the type signature
>>
>> unfold :: (b -> Bool) -> (b -> a) -> (b -> b) -> b -> [a]
>> unfold p h t x | p x = []
>>                | otherwise = h x : unfold p h t (t x)
>>
>>
>> -- Hutton, Graham. Programming in Haskell (Kindle Location 2329).
>> Cambridge University Press. Kindle Edition.
>>
>> -- cribbed type signature
>> -- Had to copy (f . head), my attempt was (f head).
>> -- I had no idea the function "null" existed before Googling the
>> solution.
>> -- Is Googling to learn the existence of "null" accepted pedagological
>> practice?
>> -- Is it a lacuna on Hutton's part?
>>
>> map :: (a -> b) -> [a] -> [b]
>> map f = unfold null (f . head) tail
>>
>> -- had to copy the signature, although I didn't try hard to come up with
>> it on my own.
>> -- I had tried to use (==[]).  I got the solution "False" by copying from
>> the internet.
>> -- I would not have gotten the word "const" without cheating from the
>> internet.  It is nowhere in Hutton's book up to this point.
>>
>> iterate :: (a -> a) -> a -> [a]
>> iterate f = unfold (const False) id f
>>
>> -- chop8 :: [Bit] -> [[Bit]]
>> -- chop8 [] = []
>> -- chop8 bits = take 8 bits : chop8 (drop 8 bits)
>>
>> -- Hutton, Graham. Programming in Haskell (Kindle Locations 2681-2683).
>> Cambridge University Press. Kindle Edition.
>>
>> -- I attempted this first, and i pretty much got it on my own.
>>
>> chop8 :: [Bit] -> [[Bit]]
>> chop8 bits = unfold (==[]) (take 8) (drop 8) bits
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180822/11f45436/attachment-0001.html>

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

Message: 2
Date: Thu, 23 Aug 2018 06:26:05 -0400
From: Jack Vice <jack.v...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Runtime error “Could not deduce
        (Integral Float) arising from a use of..”
Message-ID:
        <calazo9evddl0t7de0v6k_8+ikbxh74h0mvbeyfitkkftkle...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I am trying to calculate the standard deviation for each index in a list of
lists of floats. Using Ubuntu 18.04, ghc 8.0.2. I am getting the following
runtime error which I have googled and still don't understand what
"Integral Float" is exactly or even which parameter is causing the trouble.

*Main> let z = stdDev 0 2 y x
<interactive>:250:9: error:
• Could not deduce (Integral Float) arising from a use of ‘stdDev’
  from the context: Floating a
    bound by the inferred type of z :: Floating a => [a]
    at <interactive>:250:5-38
• In the expression: stdDev 0 (length (head (x))) y x
  In an equation for ‘z’: z = stdDev 0 (length (head (x))) y x

Code:

-- i is start index, l is length of each list, ms is list of means,
--    xs is Matrix
stdDev i l ms xs
     | i < l     = sqrt(fromIntegral(sumOfMinusMeans i (ms!!i) xs) /
                             fromIntegral(l)):(stdDev (i+1) l ms xs)
     | otherwise = []

--i is index, m is mean for the index
sumOfMinusMeans i m (x:xs)
     | xs == []     = (x!!i - m)**2
     | i < length x = (x!!i - m)**2 + (sumOfMinusMeans i m xs)
     | otherwise    = 0

Types:

*Main> :t stdDev
stdDev
  :: (Floating a1, Floating a, Integral a1) =>
     Int -> Int -> [a1] -> [[a1]] -> [a]

*Main> :t sumOfMinusMeans
sumOfMinusMeans :: (Eq t, Floating t) => Int -> t -> [[t]] -> t

Variables:

*Main> y
[380.0,1.0]
*Main> x
[[600.0,1.0],[400.0,1.0],[170.0,1.0],[430.0,1.0],[300.0,1.0]]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180823/a985c906/attachment-0001.html>

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

Message: 3
Date: Thu, 23 Aug 2018 08:10:35 -0400
From: Kyle Murphy <orc...@gmail.com>
To: beginners <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Runtime error “Could not deduce
        (Integral Float) arising from a use of..”
Message-ID:
        <CA+y6Jcy4A5=k5aavxobg3wa2ohnyz5r6dbppvdv4tm9qyfo...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

GHC has deduced that the third and fourth arguments of stdDev must be
members of both the Floating and Integral classes based on the functions
used on them. GHC has also deduced that the types of y and x are [Float]
and [[Float]] respectively. The error is that GHC has no definition in
scope that would make Float a member of the Integral class.

How to fix this is a bit more than I can go into right now, but will likely
involve carefully converting from type to type at particular points in
stdDev. As a first step, it's always a good idea to explicitly tell GHC
what YOU think the types are for a function, and then let it tell you where
it disagrees.

On Thu, Aug 23, 2018, 6:26 AM Jack Vice <jack.v...@gmail.com> wrote:

> I am trying to calculate the standard deviation for each index in a list
> of lists of floats. Using Ubuntu 18.04, ghc 8.0.2. I am getting the
> following runtime error which I have googled and still don't understand
> what "Integral Float" is exactly or even which parameter is causing the
> trouble.
>
> *Main> let z = stdDev 0 2 y x
> <interactive>:250:9: error:
> • Could not deduce (Integral Float) arising from a use of ‘stdDev’
>   from the context: Floating a
>     bound by the inferred type of z :: Floating a => [a]
>     at <interactive>:250:5-38
> • In the expression: stdDev 0 (length (head (x))) y x
>   In an equation for ‘z’: z = stdDev 0 (length (head (x))) y x
>
> Code:
>
> -- i is start index, l is length of each list, ms is list of means,
> --    xs is Matrix
> stdDev i l ms xs
>      | i < l     = sqrt(fromIntegral(sumOfMinusMeans i (ms!!i) xs) /
>                              fromIntegral(l)):(stdDev (i+1) l ms xs)
>      | otherwise = []
>
> --i is index, m is mean for the index
> sumOfMinusMeans i m (x:xs)
>      | xs == []     = (x!!i - m)**2
>      | i < length x = (x!!i - m)**2 + (sumOfMinusMeans i m xs)
>      | otherwise    = 0
>
> Types:
>
> *Main> :t stdDev
> stdDev
>   :: (Floating a1, Floating a, Integral a1) =>
>      Int -> Int -> [a1] -> [[a1]] -> [a]
>
> *Main> :t sumOfMinusMeans
> sumOfMinusMeans :: (Eq t, Floating t) => Int -> t -> [[t]] -> t
>
> Variables:
>
> *Main> y
> [380.0,1.0]
> *Main> x
> [[600.0,1.0],[400.0,1.0],[170.0,1.0],[430.0,1.0],[300.0,1.0]]
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180823/988e7a15/attachment.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 122, Issue 13
******************************************

Reply via email to