Text.Tabular.Table type errors - what is the type system asking from me? - haskell

I have the following code, using this tabulation library:
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}
import ClassyPrelude
import qualified Text.Tabular as T
data Category = Age | Gender | Usual | Years
deriving (Show, Read, Eq, Enum, Bounded)
tabulate :: Text -> [[Int]] -> T.Table (T.Header Int) (T.Header Text) Int
tabulate lbl tab = T.Table (T.Group T.NoLine (map T.Header leftcoll)) (T.Group T.DoubleLine [T.Header lbl, T.Header "All", T.Header "Cluster0", T.Header "Cluster1"]) rest
where leftcoll = map (`indexEx` 0) tab
rest = map (drop 1) tab
When I try to compile it, I get the following errors:
Couldn't match type ‘Int’ with ‘T.Header Int’
Expected type: [T.Header Int]
Actual type: [Int]
In the second argument of ‘map’, namely ‘leftcoll’
In the second argument of ‘T.Group’, namely
‘(map T.Header leftcoll)’
Couldn't match expected type ‘T.Header Text’
with actual type ‘Text’
In the first argument of ‘T.Header’, namely ‘lbl’
In the expression: T.Header lbl
I have absolutely no clue why this is the case. From the Table type documentation and example, it would appear that I simply have to apply the Header constructor to a list of values and then put them inside the Group constructor to get a whole row (or column) of values, but the errors there seem to suggest that the lists (and data) I'm passing as arguments to the Header constructor already need to be Headers. Thus, I'm confused about what the type system is telling me here, and how to get what I want.
Essentially, the table should look something like this:
Foo All Cluster0 Cluster1
=========================
1 10 3 7
2 11 10 1
....

It took me a while to find this one, because there is no problem in the definition of your function: it's the type declaration that is wrong.
Let's take a look at the definition of Table:
data Table rh ch a = Table (Header rh) (Header ch) [[a]]
The column header and row header type paramater are already warped in the Header type, so there no need to do it once more.
Instead of defining:
tabulate :: Text -> [[Int]] -> T.Table (T.Header Int) (T.Header Text) Int
you can defined:
tabulate :: Text -> [[Int]] -> T.Table Int Text Int
To debug that kind of things, I usually extract part of the expression to a where clause, along with a type annotation that tells the compiler what each the expression should be. This often gets me better error messages. For example, here, I extracted:
where tagada :: [T.Header Int]
tagada = map T.Header leftcoll
In the error, I could read:
Expected type: [T.Header (T.Header Int)]
Actual type: [T.Header Int]
That's when I realized that the Header type was maybe used twice.

Related

What is the type keyword in Haskell

Stumbled on the type keyword in Haskell:
type Item = String
but not sure what it does, how to use it or how it is different from data. The online google search has been of no help.
I tried implementing it in a code like this:
import System.IO
main = do
putStrLn "Hello, what's your name?"
type Item = String
let test :: Item
test = "chris"
putStrLn test
but I got an error
parse error on input ‘type’
Please in a lay man's term what is type and how can it be used and how is it different from data?
It is a type alias. It means that you can use Item in your code where you can use String instead.
A type alias is often used when you for example want to give a name to more complex types. For example:
import Data.Map(Map)
type Dictionary = Map String String
here you thus can use Dictionary instead of each time writing Map String String.
It is furthermore often used if you want to specify that you are working with Items, the alias is then used in the type signature and in the documentation, which is often better than writing String.
It is also used if you do not yet know what type you will use for a specific object. By using a type alias, you can the work with Item, and later if you change your made define a type for Item or make it an alias of another type. This makes it more convenient to change the types.
I tried implementing it in a code like this:
import System.IO
main = do
putStrLn "Hello, what's your name?"
type Item = String
let test :: Item
test = "chris"
putStrLn test
A type alias is defined at the top level, so not in a do block, that would make a type definition locally scoped. While, like #moonGoose says, there are some proposals to make type definitions more locally scoped, currently it is not the case.
You can define the type alias like:
import System.IO
type Item = String
main = do
putStrLn "Hello, what's your name?"
let test :: Item
test = "chris"
putStrLn test
type A = B
means exactly the same as
typedef B A
in C or C++, and it behaves basically the same as simply
a = b
except that A and B are type-level entities, not value-level ones. For example
Prelude> type A = Int
Prelude> :i A
type A = Int -- Defined at <interactive>:1:1
Prelude> a = 37
Prelude> a
37
Because now A = Int, I can then use the type identifier A exactly everywhere I could also use Int directly:
Prelude> 37 :: Int
37
Prelude> 37 :: A
37
and even
Prelude> (37 :: Int) :: A
37
Note that there is no type conversion going on here, like you might have in other languages. Int and A are simply different names for the same type, so annotating with both is merely a tautology.
Contrast this with data (or newtype), which define a new, separate type which just happens to contain the, well, data of the specified type.
Prelude> data A' = A' { getA :: Int }
Prelude> (37 :: Int) :: A'
<interactive>:12:2: error:
• Couldn't match expected type ‘A'’ with actual type ‘Int’
• In the expression: (37 :: Int) :: A'
In an equation for ‘it’: it = (37 :: Int) :: A'

