Sort a list of Int pairs by the difference of the values (a, b) - haskell

How do I sort a list of Int pairs by the difference of the values |first - second| in an ascending order?
For calculating the difference I wrote this piece of code:
ab :: (Int, Int) -> Int
ab (x, y) = if x - y >= 0 then (x - y)
else (x - y) * (-1)
I wanted to use quicksort on the values I get:
sort :: [(Int,Int)] -> [(Int,Int)]
sort [] = []
sort (x:xs) = sort smallerOrEqual ++ [x] ++ sort larger
where smallerOrEqual = [a | a <- xs, a <= x]
larger = [a | a <- xs, a > x]
The problem is how do I build my ab function into the sort function? I have tried several ways but always got compiler errors.

Let's do that with the standard library functions only!
First of all, there is a generic version of sorting function named sortBy (I'll show the types of relevant functions as we go, using GHCi's brilliant :t command):
ghci> import Data.List
ghci> :t sortBy
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
First parameter of sortBy suggests that to compare elements we need a sorting predicate — a function which takes two elements of the list and tells if the first one is greater. In many cases, yours included, you don't have to define such a function by yourself. Instead, you can use a function which “measures” how important an element of a list is. E.g. you have an element of a list (x,y) and its measure is |x-y| — this is exactly your ab function, but remember that we want it to be defined via standard ones.
For now, we have two tasks: 1) define measure function of type (Int, Int) -> Int; 2) learn how to turn it into into a sorting predicate. I told that the the latter one is trivial, as it can be done via standard function comparing:
ghci> import Data.Ord
ghci> :t comparing
comparing :: Ord a => (b -> a) -> b -> b -> Ordering
So what I'm suggesting is that comparing ab is a perfect match for the first argument of sortBy. Not let's turn to the other task: defining ab via standard functions.
Consider the type of - function:
ghci> :t (-)
(-) :: Num a => a -> a -> a
If you substitute Int for the a(¹) you get nearly the type you want to have, i.e. Int -> Int -> Int. Here we hit very frequent task of turning a function from two arguments ((-)) into a function acting on pairs. Luckily, there is a standard function for doing this, namely, uncurry:
ghci> :t uncurry (-)
uncurry (-) :: Num c => (c, c) -> c
That's what we need! Now we just have to pipe it with the abs function which computes |·|, and we are good. We compose functions be means of .. Resulting solution is this one:
import Data.List (sortBy)
import Data.Ord (comparing)
sortAbsPairs :: [(Int,Int)] -> [(Int,Int)]
sortAbsPairs = sortBy (comparing $ abs . uncurry (-))
You can try it out in GHCi assuming you saved it in sort.hs:
ghci>:l sort.hs
Ok, one module loaded.
ghci> sortAbsPairs [(8,20), (5, 10), (1,2)]
[(1, 2), (5, 10), (8, 20)]
(¹) You actually can ask GHCi to substitute types for type parameters of functions by setting up a language extension called TypeApplications:
ghci> :set -XTypeApplications
ghci> :t (-) #Int
(-) #Int :: Int -> Int -> Int

