 
            What is the difference between empty list [] and list with one unit element [()]? daryoush
 
            dmehrtash:
What is the difference between empty list [] and list with one unit element [()]?
Prelude> length [] 0 Prelude> length [()] 1
Also, they differ in type. [()] is a list of unit elements, and happens to contain exactly one of them. [] is a (polymorphic) list of any kind of element, and happens not to contain any of them. Regards, John
 
            On Fri, 10 Oct 2008 00:24:08 -0400, John Dorsey 
dmehrtash:
What is the difference between empty list [] and list with one unit element [()]?
Prelude> length [] 0 Prelude> length [()] 1
Also, they differ in type.
[()] is a list of unit elements, and happens to contain exactly one of them.
[] is a (polymorphic) list of any kind of element, and happens not to contain any of them.
Prelude> :type [] [] :: [a] Prelude> :type [()] [()] :: [()] In fact, [()] contains an empty tuple, called a "unit" (see "4 Notes and tips" of "Constructor - HaskellWiki" at http://www.haskell.org/haskellwiki/Constructor), whereas [] is just an empty list. -- Benjamin L. Russell
 
            What is the difference between empty list [] and list with one unit element [()]?
The [] constructor takes no arguments and is like Nothing in the Maybe type. The list ":" (cons) infix constructor takes two arguments, an element of type a and a list of type a, to construct a new list. Compare to Maybe. data [] a = [] | a : [a] data Maybe a = Nothing | Just a Another way of saying [()] is ():[] which, comparing with the Maybe type, is similar to saying Just () but Just only takes one argument where (:) takes two. Both List and Maybe are containers that have a null constructor, namely [] and Nothing. "():[]" contains () similar to how "Just ()" contains (). You can make your own list type and put () in it as follows. data List a = Empty | Cons a (List a) deriving (Show, Eq) () `Cons` Empty -- This is ():[] -Sam PS. I'm new on the list and also to Haskell.
 
            Sam Danielson wrote:
The [] constructor takes no arguments and is like Nothing in the Maybe type. The list ":" (cons) infix constructor takes two arguments, an element of type a and a list of type a, to construct a new list. Compare to Maybe.
data [] a = [] | a : [a] data Maybe a = Nothing | Just a
Another way of saying [()] is
():[]
which, comparing with the Maybe type, is similar to saying
Just ()
but Just only takes one argument where (:) takes two.
Both List and Maybe are containers that have a null constructor, namely [] and Nothing. "():[]" contains () similar to how "Just ()" contains (). You can make your own list type and put () in it as follows.
Or, in Monad terms: "[()]" and "Just ()" are both "return ()" in their respective Monads. "[]" and "Nothing" are both "mzero" in their respective MonadsPluses. (Both are also "fail" in their respective Monads, but I find "fail"'s presence in Monad a bit inelegant, though handy.) -- src/
 
            "Daryoush Mehrtash" 
What is the difference between empty list [] and list with one unit element [()]?
Prelude> :m + Data.List Prelude Data.List> []\\[()] [] or, for completeness, the difference between a list with one unit element and the empty list: Prelude Data.List> [()]\\[] [()] :-P -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
 
            What is the difference between empty list [] and list with one unit element [()]?
Or, yet: ():[()] --is legal 10:[()] --is not One list can contain elements of a single type. Since the type of () is () (element constructors and types are allowed to have the same name), a list of type [()] can only contain elements of type (), i.e., ()s. Try this is ghci: :t [()] :t [(),(),(),()] Best, Maurício
 
            (This is a literate haskell post, save into SMM.lhs and load in ghci!) Here's one place you might use [()] and []:
guard :: Bool -> [()] guard True = [()] guard False = []
You can then use "guard" in monadic list computations to abort the computation on some branches:
sendmoney :: [[Int]] sendmoney = do choice@[s,e,n,d,m,o,r,y] <- generate 8 [0..9] guard (s /= 0) guard (m /= 0) guard (val [s,e,n,d] + val [m,o,r,e] == val [m,o,n,e,y]) return choice
(evaluating this in ghci takes a little while, but it does succeed! You can easily optimize by noticing that m must be equal to 1 and therefore s must be 8 or 9.) Using guard in this way works because of the definition of bind on lists: xs >>= f = concatMap f xs = concat (map f xs) Consider a simpler example:
simple = do x <- [1,2,3] guard (x /= 2) return x
This is the same as [1,2,3] >>= \x -> guard (x /= 2) >>= \_ -> return x = mapConcat (\x -> mapConcat (\_ -> return x) (guard (x /= 2))) [1,2,3] = concat [ mapConcat (\_ -> return 1) (guard (1 /= 2)) , mapConcat (\_ -> return 2) (guard (2 /= 2)) , mapConcat (\_ -> return 3) (guard (3 /= 2)) ] = concat [ mapConcat (\_ -> return 1) [()] , mapConcat (\_ -> return 2) [] , mapConcat (\_ -> return 3) [()] ] = concat [ concat [ [1] ] , concat [] , concat [ [3] ] ] = concat [ [1], [], [3] ] = [1,3] Another fun example:
double :: [()] double = [(), ()]
sixteen:: Int sixteen = length $ do double double double double
Helper code for "send more money" follows...
generate :: Int -> [a] -> [[a]] generate 0 _ = return [] generate n as = do (x,xs) <- select as rest <- generate (n-1) xs return (x:rest)
select :: [a] -> [(a,[a])] select [] = [] select [x] = return (x,[]) select (x:xs) = (x,xs) : [ (y, x:ys) | (y,ys) <- select xs ]
val xs = val' 0 xs where val' v [] = v val' v (x:xs) = val' (10*v + x) xs
 
            I was in fact trying to figure out how "guard" worked in the "do".    The
interesting  (for a beginner) insight is that:
[()]  map f = [f]  --( just as any list with one element would have been
such as [1] map f = [f] )   where as
[] map f = []
so if your guard computes to [()]  (or any list of one element) the
following steps in the do  would continue.  Where as if it computes to an
empty list then following steps are not executed.
daryoush
On Fri, Oct 10, 2008 at 6:33 AM, Ryan Ingram 
(This is a literate haskell post, save into SMM.lhs and load in ghci!)
Here's one place you might use [()] and []:
guard :: Bool -> [()] guard True = [()] guard False = []
You can then use "guard" in monadic list computations to abort the computation on some branches:
sendmoney :: [[Int]] sendmoney = do choice@[s,e,n,d,m,o,r,y] <- generate 8 [0..9] guard (s /= 0) guard (m /= 0) guard (val [s,e,n,d] + val [m,o,r,e] == val [m,o,n,e,y]) return choice
(evaluating this in ghci takes a little while, but it does succeed! You can easily optimize by noticing that m must be equal to 1 and therefore s must be 8 or 9.)
Using guard in this way works because of the definition of bind on lists:
xs >>= f = concatMap f xs = concat (map f xs)
Consider a simpler example:
simple = do x <- [1,2,3] guard (x /= 2) return x
This is the same as [1,2,3] >>= \x -> guard (x /= 2) >>= \_ -> return x
= mapConcat (\x -> mapConcat (\_ -> return x) (guard (x /= 2))) [1,2,3] = concat [ mapConcat (\_ -> return 1) (guard (1 /= 2)) , mapConcat (\_ -> return 2) (guard (2 /= 2)) , mapConcat (\_ -> return 3) (guard (3 /= 2)) ] = concat [ mapConcat (\_ -> return 1) [()] , mapConcat (\_ -> return 2) [] , mapConcat (\_ -> return 3) [()] ] = concat [ concat [ [1] ] , concat [] , concat [ [3] ] ] = concat [ [1], [], [3] ] = [1,3]
Another fun example:
double :: [()] double = [(), ()]
sixteen:: Int sixteen = length $ do double double double double
Helper code for "send more money" follows...
generate :: Int -> [a] -> [[a]] generate 0 _ = return [] generate n as = do (x,xs) <- select as rest <- generate (n-1) xs return (x:rest)
select :: [a] -> [(a,[a])] select [] = [] select [x] = return (x,[]) select (x:xs) = (x,xs) : [ (y, x:ys) | (y,ys) <- select xs ]
val xs = val' 0 xs where val' v [] = v val' v (x:xs) = val' (10*v + x) xs
 
            On Fri, 2008-10-10 at 10:59 -0700, Daryoush Mehrtash wrote:
I was in fact trying to figure out how "guard" worked in the "do". The interesting (for a beginner) insight is that:
[()] map f = [f]
I don't think any clarity is added by made-up notation. I think you mean map f [()] = [f ()] or [()] >>= f = f () or [()] >> f = f or do [()] f = f or [ f | _ <- [()] ] = [ f ]
--( just as any list with one element would have been such as [1] map f = [f] ) where as
[] map f = []
And map f [] = [] or [] >>= f = [] or [] >> f = [] or do [] f = [] or [ f | _ <- [] ] = [] jcc
 
            I don't think any clarity is added by made-up notation.  I think you
mean
In fact I was "trying" to be correct on this. Is it wrong to show:
[()] >> f = f
as was doing:
[()]  map f = [f]
I want to say map function f over a single element list will yield a list of
single element, the element being function f.
daryoush
On Fri, Oct 10, 2008 at 10:56 AM, Jonathan Cast
On Fri, 2008-10-10 at 10:59 -0700, Daryoush Mehrtash wrote:
I was in fact trying to figure out how "guard" worked in the "do". The interesting (for a beginner) insight is that:
[()] map f = [f]
I don't think any clarity is added by made-up notation. I think you mean
map f [()] = [f ()]
or
[()] >>= f = f ()
or
[()] >> f = f
or
do [()] f = f
or
[ f | _ <- [()] ] = [ f ]
--( just as any list with one element would have been such as [1] map f = [f] ) where as
[] map f = []
And
map f [] = []
or
[] >>= f = []
or
[] >> f = []
or
do [] f = []
or
[ f | _ <- [] ] = []
jcc
 
            On Fri, 2008-10-10 at 11:14 -0700, Daryoush Mehrtash wrote:
I don't think any clarity is added by made-up notation. I think you mean In fact I was "trying" to be correct on this.
Great!
Is it wrong to show:
[()] >> f = f
as was doing:
[()] map f = [f]
Yes. Juxtaposition is always application in Haskell, and is always left-associative, and binds more tightly than any other operator. So your left-hand side means [()] applied to two arguments, map and f. This is not legal Haskell, because [()] is not a function. You intended to apply the function map to two arguments, f and [()]. The notation for that is map f [()] so, making that change, you get map f [()] = [f] This is still wrong: map :: (a -> b) -> [a] -> [b] so if f :: (() -> b) then map f [()] :: [b] but if f :: (() -> b) then [f] :: [() -> b] Unification of these types (required for an equation between the two terms) proceeds as follows: [b] = [() -> b] so b = () -> b But the unifier doesn't have a rule to solve recursive equations on types like the above; so unification fails; your rule isn't even well-typed. The correct rule is map f [()] = [f ()] where f () :: b so [f ()] :: [b] so everything type-checks. (>>) is different from map in three ways: (1) The arguments are in a different order. It's a minor issue, but of course you have to get it right. (2) >> is an infix operator (syntactically distinct from functions: map and (>>) are functions while `map` and >> are infix operators). So you can use it in the middle of your left-hand side. (2) (>>) has some subtle differences from map. The definitions are, roughly: map f xn = xn >>= \ x -> return (f x) xn >> ys = xn >>= \ x -> ys map does something interesting with the elements of its argument list: it passes them to the function f (it also builds a list of the result, which (>>) leaves to its second argument). (>>) just ignores those elements. This difference is reflected by the types, as well: map :: (a -> b) -> [a] -> [b] The type variable `a' appears twice, so in (map f xn) you know the argument to f and the elements of xn are related (in some way). (>>) :: [a] -> [b] -> [b] The type variable `a' appears only once, so in (xn >> ys) the elements of xn are just ignored; only the list structure matters.
I want to say map function f over a single element list will yield a list of single element, the element being function f.
Haskell does distinguish between a function and the result of applying that function to an argument, so the element *isn't* actually f --- it's the result of applying f to an argument. jcc
participants (10)
- 
                 Benjamin L.Russell Benjamin L.Russell
- 
                 Daryoush Mehrtash Daryoush Mehrtash
- 
                 Don Stewart Don Stewart
- 
                 John Dorsey John Dorsey
- 
                 Jon Fairbairn Jon Fairbairn
- 
                 Jonathan Cast Jonathan Cast
- 
                 Mauricio Mauricio
- 
                 Ryan Ingram Ryan Ingram
- 
                 Sam Danielson Sam Danielson
- 
                 Simon Richard Clarkstone Simon Richard Clarkstone
