i have given two points.
Now of i need to check if those points are identical, so i do:
type datatypePoint = (Float,Float)
anyLine :: datatypePoint -> datatypePoint -> datatypeLine
anyLine a b = [[fst a, fst b] , [snd a, snd b]]
| (fst a == fst b) && (snd a == snd b) = error "Identical"
| otherwise = error "Not identical"
But i get error:
unexpected |
anybody could tell me why? What am i doing wrong?
You have a few errors here, first off, all types start with upper case letters in Haskell
type Point = (Float,Float)
anyLine :: Point -> Point -> Point
Next, pattern matching happens before the = sign.
anyLine (a1, a2) (b1, b2)
| a1 == b1 && a2 == b2 = error "Identical"
| otherwise = error "Not identical"
And with guards we omit the equality sign.
This could also just be
anyLine a b
| a == b = ...
| otherwise = ...
I think it's well worth the time to read a good Haskell tutorial to learn some of the basic concepts you're missing, I personally favor Learn You A Haskell.
You can specify a result or define cases; you can't do both at the same time.
anyLine :: datatypePoint -> datatypePoint -> datatypeLine
anyLine a b
| (fst a == fst b) && (snd a == snd b) = error "Identical"
| otherwise = error "Not identical"
Other folks have already answered the question, but I wanted to point out that this would be even simpler if you used "newtype" and "deriving"
newtype Point a = Point (a, a) deriving (Eq)
anyLine a b
| a == b = ....
| otherwise = ....
It also doesn't hurt to keep the type a generic, so now this will work for "Point"s of Floats, Ints, etc.
Related
I have this code that will return the index of a char in a char array but I want my function to return something like -1 if the value isn't in the array. As it stands the function returns the size of the array if the element isn't in the array. Any ideas on how to change my code in order to apply this feature?
I am trying not to use any fancy functions to do this. I just want simple code without built-in functions.
isPartOf :: [(Char)] -> (Char) -> Int
isPartOf [] a = 0
isPartOf (a:b) c
| a == c = 0
| otherwise = 1 + isPartOf b c
For example:
*Main> isPartOf [('a'),('b'),('c')] ('z')
3
But I want:
*Main> isPartOf [('a'),('b'),('c')] ('z')
-1
Let's try to define such a function, but instead of returning -1 in case of element being not a part of the list, we can return Nothing:
isPartOf :: Eq a => [a] -> a -> Maybe Int
isPartOf [] _ = Nothing
isPartOf (x : xs) a | x == a = Just 0
| otherwise = fmap ((+) 1) (isPartOf xs a)
So, it works like that:
>> isPartOf [('a'),('b'),('c')] ('z')
Nothing
it :: Maybe Int
>> isPartOf [('a'),('b'),('c')] ('c')
Just 2
it :: Maybe Int
After that we can use built-in function fromMaybe to convert the Nothing case to -1:
>> fromMaybe (-1) $ isPartOf [('a'),('b'),('c')] ('c')
2
it :: Int
>> fromMaybe (-1) $ isPartOf [('a'),('b'),('c')] ('z')
-1
it :: Int
In case you're curios if such a function already exist, you can use Hoogle for that, searching the [a] -> a -> Maybe Int function: https://www.haskell.org/hoogle/?hoogle=%5Ba%5D+-%3E+a+-%3E+Maybe+Int
And the first answer will be elemIndex:
>> elemIndex 'c' [('a'),('b'),('c')]
Just 2
it :: Maybe Int
>> elemIndex 'z' [('a'),('b'),('c')]
Nothing
it :: Maybe Int
Hope this helps.
The smallest change to achieve this is
isPartOf :: [Char] -> Char -> Int
isPartOf [] a = (-1) -- was: 0
isPartOf (a:b) c
| a == c = 0
| otherwise = 1 + -- was: isPartOf b c
if (isPartOf b c) < 0 then (-2) else (isPartOf b c)
This is terrible computationally though. It recalculates the same value twice; what's worse is that the calculation is done with the recursive call and so the recursive call will be done twice and the time complexity overall will change from linear to exponential!
Let's not do that. But also, what's so special about Char? There's lots of stuff special about the Char but none are used here, except the comparison, (==).
The types the values of which can be compared by equality are known as those belonging to the Eq (for "equality") type class: Eq a => a. a is a type variable capable of assuming any type whatsoever; but here it is constrained to be such that ... yes, belongs to the Eq type class.
And so we write
isPartOf :: Eq a => [a] -> a -> Int
isPartOf [] a = (-1)
isPartOf (a:b) c
| a == c = 0
| otherwise = let d = isPartOf b c in
1 + if d < 0 then (-2) else d
That (-2) looks terribly ad-hoc! A more compact and idiomatic version using guards will also allow us to address this:
isPartOf :: Eq a => [a] -> a -> Int
isPartOf [] a = (-1)
isPartOf (a:b) c
| a == c = 0
| d < 0 = d
| otherwise = 1 + d
where
d = isPartOf b c
Yes, we can define d in the where clause, and use it in our guards, as well as in the body of each clause. Thanks to laziness it won't even be calculated once if its value wasn't needed, like in the first clause.
Now this code is passable.
The conditional passing and transformation is captured by the Maybe data type's Functor interface / instance:
fmap f Nothing = Nothing -- is not changed
fmap f (Just x) = Just (f x) -- is changed
which is what the other answer here is using. But it could be seen as "fancy" when we only start learning Haskell.
When you've written more functions like that, and become "fed up" with repeating the same pattern manually over and over, you'll come to appreciate it and will want to use it. But only then.
Yet another concern is that our code calculates its result on the way back from the recursion's base case.
But it could instead calculate it on the way forward, towards it, so it can return it immediately when the matching character is found. And if the end of list is found, discard the result calculated so far, and return (-1) instead. This is the approach taken by the second answer.
Though creating an additional function litters the global name space. It is usual to do this by defining it internally, in the so called "worker/wrapper" transformation:
isPartOf :: Eq a => [a] -> a -> Int
isPartOf xs c = go xs 0
where
go [] i = (-1)
go (a:b) i
| a == c = i
| otherwise = -- go b (1 + i)
go b $! (1 + i)
Additional boon is that we don't need to pass around the unchanged value c -- it is available in the outer scope, from the point of view of the internal "worker" function go, "wrapped" by and accessible only to our function, isPartOf.
$! is a special call operator which ensures that its argument value is calculated right away, and not delayed. This eliminates an unwanted (in this case) laziness and improves the code efficiency even more.
But from the point of view of overall cleanliness of the design it is better to return the index i wrapped in a Maybe (i.e. Just i or Nothing) instead of using a "special" value which is not so special after all -- it is still an Int.
It is good to have types reflect our intentions, and Maybe Int expresses it clearly and cleanly, so we don't have to remember which of the values are special and which regular, so that that knowledge is not external to our program text, but inherent to it.
It is a small and easy change, combining the best parts from the two previous variants:
isPartOf :: Eq a => [a] -> a -> Maybe Int
isPartOf .....
.......
....... Nothing .....
.......
....... Just i .....
.......
(none of the code was tested. if there are errors, you're invited to find them and correct them, and validate it by testing).
You can achieve it easily if you just pass current element idx to the next recursion:
isPartOf :: [Char] -> Char -> Int
isPartOf lst c = isPartOf' lst c 0
isPartOf' :: [Char] -> Char -> Int -> Int
isPartOf' [] a _ = -1
isPartOf' (a:b) c idx
| a == c = idx
| otherwise = isPartOf' b c (idx + 1)
You are using your function as an accumulator. This is cool except the additions with negative one. An accumulator cannot switch from accumulating to providing a negative 1. You want two different things from your function accumulator. You can use a counter for one thing then if the count becomes unnecessary because no match is found and a negative 1 is issued and nothing is lost. The count would be yet another parameter. ugh. You can use Maybe but that complicates. Two functions, like above is simpler. Here are two functions. The first is yours but the accumulator is not additive it's concatenative.
cIn (x:xs) c | x == c = [1]
| null xs = [-1]
| otherwise = 1:cIn xs c
Cin ['a','b','c'] 'c'
[1,1,1]
cIn ['a','b','c'] 'x'
[1,1,-1]
So the second function is
f ls = if last ls == 1 then sum ls else -1
It will
f $ Cin ['a','b','c'] 'c'
3
and
f $ Cin ['a','b','c'] 'x'
-1
You can zero the index base by changing [1] to [0]
I am going through Learn you a haskell book, and in Chapter 8 there is a snippet of code which looks like this
data LockerState = Taken | Free deriving (Eq, Show)
type Code = String
type LockerMap = Map.Map Int (LockerState, Code)
lookup' :: Int -> LockerMap -> Either String Code
lookup' num_ map_ =
case (Map.lookup num_ map_) of
Nothing -> Left $ "LockerNumber doesn't exist!"
Just (state, code) -> if state == Taken
then Left $ "LockerNumber already taken!"
else Right $ code
This works. However, I wanted to convert if/else block to guard statements like this:
lookup' :: Int -> LockerMap -> Either String Code
lookup' num_ map_ =
case (Map.lookup num_ map_) of
Nothing -> Left $ "LockerNumber doesn't exist!"
Just (state, code) ->
| state == Taken = Left $ "LockerNumber already taken!"
| otherwise = Right $ Code
This doesn't compile. It seems that usage of guards in Haskell is very restrictive/non intuitive. SO Ex1 SO Ex2. Is there a definite source which I can read which tells at which places I can use guards?
There are two places guards are allowed: function definitions and case expressions. In both contexts, guards appear after a pattern and before the body, so you use = in functions and -> in case branches, as usual:
divide x y
| y == 0 = Nothing
--------
| otherwise = Just (x / y)
-----------
positively mx = case mx of
Just x | x > 0 -> Just x
-------
_ -> Nothing
Guards are simply constraints for patterns, so Just x matches any non-Nothing value, but Just x | x > 0 only matches a Just whose wrapped value is also positive.
I suppose the definitive reference is the Haskell Report, specifically §3.13 Case Expressions and §4.4.3 Function and Pattern Bindings, which describe the syntax of guards and specify where they’re allowed.
In your code, you want:
Just (state, code)
| state == Taken -> Left "LockerNumber already taken!"
| otherwise -> Right code
This is also expressible with patterns alone:
Just (Taken, _) -> Left "LockerNumber already taken!"
Just (_, code) -> Right code
Apologies for my poor wording of the question. I've tried searching for an answer but not knowing what to search is making it very difficult to find one.
Here is a simple function which calculates the area of a triangle.
triangleArea :: Float -> Float -> Float -> Float
triangleArea a b c
| (a + b) <= c = error "Not a triangle!"
| (a + c) <= b = error "Not a triangle!"
| (b + c) <= a = error "Not a triangle!"
| otherwise = sqrt (s * (s - a) * (s - b) * (s - c))
where s = (a + b + c) / 2
Three lines of the function have been taken up for the purposes of error checking. I was wondering if these three lines could be condensed into one generic line.
I was wondering if something similar to the following would be possible
(arg1 + arg2) == arg3
where Haskell knows to check each possible combination of the three arguments.
I think #behzad.nouri's comment is the best. Sometimes doing a little math is the best way to program. Here's a somewhat overdone expansion on #melpomene's solution, which I thought would be fun to share. Let's write a function similar to permutations but that computes combinations:
import Control.Arrow (first, second)
-- choose n xs returns a list of tuples, the first component of each having
-- n elements and the second component having the rest, in all combinations
-- (ignoring order within the lists). N.B. this would be faster if implemented
-- using a DList.
choose :: Int -> [a] -> [([a],[a])]
choose 0 xs = [([], xs)]
choose _ [] = []
choose n (x:xs) =
map (first (x:)) (choose (n-1) xs) ++
map (second (x:)) (choose n xs)
So..
ghci> choose 2 [1,2,3]
[([1,2],[3]),([1,3],[2]),([2,3],[1])]
Now you can write
triangleArea a b c
| or [ x + y <= z | ([x,y], [z]) <- choose 2 [a,b,c] ] = error ...
This doesn't address the question of how to shorten your error checking code, but you may be able to limit how often you repeat it by defining some new types with invariants. This function needs error checking because you can't trust the user to supply Float triples that make a reasonable triangle, and if you continue to define functions this way then every triangle-related function you write would need similar error checks.
However, if you define a Triangle type, you can check your invariants only once, when a triangle is created, and then all other functions will be guaranteed to receive valid triangles:
module Triangle (Triangle(), mkTriangle, area) where
data Triangle a = Triangle a a a deriving Show
mkTriangle :: (Num a, Ord a) => a -> a -> a -> Either String (Triangle a)
mkTriangle a b c
| a + b <= c = wrong
| a + c <= b = wrong
| b + c <= a = wrong
| otherwise = Right $ Triangle a b c
where wrong = Left "Not a triangle!"
area :: Floating a => Triangle a -> a
area (Triangle a b c) = sqrt (s * (s - a) * (s - b) * (s - c))
where s = (a + b + c) / 2
Here we export the Triangle type, but not its constructor, so that the client must use mkTriangle instead, which can do the required error checking. Then area, and any other triangle functions you write, can omit the checks that they are receiving a valid triangle. This general pattern is called "smart constructors".
Here are two ideas.
Using existing tools, you can generate all the permutations of the arguments and check that they all satisfy a condition. Thus:
import Data.List
triangleArea a b c
| any (\[x, y, z] -> x + y <= z) (permutations [a,b,c])
= error "Not a triangle!"
| otherwise = {- ... -}
This doesn't require writing very much additional code; however, it will search some permutations you don't care about.
Use the usual trick for choosing an element from a list and the left-overs. The zippers function is one I use frequently:
zippers :: [a] -> [([a], a, [a])]
zippers = go [] where
go b [] = []
go b (v:e) = (b, v, e) : go (v:b) e
We can use it to build a function which chooses only appropriate triples of elements:
triples :: [a] -> [(a, a, a)]
triples xs = do
(b1, v1, e1) <- zippers xs
(b2, v2, e2) <- zippers e1
v3 <- b1 ++ b2 ++ e2
return (v1, v2, v3)
Now we can write our guard like in part (1), but it will only consider unique pairings for the addition.
triangleArea a b c
| any (\(x, y, z) -> x + y <= z) (triples [a,b,c])
= error "Not a triangle!"
| otherwise = {- ... -}
this is an expansion to my last question here: basic haskell : Copying elements
however when an invalid input is added then I want it to print out an error message saying "negative value" or something similar. Is this possible in haskell?
working code:
copy :: Int->a->[a]
copy 0 _ = []
copy y a = [a]++(copy (y-1) a)
final line:
copy b c = error "negative value"
Because partial functions make me sad, I'd suggest doing something more along the lines of
copy :: Int -> a -> Maybe [a]
copy 0 _ = Just []
copy n a | n < 0 = Nothing
| otherwise = fmap (a:) (copy (n-1) a)
We've swapped out that if for a "guard"
foo bar | baz = quux
| ...
is just
foo bar = if baz then quux else ...
Note that I also changed your code a little,
[a] ++ copy (y-1) a ====> fmap (a:) (copy (y-1) a)
You can think of (:) as append.
1 : [2, 3] ==> [1, 2, 3]
It's the preferred alternative to [1] ++ [2, 3]. Say it out loud as "cons", like "construct". We can write this with an operator section
(a:) ==> \x -> a : x
Next we use this wonky fmap function. Think of fmap like this
fmap f Nothing = Nothing
fmap f (Just x) = Just (f x)
So it unwraps a Just and applies a function before rewrapping the result. So our final code returns Nothing if our number is negative, otherwise, just the list.
Why aren't I recommending error? Well because error will blow up your whole program with pretty minimal information and it's a bad idea to try to catch it. Haskell doesn't even mandate that it's possible to do so, GHC just implements error in such a way that it's possible. In other words, you have little chance to recover.
This isn't a big deal for 10 lines of code, but I've spent upwards of 6 hours searching for the offending call to a function using error. It's much faster to debug and more idiomatic haskell.
You can do this with guards
copy :: Int -> a -> [a]
copy n x
| n < 0 = error "negative value"
| n == 0 = []
| otherwise = x : copy (n - 1) x
However, if this fails then it will likely crash your program. A better way is to use the Maybe type:
copySafe :: Int -> a -> Maybe [a]
copySafe n x
| n < 0 = Nothing
| otherwise = Just (copy n x)
Then you can use it as
main = do
putStrLn "Enter a number:"
nStr <- getLine
let n = read nStr :: Int
maybeXs = copySafe n n
case maybeXs of
Nothing -> putStrLn "You entered a negative number!"
Just xs -> print xs
This style forces you to consider both cases of copySafe, either it can fail on a negative value or it can return a valid list. It doesn't crash your program and the error handling is enforced by the type system.
look at http://www.haskell.org/haskellwiki/Error_vs._Exception
for example
copy b c = if c > b then error "negativ value"
I just started learning Haskell. I think I've got the basics down, but I want to make sure I'm actually forcing myself to think functionally too.
data Dir = Right | Left | Front | Back | Up | Down deriving (Show, Eq, Enum)
inv Right = Left
inv Front = Back
inv Up = Down
Anyway, the jist of what I'm trying to do is to create a function to map between each "Dir" and its opposite/inv. I know I could easily continue this for another 3 lines, but I can't help but wonder if there's a better way. I tried adding:
inv a = b where inv b = a
but apparently you can't do that. So my question is: Is there either a way to generate the rest of the inverses or an altogether better way to create this function?
Thanks much.
If the pairing between Up and Down and so on is an important feature then maybe this knowledge should be reflected in the type.
data Axis = UpDown | LeftRight | FrontBack
data Sign = Positive | Negative
data Dir = Dir Axis Sign
inv is now easy.
Do you have a closed-form solution over the indices that corresponds to this function? If so, yes, you can use the Enum deriving to simplify things. For example,
import Prelude hiding (Either(..))
data Dir = Right
| Front
| Up
| Left
| Back
| Down
deriving (Show, Eq, Ord, Enum)
inv :: Dir -> Dir
inv x = toEnum ((3 + fromEnum x) `mod` 6)
Note, this relies on the ordering of the constructors!
*Main> inv Left
Right
*Main> inv Right
Left
*Main> inv Back
Front
*Main> inv Up
Down
This is very C-like, exploits the ordering of constructors, and is un-Haskelly. A compromise is to use more types, to define a mapping between the constructors and their mirrors, avoiding the use of arithmetic.
import Prelude hiding (Either(..))
data Dir = A NormalDir
| B MirrorDir
deriving Show
data NormalDir = Right | Front | Up
deriving (Show, Eq, Ord, Enum)
data MirrorDir = Left | Back | Down
deriving (Show, Eq, Ord, Enum)
inv :: Dir -> Dir
inv (A n) = B (toEnum (fromEnum n))
inv (B n) = A (toEnum (fromEnum n))
E.g.
*Main> inv (A Right)
B Left
*Main> inv (B Down)
A Up
So at least we didn't have to do arithmetic. And the types distinguish the mirror cases. However, this is very un-Haskelly. It is absolute fine to enumerate the cases! Others will have to read your code at some point...
pairs = ps ++ map swap ps where
ps = [(Right, Left), (Front, Back), (Up, Down)]
swap (a, b) = (b, a)
inv a = fromJust $ lookup a pairs
[Edit]
Or how about this?
inv a = head $ delete a $ head $ dropWhile (a `notElem`)
[[Right,Left],[Front,Back],[Up,Down]]
It is good to know, that Enumeration starts with zero.
Mnemonic: fmap fromEnum [False,True] == [0,1]
import Data.Bits(xor)
-- Enum: 0 1 2 3 4 5
data Dir = Right | Left | Front | Back | Up | Down
deriving (Read,Show,Eq,Ord,Enum,Bounded)
inv :: Dir -> Dir
inv = toEnum . xor 1 . fromEnum
I don't think I'd recommend this, but the simple answer in my mind would be to add this:
inv x = fromJust $ find ((==x) . inv) [Right, Front, Up]
I couldn't resist tweaking Landei's answer to fit my style; here's a similar and slightly-more-recommended solution that doesn't need the other definitions:
inv a = fromJust $ do pair <- find (a `elem`) invList
find (/= a) pair
where invList = [[Right, Left], [Up, Down], [Front, Back]]
It uses the Maybe monad.