Couldn't match expected type in Haskell code that print nested list?

Here is my function
data Item a = One a | Many [Item a]
let flat (One x) = show x
let flat (Many xs) = show xs
Here is the output
Prelude> flat [[3]]
<interactive>:21:6:
Couldn't match expected type ‘Item t0’ with actual type ‘[[t1]]’
In the first argument of ‘flat’, namely ‘[[3]]’
In the expression: flat [[3]]
In an equation for ‘it’: it = flat [[3]]
It seems like flat doesn't recognize Item as its function signature so I tried redefine the function signature
flat :: Item a -> [a]
<interactive>:22:1:
Couldn't match type ‘a1’ with ‘Char’
‘a1’ is a rigid type variable bound by
an expression type signature: Item a1 -> [a1] at <interactive>:22:1
Expected type: Item a1 -> [a1]
Actual type: Item a1 -> String
In the expression: flat :: Item a -> [a]
In an equation for ‘it’: it = flat :: Item a -> [a]
But Haskell does not let you redefine function signature in ghci, is there a way around this?
flat [[3]] yields a type error. [[3]] has type Num a => [[a]], not Show a => Item a that you can pass into flat.
flat (Many [3]) will return "[3]".
Answering a follow-up question you asked in the comments of #jtobin's answer: yes there is a way to automatically dectect that [3] needs to be wrapped into a Maybe constructor. However you'll probably need to add type annotations (cf. example to help Haskell figure out what to do=.
We start with a bunch of language extensions.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
Then comes your definition of Item.
module Item where
data Item a = One a | Many [Item a]
We introduce a class of things which may be reified to an Item a and declare two instances: the Many one and the base case. You can see that we now have overlapping instances (e.g. for Itemable [Int] [Int]) so you're playing with fire here.
class Itemable b a where
item :: b -> Item a
instance Itemable b a => Itemable [b] a where
item = Many . fmap item
instance Itemable a a where
item = One
You can finally define flat as a function that turns a b into an Item a first and then flattens it:
flat :: Itemable b a => b -> [a]
flat = go . item where
go (One a) = [a]
go (Many as) = concatMap go as
Which works as the following example typechecking and evaluating to [2,43,7,8,1] shows:
example :: [Int]
example = flat [[[[[[2::Int],[43]],[[7],[8]],[[1]]]]]]
However, as soon as you try to use the overlapping instances it'll blow in your face. E.g.:
example' :: [[Int]]
example' = flat [[[[[[2::Int],[43]],[[7],[8]],[[1]]]]]]

Get a random list item in Haskell

