Although heap sort solves all these limitation, I found tournament knock out itself can work out.
data Infinite a = NegInf | Only a | Inf deriving (Eq, Show, Ord)
only (Only x) = x
data Tr a = Empty | Br (Tr a) a (Tr a) deriving Show
key (Br _ k _ ) = k
wrap x = Br Empty (Only x) Empty
branch t1 t2 = Br t1 (min (key t1) (key t2)) t2
fromList :: (Ord a) => [a] -> Tr (Infinite a)
fromList = build . (map wrap) where
build [] = Empty
build [t] = t
build ts = build $ pair ts
pair (t1:t2:ts) = (branch t1 t2):pair ts
pair ts = ts
pop (Br Empty _ Empty) = Br Empty Inf Empty
pop (Br l k r) | k == key l = let l' = pop l in Br l' (min (key l') (key r)) r
| k == key r = let r' = pop r in Br l (min (key l) (key r')) r'
top = only . key
tsort :: (Ord a) => [a] -> [a]
tsort = sort' . fromList where
sort' Empty = []
sort' (Br _ Inf _) = []
sort' t = (top t) : (sort' $ pop t)