Concatenating strings together into a list - haskell

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).

Related

How to randomly shuffle a list

I have random number generator
rand :: Int -> Int -> IO Int
rand low high = getStdRandom (randomR (low,high))
and a helper function to remove an element from a list
removeItem _ [] = []
removeItem x (y:ys) | x == y = removeItem x ys
| otherwise = y : removeItem x ys
I want to shuffle a given list by randomly picking an item from the list, removing it and adding it to the front of the list. I tried
shuffleList :: [a] -> IO [a]
shuffleList [] = []
shuffleList l = do
y <- rand 0 (length l)
return( y:(shuffleList (removeItem y l) ) )
But can't get it to work. I get
hw05.hs:25:33: error:
* Couldn't match expected type `[Int]' with actual type `IO [Int]'
* In the second argument of `(:)', namely
....
Any idea ?
Thanks!
Since shuffleList :: [a] -> IO [a], we have shuffleList (xs :: [a]) :: IO [a].
Obviously, we can't cons (:) :: a -> [a] -> [a] an a element onto an IO [a] value, but instead we want to cons it onto the list [a], the computation of which that IO [a] value describes:
do
y <- rand 0 (length l)
-- return ( y : (shuffleList (removeItem y l) ) )
shuffled <- shuffleList (removeItem y l)
return y : shuffled
In do notation, values to the right of <- have types M a, M b, etc., for some monad M (here, IO), and values to the left of <- have the corresponding types a, b, etc..
The x :: a in x <- mx gets bound to the pure value of type a produced / computed by the M-type computation which the value mx :: M a denotes, when that computation is actually performed, as a part of the combined computation represented by the whole do block, when that combined computation is performed as a whole.
And if e.g. the next line in that do block is y <- foo x, it means that a pure function foo :: a -> M b is applied to x and the result is calculated which is a value of type M b, denoting an M-type computation which then runs and produces / computes a pure value of type b to which the name y is then bound.
The essence of Monad is thus this slicing of the pure inside / between the (potentially) impure, it is these two timelines going on of the pure calculations and the potentially impure computations, with the pure world safely separated and isolated from the impurities of the real world. Or seen from the other side, the pure code being run by the real impure code interacting with the real world (in case M is IO). Which is what computer programs must do, after all.
Your removeItem is wrong. You should pick and remove items positionally, i.e. by index, not by value; and in any case not remove more than one item after having picked one item from the list.
The y in y <- rand 0 (length l) is indeed an index. Treat it as such. Rename it to i, too, as a simple mnemonic.
Generally, with Haskell it works better to maximize the amount of functional code at the expense of non-functional (IO or randomness-related) code.
In your situation, your “maximum” functional component is not removeItem but rather a version of shuffleList that takes the input list and (as mentioned by Will Ness) a deterministic integer position. List function splitAt :: Int -> [a] -> ([a], [a]) can come handy here. Like this:
funcShuffleList :: Int -> [a] -> [a]
funcShuffleList _ [] = []
funcShuffleList pos ls =
if (pos <=0) || (length(take (pos+1) ls) < (pos+1))
then ls -- pos is zero or out of bounds, so leave list unchanged
else let (left,right) = splitAt pos ls
in (head right) : (left ++ (tail right))
Testing:
λ>
λ> funcShuffleList 4 [0,1,2,3,4,5,6,7,8,9]
[4,0,1,2,3,5,6,7,8,9]
λ>
λ> funcShuffleList 5 "#ABCDEFGH"
"E#ABCDFGH"
λ>
Once you've got this, you can introduce randomness concerns in simpler fashion. And you do not need to involve IO explicitely, as any randomness-friendly monad will do:
shuffleList :: MonadRandom mr => [a] -> mr [a]
shuffleList [] = return []
shuffleList ls =
do
let maxPos = (length ls) - 1
pos <- getRandomR (0, maxPos)
return (funcShuffleList pos ls)
... IO being just one instance of MonadRandom.
You can run the code using the default IO-hosted random number generator:
main = do
let inpList = [0,1,2,3,4,5,6,7,8]::[Integer]
putStrLn $ "inpList = " ++ (show inpList)
-- mr automatically instantiated to IO:
outList1 <- shuffleList inpList
putStrLn $ "outList1 = " ++ (show outList1)
outList2 <- shuffleList outList1
putStrLn $ "outList2 = " ++ (show outList2)
Program output:
$ pickShuffle
inpList = [0,1,2,3,4,5,6,7,8]
outList1 = [6,0,1,2,3,4,5,7,8]
outList2 = [8,6,0,1,2,3,4,5,7]
$
$ pickShuffle
inpList = [0,1,2,3,4,5,6,7,8]
outList1 = [4,0,1,2,3,5,6,7,8]
outList2 = [2,4,0,1,3,5,6,7,8]
$
The output is not reproducible here, because the default generator is seeded by its launch time in nanoseconds.
If what you need is a full random permutation, you could have a look here and there - Knuth a.k.a. Fisher-Yates algorithm.

