Insufficient definition of replicate - haskell

I have a question that I think is rather tricky.
The standard prelude contains the function
replicate :: Int -> a -> [a]
The following might seem like a reasonable definition for it
replicate n x = take n [x,x,..]
But it is actually not sufficient. Why not?
I know that the replicate function is defined as:
replicate :: Int -> a -> [a]
replicate n x = take n (repeat x)
And repeat is defined as:
repeat :: a -> [a]
repeat x = xs where xs = x:xs
Is the definition insufficient (from the question) because it uses an infinite list?

First of all there is a small syntax error in the question, it should be:
replicate n x = take n [x,x..]
-- ^ no comma
but let's not be picky.
Now when you use range syntax (i.e. x..), then x should be of a type that is an instance of Enum. Indeed:
Prelude> :t \n x -> take n [x,x..]
\n x -> take n [x,x..] :: Enum a => Int -> a -> [a]
You can argue that x,x.. will only generate x, but the Haskell compiler does not know that at compile time.
So the type in replicate (in the question) is too specific: it implies a type constraint - Enum a - that is actually not necessary.
Your own definition on the other hand is perfectly fine. Haskell has no problem with infinite lists since it uses lazy evaluation. Furthermore because you define xs with xs as tail, you actually constructed a circular linked list which also is better in terms of memory usage.

Related

Besides as-pattern, what else can # mean in Haskell?

