module Data.ListLike.Base 
    (
    ListLike(..),
    InfiniteListLike(..),
    zip, zipWith, sequence_
    ) where
import Prelude hiding (length, head, last, null, tail, map, filter, concat, 
                       any, lookup, init, all, foldl, foldr, foldl1, foldr1,
                       maximum, minimum, iterate, span, break, takeWhile,
                       dropWhile, reverse, zip, zipWith, sequence,
                       sequence_, mapM, mapM_, concatMap, and, or, sum,
                       product, repeat, replicate, cycle, take, drop,
                       splitAt, elem, notElem, unzip, lines, words,
                       unlines, unwords)
import qualified Data.List as L
import Data.ListLike.FoldableLL
import qualified Control.Monad as M
import Data.Monoid
import Data.Maybe
class (FoldableLL full item, Monoid full) =>
    ListLike full item | full -> item where
    
    
    empty :: full
    empty = mempty
    
    singleton :: item -> full
    
    
    cons :: item -> full -> full
    cons item l = append (singleton item) l
    
    snoc :: full -> item -> full
    snoc l item = append l (singleton item)
    
    append :: full -> full -> full 
    append = mappend
    
    head :: full -> item
    
    last :: full -> item
    last l = case genericLength l of
                  (0::Integer) -> error "Called last on empty list"
                  1 -> head l
                  _ -> last (tail l)
    
    tail :: full -> full 
    
    init :: full -> full
    init l
        | null l = error "init: empty list"
        | null xs = empty
        | otherwise = cons (head l) (init xs)
        where xs = tail l
    
    null :: full -> Bool
    null x = genericLength x == (0::Integer)
    
    length :: full -> Int
    length = genericLength
    
    
    map :: ListLike full' item' => (item -> item') -> full -> full'
    map func inp  
        | null inp = empty
        | otherwise = cons (func (head inp)) (map func (tail inp))
    
    rigidMap :: (item -> item) -> full -> full
    rigidMap = map
    
    reverse :: full -> full 
    reverse l = rev l empty
        where rev rl a
                | null rl = a
                | otherwise = rev (tail rl) (cons (head rl) a)
    
    intersperse :: item -> full -> full
    intersperse sep l
        | null l = empty
        | null xs = singleton x
        | otherwise = cons x (cons sep (intersperse sep xs))
        where x = head l
              xs = tail l
    
    
    
    
    concat :: (ListLike full' full, Monoid full) => full' -> full
    concat = fold
    
    concatMap :: (ListLike full' item') =>
                 (item -> full') -> full -> full'
    concatMap = foldMap
    
    rigidConcatMap :: (item -> full) -> full -> full
    rigidConcatMap = concatMap
    
    any :: (item -> Bool) -> full -> Bool
    any p = getAny . foldMap (Any . p)
    
    all :: (item -> Bool) -> full -> Bool
    all p = getAll . foldMap (All . p)
    
    maximum :: Ord item => full -> item
    maximum = foldr1 max
    
    minimum :: Ord item => full -> item
    minimum = foldr1 min
    
    
    replicate :: Int -> item -> full
    replicate = genericReplicate
    
    
    take :: Int -> full -> full
    take = genericTake
    
    drop :: Int -> full -> full
    drop = genericDrop
    
    splitAt :: Int -> full -> (full, full)
    splitAt = genericSplitAt
    
    takeWhile :: (item -> Bool) -> full -> full
    takeWhile func l 
        | null l = empty
        | func x = cons x (takeWhile func (tail l))
        | otherwise = empty
        where x = head l
    
    dropWhile :: (item -> Bool) -> full -> full
    dropWhile func l
        | null l = empty
        | func (head l) = dropWhile func (tail l)
        | otherwise = l
    
    span :: (item -> Bool) -> full -> (full, full)
    span func l
        | null l = (empty, empty)
        | func x = (cons x ys, zs) 
        | otherwise = (empty, l)
       where (ys, zs) = span func (tail l)
             x = head l
    
    break :: (item -> Bool) -> full -> (full, full)
    break p = span (not . p)
    
    group :: (ListLike full' full, Eq item) => full -> full'
    group = groupBy (==)
    
    inits :: (ListLike full' full) => full -> full'
    inits l
        | null l = singleton empty
        | otherwise =
            append (singleton empty)
                   (map (cons (head l)) theinits)
            where theinits = asTypeOf (inits (tail l)) [l]
    
    tails :: ListLike full' full => full -> full'
    tails l
        | null l = singleton empty
        | otherwise = cons l (tails (tail l))
    
    
    isPrefixOf :: Eq item => full -> full -> Bool
    isPrefixOf needle haystack
        | null needle = True
        | null haystack = False
        | otherwise = (head needle) == (head haystack) && 
                      isPrefixOf (tail needle) (tail haystack)
    
    isSuffixOf :: Eq item => full -> full -> Bool
    isSuffixOf needle haystack = isPrefixOf (reverse needle) (reverse haystack)
    
    isInfixOf :: Eq item => full -> full -> Bool
    isInfixOf needle haystack = 
        any (isPrefixOf needle) thetails
        where thetails = asTypeOf (tails haystack) [haystack]
    
    
    elem :: Eq item => item -> full -> Bool
    elem i = any (== i)
    
    notElem :: Eq item => item -> full -> Bool
    notElem i = all (/= i)
    
    find :: (item -> Bool) -> full -> Maybe item
    find f l = case findIndex f l of
                    Nothing -> Nothing
                    Just x -> Just (index l x)
    
    filter :: (item -> Bool) -> full -> full 
    filter func l 
        | null l = empty
        | func (head l) = cons (head l) (filter func (tail l))
        | otherwise = filter func (tail l)
    
    partition :: (item -> Bool) -> full -> (full, full)
    partition p xs = (filter p xs, filter (not . p) xs)
    
    
    index :: full -> Int -> item
    index l i 
        | null l = error "index: index not found"
        | i < 0 = error "index: index must be >= 0"
        | i == 0 = head l
        | otherwise = index (tail l) (i  1)
    
    elemIndex :: Eq item => item -> full -> Maybe Int
    elemIndex e l = findIndex (== e) l
    
    elemIndices :: (Eq item, ListLike result Int) => item -> full -> result
    elemIndices i l = findIndices (== i) l
    
    findIndex :: (item -> Bool) -> full -> Maybe Int
    findIndex f = listToMaybe . findIndices f
    
    findIndices :: (ListLike result Int) => (item -> Bool) -> full -> result
    findIndices p xs = map snd $ filter (p . fst) $ thezips
        where thezips = asTypeOf (zip xs [0..]) [(head xs, 0::Int)]
    
    
    sequence :: (Monad m, ListLike fullinp (m item)) =>
                fullinp -> m full
    sequence l = foldr func (return empty) l
        where func litem results = 
                do x <- litem
                   xs <- results
                   return (cons x xs)
    
    mapM :: (Monad m, ListLike full' item') => 
            (item -> m item') -> full -> m full'
    mapM func l = sequence mapresult
            where mapresult = asTypeOf (map func l) []
    
    rigidMapM :: Monad m => (item -> m item) -> full -> m full
    rigidMapM = mapM
            
    
    mapM_ :: (Monad m) => (item -> m b) -> full -> m ()
    mapM_ func l = sequence_ mapresult
            where mapresult = asTypeOf (map func l) []
    
    
    nub :: Eq item => full -> full
    nub = nubBy (==)
    
    delete :: Eq item => item -> full -> full
    delete = deleteBy (==)
    
    deleteFirsts :: Eq item => full -> full -> full
    deleteFirsts = foldl (flip delete)
    
    union :: Eq item => full -> full -> full
    union = unionBy (==)
    
    intersect :: Eq item => full -> full -> full
    intersect = intersectBy (==)
    
    
    sort :: Ord item => full -> full
    sort = sortBy compare
    
    insert :: Ord item => item -> full -> full 
    insert = insertBy compare
    
    
    toList :: full -> [item]
    toList = fromListLike
    
    fromList :: [item] -> full 
    fromList [] = empty
    fromList (x:xs) = cons x (fromList xs)
    
    fromListLike :: ListLike full' item => full -> full'
    fromListLike = map id
    
    
    nubBy :: (item -> item -> Bool) -> full -> full
    nubBy f l
        | null l = empty
        | otherwise =
            cons (head l) (nubBy f (filter (\y -> not (f (head l) y)) (tail l)))
    
    deleteBy :: (item -> item -> Bool) -> item -> full -> full
    deleteBy func i l
        | null l = empty
        | otherwise =
            if func i (head l)
               then tail l
               else cons (head l) (deleteBy func i (tail l))
    
    deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> full
    deleteFirstsBy func = foldl (flip (deleteBy func))
    
    unionBy :: (item -> item -> Bool) -> full -> full -> full
    unionBy func x y =
        append x $ foldl (flip (deleteBy func)) (nubBy func y) x
    
    intersectBy :: (item -> item -> Bool) -> full -> full -> full
    intersectBy func xs ys = filter (\x -> any (func x) ys) xs
    
    groupBy :: (ListLike full' full, Eq item) => 
                (item -> item -> Bool) -> full -> full'
    groupBy eq l
        | null l = empty
        | otherwise = cons (cons x ys) (groupBy eq zs)
                      where (ys, zs) = span (eq x) xs
                            x = head l
                            xs = tail l
    
    sortBy :: Ord item => (item -> item -> Ordering) -> full -> full 
    sortBy cmp = foldr (insertBy cmp) empty
    
    insertBy :: Ord item => (item -> item -> Ordering) -> item ->
                full -> full 
    insertBy cmp x ys
        | null ys = singleton x
        | otherwise = case cmp x (head ys) of
                        GT -> cons (head ys) (insertBy cmp x (tail ys))
                        _ ->  cons x ys
    
    
    genericLength :: Num a => full -> a
    genericLength l = calclen 0 l
        where calclen accum cl =
                  if null cl
                     then accum
                     else calclen (accum + 1) (tail cl)
    
    genericTake :: Integral a => a -> full -> full
    genericTake n l
        | n <= 0 = empty
        | null l = empty
        | otherwise = cons (head l) (genericTake (n  1) (tail l))
    
    genericDrop :: Integral a => a -> full -> full
    genericDrop n l 
        | n <= 0 = l
        | null l = l
        | otherwise = genericDrop (n  1) (tail l)
    
    genericSplitAt :: Integral a => a -> full -> (full, full)
    genericSplitAt n l = (genericTake n l, genericDrop n l)
    
    genericReplicate :: Integral a => a -> item -> full
    genericReplicate count x 
        | count <= 0 = empty
        | otherwise = map (\_ -> x) [1..count]
class (ListLike full item) => InfiniteListLike full item | full -> item where
    
    iterate :: (item -> item) -> item -> full
    iterate f x = cons x (iterate f (f x))
    
    repeat :: item -> full
    repeat x = xs
        where xs = cons x xs
    
    cycle :: full -> full
    cycle xs 
        | null xs = error "ListLike.cycle: empty list"
        | otherwise = xs' where xs' = append xs xs'
instance ListLike [a] a where
    empty = []
    singleton x = [x]
    cons x l = x : l
    snoc l x = l ++ [x]
    append = (++)
    head = L.head
    last = L.last
    tail = L.tail
    init = L.init
    null = L.null
    length = L.length
    map f = fromList . L.map f
    rigidMap = L.map
    reverse = L.reverse
    intersperse = L.intersperse
    toList = id
    fromList = id
    
    concat = L.concat . toList
    
    rigidConcatMap = L.concatMap
    any = L.any
    all = L.all
    maximum = L.maximum
    minimum = L.minimum
    
    
    replicate = L.replicate
    take = L.take
    drop = L.drop
    splitAt = L.splitAt
    takeWhile = L.takeWhile
    dropWhile = L.dropWhile
    span = L.span
    break = L.break
    group = fromList . L.group
    inits = fromList . L.inits
    tails = fromList . L.tails
    isPrefixOf = L.isPrefixOf
    isSuffixOf = L.isSuffixOf
    isInfixOf = L.isInfixOf
    elem = L.elem
    notElem = L.notElem
    find = L.find
    filter = L.filter
    partition = L.partition
    index = (L.!!)
    elemIndex = L.elemIndex
    elemIndices item = fromList . L.elemIndices item
    findIndex = L.findIndex
    sequence = M.sequence . toList
    
    mapM_ = M.mapM_
    nub = L.nub
    delete = L.delete
    deleteFirsts = (L.\\)
    union = L.union
    intersect = L.intersect
    sort = L.sort
    groupBy func = fromList . L.groupBy func
    unionBy = L.unionBy
    intersectBy = L.intersectBy
    sortBy = L.sortBy
    insert = L.insert
zip :: (ListLike full item,
          ListLike fullb itemb,
          ListLike result (item, itemb)) =>
          full -> fullb -> result
zip = zipWith (\a b -> (a, b))
zipWith :: (ListLike full item,
            ListLike fullb itemb,
            ListLike result resultitem) =>
            (item -> itemb -> resultitem) -> full -> fullb -> result
zipWith f a b
    | null a = empty
    | null b = empty
    | otherwise = cons (f (head a) (head b)) (zipWith f (tail a) (tail b))
sequence_ :: (Monad m, ListLike mfull (m item)) => mfull -> m ()
sequence_ l = foldr (>>) (return ()) l