What is the difference between `let .. in do` and `<-` notation in Haskell Monads?

I'm trying to implement a function which converts a string to a list of Maybe Ints, e.g. readInts "1 2 42 foo" = [Just 1,Just 2,Just 42,Nothing].
My first aproach was:
readInts (s::String) = do {
ws <- words s;
return (map (readMaybe::(String -> Maybe Int)) ws)
}
This resulted in the following error:
lab_monad.hs:20:52:
Couldn't match type ‘Char’ with ‘[Char]’
Expected type: [String]
Actual type: String
In the second argument of ‘map’, namely ‘ws’
In the first argument of ‘return’, namely
‘(map (readMaybe :: String -> Maybe Int) ws)’
Failed, modules loaded: none.
What I tried next (and worked), was:
readInts (s::String) = do {
let ws = (words s) in do
return (map (readMaybe::(String -> Maybe Int)) ws)
}
My question here is, words s obviously is of type [String]. Why does the interpreter say it is a String? What am I not understanding about <- operator?
ws <- words s, in the list monad, nondeterministically assigns one word from words s to ws; the remaining code simply works with that one word, and the return function "magically" combines the results of working on all the words into the result list.
readInts s = do
ws <- words s -- ws represents *each* word in words s
return (readMaybe ws)
The do notation is just syntactic sugar for using monadic bind:
readInts s = words s >>= (\ws -> return (readMaybe ws))
Without using the Monad instance for lists, you can use map to apply the same function to each word.
readInts s = map readMaybe (words s)
let, on the other hand, simply provides a name for a more complicated expression to be used in another expression. It can be considered syntactic sugar for defining and immediately applying an anonymous function. That is,
let x = y + z in f x
is equivalent to
(\x -> f x) (y + z)
^ ^ ^
| | |
| | RHS of let binding
| part after "in"
LHS of let binding
A let statement with multiple bindings is equivalent to nested let statements:
let x = y + z
a = b + c
in x + a
is equivalent to
let x = y + z
in let a = b + c
in x + a
which desugars to
(\x -> (\a -> x + a)(b + c))(y + z)

Type error in explicitly typed binding in Haskell

I'm a having a type error on my Haskell Code. termEnVoc is expected to return True if the Term given is part of the Vocabulario (vocabulary), I'm not completely sure if it works but anyway I can't understand why do I get a type error.
Here it's the code:
type Cte = Simbolo
type Funcion = (Simbolo,Aridad)
type Predicado = (Simbolo, Aridad)
type Vocabulario = ([Cte], [Funcion], [Predicado])
data Term = C Simbolo | L Var | F Simbolo [Term]
deriving (Show, Eq)
termEnVoc :: Term -> Vocabulario -> Bool --This is line 38, the one with the error
termEnVoc = \t -> \(cs,fs,ps)-> (or(map (\x ->(x==t))cs) || or(map (\x ->(x==t))f) || or(map (\x ->(x==t))p));
And here the error:
ERROR file:.\tarea3.hs:38 - Type error in explicitly typed binding
*** Term : termEnVoc
*** Type : [Char] -> ([[Char]],[([Char],Int)],[([Char],Int)]) -> Bool
*** Does not match : Term -> Vocabulario -> Bool
As chi suggests, the main problem appears to be that you are trying to compare Terms with values of other types. It's hard to see just what you're trying to do (specifically, what different types are supposed to represent), but here's the general way you probably want to structure the function definition:
termEnVoc (C simbolo) (cs, fs, ps) = cte `elem` cs
termEnVoc (F simbolo termList) (cs, fs, ps) = head $ filter ((== f) . fst) fs
termEnVoc (L var) (cs, fs, ps) = head $ filter ((== var) . fst) ps
As I indicated, some (or even most) of the details may be wrong, but this should give you a sense of how to structure the definition. The code above makes use of the following:
(== x) = (\y -> y == x)
You can actually do this with operators in general:
(/ 3) = (\x -> x/3)
and
(3 /) = (\x -> 3/x)
The only one that's wonky is subtraction, and I always have to look up the rules for that.
elem a as = or $ map (== a) as
a `elem` b = elem a b
filter p [] = []
filter p (x:xs)
| p x = x : filter p xs
| otherwise = filter p xs
Note that the real definitions of the above are likely different, for efficiency reasons.
I finally decided that the problem was as dfeuer said that I was comparing terms with values of other types.
I end up with this method:
esTerm :: Vocabulario -> Term -> Bool
esTerm = \(c,f,p)-> \t -> case t of {
C x -> elem x c;
L x -> True;
F n ts -> case (lookup n f) of {
Nothing -> False;
Just x -> x==(length ts)&& and(map (esTerm (c,f,p)) ts);
}
}
Thanks for the help, it was really useful for fixing other mistakes I was making on my project.

Haskell custom data types

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

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