module Data.FMList ( 
    FMList(..)
  , transform
    
  
  , empty
  , singleton
  , cons
  , snoc
  , pair
  , append
  
  , fromList
  , fromFoldable
  
  
  , null
  , length
  , genericLength
  
  , head
  , tail
  , last
  , init
  , reverse
  
  
  , toList
  , flatten
  , foldMapA
  
  , filter
  , take
  , drop
  , takeWhile
  , dropWhile
  
  , zip
  , zipWith
  
  
  , iterate
  , repeat
  , unfold
  , unfoldr
  
  ) where
import Prelude 
  ( (.), ($), ($!), flip, const, id, error
  , Either(..), either
  , Bool(..), (&&)
  , Ord(..), Num(..), Int
  , Show(..), String, (++)
  )
import Data.Maybe (Maybe(..), maybe, fromMaybe, isNothing)
import Data.Monoid
import Data.Foldable
import Data.Traversable
import Control.Monad
import Control.Applicative
newtype FMList a = FM { unFM :: forall m . Monoid m => (a -> m) -> m }
transform :: (forall m. Monoid m => (a -> m) -> (b -> m)) -> FMList b -> FMList a
transform t (FM l) = FM (l . t)
nil          :: FMList a
nil          = FM mempty
one          :: a -> FMList a
one x        = FM ($ x)
(><)         :: FMList a -> FMList a -> FMList a
FM l >< FM r = FM (l `mappend` r)
singleton    :: a -> FMList a
singleton    = one
cons         :: a -> FMList a -> FMList a
cons x l     = one x >< l
snoc         :: FMList a -> a -> FMList a
snoc l x     = l >< one x
pair         :: a -> a -> FMList a
pair l r     = one l >< one r
append       :: FMList a -> FMList a -> FMList a
append       = (><)
fromList     :: [a] -> FMList a
fromList     = fromFoldable
fromFoldable :: Foldable f => f a -> FMList a
fromFoldable l = FM $ flip foldMap l
mhead        :: FMList a -> Maybe a
mhead l      = getFirst (unFM l (First . Just))
null         :: FMList a -> Bool
null         = isNothing . mhead
length       :: FMList a -> Int
length       = genericLength
genericLength :: Num b => FMList a -> b
genericLength l = getSum $ unFM l (const $ Sum 1)
head         :: FMList a -> a
head l       = mhead l `fromMaybeOrError` "Data.FMList.head: empty list"
tail         :: FMList a -> FMList a
tail l       = if null l then error "Data.FMList.tail: empty list" else drop (1::Int) l
last         :: FMList a -> a
last l       = getLast (unFM l (Last . Just)) `fromMaybeOrError` "Data.FMList.last: empty list"
init         :: FMList a -> FMList a
init l       = if null l then error "Data.FMList.init: empty list" else reverse . drop (1::Int) . reverse $ l
reverse      :: FMList a -> FMList a
reverse l    = FM $ getDual . unFM l . (Dual .)
flatten      :: Foldable t => FMList (t a) -> FMList a
flatten      = transform foldMap
filter       :: (a -> Bool) -> FMList a -> FMList a
filter p     = transform (\f x -> if p x then f x else mempty)
transformCS  :: (forall m. Monoid m => (b -> m) -> a -> (m -> s -> m) -> s -> m) -> s -> FMList a -> FMList b
transformCS t s0 l = FM $ \f -> foldr (\e r -> t f e (\a -> mappend a . r)) mempty l s0
take         :: (Ord n, Num n) => n -> FMList a -> FMList a
take         = transformCS (\f e c i -> if i > 0 then c (f e) (i1) else mempty)
takeWhile    :: (a -> Bool) -> FMList a -> FMList a
takeWhile p  = transformCS (\f e c _ -> if p e then c (f e) True else mempty) True
drop         :: (Ord n, Num n) => n -> FMList a -> FMList a
drop         = transformCS (\f e c i -> if i > 0 then c mempty (i1) else c (f e) 0)
dropWhile    :: (a -> Bool) -> FMList a -> FMList a
dropWhile p  = transformCS (\f e c ok -> if ok && p e then c mempty True else c (f e) False) True
zipWith      :: (a -> b -> c) -> FMList a -> FMList b -> FMList c
zipWith t    = transformCS (\f e2 c r1 -> foldr (\e1 _ -> c (f (t e1 e2)) (drop (1::Int) r1)) mempty r1)
zip          :: FMList a -> FMList b -> FMList (a,b)
zip          = zipWith (,)
iterate      :: (a -> a) -> a -> FMList a
iterate f x  = x `cons` iterate f (f x)
repeat       :: a -> FMList a
repeat       = cycle . one
cycle        :: FMList a -> FMList a
cycle l      = l >< cycle l >< l
unfoldr      :: (b -> Maybe (a, b)) -> b -> FMList a
unfoldr g    = unfold (maybe empty (\(a, b) -> Right a `pair` Left b) . g)
unfold       :: (b -> FMList (Either b a)) -> b -> FMList a
unfold g     = transform (\f -> either (foldMap f . unfold g) f) . g
newtype WrapApp f m = WrapApp { unWrapApp :: f m }
instance (Applicative f, Monoid m) => Monoid (WrapApp f m) where
  mempty                          = WrapApp $ pure mempty
  mappend (WrapApp a) (WrapApp b) = WrapApp $ mappend <$> a <*> b
foldMapA :: (Foldable t, Applicative f, Monoid m) => (a -> f m) -> t a -> f m
foldMapA f = unWrapApp . foldMap (WrapApp . f)
instance Functor FMList where
  fmap g     = transform (. g)
  
instance Foldable FMList where
  foldMap    = flip unFM
  
instance Traversable FMList where
  traverse f = foldMapA (fmap one . f)
instance Monad FMList where
  return     = one
  m >>= g    = transform (\f -> foldMap f . g) m
  fail _     = nil
instance Applicative FMList where
  pure       = one
  gs <*> xs  = transform (\f g -> unFM xs (f . g)) gs
    
instance Monoid (FMList a) where
  mempty     = nil
  mappend    = (><)
  
instance MonadPlus FMList where
  mzero      = nil
  mplus      = (><)
  
instance Alternative FMList where
  empty      = nil
  (<|>)      = (><)
  
instance Show a => Show (FMList a) where
  show l     = "fromList " ++ (show $! toList l)
  
fromMaybeOrError :: Maybe a -> String -> a
fromMaybeOrError ma e = fromMaybe (error e) ma