While sortBy is well-known, it is mostly accompanied by comparing. You can use sortOn instead. sortOn has the advantage that it uses the Schwartzian transform, i.e. it only computes the difference once for each element.
--Prelude Data.List> :t sortOn
--sortOn :: Ord b => (a -> b) -> [a] -> [a]
import Data.List(sortOn)
sort = sortOn (abs . uncurry (-))
But if you really want to use your original sort, pattern match the pairs:
sort ((x,x'):xs) = [ (a,a') | (a,a') <- xs, -- ... your homework here
I extend the homework part at a later point to make it a full answer.

Related

How to check that all list items are odd and bigger than 10?

I need to check if a list only contains odd numbers, bigger than 10.
This is what I did.
f :: [Int] -> Bool
f xs= [x |x<-xs, x >10, odd x]
Why does this not work?
When you write [x |x<-xs, x >10, odd x] you're making up a list of Ints, a [Int], not a Boolean. For instance you can verify that
[x | x <- [1..20], x > 10, odd x] is the list [11,13,15,17,19]. So it does contain the numbers that you want, but how do you tell that those are all of the numebrers in xs?
You could certainly equate that list to xs itself, and that would work:
f xs = xs == [x |x<-xs, x >10, odd x]
This way the == ensures that when you only take odd numbers greater than 10 from xs you get back exactly xs, meaning that all numbers satisfy the predicate.
Maybe this is the mistake you were looking for.
I'm not sure whether this solution traverses xs twice (once to extract the entries satisfying the predicate, and once to check for equality) or not. It looks very simple, so I can't help but think that the list is traversed only once.
Anyway, another strategy is to stick to your request: you want all numbers x from the list xs for which odd x and x > 10 are both True:
f :: [Int] -> Bool
f xs = all (\x -> odd x && x > 10) xs
By noticing that both sides have a trailing xs, you can reduce the definition:
f :: [Int] -> Bool
f = all (\x -> odd x && x > 10)
And that lambda, if you want, could be define more succintly as (odd & (> 10)), thus getting
f :: [Int] -> Bool
f = all (odd & (> 10))
provided you import Control.Monad (liftM2) and define
(&) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool)
(&) = liftM2 (&&)
Your type signature mentions that the function returns a boolean value, but your proposed body returns a list of numbers. Haskell has no automatic conversions such as Lisp.
Should you wish to stick to pedestrian code, you could get the sublist of offending numbers, and just check that the sublist is empty.
f :: [Int] -> Bool
f xs = let offenders = [x | x <- xs, x <= 10 || even x]
in (null offenders)
Note that due to the laziness of the language runtime, evaluation of offenders stops as soon as we find a first element.
Should you want something a bit more haskell-ish, you can use the sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) polymorphic library function to turn a list of predicates into a single function returning a list of boolean values, then pass that list to and. That checks one number.
Then use all to apply these checks to all numbers in the input list. Like this:
f2 :: [Int] -> Bool
f2 = all (and . sequence [(>10), odd])
Explanation:
To understand how exactly the sequence function gets specialized by the compiler, one can use the TypeApplications language extension.
With the extension enabled, given 3 type arguments, expression sequence #tt #tm #ta maps tt to the Traversable instance, tm to the Monad instance and ta to argument type a.
$ ghci
GHCi, version 8.8.4: https://www.haskell.org/ghc/ :? for help
λ>
λ> :type sequence
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
λ>
λ> :set -XTypeApplications
λ>
We start with the easiest part, mapping tt to lists and ta to Bool, leaving tm undefined as an underscore _:
λ>
λ> :type sequence #[] #_ #Bool
sequence #[] #_ #Bool :: Monad _ => [_ Bool] -> _ [Bool]
λ>
Now, if we assign tm to “function of an Int variable”, we have the whole picture:
λ>
λ> :type sequence #[] #((->)Int) #Bool
sequence #[] #((->)Int) #Bool :: [Int -> Bool] -> Int -> [Bool]
λ>
The last type can be interpreted as [Int -> Bool] -> (Int -> [Bool]), that is, function sequence transforming a list of predicates into a single function returning a list of boolean values.

Given a list, how can I perform some transformation only on sub-lists whose each two elements satisfy a binary predicate?

