module Control.Alternative.Free.Final
  ( Alt(..)
  , runAlt
  , liftAlt
  , hoistAlt
  ) where
import Control.Applicative
import Data.Functor.Apply
import Data.Functor.Alt ((<!>))
import qualified Data.Functor.Alt as Alt
import Data.Semigroup
newtype Alt f a = Alt { _runAlt :: forall g. Alternative g => (forall x. f x -> g x) -> g a }
instance Functor (Alt f) where
  fmap f (Alt g) = Alt (\k -> fmap f (g k))
instance Apply (Alt f) where
  Alt f <.> Alt x = Alt (\k -> f k <*> x k)
instance Applicative (Alt f) where
  pure x = Alt (\_ -> pure x)
  Alt f <*> Alt x = Alt (\k -> f k <*> x k)
instance Alt.Alt (Alt f) where
  Alt x <!> Alt y = Alt (\k -> x k <|> y k)
instance Alternative (Alt f) where
  empty = Alt (\_ -> empty)
  Alt x <|> Alt y = Alt (\k -> x k <|> y k)
instance Semigroup (Alt f a) where
  (<>) = (<|>)
instance Monoid (Alt f a) where
  mempty = empty
  mappend = (<>)
liftAlt :: f a -> Alt f a
liftAlt f = Alt (\k -> k f)
runAlt :: forall f g a. Alternative g => (forall x. f x -> g x) -> Alt f a -> g a
runAlt phi g = _runAlt g phi
hoistAlt :: (forall a. f a -> g a) -> Alt f b -> Alt g b
hoistAlt phi (Alt g) = Alt (\k -> g (k . phi))