Haskell custom data types - haskell

I have struggled with this for hours, and I cannot figure it out.
module Main where
import Data.List
import Data.Function
type Raw = (String, String)
icards = [("the", "le"),("savage", "violent"),("work", "travail"),("wild", "sauvage"),
("chance", "occasion"),("than a", "qu'un"),("expensive.", "cher."),("saves", "en
vaut"),("time", "temps"),("in", "<`a>"), ("worse", "pire"),("{", "{"),("A", "Un"),
("stitch", "point"),("crime;", "crime,"),("a", "une"),("nine.", "cent."),("It's",
"C'est"),("all","tout"),("rare", "rare"),("you", "vous"),("Abandon","Abandonnez"),
("stash", "planquer"),("Everything", "Tout!ce!qui!est"),("who enter.", "qui entrez."),
("Zazie", "Zazie"),("is", "est"),("cat", "chat"),("it's", "c'est"),("raisin", "raisin
sec"),("hope,", "espoir,"),("mistake.", "faute."),("luck", "chance"),("blueberry",
"myrtille"),("I!took", "J'ai pris"),("that", "qui"),("a!chance.", "des risques."),
("drink", "boisson"),("Live", "Vivre"),("regrets.", "regrets."),("stone", "pierre"),
("broke", "a fait d<e'>border"),("without", "sans"),("The!straw", "La goutte d'eau"),
("camel's!back.", "vase.")]
data Entry = Entry {wrd, def :: String, len :: Int, phr :: Bool}
deriving Show
-- English-to-French, hash-table section
entries :: [Entry]
entries = map (\(x, y) -> Entry x y (length x) (' ' `elem` x)) icards
type Run = [Entry]
maxl = maximum [len e | e <- entries]
runs :: [Run]
runs = f 0 $ groupBy ((==) `on` len) $ sortBy (compare `on` len) entries
where f _ [] = []
f i (r # (Entry {len = l} : _) : rs) | i == l = r : f (i + 1) rs
f i rs = [] : f (i + 1) rs
type Word = String
search' :: Word -> [Entry] -> String
search' searchWord subList
search' _ [] = "unknown"
search' ([def x | x <- subList, (wrd x) == searchWord])==[] = "no match"
search' = [def x | x <- subList, (wrd x) == searchWord]
--search' searchWord subList = (def | x <- subList, (wrd x) == searchWord)
--search' searchWord subList = [def x::String | x <- subList, (wrd x) == searchWord]
--search' searchWord [subList] = [def | x <- subList, (wrd x) == searchWord]
--search' searchWord subList = [def | x <- subList, (wrd x) == searchWord]
--search' searchWord subList = [def x | x <- subList, (wrd x) == searchWord]
--search' searchWord subList = [x->def | x <- subList, (x->wrd) == searchWord]
search :: [Run] -> Word -> String
search runList searchWord = search' searchWord $ runList!!wrdLen
where wrdLen = (length searchWord)
I need help with the search' function. GHCi will tell me that expected type is char... and actual type is Entry-> String.
But I expected type to be the string. I don't know why it thinks I want just a char.
In general here is what I expect:
Send a [Run] and a Word to Search, where [Run] = [[Entries]] and Word = String
the [Run] should be formatted so all of the Entries in [Run]!!0 are length 0, [Run]!!1 are length 1 etc.
So, function search should check the length of the sent Word, then call search' and send it the subList associated to the list of entries that have the same length as the word.
Once inside search' I just want to do a linear search of the list for the wrd == Word, then return the def of that word.
any help would be fantastic.

There are two separate problems:
1. You should apply def to an Entry if you want a String. So, the definition of search' should look like this:
search' searchWord subList = [def x | x <- subList, wrd x == searchWord]
2. It is not obvious, a priori, that searching will always find exactly one match. There may be no matches, or many matches. (I understand that you may expect that the data you provide will result in exactly one match, but that kind of reasoning is a bit beyond what can be done both efficiently and statically.) So, your search' and search functions should return lists. The type signatures should look like this:
search' :: Word -> [Entry] -> [String]
search :: [Run] -> Word -> [String]
...and, indeed, if you leave the type signatures off, GHC will infer exactly those types (up to type synonyms).
edit: To address the updated question, you probably want something like this:
search' searchWord subList = case [def x | x <- subList, wrd x == searchWord] of
[] -> "no match"
(match:_) -> match
Learn You a Haskell has a section about pattern matching if you want to know more. It also has a section on lists and list comprehensions, and is generally just a good tutorial.
However, I strongly advise against writing search' this way: it's a bit dishonest! (For example, as the caller of search', how can I differentiate between the result 'the search succeeded, and the translation is "no match"' and the result 'the search failed'?)

Hm, let's see. You have a list of stuff, [a]. You have some criteria for determining whether or not the search succeeded, a -> Bool. And you want to perform the search on the list, returning a value of the element type a. Stop...Hoogle time! Hoogling [a] -> (a -> Bool) -> a, the top hit is find :: (a -> Bool) -> [a] -> Maybe a. The only catch is that it returns a Maybe a: it will either find Just something or Nothing. I'd say this is an appropriate upgrade for your search function.
search :: [Run] -> Word -> Maybe Entry
search runList searchWord = find (\x -> wrd x == searchWord) $ runList!!wrdLen
where wrdLen = (length searchWord)
Since we've changed the contract for search to produce a Maybe Entry instead of a simple String, if you were using it like this before:
doStuff (search runList searchWord)
You will now have to take into account the possibility of the search failing.
case search runList searchWord of
Just foundWord -> doStuff (def foundWord)
Nothing -> doSomethingElse
If you are absolutely sure that the search will never fail, you can unwrap it with fromJust
doStuff (fromJust $ def $ search runList searchWord)
Although fromJust is generally discouraged.
Now, one other thing. You said you wanted to return only the def, not the entire Entry. As you should know, we can use def :: Entry -> String as a field accessor to extract the def out of an Entry. But how do we apply this to a Maybe Entry?
Stop...Hoogle time! We have a value, v :: Maybe a. We have a function that works on plain old a values, f :: a -> b. We want to somehow apply f to v, yielding a result of type b. Hoogling Maybe a -> (a -> b) -> b, I see two good options.
maybe :: b -> (a -> b) -> Maybe a -> b
maybe n _ Nothing = n
maybe _ f (Just x) = f x
The maybe function takes a function and a maybe value, and also a default. If the maybe value turns out to be Nothing, it just uses the default. Otherwise, it uses the function f on the value inside of the Just constructor.
search :: [Run] -> Word -> String
search runList searchWord = search' (\x -> wrd x == searchWord) $ runList!!wrdLen
where wrdLen = (length searchWord)
search' :: (Entry -> Bool) -> [Entry] -> String
search' f es = maybe "not found" def $ find f es
-- or eta reduce: search' = maybe "not found" def . find
This solution is OK, but I prefer the next one better.
fmap :: Functor f => (a -> b) -> f a -> f b
If you are not familiar with functors, I highly recommend Learn you a Haskell > the Functor typeclass. Maybe is a functor, which means we can use fmap on maybe values.
search' :: (Entry -> Bool) -> [Entry] -> Maybe String
search' f es = fmap def $ find f es

Related

How to define a lambda function that filters list based on subtype of a sum type?

The example is taken from a "Haskell programming from first principles"
The goal of filter function is get rid of all the objects except those of 'DbDate' type.
On somone's github I found a way to filter sum types with list comprehension and pattern matching(1). Now I am trying to find a way to redefine this filter with a lambda function(2) or normal "case of" of "if then" function. I do not know how to properly check the type of arguments of a function when I deal with custom data type.
Book doesn't introduce the reader to any super specific library functions, just standard maps, folds, filters and other stuff you'd find in prelude.
import Data.Time
data DatabaseItem = DbString String
| DbNumber Integer
| DbDate UTCTime
deriving (Eq, Ord, Show)
--List that needs to be filtered
theDatabase :: [DatabaseItem]
theDatabase =
[ DbDate (UTCTime (fromGregorian 1911 5 1)
(secondsToDiffTime 34123))
, DbNumber 9001
, DbString "Hello, world!"
, DbDate (UTCTime (fromGregorian 1921 5 1)
(secondsToDiffTime 34123))
]
--1 works fine, found on someone's git hub
filterDbDate :: [DatabaseItem] -> [UTCTime]
filterDbDate dbes = [x | (DbDate x) <- dbes]
--2 Looking for the eqivalents with lambda or "case" or "if then"
--pattern is not satisfactory
filterDbDate :: [DatabaseItem] -> [UTCTime]
filterDbDate dbes = filter (\(DbDate x) -> True) theDatabase
filter has the type (a -> Bool) -> [a] -> [a] so it is not able to change the type of your list.
According to The Haskell 98 Report (section 3.11) the list comprehension used in the code you found on github desugars to:
filterDbDate2 :: [DatabaseItem] -> [UTCTime]
filterDbDate2 dbes = let extractTime (DbDate time) = [time]
extractTime _ = []
in concatMap extractTime theDatabase
You can rewrite extractTime to use case ... of:
filterDbDate3 :: [DatabaseItem] -> [UTCTime]
filterDbDate3 dbes = let extractTime item = case item of (DbDate time) -> [time]
_ -> []
in concatMap extractTime theDatabase
And replace it by a lambda:
filterDbDate4 :: [DatabaseItem] -> [UTCTime]
filterDbDate4 dbes = concatMap (\item ->
case item of
(DbDate time) -> [time]
_ -> [])
theDatabase
But imho your original solution using list comprehension looks the best:
filterDbDate dbes = [x | (DbDate x) <- dbes]
As #Niko has already said in his answer, filter cannot change the type. However, there is a variant of filter which can: Data.Maybe.mapMaybe :: (a -> Maybe b) -> [a] -> [b]. The idea is that if you want to keep an element, then you return Just newvalue from the lambda; otherwise you return Nothing. In that case, you could rewrite filterDbDate as:
import Data.Maybe
filterDbDate dbes = mapMaybe (\x -> case x of { DBDate d -> Just d; _ -> Nothing }) dbes
Personally, I would say that this is the second-clearest way to write this function (after the list comprehension method).
You were indeed on the right track, as pattern matching is an easy way of solving this, however you will get error as your pattern-matching is not comprehensive. Also, note that if you use filter, you will still get a list of [DatabaseItem] as filter never changes the type. You can however use map to do it. So:
Case Of
You can have a case .. of inside your lambda function:
filterDbDate' :: [DatabaseItem] -> [UTCTime]
filterDbDate' = map (\(DbDate x) -> x) .filter (\x ->
case x of
DbDate x -> True
_ -> False)
Recursion + Pattern Matching
However I think it's more clear using a recursion:
filterDbDate'' :: [DatabaseItem] -> [UTCTime]
filterDbDate'' [] = []
filterDbDate'' ((DbDate d):ds) = d : filterDbDate ds
filterDbDate'' (_:ds) = filterDbDate ds
Best Way
To be honest, when you have to mix up filter and map, and your lambdas are easy like this one, list comprehensions like yours are the cleanest way:
filterDbDate ds = [d | (DbDate d) <- ds]

Implementation of a program in which characters of a string repeated certain times in haskell

This is a question from my homework thus tips would be much likely appreciated.
I am learning Haskell this semester and my first assignment requires me to write a function that inputs 2 string (string1 and string2) and returns a string that is composed of (the repeated) characters of first string string1 until a string of same length as string2 has been created.
I am only allowed to use the Prelude function length.
For example: take as string1 "Key" and my name "Ahmed" as string2 the function should return "KeyKe".
Here is what I've got so far:
makeString :: Int -> [a] -> [a]
makeString val (x:xs)
| val > 0 = x : makeString (val-1) xs
| otherwise = x:xs
Instead of directly giving it two strings i am giving it an integer value (since i can subtitute it for length later on), but this is giving me a runtime-error:
*Main> makeString 8 "ahmed"
"ahmed*** Exception: FirstScript.hs: (21,1)-(23,21) : Non-exhaustive patterns in function makeString
I think it might have something to do my list running out and becoming an empty list(?).
A little help would be much appreciated.
I think this code is enough to solve your problem:
extend :: String -> String -> String
extend src dst = extend' src src (length dst)
where
extend' :: String -> String -> Int -> String
extend' _ _ 0 = []
extend' [] src size = extend' src src size
extend' (x:xs) src size = x : extend' xs src (size - 1)
The extend' function will cycle the first string until is is consumed then will begin to consume it again.
You can also make it using take and cycle like functions:
repeatString :: String -> String
repeatString x = x ++ repeatString x
firstN :: Int -> String -> String
firstN 0 _ = []
firstN n (x:xs) = x : firstN ( n - 1 ) xs
extend :: String -> String -> String
extend src dst = firstN (length dst) (repeatString src)
or a more generic version
repeatString :: [a] -> [a]
repeatString x = x ++ repeatString x
firstN :: (Num n, Eq n ) => n -> [a] -> [a]
firstN 0 _ = []
firstN n (x:xs) = x : firstN ( n - 1 ) xs
extend :: [a] -> [b] -> [a]
extend _ [] = error "Empty target"
extend [] _ = error "Empty source"
extend src dst = firstN (length dst) (repeatString src)
which is capable of taking any type of lists:
>extend [1,2,3,4] "foo bar"
[1,2,3,4,1,2,3]
Like Carsten said, you should
handle the case when the list is empty
push the first element at the end of the list when you drop it.
return an empty list when n is 0 or lower
For example:
makeString :: Int -> [a] -> [a]
makeString _ [] = [] -- makeString 10 "" should return ""
makeString n (x:xs)
| n > 0 = x:makeString (n-1) (xs++[x])
| otherwise = [] -- makeString 0 "key" should return ""
trying this in ghci :
>makeString (length "Ahmed") "Key"
"KeyKe"
Note: This answer is written in literate Haskell. Save it as Filename.lhs and try it in GHCi.
I think that length is a red herring in this case. You can solve this solely with recursion and pattern matching, which will even work on very long lists. But first things first.
What type should our function have? We're taking two strings, and we will repeat the first string over and over again, which sounds like String -> String -> String. However, this "repeat over and over" thing isn't really unique to strings: you can do that with every kind of list, so we pick the following type:
> repeatFirst :: [a] -> [b] -> [a]
> repeatFirst as bs = go as bs
Ok, so far nothing fancy happened, right? We defined repeatFirst in terms of go, which is still missing. In go we want to exchange the items of bs with the corresponding items of as, so we already know a base case, namely what should happen if bs is empty:
> where go _ [] = []
What if bs isn't empty? In this case we want to use the right item from as. So we should traverse both at the same time:
> go (x:xs) (_:ys) = x : go xs ys
We're currently handling the following cases: empty second argument list, and non-empty lists. We still need to handle the empty first argument list:
> go [] ys =
What should happen in this case? Well, we need to start again with as. And indeed, this works:
> go as ys
Here's everything again at a single place:
repeatFirst :: [a] -> [b] -> [a]
repeatFirst as bs = go as bs
where go _ [] = []
go (x:xs) (_:ys) = x : go xs ys
go [] ys = go as ys
Note that you could use cycle, zipWith and const instead if you didn't have constraints:
repeatFirst :: [a] -> [b] -> [a]
repeatFirst = zipWith const . cycle
But that's probably for another question.

Haskell: put in State monad seems to be elided

I'm writing a program to allocate pizzas to people; each person will get one pizza, ideally of their favorite type, unless stock has run out, in which case they are given their next favorite type recursively.
My approach is to compute a ((User, Pizza), Int) for the amount a person would like said pizza, sort those, and recurse through using a state monad to keep inventory counts.
The program is written and type checks:
allocatePizzasImpl :: [((User, Pizza), Int)]
-> State [(Pizza, Int)] [(User, Pizza)]
allocatePizzasImpl [] = return []
allocatePizzasImpl ((user, (flavor, _)):ranks) =
do inventory <- get
-- this line is never hit
put $ updateWith inventory (\i -> if i <= 0
then Nothing
else Just $ i - 1) flavor
next <- allocatePizzasImpl $ filter ((/= user) . fst) ranks
return $ (user, flavor) : next
and I have a helper function to extract the result:
allocatePizzas :: [Pizza]
-> [((User, Pizza), Int)]
-> [(User, Pizza)]
allocatePizzas pizzas rank = fst
. runState (allocatePizzasImpl rank)
$ buildQuotas pizzas
but the line indicated by -- this line is never hit is... never hit by any GHCI breakpoints; furthermore, if I break on the return call, GHCI says inventory isn't in scope.
When run, the result is assigning the same pizza (with one inventory count) to all users. Something is going wrong, but I have absolutely no idea how to proceed. I'm new to Haskell, so any comments on style would be appreciated as well =)
Thanks!
PS: For completeness, updateWith is defined as:
updateWith :: (Eq a, Eq b)
=> [(a, b)] -- inventory
-> (b -> Maybe b) -- update function; Nothing removes it
-> a -- key to update
-> [(a, b)]
updateWith set update key =
case lookup key set of
Just b -> replace set
(unwrapPair (key, update b))
(fromMaybe 0 $ elemIndex (key, b) set)
Nothing -> set
where replace :: [a] -> Maybe a -> Int -> [a]
replace [] _ _ = []
replace (_:xs) (Just val) 0 = val:xs
replace (_:xs) Nothing 0 = xs
replace (x:xs) val i = x : (replace xs val $ i - 1)
unwrapPair :: Monad m => (a, m b) -> m (a, b)
unwrapPair (a, mb) = do b <- mb
return (a, b)
I think your function replace is broken:
replace (_:xs) (Just val) 0 = val:xs
This doesn't pay any attention to the value it's replacing. Wasn't your intention to replace just the pair corresponding to key?
I think you want
updateWith [] e k = []
updateWith ((k', v):kvs) e k
| k' == k = case e v of
Just v' -> (k, v'):kvs
Nothing -> kvs
| otherwise = (k', v) : updateWith kvs e k
The issue (ignoring other conceptual things mentioned by the commenters) turned out to be using fst to extract the result from the State would for some reason not cause the State to actually be computed. Running the result through seq fixed it.
I'd be interested in knowing why this is the case, though!
Edit: As Daniel Wagner pointed out in the comments, I wasn't actually using inventory, which turned out to be the real bug. Marking this as accepted.

Concatenating strings together into a list

What I'm trying to do is that I want to take a list of strings as input and do some operations then return back a list of strings. The problem is, I am looking for specific yet generic patterns of the string for each case:
func :: [String] -> [String]
func [] = []
func [x] = [x]
func (["Not","(","Not"]:es:[")"]) = es --HERE
func ("Not":"(":pred:"And":rest:")") = ("Not":pred:"Or":(pushNotInwards rest))
func ("Not":"(":pred:"Or":rest:")") = ("Not":pred:"And":(pushNotInwards rest))
func ("Not":"(":"ForAll":x:scope:")") = ("Exists":"Not":"("scope:")")
func ("Not":"(":"Exists":x:scope:")") = ("ForAll":"Not":"(":scope:")")
For the third case for instance, I want to take a list of strings in the form of:
["Not","(","Not",some_strings,")"]
I tried using ++ on the left hand side as:
func (["Not"]++["("]++["Not"])++es++[")"]) = es
I also tried concat and : but they didn't work either. Any suggestions?
You seem to have some confusion about the different string operators.
A String is just a synonym for a list of chars i.e. [Char]. The colon : operator (aka cons) adds one element to the beginning of a list. Here's its type:
*Main> :t (:)
(:) :: a -> [a] -> [a]
For example:
*Main> 1:[2,3]
[1,2,3]
*Main> 'a':"bc"
"abc"
The ++ operator concatenates two lists. Here's its type:
*Main> :t (++)
(++) :: [a] -> [a] -> [a]
Pattern matching can only be done using a data constructor. The : operator is a data constructor, but the ++ operator is not. So you cannot define a function using pattern matching over the ++ operator.
To define a function using pattern matching, I'd suggest defining a new data type for the different functions and qualifier rather than using strings:
-- Logic Operation
data LogicOp =
Not LogicOp | And [LogicOp] | Or [LogicOp] |
Forall String LogicOp | Exists String LogicOp | T | F
deriving (Eq, Show)
func :: LogicOp -> LogicOp
func (Not (Not x)) = x
func (Not (And (pred:rest))) = Or (Not pred:[func (Not (And rest))])
func (Not (Or (pred:rest))) = And (Not pred:[func (Not (Or rest))])
func (Not (Forall x scope)) = Exists x (Not scope)
func (Not (Exists x scope)) = Forall x (Not scope)
func x = x
Here are some examples:
*Main> func (Not (Not T))
T
*Main> func (Not (And [T, F, T]))
Or [Not T,Or [Not F,Or [Not T,Not (And [])]]]
*Main> func (Not (Or [T, F, T]))
And [Not T,And [Not F,And [Not T,Not (Or [])]]]
*Main> func (Not (Forall "x" (And T F))
*Main> func (Not (Forall "x" (And [T, F])))
Exists "x" (Not (And [T,F]))
*Main> func (Not (Exists "x" (And [T, F])))
Forall "x" (Not (And [T,F]))
You should probably not use strings for that. Create a new type:
data SomeExpr = Not SomeExpr
| And SomeExpr SomeExpr
| Or SomeExpr SomeExpr
deriving (Show)
Then you could match on that expression:
func :: SomeExpr -> SomeExpr
func (Not (Not x)) = func x
func (Not (And x y)) = Or (Not $ func x) (Not $ func y)
func (Not (Or x y)) = And (Not $ func x) (Not $ func y)
...
func x = x
You can't pattern match a list in the middle, e.g You want to match [1,2,3,4,5] with (1:middle:5:[]), but this is invalid.
Yes, using an own type has it's own problems, you have to parse it etc, but it is much more easier and safer than with strings (which could have arbitrary content).

Doing a binary search on some elements in Haskell

I'm trying to complete the last part of my Haskell homework and I'm stuck, my code so far:
data Entry = Entry (String, String)
class Lexico a where
(<!), (=!), (>!) :: a -> a -> Bool
instance Lexico Entry where
Entry (a,_) <! Entry (b,_) = a < b
Entry (a,_) =! Entry (b,_) = a == b
Entry (a,_) >! Entry (b,_) = a > b
entries :: [(String, String)]
entries = [("saves", "en vaut"), ("time", "temps"), ("in", "<`a>"),
("{", "{"), ("A", "Un"), ("}", "}"), ("stitch", "point"),
("nine.", "cent."), ("Zazie", "Zazie")]
build :: (String, String) -> Entry
build (a, b) = Entry (a, b)
diction :: [Entry]
diction = quiksrt (map build entries)
size :: [a] -> Integer
size [] = 0
size (x:xs) = 1+ size xs
quiksrt :: Lexico a => [a] -> [a]
quiksrt [] = []
quiksrt (x:xs)
|(size [y|y <- xs, y =! x]) > 0 = error "Duplicates not allowed."
|otherwise = quiksrt [y|y <- xs, y <! x]++ [x] ++ quiksrt [y|y <- xs, y >! x]
english :: String
english = "A stitch in time save nine."
show :: Entry -> String
show (Entry (a, b)) = "(" ++ Prelude.show a ++ ", " ++ Prelude.show b ++ ")"
showAll :: [Entry] -> String
showAll [] = []
showAll (x:xs) = Main.show x ++ "\n" ++ showAll xs
main :: IO ()
main = do putStr (showAll ( diction ))
The question asks:
Write a Haskell programs that takes
the English sentence 'english', looks
up each word in the English-French
dictionary using binary search,
performs word-for-word substitution,
assembles the French translation, and
prints it out.
The function 'quicksort' rejects
duplicate entries (with 'error'/abort)
so that there is precisely one French
definition for any English word. Test
'quicksort' with both the original
'raw_data' and after having added
'("saves", "sauve")' to 'raw_data'.
Here is a von Neumann late-stopping
version of binary search. Make a
literal transliteration into Haskell.
Immediately upon entry, the Haskell
version must verify the recursive
"loop invariant", terminating with
'error'/abort if it fails to hold. It
also terminates in the same fashion if
the English word is not found.
function binsearch (x : integer) : integer
local j, k, h : integer
j,k := 1,n
do j+1 <> k --->
h := (j+k) div 2
{a[j] <= x < a[k]} // loop invariant
if x < a[h] ---> k := h
| x >= a[h] ---> j := h
fi
od
{a[j] <= x < a[j+1]} // termination assertion
found := x = a[j]
if found ---> return j
| not found ---> return 0
fi
In the Haskell version
binsearch :: String -> Integer -> Integer -> Entry
as the constant dictionary 'a' of type
'[Entry]' is globally visible. Hint:
Make your string (English word) into
an 'Entry' immediately upon entering
'binsearch'.
The programming value of the
high-level data type 'Entry' is that,
if you can design these two functions
over the integers, it is trivial to
lift them to to operate over Entry's.
Anybody know how I'm supposed to go about my binarysearch function?
The instructor asks for a "literal transliteration", so use the same variable names, in the same order. But note some differences:
the given version takes only 1
parameter, the signature he gives
requires 3. Hmmm,
the given version is not recursive, but he asks for a
recursive version.
Another answer says to convert to an Array, but for such a small exercise (this is homework after all), I felt we could pretend that lists are direct access. I just took your diction::[Entry] and indexed into that. I did have to convert between Int and Integer in a few places.
Minor nit: You've got a typo in your english value (bs is a shortcut to binSearch I made):
*Main> map bs (words english)
[Entry ("A","Un"),Entry ("stitch","point"),Entry ("in","<`a>"),Entry ("time","te
mps"),*** Exception: Not found
*Main> map bs (words englishFixed)
[Entry ("A","Un"),Entry ("stitch","point"),Entry ("in","<`a>"),Entry ("time","te
mps"),Entry ("saves","en vaut"),Entry ("nine.","cent.")]
*Main>
A binary search needs random access, which is not possible on a list. So, the first thing to do would probably be to convert the list to an Array (with listArray), and do the search on it.
here's my code for just the English part of the question (I tested it and it works perfectly) :
module Main where
class Lex a where
(<!), (=!), (>!) :: a -> a -> Bool
data Entry = Entry String String
instance Lex Entry where
(Entry a _) <! (Entry b _) = a < b
(Entry a _) =! (Entry b _) = a == b
(Entry a _) >! (Entry b _) = a > b
-- at this point, three binary (infix) operators on values of type 'Entry'
-- have been defined
type Raw = (String, String)
raw_data :: [Raw]
raw_data = [("than a", "qu'un"), ("saves", "en vaut"), ("time", "temps"),
("in", "<`a>"), ("worse", "pire"), ("{", "{"), ("A", "Un"),
("}", "}"), ("stitch", "point"), ("crime;", "crime,"),
("a", "une"), ("nine.", "cent."), ("It's", "C'est"),
("Zazie", "Zazie"), ("cat", "chat"), ("it's", "c'est"),
("raisin", "raisin sec"), ("mistake.", "faute."),
("blueberry", "myrtille"), ("luck", "chance"),
("bad", "mauvais")]
cook :: Raw -> Entry
cook (x, y) = Entry x y
a :: [Entry]
a = map cook raw_data
quicksort :: Lex a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort (filter (<! x) xs) ++ [x] ++ quicksort (filter (=! x) xs) ++ quicksort (filter (>! x) xs)
getfirst :: Entry -> String
getfirst (Entry x y) = x
getsecond :: Entry -> String
getsecond (Entry x y) = y
binarysearch :: String -> [Entry] -> Int -> Int -> String
binarysearch s e low high
| low > high = " NOT fOUND "
| getfirst ((e)!!(mid)) > s = binarysearch s (e) low (mid-1)
| getfirst ((e)!!(mid)) < s = binarysearch s (e) (mid+1) high
| otherwise = getsecond ((e)!!(mid))
where mid = (div (low+high) 2)
translator :: [String] -> [Entry] -> [String]
translator [] y = []
translator (x:xs) y = (binarysearch x y 0 ((length y)-1):translator xs y)
english :: String
english = "A stitch in time saves nine."
compute :: String -> [Entry] -> String
compute x y = unwords(translator (words (x)) y)
main = do
putStr (compute english (quicksort a))
An important Prelude operator is:
(!!) :: [a] -> Integer -> a
-- xs!!n returns the nth element of xs, starting at the left and
-- counting from 0.
Thus, [14,7,3]!!1 ~~> 7.

Resources