(In my actual use case I have a list of type [SomeType], SomeType having a finite number of constructors, all nullary; in the following I'll use String instead of [SomeType] and use only 4 Chars, to simplify a bit.)
I have a list like this "aaassddddfaaaffddsssadddssdffsdf" where each element can be one of 'a', 's', 'd', 'f', and I want to do some further processing on each contiguous sequence of non-as, let's say turning them upper case and reversing the sequence, thus obtaining "aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD". (I've added the reversing requirement to make it clear that the processing involves all the contiguous non 'a'-s at the same time.)
To turn each sub-String upper case, I can use this:
func :: String -> String
func = reverse . map Data.Char.toUpper
But how do I run that func only on the sub-Strings of non-'a's?
My first thought is that Data.List.groupBy can be useful, and the overall solution could be:
concat $ map (\x -> if head x == 'a' then x else func x)
$ Data.List.groupBy ((==) `on` (== 'a')) "aaassddddfaaaffddsssadddssdffsdf"
This solution, however, does not convince me, as I'm using == 'a' both when grouping (which to me seems good and unavoidable) and when deciding whether I should turn a group upper case.
I'm looking for advices on how I can accomplish this small task in the best way.
You could classify the list elements by the predicate before grouping. Note that I’ve reversed the sense of the predicate to indicate which elements are subject to the transformation, rather than which elements are preserved.
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Arrow ((&&&))
import Data.Function (on)
import Data.Monoid (First(..))
mapSegmentsWhere
:: forall a. (a -> Bool) -> ([a] -> [a]) -> [a] -> [a]
mapSegmentsWhere p f
= concatMap (applyMatching . sequenceA) -- [a]
. groupBy ((==) `on` fst) -- [[(First Bool, a)]]
. map (First . Just . p &&& id) -- [(First Bool, a)]
where
applyMatching :: (First Bool, [a]) -> [a]
applyMatching (First (Just matching), xs)
= applyIf matching f xs
applyIf :: forall a. Bool -> (a -> a) -> a -> a
applyIf condition f
| condition = f
| otherwise = id
Example use:
> mapSegmentsWhere (/= 'a') (reverse . map toUpper) "aaassddddfaaaffddsssadddssdffsdf"
"aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD"
Here I use the First monoid with sequenceA to merge the lists of adjacent matching elements from [(Bool, a)] to (Bool, [a]), but you could just as well use something like map (fst . head &&& map snd). You can also skip the ScopedTypeVariables if you don’t want to write the type signatures; I just included them for clarity.
If we need to remember the difference between the 'a's and the rest, let's put them in different branches of an Either. In fact, let's define a newtype now that we are at it:
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ViewPatterns #-}
import Data.Bifoldable
import Data.Char
import Data.List
newtype Bunched a b = Bunched [Either a b] deriving (Functor, Foldable)
instance Bifunctor Bunched where
bimap f g (Bunched b) = Bunched (fmap (bimap f g) b)
instance Bifoldable Bunched where
bifoldMap f g (Bunched b) = mconcat (fmap (bifoldMap f g) b)
fmap will let us work over the non-separators. fold will return the concatenation of the non-separators, bifold will return the concatenation of everything. Of course, we could have defined separate functions unrelated to Foldable and Bifoldable, but why avoid already existing abstractions?
To split the list, we can use an unfoldr that alternately searches for as and non-as with the span function:
splitty :: Char -> String -> Bunched String String
splitty c str = Bunched $ unfoldr step (True, str)
where
step (_, []) = Nothing
step (True, span (== c) -> (as, ys)) = Just (Left as, (False, ys))
step (False, span (/= c) -> (xs, ys)) = Just (Right xs, (True, ys))
Putting it to work:
ghci> bifold . fmap func . splitty 'a' $ "aaassddddfaaaffddsssadddssdffsdf"
"aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD"
Note: Bunched is actually the same as Tannen [] Either from the bifunctors package, if you don't mind the extra dependency.
There are other answers here, but I think they get too excited about iteration abstractions. A manual recursion, alternately taking things that match the predicate and things that don't, makes this problem exquisitely simple:
onRuns :: Monoid m => (a -> Bool) -> ([a] -> m) -> ([a] -> m) -> [a] -> m
onRuns p = go p (not . p) where
go _ _ _ _ [] = mempty
go p p' f f' xs = case span p xs of
(ts, rest) -> f ts `mappend` go p' p f' f rest
Try it out in ghci:
Data.Char> onRuns ('a'==) id (reverse . map toUpper) "aaassddddfaaaffddsssadddssdffsdf"
"aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD"
Here is a simple solution - function process below - that only requires that you define two functions isSpecial and func. Given a constructor from your type SomeType, isSpecial determines whether it is one of those constructors that form a special sublist or not. The function func is the one you included in your question; it defines what should happen with the special sublists.
The code below is for character lists. Just change isSpecial and func to make it work for your lists of constructors.
isSpecial c = c /= 'a'
func = reverse . map toUpper
turn = map (\x -> ([x], isSpecial x))
amalgamate [] = []
amalgamate [x] = [x]
amalgamate ((xs, xflag) : (ys, yflag) : rest)
| xflag /= yflag = (xs, xflag) : amalgamate ((ys, yflag) : rest)
| otherwise = amalgamate ((xs++ys, xflag) : rest)
work = map (\(xs, flag) -> if flag then func xs else xs)
process = concat . work . amalgamate . turn
Let's try it on your example:
*Main> process "aaassddddfaaaffddsssadddssdffsdf"
"aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD"
*Main>
Applying one function at a time, shows the intermediate steps taken:
*Main> turn "aaassddddfaaaffddsssadddssdffsdf"
[("a",False),("a",False),("a",False),("s",True),("s",True),("d",True),
("d",True),("d",True),("d",True),("f",True),("a",False),("a",False),
("a",False),("f",True),("f",True),("d",True),("d",True),("s",True),
("s",True),("s",True),("a",False),("d",True),("d",True),("d",True),
("s",True),("s",True),("d",True),("f",True),("f",True),("s",True),
("d",True),("f",True)]
*Main> amalgamate it
[("aaa",False),("ssddddf",True),("aaa",False),("ffddsss",True),
("a",False),("dddssdffsdf",True)]
*Main> work it
["aaa","FDDDDSS","aaa","SSSDDFF","a","FDSFFDSSDDD"]
*Main> concat it
"aaaFDDDDSSaaaSSSDDFFaFDSFFDSSDDD"
*Main>
We can just do what you describe, step by step, getting a clear simple minimal code which we can easily read and understand later on:
foo :: (a -> Bool) -> ([a] -> [a]) -> [a] -> [a]
foo p f xs = [ a
| g <- groupBy ((==) `on` fst)
[(p x, x) | x <- xs] -- [ (True, 'a'), ... ]
, let (t:_, as) = unzip g -- ( [True, ...], "aaa" )
, a <- if t then as else (f as) ] -- final concat
-- unzip :: [(b, a)] -> ([b], [a])
We break the list into same-p spans and unpack each group with the help of unzip. Trying it out:
> foo (=='a') reverse "aaabcdeaa"
"aaaedcbaa"
So no, using == 'a' is avoidable and hence not especially good, introducing an unnecessary constraint on your data type when all we need is equality on Booleans.