After reviewing this SO question I am trying to use the random number generator to return a random list item based on the return of the randomIO generator.
Full Code:
module Randomizer where
import System.IO
import System.Random
data Action = Create | Destroy
deriving (Enum, Eq, Show)
type History = [Action]
-- | this looks at three sets of histories, and returns an appropriate Action
type ThreeHistoryDecisionMaker = History -> History -> History -> Action
allThreeDecisionMakers :: [ThreeHistoryDecisionMaker]
allThreeDecisionMakers = [decision1, decision2, decision3, decision4, decision5]
chooseRandomDecision :: [ThreeHistoryDecisionMaker] -> Int -> Strategy3P
chooseRandomDecision = allThreeDecisionMakers !! randomIO(0,4)
But I get the following errors:
special_program1.hs:249:16:
Couldn't match type ‘Action’
with ‘History -> History -> History -> Action’
Expected type: [[ThreeHistoryDecisionMaker] -> Int -> ThreeHistoryDecisionMaker]
Actual type: [ThreeHistoryDecisionMaker]
In the first argument of ‘(!!)’, namely ‘allThreeDecisionMakers’
In the expression: all3PStrategies !! randomIO (0, 4)
special_program1.hs:249:35:
Couldn't match expected type ‘(t0, t1) -> Int’
with actual type ‘IO a0’
The function ‘randomIO’ is applied to one argument,
but its type ‘IO a0’ has none
In the second argument of ‘(!!)’, namely ‘randomIO (0, 4)’
In the expression: all3PStrategies !! randomIO (0, 4)
Why is the first error block wanting to expect a list of everything inside it?
What does the second code block mean?
randomIO is not a "random function". Such a thing doesn't exist in Haskell, it wouldn't be referentially transparent. Instead, as the name suggests, it's an IO action which can yield a random value. It makes no sense to index a list with an IO action, !! randomIO(0,4) isn't possible. (It's impossible also for another reason: randomIO creates unlimited values, you want randomRIO (with an R for "range parameter") if you need to specify a (0,4) range.)
What you need to to do to get the value yielded by the action: well, monads! If you haven't learned the theory about those yet, never mind. A random-indexer could look thus:
atRandIndex :: [a] -> IO a -- note that this is gives itself an IO action
atRandIndex l = do
i <- randomRIO (0, length l - 1)
return $ l !! i
I suggest you actually use that function to implement your task.
But back to the code you posted... there's more problems. If you specify the type of chooseRandomDecision with two arguments, then you need to actually define it as a function of these arguments! But your definition doesn't accept any arguments at all, it merely uses the globally-defined list allThreeDecisionMakers (use of global variables never needs to be stated in the type).
Moreover, if you're choosing from a list of THDMakers, then the resulting element will also have that type, what else! So unless Strategy3P is simply another synonym of History -> History -> History -> Action, this won't do as a result, even if you contain it in the right monad.
This answer offers a simple, effective solution to the problem posed in the title: "Get a random list item in Haskell".
The package Test.QuickCeck provides a number of helpful, straightforward functions for generating random values (http://hackage.haskell.org/package/QuickCheck-2.7.6/docs/Test-QuickCheck.html#g:5). A function that returns random values from a list (wrapped IO) can be built by composing the QuickTest functions elements and generate:
import Test.QuickCheck (generate, elements)
randItem :: [a] -> IO a
randItem = generate . elements
chris Frisina's function chooseRandomDecision would then look like this:
chooseRandomDecision :: [ThreeHistoryDecisionMaker] -> IO ThreeHistoryDecisionMaker
chooseRandomDecision = randItem
The user Cale in the #haskell channel on freenode helped coach me to this solution.
note: This solution works with QuickCheck 2.7.6, but needs some alteration for earlier versions. You can update to the latest version with cabal install QuickCheck. See this question.

Can't compile because of types when using nub, map and take

I've got this simple function:
bombplaces::Int->[(Int,Int)]->[(Int,Int)]
bombplaces bombCount listOfPossiblePoints = nub (map (take bombCount) (perms listOfPossiblePoints))
bombs are (x,y) (carthesian points)
i need to get an all permutations and take only first few (bombCount) points.
I'm getting following error:
Couldn't match expected type `(Int,Int)' with actual type `[a0]'
Expected type: [a0] -> (Int,Int)
Actual type: [a0] -> [a0]
In the return type of a call of `take'
In the first argument of `map', namely `(take liczbaBomb)'
If you remove the type signature and ask GHCi for the type, your problem will be obvious:
> :t bombplaces
bombplaces :: Eq a => Int -> [a] -> [[a]]
That is, bombplaces wants to return a list of lists whereas you want it to return a plain list. You need to either change the type signature, or change the definition of the function, depending on what you want the behaviour to be.
N.B. You didn't tell us what definition of perms you are using, so I assumed the obvious one.

Writing A Function Polymorphic In A Type Family

I was experimenting with type families yesterday and ran into an obstacle with the following code:
{-# LANGUAGE TypeFamilies #-}
class C a where
type A a
myLength :: A a -> Int
instance C String where
type A String = [String]
myLength = length
instance C Int where
type A Int = [Int]
myLength = length
main = let a1 = [1,2,3]
a2 = ["hello","world"]
in print (myLength a1)
>> print (myLength a2)
Here I have a type associated with class C and a function that calculates the length of the associated type. However the above code gives me this error:
/tmp/type-families.hs:18:30:
Couldn't match type `A a1' with `[a]'
In the first argument of `myLength', namely `a1'
In the first argument of `print', namely `(myLength a1)'
In the first argument of `(>>)', namely `print (myLength a1)'
/tmp/type-families.hs:19:30:
Couldn't match type `A a2' with `[[Char]]'
In the first argument of `myLength', namely `a2'
In the first argument of `print', namely `(myLength a2)'
In the second argument of `(>>)', namely `print (myLength a2)'
Failed, modules loaded: none.
If, however I change "type" to "data" the code compiles and works:
{-# LANGUAGE TypeFamilies #-}
class C a where
data A a
myLength :: A a -> Int
instance C String where
data A String = S [String]
myLength (S a) = length a
instance C Int where
data A Int = I [Int]
myLength (I a) = length a
main = let a1 = I [1,2,3]
a2 = S ["hello","world"]
in
print (myLength a1) >>
print (myLength a2)
Why does "length" not work as expected in the first case? The lines "type A String ..." and "type A Int ..." specify that the type "A a" is a list so myLength should have the following types respectively : "myLength :: [String] -> Int" or "myLength :: [Int] -> Int".
Hm. Let's forget about types for a moment.
Let's say you have two functions:
import qualified Data.IntMap as IM
a :: Int -> Float
a x = fromInteger (x * x) / 2
l :: Int -> String
l x = fromMaybe "" $ IM.lookup x im
where im = IM.fromList -- etc...
Say there exists some value n :: Int that you care about. Given only the value of a n, how do you find the value of l n? You don't, of course.
How is this relevant? Well, the type of myLength is A a -> Int, where A a is the result of applying the "type function" A to some type a. However, myLength being part of a type class, the class parameter a is used to select which implementation of myLength to use. So, given a value of some specific type B, applying myLength to it gives a type of B -> Int, where B ~ A a and you need to know the a in order to look up the implementation of myLength. Given only the value of A a, how do you find the value of a? You don't, of course.
You could reasonably object that in your code here, the function A is invertible, unlike the a function in my earlier example. This is true, but the compiler can't do anything with that because of the open world assumption where type classes are involved; your module could, in theory, be imported by another module that defines its own instance, e.g.:
instance C Bool where
type A Bool = [String]
Silly? Yes. Valid code? Also yes.
In many cases, the use of constructors in Haskell serves to create trivially injective functions: The constructor introduces a new entity that is defined only and uniquely by the arguments it's given, making it simple to recover the original values. This is precisely the difference between the two versions of your code; the data family makes the type function invertible by defining a new, distinct type for each argument.

Resources