[Haskell-cafe] GPT & Haskell

Aloïs Cochard alois.cochard at gmail.com
Sat Apr 1 17:43:21 UTC 2023


Thanks for fixing the link Nenad,

I leave you with an excerpt from Oleg's last paper which contains that
beautiful quote:

``This make me think that the authors are under the impression that
compilers can magically transform bad code into efficient high-quality code
by clever enough optimizations. As a compiler writer, I consider this a
complete myth that many students and non-compiler-developers hope is a
truth. I agree that compilers should aim to improve the efficiency of the
code given as input, but one cannot expect the compiler to recognize
algorithms and swap them for ones with better asymptotic complexity or *make
other major code transformations that really should be the job of the
programmer*. [emphasis mine]''

Magnus Myreen.

On Sat, 1 Apr 2023 at 18:06, Nenad Končar <nlpresearcher at gmail.com> wrote:

> GPT-4 when prompted with an improved prompt:
>
> *Write binary search in Haskel. Print results using putStrLn. Ensure
> bug-free code by specifying preconditions, postconditions, invariants,
> variants and internal states. Calculate the middle index using a safer
> formula to avoid intermediate overflow.*
>
>
>
> gives the following response:
>
> *-- Binary search is a recursive algorithm that finds an element in a
> sorted list by*
>
> *-- repeatedly dividing the list into two halves and comparing the element
> with the middle value.*
>
> *-- It returns the index of the element if found, or Nothing otherwise.*
>
>
>
> *-- Precondition: The input list must be sorted in ascending order.*
>
> *-- Postcondition: The output index must be within the bounds of the list
> and point to the element, or be Nothing.*
>
> *-- Invariant: The element, if present, must be in the current sublist.*
>
> *-- Variant: The length of the current sublist decreases by half at each
> recursive call.*
>
> *-- Internal state: The current sublist is defined by two indices: low and
> high.*
>
>
>
> *binarySearch :: Ord a => [a] -> a -> Maybe Int*
>
> *binarySearch xs x = go xs x 0 (length xs - 1)*
>
> *  where*
>
> *    -- The go function performs the recursive search on the sublist
> [low..high].*
>
> *    go :: Ord a => [a] -> a -> Int -> Int -> Maybe Int*
>
> *    go xs x low high*
>
> *      -- Base case 1: The sublist is empty, so the element is not found.*
>
> *      | low > high = Nothing*
>
> *      -- Base case 2: The middle value is equal to the element, so the
> index is found.*
>
> *      | xs !! mid == x = Just mid*
>
> *      -- Recursive case 1: The element is smaller than the middle value,
> so search in the left half.*
>
> *      | x < xs !! mid = go xs x low (mid - 1)*
>
> *      -- Recursive case 2: The element is larger than the middle value,
> so search in the right half.*
>
> *      | otherwise = go xs x (mid + 1) high*
>
> *      where*
>
> *        -- Calculate the middle index using a safer formula to avoid
> overflow.*
>
> *        mid = low + (high - low) `div` 2*
>
>
>
> *-- A sample list to test the binary search function.*
>
> *sampleList :: [Int]*
>
> *sampleList = [1, 3, 5, 7, 9, 11, 13, 15]*
>
>
>
> *-- A sample element to search for in the list.*
>
> *sampleElement :: Int*
>
> *sampleElement = 9*
>
>
>
> *-- Print the result of the binary search using putStrLn.*
>
> *main :: IO ()*
>
> *main = do*
>
> *  let result = binarySearch sampleList sampleElement*
>
> *  case result of*
>
> *    Nothing -> putStrLn "Element not found."*
> *    Just i -> putStrLn $ "Element found at index " ++ show i ++ "."*
>
> The above code runs:
> *https://onecompiler.com/haskell/3z4c7f5dt
> <https://onecompiler.com/haskell/3z4c7f5dt>*
>
>
> Furthermore, GPT-4 when prompted:
>
> *For the binary search algorithm, list all possible preconditions,
> postconditions, invariants, variants, internal states, underflows,
> overflows, divisions by zero, mistakes, errors, bugs, run-time exceptions,
> faults, defects and pitfalls.*
>
> and then prompting GPT-4 again with:
>
> *Summarize the following:*
>
> *<result from the previous prompt given to * *GPT-4*
> *>*
>
> gives the following response:
>
> *Hi there,*
>
> *I hope this email finds you well. I am writing to summarize the
> following:*
>
>
>
>
>
>
>
>
>
>
> *- The algorithm searches for a target value in a sorted array using
> binary search. - The algorithm returns the index of the target value in the
> array or -1 if the target value is not found. - The algorithm does not
> modify the input array. - The algorithm assumes that the input array is
> sorted in ascending or descending order, the target value is comparable
> with the elements of the array, and the lower and upper bounds of the
> search range are valid indices of the array. - The algorithm maintains the
> invariant that the target value is always within the search range or does
> not exist in the array. - The algorithm reduces the size of the search
> range by at least one after each iteration. - The algorithm handles edge
> cases such as empty array, single element array, target value at the first
> or last position of the array, lower and upper bounds being equal, negative
> or large positive integers, and division by zero when calculating the
> middle index. - The algorithm avoids integer underflow or overflow when
> calculating the middle index by using bitwise operations instead of
> arithmetic operations. - The algorithm has been tested with various test
> cases to ensure its correctness and efficiency. - The algorithm has been
> verified using formal methods to prove its preconditions, postconditions,
> invariants and variants.*
> *Please let me know if you have any questions or feedback about the
> algorithm. I appreciate your time and attention.*
>
>
> The following web pages provide some credence to GPT-4's claim of
> avoiding overflows/underflows by using bitwise operations instead of
> arithmetic operations:
>
> https://stackoverflow.com/questions/10078778/bitwise-overflow-checking-in-c
>
> https://www.opensourceforu.com/2009/03/joy-of-programming-how-to-detect-integer-overflow/
>
> The truth is that bitwise operations can recognise if an overflow is about
> to happen prior to it happening. I do not see how bitwise operations can
> *avoid* overflow and therefore GPT-4's claim in this case, in my humble
> view, should be classified as it having a *vivid imagination*.
>
>
>
>
>
>
> On Sat, 1 Apr 2023 at 16:11, Nenad Končar <nlpresearcher at gmail.com> wrote:
>
>> Here is the correct link to Haskel code:
>>
>> https://onecompiler.com/haskell/3z4c7f5dt
>>
>> On Sat, 1 Apr 2023 at 15:42, Gregory Guthrie <guthrie at miu.edu> wrote:
>>
>>> Yes, will check on it.
>>>
>>>
>>>
>>> That is because the reason that a simple program was used was because
>>> the example was to ask GPT to solve it is a range of languages, one of
>>> which was Haskell and there were links to solutions in all of them..
>>>
>>>
>>>
>>> “*Write binary search in xxxx.  Ensure bug-free code by specifying
>>> preconditions, postconditions, invariants, variants, internal states.”*
>>>
>>>
>>>
>>>   { HTML, CSS and JavaScript, C++, Haskell, JavaScript, Python,
>>> CommonLisp, C, C#, PHP, Java, Go, Erlang, Alloy, TLA+, X-Machine, PVS
>>> Verifier, SPIN model checker, Guarded Command Language, Hoare triples,
>>> Gries & Owicki concurrent code}
>>>
>>>
>>>
>>> It was an interesting exercise from Dr. Nenad Koncar, a successful NL
>>> researcher and developer. I’ll ask him for a corrected link to the Haskell
>>> version.
>>>
>>>
>>>
>>> Dr. Gregory Guthrie
>>>
>>>
>>>
>>> *From:* Aloïs Cochard <alois.cochard at gmail.com>
>>> *Sent:* Saturday, April 1, 2023 8:23 AM
>>> *To:* Gregory Guthrie <guthrie at miu.edu>
>>> *Cc:* haskell-cafe at haskell.org; Nenad Končar <nlpresearcher at gmail.com>;
>>> Haskell Community <
>>> replies+f6607596e3ee63f105e2b0327b86f062 at discourse.haskell.org>
>>> *Subject:* Re: [Haskell-cafe] GPT & Haskell
>>>
>>>
>>>
>>> Dear Gregory,
>>>
>>>
>>>
>>> Can you please fix your onecompiler vanity link? It points to the C++
>>> runtime implementation.
>>>
>>>
>>>
>>> Thanks
>>>
>>>
>>>
>>> On Fri, 31 Mar 2023 at 22:04, Gregory Guthrie <guthrie at miu.edu> wrote:
>>>
>>> From a colleague:
>>>
>>>   GPT Pretty smart(?!).
>>>
>>> But this is of course simple, and searchable.
>>>
>>>
>>>
>>> Still…
>>>
>>>
>>> --------------------------------------------------------------------------------------------------
>>>
>>> GPT-4 when prompted:
>>>
>>> *Write binary search in Haskel. Print results using putStrLn. Ensure
>>> bug-free code by specifying preconditions, postconditions, invariants,
>>> variants, internal states.*
>>>
>>>
>>>
>>> gives the following response:
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>> *-- Binary search in Haskell -- Precondition: the list is sorted in
>>> ascending order -- Postcondition: the function returns the index of the
>>> target element if found, or Nothing otherwise -- Invariant: the search
>>> space is always within the bounds of the list -- Variant: the search space
>>> decreases by half at each recursive call -- Internal state: the lower and
>>> upper bounds of the search space binarySearch :: Ord a => [a] -> a -> Maybe
>>> Int binarySearch xs x = go xs x 0 (length xs - 1)   where     go xs x lo hi
>>>       | lo > hi = Nothing -- base case: search space is empty       | x ==
>>> midElem = Just mid -- base case: target element is found       | x <
>>> midElem = go xs x lo (mid - 1) -- recursive case: search in the left half
>>>     | otherwise = go xs x (mid + 1) hi -- recursive case: search in the
>>> right half       where         mid = (lo + hi) `div` 2 -- calculate the
>>> middle index         midElem = xs !! mid -- get the middle element -- Print
>>> results using putStrLn main :: IO () main = do   let xs = [1, 3, 5, 7, 9]
>>> -- a sorted list of integers   let x = 5 -- a target element to search for
>>>   let result = binarySearch xs x -- call the binary search function   case
>>> result of -- pattern match on the result     Nothing -> putStrLn "Element
>>> not found" -- print a message if Nothing is returned     Just i -> putStrLn
>>> $ "Element found at index " ++ show i -- print a message with the index if
>>> Just i is returned*
>>>
>>>
>>>
>>> The above code runs:
>>>
>>> *https://onecompiler.com/cpp/3z48yt2pp
>>> <https://onecompiler.com/cpp/3z48yt2pp>*
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> To (un)subscribe, modify options or view archives go to:
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> Only members subscribed via the mailman list are allowed to post.
>>>
>>>
>>>
>>> --
>>>
>>> *Λ\oïs*
>>>
>>> http://twitter.com/aloiscochard
>>>
>>> http://github.com/aloiscochard
>>>
>>

-- 
*Λ\oïs*
http://twitter.com/aloiscochard
http://github.com/aloiscochard
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20230401/ca94a1b2/attachment-0001.html>


More information about the Haskell-Cafe mailing list