How to make a list of partially applied functions using map?

I'm trying to make a list of functions (for use with zipwith later on) so that I effectively have [take 1,take 2,take 3] so each element of the list should have type [Int] -> [Int].
This is what I've tried, which feels like it ought to be right. I'm not sure why I'm getting the error message?
Prelude> map (\x -> take x) [1..5]
<interactive>:46:1:
No instance for (Show ([a0] -> [a0]))
(maybe you haven't applied enough arguments to a function?)
arising from a use of ‘print’
In a stmt of an interactive GHCi command: print it
First of all, your code works. But functions cannot get shown. Try show id, and you end up with a very similar error message.
But before we delve into the application of your list of functions let us have a look at the types, just to check whether your logic is sound. For the sake of simplicity, we say that 1 :: Int. Also, \x -> take x is just take, so we can reproduce your behaviour with map take [1..5]. Now we have the following participants in our little type turmoil:
map :: (a -> b ) -> [a] -> [b]
take :: Int -> ([c] -> [c]) -- explicit parentheses
Now we plug take into map. In our map, a ~ Int due to take's first argument, and b ~ [c] -> [c]. Therefore, we have
map take :: [Int] -> [[c] -> [c]]
Now we use map take [1..5], which simply removes the type in our line above:
map take :: [Int] -> [[c] -> [c]]
[1..5] :: [Int]
map take [1..5] :: [[c] -> [c]]
And we're done. We end up at exact the same type as in your error message. Does everything end up right? Yes. There's nothing wrong with your code.
However, as already said, [[c] -> [c]] cannot get shown. We have to apply those functions in your list:
Prelude> map (\f -> f [1..10]) (map take [1..5])
[[1],[1,2],[1,2,3],[1,2,3,4],[1,2,3,4,5]]
#kosmikus answered your question in a comment, but here in case anyone is interested is what :t does in the in console.
Here is the list of 5 functions that you wanted, typed directly:
Prelude> :t [(take 1), (take 2), (take 3), (take 4), (take 5)]
[(take 1), (take 2), (take 3), (take 4), (take 5)] :: [[a] -> [a]]
Using your expression with map:
Prelude> :t map (\x -> take x) [1..5]
map (\x -> take x) [1..5] :: [[a] -> [a]]
Incidentally you can also say:
Prelude> :t map take [1..5]
map take [1..5] :: [[a] -> [a]]
What you can’t do is render the value itself in the GHCI console, there’s no way to show functions from lists to lists. The :t trick by #kosmikus is nice. That said, you can use your list of functions and see them in action. For example:
Prelude> let takers = map take [1..5] in head(tail takers) [8,9,10,11]
[8,9]
which applies the function take 2 to the list [8 9 10 11].

Project Euler 3 - Haskell

I'm working my way through the Project Euler problems in Haskell. I have got a solution for Problem 3 below, I have tested it on small numbers and it works, however due to the brute force implementation by deriving all the primes numbers first it is exponentially slow for larger numbers.
-- Project Euler 3
module Main
where
import System.IO
import Data.List
main = do
hSetBuffering stdin LineBuffering
putStrLn "This program returns the prime factors of a given integer"
putStrLn "Please enter a number"
nums <- getPrimes
putStrLn "The prime factors are: "
print (sort nums)
getPrimes = do
userNum <- getLine
let n = read userNum :: Int
let xs = [2..n]
return $ getFactors n (primeGen xs)
--primeGen :: (Integral a) => [a] -> [a]
primeGen [] = []
primeGen (x:xs) =
if x >= 2
then x:primeGen (filter (\n->n`mod` x/=0) xs)
else 1:[2]
--getFactors
getFactors :: (Integral a) => a -> [a] -> [a]
getFactors n xs = [ x | x <- xs, n `mod` x == 0]
I have looked at the solution here and can see how it is optimised by the first guard in factor. What I dont understand is this:
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
Specifically the first argument of filter.
((==1) . length . primeFactors)
As primeFactors is itself a function I don't understand how it is used in this context. Could somebody explain what is happening here please?
If you were to open ghci on the command line and type
Prelude> :t filter
You would get an output of
filter :: (a -> Bool) -> [a] -> [a]
What this means is that filter takes 2 arguments.
(a -> Bool) is a function that takes a single input, and returns a Bool.
[a] is a list of any type, as longs as it is the same type from the first argument.
filter will loop over every element in the list of its second argument, and apply it to the function that is its first argument. If the first argument returns True, it is added to the resulting list.
Again, in ghci, if you were to type
Prelude> :t (((==1) . length . primeFactors))
You should get
(((==1) . length . primeFactors)) :: a -> Bool
(==1) is a partially applied function.
Prelude> :t (==)
(==) :: Eq a => a -> a -> Bool
Prelude> :t (==1)
(==1) :: (Eq a, Num a) => a -> Bool
It only needs to take a single argument instead of two.
Meaning that together, it will take a single argument, and return a Boolean.
The way it works is as follows.
primeFactors will take a single argument, and calculate the results, which is a [Int].
length will take this list, and calculate the length of the list, and return an Int
(==1) will
look to see if the values returned by length is equal to 1.
If the length of the list is 1, that means it is a prime number.
(.) :: (b -> c) -> (a -> b) -> a -> c is the composition function, so
f . g = \x -> f (g x)
We can chain more than two functions together with this operator
f . g . h === \x -> f (g (h x))
This is what is happening in the expression ((==1) . length . primeFactors).
The expression
filter ((==1) . length . primeFactors) [3,5..]
is filtering the list [3, 5..] using the function (==1) . length . primeFactors. This notation is usually called point free, not because it doesn't have . points, but because it doesn't have any explicit arguments (called "points" in some mathematical contexts).
The . is actually a function, and in particular it performs function composition. If you have two functions f and g, then f . g = \x -> f (g x), that's all there is to it! The precedence of this operator lets you chain together many functions quite smoothly, so if you have f . g . h, this is the same as \x -> f (g (h x)). When you have many functions to chain together, the composition operator is very useful.
So in this case, you have the functions (==1), length, and primeFactors being compose together. (==1) is a function through what is called operator sections, meaning that you provide an argument to one side of an operator, and it results in a function that takes one argument and applies it to the other side. Other examples and their equivalent lambda forms are
(+1) => \x -> x + 1
(==1) => \x -> x == 1
(++"world") => \x -> x ++ "world"
("hello"++) => \x -> "hello" ++ x
If you wanted, you could re-write this expression using a lambda:
(==1) . length . primeFactors => (\x0 -> x0 == 1) . length . primeFactors
=> (\x1 -> (\x0 -> x0 == 1) (length (primeFactors x1)))
Or a bit cleaner using the $ operator:
(\x1 -> (\x0 -> x0 == 1) $ length $ primeFactors x1)
But this is still a lot more "wordy" than simply
(==1) . length . primeFactors
One thing to keep in mind is the type signature for .:
(.) :: (b -> c) -> (a -> b) -> a -> c
But I think it looks better with some extra parentheses:
(.) :: (b -> c) -> (a -> b) -> (a -> c)
This makes it more clear that this function takes two other functions and returns a third one. Pay close attention the the order of the type variables in this function. The first argument to . is a function (b -> c), and the second is a function (a -> b). You can think of it as going right to left, rather than the left to right behavior that we're used to in most OOP languages (something like myObj.someProperty.getSomeList().length()). We can get this functionality by defining a new operator that has the reverse order of arguments. If we use the F# convention, our operator is called |>:
(|>) :: (a -> b) -> (b -> c) -> (a -> c)
(|>) = flip (.)
Then we could have written this as
filter (primeFactors |> length |> (==1)) [3, 5..]
And you can think of |> as an arrow "feeding" the result of one function into the next.
This simply means, keep only the odd numbers that have only one prime factor.
In other pseodo-code: filter(x -> length(primeFactors(x)) == 1) for any x in [3,5,..]

create a function to sum the odd square in haskell

sumoddsquare' :: (Num a) => [a] -> a
sumoddsquare' = sum [x^2 | x <- [1..5], odd x]
My desired output is 35
The syntax error I get is
Couldn't match expected type `[a] -> a'
with actual type `[Integer]'
In the expression: [x ^ 2 | x <- [1 .. 9999], odd x]
In an equation for sumoddsquare':
sumoddsquare' = [x ^ 2 | x <- [1 .. 9999], odd x]
Can you explain this syntax error and also provide a solution for this question?
You've given sumoddsquare' the type Num a => [a] -> a, but you've left off any parameter. Maybe you meant
sumoddsquare' xs = sum [x^2 | x <- xs, odd x]
Although the Num constraint is not sufficient here, inspect the types of ^2 and odd to determine what you should be using. (spoilers below)
Judging by the error message, you've actually defined sumoddsquare' in your code as
sumoddsquare' :: [a] -> a
sumoddsquare' = [x^2 | x <- [1..9999], odd x]
Rather than what you've posted above. Now, you've given the type [a] -> a to sumoddsquares' explicitly, the compiler takes that as a fact, but then it sees the definition. You don't define the argument explicitly in the definition, so the compiler thinks you're defining the function in point-free style. When it sees the right hand side of the =, it gets confused because [x^2 | x <- [1..9999], odd x] has the type [Integer], but it has already accepted the fact that sumoddsquares' has the type [a] -> a. It doesn't know how to reconcile this, so it throws the error you see.
You can usually find the source of these types of error messages by commenting out the explicit type signature. If it then compiles, you can inspect the type in GHCi by doing
> :load sumoddsquare_no_type_sig.hs
> :type sumoddsquare'
[Integer]
And this would tell you that sumoddsquare' is not a function. However, you want it to be a function, so how do you fix this? First, look at the definition. Are all of your arguments declared explicitly? If no, add them.
-- sumoddsquare' :: Num a => [a] -> a
sumoddsquare' xs = [x^2 | x <- [1..9999], odd x]
Then you see
> :reload
> :type sumoddsquare'
[a] -> [Integer]
That's at least a function, but how do we get from the very general type [a] to [Integer]? Since we currently know nothing about a, then this function must not depend on the first argument at all! We can then look through our definition to find where a list might go
-- sumoddsquare' :: Num a => [a] -> a
sumoddsquare' xs = [x^2 | x <- xs, odd x]
-- ^--- This is the only place I saw a list used
Then
> :reload
> :type sumoddsquare'
Integral a => [a] -> [a]
That's closer! We see that the input has been restricted to Integral and we return a more general type than just [Integer]. This tells us we first need to fix the constraint in our type signature from Num a to Integral a. The last puzzle is figuring out how to convert Integral a => [a] into Integral a => a. We want to sum, so now we see that we've left out the sum function in front of the list comprehension
-- sumoddsquare' :: Integral a => [a] -> a
sumoddsquare' xs = sum [x^2 | x <- xs, odd x]
And finally
> :reload
> :type sumoddsquare'
Integral a => [a] -> a
We have a type that matches what we want. We can now uncomment the type signature in our source code.
As a bonus, this problem can be solved entirely with higher order functions as
sumoddsquares' xs = sum $ map (^2) $ filter odd $ xs
-- or point free as
-- sumoddsquares' = sum . map (^2) . filter odd
And in fact, all list comprehensions are just syntactic sugar for maps, filters, and concats. These two pieces of code end up being essentially identical after compilation.

Resources