I am studying Haskell currently and try to understand a project that uses Haskell to implement cryptographic algorithms. After reading Learn You a Haskell for Great Good online, I begin to understand the code in that project. Then I found I am stuck at the following code with the "#" symbol:
-- | Generate an #n#-dimensional secret key over #rq#.
genKey :: forall rq rnd n . (MonadRandom rnd, Random rq, Reflects n Int)
=> rnd (PRFKey n rq)
genKey = fmap Key $ randomMtx 1 $ value #n
Here the randomMtx is defined as follows:
-- | A random matrix having a given number of rows and columns.
randomMtx :: (MonadRandom rnd, Random a) => Int -> Int -> rnd (Matrix a)
randomMtx r c = M.fromList r c <$> replicateM (r*c) getRandom
And PRFKey is defined below:
-- | A PRF secret key of dimension #n# over ring #a#.
newtype PRFKey n a = Key { key :: Matrix a }
All information sources I can find say that # is the as-pattern, but this piece of code is apparently not that case. I have checked the online tutorial, blogs and even the Haskell 2010 language report at https://www.haskell.org/definition/haskell2010.pdf. There is simply no answer to this question.
More code snippets can be found in this project using # in this way too:
-- | Generate public parameters (\( \mathbf{A}_0 \) and \(
-- \mathbf{A}_1 \)) for #n#-dimensional secret keys over a ring #rq#
-- for gadget indicated by #gad#.
genParams :: forall gad rq rnd n .
(MonadRandom rnd, Random rq, Reflects n Int, Gadget gad rq)
=> rnd (PRFParams n gad rq)
genParams = let len = length $ gadget #gad #rq
n = value #n
in Params <$> (randomMtx n (n*len)) <*> (randomMtx n (n*len))
I deeply appreciate any help on this.
That #n is an advanced feature of modern Haskell, which is usually not covered by tutorials like LYAH, nor can be found the the Report.
It's called a type application and is a GHC language extension. To understand it, consider this simple polymorphic function
dup :: forall a . a -> (a, a)
dup x = (x, x)
Intuitively calling dup works as follows:
the caller chooses a type a
the caller chooses a value x of the previously chosen type a
dup then answers with a value of type (a,a)
In a sense, dup takes two arguments: the type a and the value x :: a. However, GHC is usually able to infer the type a (e.g. from x, or from the context where we are using dup), so we usually pass only one argument to dup, namely x. For instance, we have
dup True :: (Bool, Bool)
dup "hello" :: (String, String)
...
Now, what if we want to pass a explicitly? Well, in that case we can turn on the TypeApplications extension, and write
dup #Bool True :: (Bool, Bool)
dup #String "hello" :: (String, String)
...
Note the #... arguments carrying types (not values). Those are something that exists at compile time, only -- at runtime the argument does not exist.
Why do we want that? Well, sometimes there is no x around, and we want to prod the compiler to choose the right a. E.g.
dup #Bool :: Bool -> (Bool, Bool)
dup #String :: String -> (String, String)
...
Type applications are often useful in combination with some other extensions which make type inference unfeasible for GHC, like ambiguous types or type families. I won't discuss those, but you can simply understand that sometimes you really need to help the compiler, especially when using powerful type-level features.
Now, about your specific case. I don't have all the details, I don't know the library, but it's very likely that your n represents a kind of natural-number value at the type level. Here we are diving in rather advanced extensions, like the above-mentioned ones plus DataKinds, maybe GADTs, and some typeclass machinery. While I can't explain everything, hopefully I can provide some basic insight. Intuitively,
foo :: forall n . some type using n
takes as argument #n, a kind-of compile-time natural, which is not passed at runtime. Instead,
foo :: forall n . C n => some type using n
takes #n (compile-time), together with a proof that n satisfies constraint C n. The latter is a run-time argument, which might expose the actual value of n. Indeed, in your case, I guess you have something vaguely resembling
value :: forall n . Reflects n Int => Int
which essentially allows the code to bring the type-level natural to the term-level, essentially accessing the "type" as a "value". (The above type is considered an "ambiguous" one, by the way -- you really need #n to disambiguate.)
Finally: why should one want to pass n at the type level if we then later on convert that to the term level? Wouldn't be easier to simply write out functions like
foo :: Int -> ...
foo n ... = ... use n
instead of the more cumbersome
foo :: forall n . Reflects n Int => ...
foo ... = ... use (value #n)
The honest answer is: yes, it would be easier. However, having n at the type level allows the compiler to perform more static checks. For instance, you might want a type to represent "integers modulo n", and allow adding those. Having
data Mod = Mod Int -- Int modulo some n
foo :: Int -> Mod -> Mod -> Mod
foo n (Mod x) (Mod y) = Mod ((x+y) `mod` n)
works, but there is no check that x and y are of the same modulus. We might add apples and oranges, if we are not careful. We could instead write
data Mod n = Mod Int -- Int modulo n
foo :: Int -> Mod n -> Mod n -> Mod n
foo n (Mod x) (Mod y) = Mod ((x+y) `mod` n)
which is better, but still allows to call foo 5 x y even when n is not 5. Not good. Instead,
data Mod n = Mod Int -- Int modulo n
-- a lot of type machinery omitted here
foo :: forall n . SomeConstraint n => Mod n -> Mod n -> Mod n
foo (Mod x) (Mod y) = Mod ((x+y) `mod` (value #n))
prevents things to go wrong. The compiler statically checks everything. The code is harder to use, yes, but in a sense making it harder to use is the whole point: we want to make it impossible for the user to try adding something of the wrong modulus.
Concluding: these are very advanced extensions. If you're a beginner, you will need to slowly progress towards these techniques. Don't be discouraged if you can't grasp them after only a short study, it does take some time. Make a small step at a time, solve some exercises for each feature to understand the point of it. And you'll always have StackOverflow when you are stuck :-)

Variadic list appender function to make a list of lists from lists in haskell

I'm looking at this question for how to take multiple lists and turn them into a list of lists. I have the following:
Prelude> x1 = [1,2,3]
Prelude> x2 = [4,5,6]
Prelude> x3 = [7,8,9]
I'd like to see some \function where this could be variadic:
Prelude> xs = map (\function -> ???) x1 x2 x3
Prelude> show xs -- that produces this
[[1,2,3], [4,5,6], [7,8,9]]
Or without map, some other variadic function F such that:
Prelude> xs = F x1 x2 x3 ... x1000
Prelude> show xs -- that produces this
[[1,2,3], [4,5,6], [7,8,9], ...., [1000000,1000001,1000002]]
My expectation from the answer was that something like
Prelude> map (:) x1 x2 x3 []
<interactive>:26:1: error:
• Couldn't match expected type ‘[Integer]
-> [Integer] -> [a0] -> t’
with actual type ‘[[Integer] -> [Integer]]’
• The function ‘map’ is applied to five arguments,
but its type ‘(Integer -> [Integer] -> [Integer])
-> [Integer] -> [[Integer] -> [Integer]]’
has only two
In the expression: map (:) x1 x2 x3 []
In an equation for ‘it’: it = map (:) x1 x2 x3 []
• Relevant bindings include it :: t (bound at <interactive>:26:1)
or
Prelude> map (:) $ x1 x2 x3 []
<interactive>:27:11: error:
• Couldn't match expected type ‘[Integer]
-> [Integer] -> [a0] -> [a]’
with actual type ‘[Integer]’
• The function ‘x1’ is applied to three arguments,
but its type ‘[Integer]’ has none
In the second argument of ‘($)’, namely ‘x1 x2 x3 []’
In the expression: map (:) $ x1 x2 x3 []
• Relevant bindings include
it :: [[a] -> [a]] (bound at <interactive>:27:1)
I failed to find this kind of function in Hoogle as well, but probably misspecified the type signature:
https://www.haskell.org/hoogle/?hoogle=%5Ba%5D+-%3E+%5Ba%5D+-%3E+%5B%5Ba%5D%2C%5Ba%5D%5D
Polyvariadic functions in Haskell are quite hard to achieve. This is because a function can fundamentally only have one argument, and hence further arguments are included only through currying, which bakes the number of arguments into the function's type.
However, that doesn't mean it's impossible, though sometimes this requires the use of extensions. Here I will go through a few, in increasing order of complexity. This probably won't be very useful, but maybe helpful.
Somewhat tangentially, a few years ago I made a respository of examples of polyvariadic functions, which you might find interesting, but which are fairly same-y and of dubious quality; I'm no professional even now, and that was a few years ago.
Method 1: Using seperate functions (No extensions)
A simple but crude method of doing this would simply be to define multiple functions to make a list with n elements, such as:
makeList1 :: a -> [a]
makeList2 :: a -> a -> [a]
-- etc.
-- Use:
myList = makeList5 1 2 3 4 5
This isn't so fantastic. Can we do better?
Method 2: Typeclasses (Requires FlexibleInstances)
This is much more interesting. Here, we sacrifice specificity to create a truly polyvariadic function:
{-# LANGUAGE FlexibleInstances #-}
class MkIntList r where
mkIntList' :: [Int] -> r
-- No arguments
instance MkIntList [Int] where
mkIntList' = id
-- One argument, then some others
instance (MkIntList r) => MkIntList (Int -> r) where
mkIntList' xs x = mkIntList' (xs ++ [x]) -- (Inefficient, but this is an illustration)
-- The variadic function
mkIntList :: (MkIntList r) => r
mkIntList = mkIntList []
-- Use:
myList1 = mkIntList 1 2 3 :: [Int] -- myList1 = [1,2,3]
myList2 = mkIntList :: [Int] -- myList2 = []
I'll leave you to get your head around this one.
Method 3: Functional Dependencies (Requires FlexibleInstances and FunctionalDependencies)
This is a polymorphic version of the previous one, in which we must keep track of the type via a functional dependency.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
class MkList a r | r -> a where
mkList' :: [a] -> r
instance MkList a [a] where
mkList' = id
instance (MkList a r) => MkList a (a -> r) where
mkList' xs x = mkList' (xs ++ [x]) -- (Again inefficient)
mkList :: (MkList a r) => r
mkList = retList []
-- Use:
myList1 = mkList 'H' 'i' '!' :: String -- myList1 = "Hi!"
myList2 = mkList True False :: [Bool] -- myList2 = [True, False]
I make a slightly more efficient version of this code a while ago.
Method 4: Metaprogramming (Requires Template Haskell)
This I think is the least theoretically interesting of the solutions, so I won't go into the frankly tedious examples.
This method involves creating a function which in turn generates Haskell code, via Template Haskell, which one can then use to generate the necessary function, based on the length of this list, at compile time. This is essentially a less labour-intensive (but slower at compile time) version of method 1.
Nowadays there are probably far more ways of doing this, but I hope that you find these examples helpful, or in the very least enlightening.
Mainly, the reason your approach isn't working is that (I think) you have slightly misunderstood map. Let's have a look at the type signature:
map :: (a -> b) -> [a] -> [b]
You can see here that the main restriction with map is that only one list is passed in as a parameter - so you can't pass multiple lists, which is what you have tried to do. The other reason this doesn't work is that map is specifically for applying a function to the elements within a list, and you're trying to use it between multiple lists, without changing the individual elements.
So how can you define your function? The problem here is that Haskell doesn't really support variadic functions (but see below). In Haskell, if you want to support any amount of arguments of the same type, you would join them together in a list; that is, fn [a, b, c] instead of fn a b c. So let's try that here: your function would be:
fn :: [[a]] -> [[a]]
fn = ???
So how do we implement this? What we want is a function which combines multiple lists, and we're given a list containing multiple lists (the arguments), so... the output is exactly the same as the input! At this point, we're probably better off ignoring fn - or indeed any attempted map (:) combination - and just writing the list ourselves. So your example would just be:
xs = [x1, x2, x3]
If even this doesn't work for you, and you really do want a variadic function, then I would suggest looking back over your program and checking whether it's using the best/easiest approach - remember the XY problem.
(Side note: if you really need it, and there's no way to solve your problem otherwise, then it is actually possible to define variadic functions in Haskell - search Haskell variadic function for more information. However, this approach is mostly useful when doing string formatting or advanced type-level stuff, making it unlikely that you would need such an approach.)

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.
Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?
Example:
module Foo where
import Data.List
foo :: Int -> Int -> Int -> Int
foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])
is there a general way of doing this independent of the number of arguments?
Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.
Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).
That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:
{-# LANGUAGE FlexibleInstances #-}
class UsingList f where
usingList :: ([Int] -> Int) -> f
instance UsingList Int where
usingList f = f []
instance UsingList r => UsingList (Int -> r) where
usingList f a = usingList (f . (a:))
foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort
It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!
With all respect, I would disagree with #leftaroundabout's answer above. Something being
unusual is not a reason to shun it as unworthy.
It is correct that you would not be able to define a polymorphic variadic list constructor
without type annotations. However, we're not usually dealing with Haskell 98, where type
annotations were never required. With Dependent Haskell just around the corner, some
familiarity with non-trivial type annotations is becoming vital.
So, let's take a shot at this, disregarding worthiness considerations.
One way to define a function that does not seem to admit a single type is to make it a method of a
suitably constructed class. Many a trick involving type classes were devised by cunning
Haskellers, starting at least as early as 15 years ago. Even if we don't understand their
type wizardry in all its depth, we may still try our hand with a similar approach.
Let us first try to obtain a method for summing any number of Integers. That means repeatedly
applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do
it:
class Eval a where
eval :: Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval i = \y -> eval (i + y)
instance Eval Integer where
eval i = i
And this is the extract from repl:
λ eval 1 2 3 :: Integer
6
Notice that we can't do without explicit type annotation, because the very idea of our approach is
that an expression eval x1 ... xn may either be a function that waits for yet another argument,
or a final value.
One generalization now is to actually make a list of values. The science tells us that
we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to
a list, then sum it and obtain the same result as above.
Here's how we can go about turning arguments of our method to a list:
class Eval a where
eval2 :: [Integer] -> Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [Integer] where
eval2 is i = i:is
This is how it would work:
λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]
Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two
different things: a (possibly empty) list of values and the next value to put in. Notice how it's
similar to the usual foldr:
λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]
The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit
tricky, as we have to make Eval a 2-parameter type class:
class Eval a i where
eval2 :: [i] -> i -> a
instance (Eval a i) => Eval (i -> a) i where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [i] i where
eval2 is i = i:is
It works as the previous with Integers, but it can also carry any other type, even a function:
(I'm sorry for the messy example. I had to show a function somehow.)
λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]
So far so good: we can convert any number of arguments into a list. However, it will be hard to
compose this function with the one that would do useful work with the resulting list, because
composition only admits unary functions − with some trickery, binary ones, but in no way the
variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:
class Ap a i r where
apply :: ([i] -> r) -> [i] -> i -> a
apply', ($...) :: ([i] -> r) -> i -> a
($...) = apply'
instance Ap a i r => Ap (i -> a) i r where
apply f xs x = \y -> apply f (x:xs) y
apply' f x = \y -> apply f [x] y
instance Ap r i r where
apply f xs x = f $ x:xs
apply' f x = f [x]
Now we can write our desired function as an application of a list-admitting function to any number
of arguments:
foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
g = f . sort
You'll still have to type annotate it at every call site, like this:
λ foo' 4 5 10 :: Integer
-1
− But so far, that's the best I can do.
The more I study Haskell, the more I am certain that nothing is impossible.

Point Free Style Required for Optimized Curry

Say we have a (contrived) function like so:
import Data.List (sort)
contrived :: Ord a => [a] -> [a] -> [a]
contrived a b = (sort a) ++ b
And we partially apply it to use elsewhere, eg:
map (contrived [3,2,1]) [[4],[5],[6]]
On the surface, this works as one would expect:
[[1,2,3,4],[1,2,3,5],[1,2,3,6]]
However, if we throw some traces in:
import Debug.Trace (trace)
contrived :: Ord a => [a] -> [a] -> [a]
contrived a b = (trace "sorted" $ sort a) ++ b
map (contrived $ trace "a value" [3,2,1]) [[4],[5],[6]]
We see that the first list passed into contrived is evaluated only once, but it is sorted for each item in [4,5,6]:
[sorted
a value
[1,2,3,4],sorted
[1,2,3,5],sorted
[1,2,3,6]]
Now, contrived can be rather simply translated to point-free style:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = (++) (sort a)
Which when partially applied:
map (contrived [3,2,1]) [4,5,6]
Still works as we expect:
[[1,2,3,4],[1,2,3,5],[1,2,3,6]]
But if we again add traces:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = (++) (trace "sorted" $ sort a)
map (contrived $ trace "a value" [3,2,1]) [[4],[5],[6]]
We see that now the first list passed into contrived is evaluated and sorted only once:
[sorted
a value
[1,2,3,4],[1,2,3,5],[1,2,3,6]]
Why is this so? Since the translation into pointfree style is so trivial, why can't GHC deduce that it only needs to sort a once in the first version of contrived?
Note: I know that for this rather trivial example, it's probably preferable to use pointfree style. This is a contrived example that I've simplified quite a bit. The real function that I'm having the issue with is less clear (in my opinion) when expressed in pointfree style:
realFunction a b = conditionOne && conditionTwo
where conditionOne = map (something a) b
conditionTwo = somethingElse a b
In pointfree style, this requires writing an ugly wrapper (both) around (&&):
realFunction a = both conditionOne conditionTwo
where conditionOne = map (something a)
conditionTwo = somethingElse a
both f g x = (f x) && (g x)
As an aside, I'm also not sure why the both wrapper works; the pointfree style of realFunction behaves like the pointfree style version of contrived in that the partial application is only evaluated once (ie. if something sorted a it would only do so once). It appears that since both is not pointfree, Haskell should have the same issue that it had with the non-pointfree contrived.
If I understand correctly, you are looking for this:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = let a' = sort a in \b -> a' ++ b
-- or ... in (a' ++)
If you want the sort to be computed only once, it has to be done before the \b.
You are correct in that a compiler could optimize this. This is known as the "full laziness" optimization.
If I remember correctly, GHC does not always do it because it's not always an actual optimization, in the general case. Consider the contrived example
foo :: Int -> Int -> Int
foo x y = let a = [1..x] in length a + y
When passing both arguments, the above code works in constant space: the list elements are immediately garbage collected as they are produced.
When partially applying x, the closure for foo x only requires O(1) memory, since the list is not yet generated. Code like
let f = foo 1000 in f 10 + f 20 -- (*)
still run in constant space.
Instead, if we wrote
foo :: Int -> Int -> Int
foo x = let a = [1..x] in (length a +)
then (*) would no longer run in constant space. The first call f 10 would allocate a 1000-long list, and keep it in memory for the second call f 20.
Note that your partial application
... = (++) (sort a)
essentially means
... = let a' = sort a in \b -> a' ++ b
since argument passing involves a binding, as in let. So, the result of your sort a is kept around for all the future calls.

How to implement delete with foldr in Haskell

I've been studying folds for the past few days. I can implement simple functions with them, like length, concat and filter. What I'm stuck at is trying to implement with foldr functions like delete, take and find. I have implemented these with explicit recursion but it doesn't seem obvious to me how to convert these types of functions to right folds.
I have studied the tutorials by Graham Hutton and Bernie Pope. Imitating Hutton's dropWhile, I was able to implement delete with foldr but it fails on infinite lists.
From reading Implement insert in haskell with foldr, How can this function be written using foldr? and Implementing take using foldr, it would seem that I need to use foldr to generate a function which then does something. But I don't really understand these solutions and don't have an idea how to implement for example delete this way.
Could you explain to me a general strategy for implementing with foldr lazy versions of functions like the ones I mentioned. Maybe you could also implement delete as an example since this probably is one of the easiest.
I'm looking for a detailed explanation that a beginner can understand. I'm not interested in just solutions, I want to develop an understanding so I can come up with solutions to similar problems myself.
Thanks.
Edit: At the moment of writing there is one useful answer but it's not quite what I was looking for. I'm more interested in an approach that uses foldr to generate a function, which then does something. The links in my question have examples of this. I don't quite understand those solutions so I would like to have more information on this approach.
delete is a modal search. It has two different modes of operation - whether it's already found the result or not. You can use foldr to construct a function that passes the state down the line as each element is checked. So in the case of delete, the state can be a simple Bool. It's not exactly the best type, but it will do.
Once you have identified the state type, you can start working on the foldr construction. I'm going to walk through figuring it out the way I did. I'll be enabling ScopedTypeVariables just so I can annotate the type of subexpressions better. One you know the state type, you know you want foldr to generate a function taking a value of that type, and returning a value of the desired final type. That's enough to start sketching things.
{-# LANGUAGE ScopedTypeVariables #-}
delete :: forall a. Eq a => a -> [a] -> [a]
delete a xs = foldr f undefined xs undefined
where
f :: a -> (Bool -> [a]) -> (Bool -> [a])
f x g = undefined
It's a start. The exact meaning of g is a little bit tricky here. It's actually the function for processing the rest of the list. It's accurate to look at it as a continuation, in fact. It absolutely represents performing the rest of the folding, with your whatever state you choose to pass along. Given that, it's time to figure out what to put in some of those undefined places.
{-# LANGUAGE ScopedTypeVariables #-}
delete :: forall a. Eq a => a -> [a] -> [a]
delete a xs = foldr f undefined xs undefined
where
f :: a -> (Bool -> [a]) -> (Bool -> [a])
f x g found | x == a && not found = g True
| otherwise = x : g found
That seems relatively straightforward. If the current element is the one being searched for, and it hasn't yet been found, don't output it, and continue with the state set to True, indicating it's been found. otherwise, output the current value and continue with the current state. This just leaves the rest of the arguments to foldr. The last one is the initial state. The other one is the state function for an empty list. Ok, those aren't too bad either.
{-# LANGUAGE ScopedTypeVariables #-}
delete :: forall a. Eq a => a -> [a] -> [a]
delete a xs = foldr f (const []) xs False
where
f :: a -> (Bool -> [a]) -> (Bool -> [a])
f x g found | x == a && not found = g True
| otherwise = x : g found
No matter what the state is, produce an empty list when an empty list is encountered. And the initial state is that the element being searched for has not yet been found.
This technique is also applicable in other cases. For instance, foldl can be written as a foldr this way. If you look at foldl as a function that repeatedly transforms an initial accumulator, you can guess that's the function being produced - how to transform the initial value.
{-# LANGUAGE ScopedTypeVariables #-}
foldl :: forall a b. (a -> b -> a) -> a -> [b] -> a
foldl f z xs = foldr g id xs z
where
g :: b -> (a -> a) -> (a -> a)
g x cont acc = undefined
The base cases aren't too tricky to find when the problem is defined as manipulating the initial accumulator, named z there. The empty list is the identity transformation, id, and the value passed to the created function is z.
The implementation of g is trickier. It can't just be done blindly on types, because there are two different implementations that use all the expected values and type-check. This is a case where types aren't enough, and you need to consider the meanings of the functions available.
Let's start with an inventory of the values that seem like they should be used, and their types. The things that seem like they must need to be used in the body of g are f :: a -> b -> a, x :: b, cont :: (a -> a), and acc :: a. f will obviously take x as its second argument, but there's a question of the appropriate place to use cont. To figure out where it goes, remember that it represents the transformation function returned by processing the rest of the list, and that foldl processes the current element and then passes the result of that processing to the rest of the list.
{-# LANGUAGE ScopedTypeVariables #-}
foldl :: forall a b. (a -> b -> a) -> a -> [b] -> a
foldl f z xs = foldr g id xs z
where
g :: b -> (a -> a) -> (a -> a)
g x cont acc = cont $ f acc x
This also suggests that foldl' can be written this way with only one tiny change:
{-# LANGUAGE ScopedTypeVariables #-}
foldl' :: forall a b. (a -> b -> a) -> a -> [b] -> a
foldl' f z xs = foldr g id xs z
where
g :: b -> (a -> a) -> (a -> a)
g x cont acc = cont $! f acc x
The difference is that ($!) is used to suggest evaluation of f acc x before it's passed to cont. (I say "suggest" because there are some edge cases where ($!) doesn't force evaluation even as far as WHNF.)
delete doesn't operate on the entire list evenly. The structure of the computation isn't just considering the whole list one element at a time. It differs after it hits the element it's looking for. This tells you it can't be implemented as just a foldr. There will have to be some sort of post-processing involved.
When that happens, the general pattern is that you build a pair of values and just take one of them at completion of the foldr. That's probably what you did when you imitated Hutton's dropWhile, though I'm not sure since you didn't include code. Something like this?
delete :: Eq a => a -> [a] -> [a]
delete a = snd . foldr (\x (xs1, xs2) -> if x == a then (x:xs1, xs1) else (x:xs1, x:xs2)) ([], [])
The main idea is that xs1 is always going to be the full tail of the list, and xs2 is the result of the delete over the tail of the list. Since you only want to remove the first element that matches, you don't want to use the result of delete over the tail when you do match the value you're searching for, you just want to return the rest of the list unchanged - which fortunately is what's always going to be in xs1.
And yeah, that doesn't work on infinite lists - but only for one very specific reason. The lambda is too strict. foldr only works on infinite lists when the function it is provided doesn't always force evaluation of its second argument, and that lambda does always force evaluation of its second argument in the pattern match on the pair. Switching to an irrefutable pattern match fixes that, by allowing the lambda to produce a constructor before ever examining its second argument.
delete :: Eq a => a -> [a] -> [a]
delete a = snd . foldr (\x ~(xs1, xs2) -> if x == a then (x:xs1, xs1) else (x:xs1, x:xs2)) ([], [])
That's not the only way to get that result. Using a let-binding or fst and snd as accessors on the tuple would also do the job. But it is the change with the smallest diff.
The most important takeaway here is to be very careful with handling the second argument to the reducing function you pass to foldr. You want to defer examining the second argument whenever possible, so that the foldr can stream lazily in as many cases as possible.
If you look at that lambda, you see that the branch taken is chosen before doing anything with the second argument to the reducing function. Furthermore, you'll see that most of the time, the reducing function produces a list constructor in both halves of the result tuple before it ever needs to evaluate the second argument. Since those list constructors are what make it out of delete, they are what matter for streaming - so long as you don't let the pair get in the way. And making the pattern-match on the pair irrefutable is what keeps it out of the way.
As a bonus example of the streaming properties of foldr, consider my favorite example:
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x:xs) []
It streams - as much as it can. If you figure out exactly when and why it does and doesn't stream, you'll understand pretty much every detail of the streaming structure of foldr.
here is a simple delete, implemented with foldr:
delete :: (Eq a) => a -> [a] -> [a]
delete a xs = foldr (\x xs -> if x == a then (xs) else (x:xs)) [] xs

Resources