How can I concisely match a list according to its latter half, and bind it's former half accordingly? - haskell

Suppose I have a function f :: String -> String and want to match arguments of the form
_ ++ "bar"
where _ is an unspecified string that I would like to return. In other words, I want to match arguments like foobar and bazbar and return foo and baz respectively.
Using ViewPatterns this is possible as follows:
{-# LANGUAGE ViewPatterns #-}
f :: String -> String
f x#(reverse . take 3 $ reverse -> "bar") = take (n-3) x
where n = length x
...but this is far from ideal. Mainly because things will get hairy very quickly if I decide that I want to combine two or more such patterns.
Ideally, I want something to be able to write something like this:
f (x:"bar") = x
but unfortunately this is not valid Haskell.
Is there an adequate solution in ViewPatterns or another extension?

On built-in String, this is a very bad idea, since your pattern match turns out to be quite expensive. On other string types, like Text or ByteString, you can use pattern guards:
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text as T
f :: Text -> Text
f x | Just x' <- T.stripSuffix "bar" x = ...
Or with ViewPatterns (of which I am less fond):
{-# LANGUAGE OverloadedStrings, ViewPatterns #-}
import qualified Data.Text as T
f :: Text -> Text
f (T.stripSuffix "bar" -> Just x') = ...

stripSuffix :: (Eq a) => [a] -> [a] -> Maybe [a]
stripSuffix needle = go <*> drop (length needle)
where
go xs [] = if xs == needle then Just [] else Nothing
go (x:xs) (_:ys) = (x:) <$> go xs ys
f (stripSuffix "bar" -> Just pref) = pref
I haven't tested it too much but this is a simple solution that doesn't bring in extra machinery of regexs / parsers.

Don't do it with pattern matching. Pattern matches are typically cheap and match the structure of the input data. This is a very expensive pattern written as if it were very cheap to compute. If you want to do this, write it as a guard clause, where you can make it clear exactly what's happening.

This is almost possible with TemplateHaskell - someone more experienced with it could improve on this answer.
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
(+++) :: Q Pat -> String -> Q Pat
x +++ y = [p| ((\string -> splitAt (length string - length y) string) -> (x, $literal_pattern)) |]
where literal_pattern = returnQ (LitP (StringL y))
This is usable in the pattern position, and you can pass in a pattern as the first argument using TemplateHaskell's quasiquoting:
f $([p|x|] +++ "bar") = x
Rather annoyingly, I can't find any explanation of how you can pass a pattern to a TemplateHaskell splice any more succintly than this.

Related

One-line implementation of split in Haskell

What I want is the following one (which I think should be included in prelude since it is very useful in text processing):
split :: Eq a => [a] -> [a] -> [[a]]
e.g:
split ";;" "hello;;world" = ["hello", "world"]
split from Data.List.Utils isn't in base. I feel there should be a short-and-sweet implementation by composing a few base functions, but I can't figure it out. Am I missing something?
Arguably, the best way to check how feasible a short-and-sweet splitOn (or split, as you and MissingH call it -- here I will stick to the name used by the split and extra packages) is trying to write it [note 1].
(By the way, I will use recursion-schemes functions and concepts in this answer, as I find systematising things a bit helps me think about this kind of problem. Do let me know if anything is unclear.)
The type of splitOn is [note 2]:
splitOn :: Eq a => [a] -> [a] -> [[a]]
One way to write a recursive function that builds one data structure from another, like splitOn does, begins by asking whether to do it by walking the original structure in a bottom-up or a top-down way (for lists, that amounts to right-to-left and left-to-right respectively). A bottom-up walk is more naturally expressed as some kind of fold:
foldr #[] :: (a -> b -> b) -> b -> [a] -> b
cata #[_] :: (ListF a b -> b) -> [a] -> b
(cata, short for catamorphism, is how recursion-schemes expresses a vanilla fold. The ListF a b -> b function, called an algebra in the jargon, specifies what happens in each fold step. data ListF a b = Nil | Cons a b, and so, in the case of lists, the algebra amounts to the two first arguments of foldr rolled into one -- the binary function corresponds to the Cons case, and the seed of the fold, to the Nil one.)
A top-down walk, on the other hand, lends itself to an unfold:
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] -- found in Data.List
ana #[_] :: (b -> ListF a b) -> b -> [a]
(ana, short for anamorphism, is the vanilla unfold in recursion-schemes. The b -> ListF a b function is a coalgebra; it specifies what happens in each unfold step. For a list, the possibilities are either emitting a list element and an updated seed or generating an empty list and terminating the unfold.)
Should splitOn be bottom-up or top-down? To implement it, we need to, at any given position in the list, look ahead in order to check whether the current list segment starts with the delimiter. That being so, it makes sense to reach for a top-down solution i.e. an unfold/anamorphism.
Playing with ways to write splitOn as an unfold shows another thing to consider: you want each individual unfold step to generate a fully-formed list chunk. Not doing so will, at best, lead you to unnecessarily walk the original list twice [note 3]; at worst, catastrophic memory usage and stack overflows on long list chunks await [note 4]. One way to achieve that is through a breakOn function, like the one in Data.List.Extra...
breakOn :: Eq a => [a] -> [a] -> ([a], [a])
... which is like break from the Prelude, except that, instead of applying a predicate to each element, it checks whether the remaining list segment has the first argument as a prefix [note 5].
With breakOn at hand, we can write a proper splitOn implementation -- one that, compiled with optimisations, matches in performance the library ones mentioned at the beginning:
splitOnAtomic :: Eq a => [a] -> [a] -> [[a]]
splitOnAtomic delim
| null delim = error "splitOnAtomic: empty delimiter"
| otherwise = apo coalgSplit
where
delimLen = length delim
coalgSplit = \case
[] -> Cons [] (Left [])
li ->
let (ch, xs) = breakOn (delim `isPrefixOf`) li
in Cons ch (Right (drop delimLen xs))
(apo, short for apomorphism, is an unfold that can be short-circuited. That is done by emitting from an unfold step, rather than the usual updated seed -- signaled by Right -- a final result -- signaled by Left. Short-circuiting is needed here because, in the empty list case, we want neither to produce an empty list by returning Nil -- which would wrongly result in splitOn delim [] = [] -- nor to resort to Cons [] [] -- which would generate an infinite tail of []. This trick corresponds directly to the additional splitOn _ [] = [[]] case added to the Data.List.Extra implementation.)
After a few slight detours, we can now address your actual question. splitOn is tricky to write in a short way because, firstly, the recursion pattern it uses isn't entirely trivial; secondly, a good implementation requires a few details that are inconvenient for golfing; and thirdly, what appears to be the best implementation relies crucially on breakOn, which is not in base.
Notes:
[note 1]: Here are the imports and pragmas needed to run the snippets in this answer:
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TemplateHaskell #-}
import Data.Functor.Foldable
import Data.Functor.Foldable.TH
import Data.List
import Data.Maybe
[note 2]: An alternative type might be Eq a => NonEmpty a -> [a] -> NonEmpty [a], if one wants to put precision above all else. I won't bother with that here to avoid unnecessary distractions.
[note 3]: As in this rather neat implementation, which uses two unfolds -- the first one (ana coalgMark) replaces the delimiters with Nothing, so that the second one (apo coalgSplit) can split in a straightforward way:
splitOnMark :: Eq a => [a] -> [a] -> [[a]]
splitOnMark delim
| null delim = error "splitOnMark: empty delimiter"
| otherwise = apo coalgSplit . ana coalgMark
where
coalgMark = \case
[] -> Nil
li#(x:xs) -> case stripPrefix delim li of
Just ys -> Cons Nothing ys
Nothing -> Cons (Just x) xs
coalgSplit = \case
[] -> Cons [] (Left [])
mxs ->
let (mch, mys) = break isNothing mxs
in Cons (catMaybes mch) (Right (drop 1 mys))
(What apo is and what Left and Right are doing here will be covered a little further in the main body of the answer.)
This implementation has fairly acceptable performance, though with optimisations it is a slower than the one in the main body of the answer by a (modest) constant factor. It might be a little easier to golf this one, though...
[note 4]: As in this single unfold implementation, which uses a coalgebra that calls itself recursively to build each chunk as a (difference) list:
splitOnNaive :: Eq a => [a] -> [a] -> [[a]]
splitOnNaive delim
| null delim = error "splitOn: empty delimiter"
| otherwise = apo coalgSplit . (,) id
where
coalgSplit = \case
(ch, []) -> Cons (ch []) (Left [])
(ch, li#(x:xs)) -> case stripPrefix delim li of
Just ys -> Cons (ch []) (Right (id, ys))
Nothing -> coalg (ch . (x :), xs)
Having to decide at each element whether to grow the current chunk or to start a new one is in itself problematic, as it breaks laziness.
[note 5]: Here is how Data.List.Extra implements breakOn. If we want to achieve that using a recursion-schemes unfold, one good strategy is defining a data structure that encodes exactly what we are trying to build:
data BrokenList a = Broken [a] | Unbroken a (BrokenList a)
deriving (Eq, Show, Functor, Foldable, Traversable)
makeBaseFunctor ''BrokenList
A BrokenList is just like a list, except that the empty list is replaced by the (non-recursive) Broken constructor, which marks the break point and holds the remainder of the list. Once generated by an unfold, a BrokenList can be easily folded into a pair of lists: the elements in the Unbroken values are consed into one list, and the list in Broken becomes the other one:
breakOn :: ([a] -> Bool) -> [a] -> ([a], [a])
breakOn p = hylo algPair coalgBreak
where
coalgBreak = \case
[] -> BrokenF []
li#(x:xs)
| p li -> BrokenF li
| otherwise -> UnbrokenF x xs
algPair = \case
UnbrokenF x ~(xs, ys) -> (x : xs, ys)
BrokenF ys -> ([], ys)
(hylo, short for hylomorphism, is simply an ana followed by a cata, i.e. an unfold followed by a fold. hylo, as implemented in recursion-schemes, takes advantage of the fact that the intermediate data structure, created by the unfold and then immediately consumed by the fold, can be fused away, leading to significant performance gains.)
It is worth mentioning that the lazy pattern match in algPair is crucial to preserve laziness. The Data.List.Extra implementation linked to above achieves that by using first from Control.Arrow, which also matches the pair given to it lazily.

Printing Dynamic Data

I have a system in haskell that uses Data.Dynamic and Type.Reflection to perform inference and calculations. I would like to be able to print the results.
Printing is easy when the type is supplied e.g
foo :: Dynamic -> String
foo dyn = case tyConName . someTypeRepTyCon . dynTypeRep $ dyn of
"Int" -> show $ fromDyn dyn (0 :: Int)
"Bool" -> show $ fromDyn dyn True
_ -> "no chance"
But if I want to be able to print tuples, I would have to add a new line for each e.g (Int, Bool), (Bool, Int), (Char, Int, Banana) ....
With the addition of more primitives and larger tuples this quickly becomes impractical.
Is there an algorithmic way to generate strings for this dynamic data, specifically for tuples and lists.
I like the main idea of the other answer, but it seems to get where it's going in a fairly roundabout way. Here's how I would style the same idea:
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTs #-}
import Type.Reflection
import Data.Dynamic
showDyn :: Dynamic -> String
showDyn (Dynamic (App (App (eqTypeRep (typeRep #(,)) -> Just HRefl) ta) tb) (va, vb))
= concat [ "DynamicPair("
, showDyn (Dynamic ta va)
, ","
, showDyn (Dynamic tb vb)
, ")"
]
showDyn (Dynamic (eqTypeRep (typeRep #Integer) -> Just HRefl) n) = show n
showDyn (Dynamic tr _) = show tr
That first pattern match is quite a mouthful, but after playing with a few different ways of formatting it I'm convinced that there just is no way to make that look good. You can try it in ghci:
> showDyn (toDyn ((3,4), (True, "hi")))
"DynamicPair(DynamicPair(3,4),DynamicPair(Bool,[Char]))"
I could only manage to obtain this horrible solution.
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeApplications #-}
{-# OPTIONS -Wall #-}
import Type.Reflection
import Data.Dynamic
Here we define the TyCon for (,) and Int. (I'm pretty sure there must be an easier way.)
pairTyCon :: TyCon
pairTyCon = someTypeRepTyCon (someTypeRep [('a','b')])
intTyCon :: TyCon
intTyCon = someTypeRepTyCon (someTypeRep [42 :: Int])
Then we dissect the Dynamic type. First we check if it is an Int.
showDynamic :: Dynamic -> String
showDynamic x = case x of
Dynamic tr#(Con k) v | k == intTyCon ->
case eqTypeRep tr (typeRep # Int) of
Just HRefl -> show (v :: Int)
_ -> error "It really should be an int"
-- to be continued
The above is ugly, since we first pattern match against the TyCon using == instead of pattern matching, which prevents the type refinement of v into an Int. So, we still have to resort to eqTypeRep to perform a second check which we already know has to succeed.
I think it could be made pretty by checking eqTypeRep in advance, for instance. Or fromDyn. It does not matter.
What matters is that the pair case below is even more messy, and can not be made pretty in the same way, as far as I can see.
-- continuing from above
Dynamic tr#(App (App t0#(Con k :: TypeRep p)
(t1 :: TypeRep a1))
(t2 :: TypeRep a2)) v | k == pairTyCon ->
withTypeable t0 $
withTypeable t1 $
withTypeable t2 $
case ( eqTypeRep tr (typeRep #(p a1 a2))
, eqTypeRep (typeRep #p) (typeRep #(,))) of
(Just HRefl, Just HRefl) ->
"DynamicPair("
++ showDynamic (Dynamic t1 (fst v))
++ ", "
++ showDynamic (Dynamic t2 (snd v))
++ ")"
_ -> error "It really should be a pair!"
_ -> "Dynamic: not an int, not a pair"
Above we match the TypeRep so that it represents something of type p a1 a2. We require that the representation of p to be pairTyCon.
As before this does not trigger type refinement, since it is done with == instead of pattern matching. We need to perform another explicit match to force p ~ (,) and another for the final refinement v :: (a1,a2). Sigh.
Finally, we can take fst v and snd v, turn them into Dynamic once again, and pair them. Effectively, we turned the original x :: Dynamic into something like (fst x, snd x) where both components are Dynamic. Now we can recurse.
I would really like to avoid the errors, but I can not see how to do that at the moment.
The redeeming part is that the approach is very general, and can be easily adapted to other type constructors.

Haskell pattern matching on vectors

Is it possible to use list style pattern matching on vectors?
ie
import qualified Data.Vector as V
f :: V.Vector a -> a
f (x:xs) = x
gives an error
-XViewPatterns can let you do this:
{-# LANGUAGE ViewPatterns #-}
module VecViewPats where
import Data.Vector (Vector)
import qualified Data.Vector as V
uncons :: Vector a -> Maybe (a, Vector a)
uncons v = if V.null v
then Nothing
else Just (V.unsafeHead v, V.unsafeTail v)
vsum :: Num a => Vector a -> a
vsum (uncons -> Just (a,av)) = a + vsum av
vsum (uncons -> Nothing) = 0
Or -XLambdaCase
import Control.Category ((>>>))
-- ...
vsum :: Num a => Vector a -> a
vsum = uncons >>> \case
Just (a,av) -> a + vsum av
Nothing -> 0
But honestly, that's seems like a bit of a code smell as you're using one data structure (Vector) as another ([]) which suggests that maybe your choice of data structure is off.
If you really just want to treat it like a list for the purposes of some algorithm, why not use toList?
#Cactus has pointed out -XPatternSynonym (introduced in 7.8) combined with -XViewPattern can be used to pattern match on vectors. I am here to extend his comment a bit further.
pattern Empty <- (V.null -> True)
The above defines a pattern synonym Empty for the empty vector. The Empty pattern matches against an empty vector using view pattern (V.null -> True). However, it cannot be used as an expression elsewhere, i.e. a uni-directional synonym, since the system doesn't really know what Empty is as a Vector (we only know that null v is True but there could be other vectors giving True as well).
To remedy this, a where clause can be added specifying that Empty actually is a empty vector, i.e. a bi-directional synonym, as well as a type signature:
pattern Empty :: Vector a
pattern Empty <- (V.null -> True) where Empty = V.empty
This pattern synonym can be used to define uncons without an if expression:
uncons :: Vector a -> Maybe (a, Vector a)
uncons Empty = Nothing
uncons v = Just (unsafeHead v, unsafeTail v)
We use uncons to define uni-directional synonym. Note I don't make it bi-directional since cons is costly for vector:
pattern (:<|) :: a -> Vector a -> Vector a
pattern x :<| xs <- (uncons -> Just (x, xs))
Anyway, we are finally able to pattern match on vectors just like lists:
vsum :: Num a => Vector a -> a
vsum Empty = 0
vsum (x :<| xs) = x + vsum xs
A complete code is here.
Vectors aren't intended for that kind of pattern matching--they were created to give Haskell O(1) lists, or lists that can be accessed from any point efficiently.
The closest thing to what you wrote would be something like this:
f v = V.head v
Or, if recursion is what you are looking for, the tail function will get the rest of the list.
But if you are trying to do something that moves along a list like that, there are Vector equivalents of functions such as foldl, find, map, and the like. It depends on what you intend to do.

Test if a value matches a constructor

Say I have a data type like so:
data NumCol = Empty |
Single Int |
Pair Int Int |
Lots [Int]
Now I wish to filter out the elements matching a given constructor from a [NumCol]. I can write it for, say, Pair:
get_pairs :: [NumCol] -> [NumCol]
get_pairs = filter is_pair
where is_pair (Pair _ _) = True
is_pair _ = False
This works, but it's not generic. I have to write a separate function for is_single, is_lots, etc.
I wish instead I could write:
get_pairs = filter (== Pair)
But this only works for type constructors that take no arguments (i.e. Empty).
So the question is, how can I write a function that takes a value and a constructor, and returns whether the value matches the constructor?
At least get_pairs itself can be defined relatively simply by using a list comprehension to filter instead:
get_pairs xs = [x | x#Pair {} <- xs]
For a more general solution of matching constructors, you can use prisms from the lens package:
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
import Control.Lens.Extras (is)
data NumCol = Empty |
Single Int |
Pair Int Int |
Lots [Int]
-- Uses Template Haskell to create the Prisms _Empty, _Single, _Pair and _Lots
-- corresponding to your constructors
makePrisms ''NumCol
get_pairs :: [NumCol] -> [NumCol]
get_pairs = filter (is _Pair)
Tags of tagged unions ought to be first-class values, and with a wee bit of effort, they are.
Jiggery-pokery alert:
{-# LANGUAGE GADTs, DataKinds, KindSignatures,
TypeFamilies, PolyKinds, FlexibleInstances,
PatternSynonyms
#-}
Step one: define type-level versions of the tags.
data TagType = EmptyTag | SingleTag | PairTag | LotsTag
Step two: define value-level witnesses for the representability of the type-level tags. Richard Eisenberg's Singletons library will do this for you. I mean something like this:
data Tag :: TagType -> * where
EmptyT :: Tag EmptyTag
SingleT :: Tag SingleTag
PairT :: Tag PairTag
LotsT :: Tag LotsTag
And now we can say what stuff we expect to find associated with a given tag.
type family Stuff (t :: TagType) :: * where
Stuff EmptyTag = ()
Stuff SingleTag = Int
Stuff PairTag = (Int, Int)
Stuff LotsTag = [Int]
So we can refactor the type you first thought of
data NumCol :: * where
(:&) :: Tag t -> Stuff t -> NumCol
and use PatternSynonyms to recover the behaviour you had in mind:
pattern Empty = EmptyT :& ()
pattern Single i = SingleT :& i
pattern Pair i j = PairT :& (i, j)
pattern Lots is = LotsT :& is
So what's happened is that each constructor for NumCol has turned into a tag indexed by the kind of tag it's for. That is, constructor tags now live separately from the rest of the data, synchronized by a common index which ensures that the stuff associated with a tag matches the tag itself.
But we can talk about tags alone.
data Ex :: (k -> *) -> * where -- wish I could say newtype here
Witness :: p x -> Ex p
Now, Ex Tag, is the type of "runtime tags with a type level counterpart". It has an Eq instance
instance Eq (Ex Tag) where
Witness EmptyT == Witness EmptyT = True
Witness SingleT == Witness SingleT = True
Witness PairT == Witness PairT = True
Witness LotsT == Witness LotsT = True
_ == _ = False
Moreover, we can easily extract the tag of a NumCol.
numColTag :: NumCol -> Ex Tag
numColTag (n :& _) = Witness n
And that allows us to match your specification.
filter ((Witness PairT ==) . numColTag) :: [NumCol] -> [NumCol]
Which raises the question of whether your specification is actually what you need. The point is that detecting a tag entitles you an expectation of that tag's stuff. The output type [NumCol] doesn't do justice to the fact that you know you have just the pairs.
How might you tighten the type of your function and still deliver it?
One approach is to use DataTypeable and the Data.Data module. This approach relies on two autogenerated typeclass instances that carry metadata about the type for you: Typeable and Data. You can derive them with {-# LANGUAGE DeriveDataTypeable #-}:
data NumCol = Empty |
Single Int |
Pair Int Int |
Lots [Int] deriving (Typeable, Data)
Now we have a toConstr function which, given a value, gives us a representation of its constructor:
toConstr :: Data a => a -> Constr
This makes it easy to compare two terms just by their constructors. The only remaining problem is that we need a value to compare against when we define our predicate! We can always just create a dummy value with undefined, but that's a bit ugly:
is_pair x = toConstr x == toConstr (Pair undefined undefined)
So the final thing we'll do is define a handy little class that automates this. The basic idea is to call toConstr on non-function values and recurse on any functions by first passing in undefined.
class Constrable a where
constr :: a -> Constr
instance Data a => Constrable a where
constr = toConstr
instance Constrable a => Constrable (b -> a) where
constr f = constr (f undefined)
This relies on FlexibleInstance, OverlappingInstances and UndecidableInstances, so it might be a bit evil, but, using the (in)famous eyeball theorem, it should be fine. Unless you add more instances or try to use it with something that isn't a constructor. Then it might blow up. Violently. No promises.
Finally, with the evil neatly contained, we can write an "equal by constructor" operator:
(=|=) :: (Data a, Constrable b) => a -> b -> Bool
e =|= c = toConstr e == constr c
(The =|= operator is a bit of a mnemonic, because constructors are syntactically defined with a |.)
Now you can write almost exactly what you wanted!
filter (=|= Pair)
Also, maybe you'd want to turn off the monomorphism restriction. In fact, here's the list of extensions I enabled that you can just use:
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, NoMonomorphismRestriction, OverlappingInstances, UndecidableInstances #-}
Yeah, it's a lot. But that's what I'm willing to sacrifice for the cause. Of not writing extra undefineds.
Honestly, if you don't mind relying on lens (but boy is that dependency a doozy), you should just go with the prism approach. The only thing to recommend mine is that you get to use the amusingly named Data.Data.Data class.

haskell - nested empty lists

Hello Haskellers and Haskellettes,
when reading http://learnyouahaskell.com/ a friend of mine came up with a problem:
Is it possible in Haskell to write a recursive function that gives True if all sub-sub-_-sublists are empty. My first guess was - should be - but i have a big problem just writing the type annotation.
he tried something like
nullRec l = if null l
then True
else if [] `elem` l
then nullRec (head [l]) && nullRec (tail l)
else False
which is - not working - :-)
i came up with something like
folding with concat - to get a a single long list
(giving me problems implementing)
or making an infinite treelike datatype - and making this from the list
(haven't implemented yet)
but the latter sound a bit like overkill for this problem.
what is your ideas - on a sunny sunday like this ;-)
Thanks in advance
as a reaction to all the comments - this being bad style i'd like to add
this is just an experiment!
DO not try this at home! ;-)
How about a typeclass?
{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
class NullRec a where
nullRec :: a -> Bool
instance NullRec a => NullRec [a] where
nullRec [] = True
nullRec ls = all nullRec ls
instance NullRec a where
nullRec _ = False
main = print . nullRec $ ([[[[()]]]] :: [[[[()]]]])
This is not possible using parametric polymorphism only, because of the following.
Consider these values:
x = [8] :: [Int]
y = [3.0] :: [Double]
z = [[]] :: [[Int]]
Obviously, you want your function to work with both x and y, thus its type must be null1 :: [a] -> Bool. (Can someone help me make this argument look formal? How can I show that this is the unique most specific context-less type unifiable with [Int] -> Bool and [Double] -> Bool? Is there a name for that relation between types?)
Now, if you have this type, then null1 z will be equal to null1 x because they differ only in values of the list elements, which are abstracted away from. (Not even close to formal proof again :()
What you want for z is null2 :: [[a]] -> Bool, which will differ in behaviour, and thus giving null1 and null2 the same name will require overloading. (see the FUZxxl's answer)

Resources