module Data.Functor.Arrow.Straight (Straight (..), type (-->)) where

import "morphisms" Control.Morphism ((.), ($), constant)

import Control.Functor.Covariant (Covariant ((<$>)))
import Control.Functor.Covariant.Pointable (Pointable (point))
import Control.Functor.Covariant.Applicative (Applicative ((<*>)))
import Control.Functor.Polyvariant.Provariant (Provariant (promap))

newtype Straight a b = Straight { straight :: a -> b }

type (-->) = Straight

instance Covariant (Straight a) where
        f <$> g = Straight (f . straight g)

instance Pointable (Straight a) where
        point = Straight . constant

instance Applicative (Straight a) where
        Straight f <*> Straight g = Straight $ \x -> f x (g x)

instance Provariant Straight where
        promap f g (Straight h) = Straight $ g . h . f