{-# LANGUAGE GADTs #-}
module Data.HashMap.InsOrd.Internal where
import Prelude hiding (filter, foldr, lookup, map, null)
import Control.Applicative ((<**>))
data SortedAp f a where
Pure :: a -> SortedAp f a
SortedAp :: !Int -> f a -> SortedAp f (a -> b) -> SortedAp f b
instance Functor (SortedAp f) where
fmap :: forall a b. (a -> b) -> SortedAp f a -> SortedAp f b
fmap a -> b
f (Pure a
a) = forall a (f :: * -> *). a -> SortedAp f a
Pure (a -> b
f a
a)
fmap a -> b
f (SortedAp Int
i f a
x SortedAp f (a -> a)
y) = forall (f :: * -> *) a b.
Int -> f a -> SortedAp f (a -> b) -> SortedAp f b
SortedAp Int
i f a
x ((a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SortedAp f (a -> a)
y)
instance Applicative (SortedAp f) where
pure :: forall a. a -> SortedAp f a
pure = forall a (f :: * -> *). a -> SortedAp f a
Pure
Pure a -> b
f <*> :: forall a b. SortedAp f (a -> b) -> SortedAp f a -> SortedAp f b
<*> SortedAp f a
y = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f SortedAp f a
y
SortedAp f (a -> b)
f <*> Pure a
y = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> a -> b
$ a
y) SortedAp f (a -> b)
f
f :: SortedAp f (a -> b)
f@(SortedAp Int
i f a
x SortedAp f (a -> a -> b)
y) <*> z :: SortedAp f a
z@(SortedAp Int
j f a
u SortedAp f (a -> a)
v)
| Int
i forall a. Ord a => a -> a -> Bool
< Int
j = forall (f :: * -> *) a b.
Int -> f a -> SortedAp f (a -> b) -> SortedAp f b
SortedAp Int
i f a
x (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SortedAp f (a -> a -> b)
y forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SortedAp f a
z)
| Bool
otherwise = forall (f :: * -> *) a b.
Int -> f a -> SortedAp f (a -> b) -> SortedAp f b
SortedAp Int
j f a
u (forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SortedAp f (a -> b)
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SortedAp f (a -> a)
v)
liftSortedAp :: Int -> f a -> SortedAp f a
liftSortedAp :: forall (f :: * -> *) a. Int -> f a -> SortedAp f a
liftSortedAp Int
i f a
x = forall (f :: * -> *) a b.
Int -> f a -> SortedAp f (a -> b) -> SortedAp f b
SortedAp Int
i f a
x (forall a (f :: * -> *). a -> SortedAp f a
Pure forall a. a -> a
id)
retractSortedAp :: Applicative f => SortedAp f a -> f a
retractSortedAp :: forall (f :: * -> *) a. Applicative f => SortedAp f a -> f a
retractSortedAp (Pure a
x) = forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
retractSortedAp (SortedAp Int
_ f a
f SortedAp f (a -> a)
x) = f a
f forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> forall (f :: * -> *) a. Applicative f => SortedAp f a -> f a
retractSortedAp SortedAp f (a -> a)
x