{-# LANGUAGE UndecidableInstances #-} module Lazy.Scope.Type where import Relude hiding (Handle) import System.IO qualified as IO import UnliftIO (MonadUnliftIO (..)) newtype Scoped s a = Scoped { forall {k} (s :: k) a. Scoped s a -> a unScoped :: a } deriving newtype (Int -> Scoped s a -> ShowS [Scoped s a] -> ShowS Scoped s a -> String (Int -> Scoped s a -> ShowS) -> (Scoped s a -> String) -> ([Scoped s a] -> ShowS) -> Show (Scoped s a) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (s :: k) a. Show a => Int -> Scoped s a -> ShowS forall k (s :: k) a. Show a => [Scoped s a] -> ShowS forall k (s :: k) a. Show a => Scoped s a -> String $cshowsPrec :: forall k (s :: k) a. Show a => Int -> Scoped s a -> ShowS showsPrec :: Int -> Scoped s a -> ShowS $cshow :: forall k (s :: k) a. Show a => Scoped s a -> String show :: Scoped s a -> String $cshowList :: forall k (s :: k) a. Show a => [Scoped s a] -> ShowS showList :: [Scoped s a] -> ShowS Show, Scoped s a -> Scoped s a -> Bool (Scoped s a -> Scoped s a -> Bool) -> (Scoped s a -> Scoped s a -> Bool) -> Eq (Scoped s a) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall k (s :: k) a. Eq a => Scoped s a -> Scoped s a -> Bool $c== :: forall k (s :: k) a. Eq a => Scoped s a -> Scoped s a -> Bool == :: Scoped s a -> Scoped s a -> Bool $c/= :: forall k (s :: k) a. Eq a => Scoped s a -> Scoped s a -> Bool /= :: Scoped s a -> Scoped s a -> Bool Eq, Eq (Scoped s a) Eq (Scoped s a) => (Scoped s a -> Scoped s a -> Ordering) -> (Scoped s a -> Scoped s a -> Bool) -> (Scoped s a -> Scoped s a -> Bool) -> (Scoped s a -> Scoped s a -> Bool) -> (Scoped s a -> Scoped s a -> Bool) -> (Scoped s a -> Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a -> Scoped s a) -> Ord (Scoped s a) Scoped s a -> Scoped s a -> Bool Scoped s a -> Scoped s a -> Ordering Scoped s a -> Scoped s a -> Scoped s a forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a forall k (s :: k) a. Ord a => Eq (Scoped s a) forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Bool forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Ordering forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Scoped s a $ccompare :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Ordering compare :: Scoped s a -> Scoped s a -> Ordering $c< :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Bool < :: Scoped s a -> Scoped s a -> Bool $c<= :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Bool <= :: Scoped s a -> Scoped s a -> Bool $c> :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Bool > :: Scoped s a -> Scoped s a -> Bool $c>= :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Bool >= :: Scoped s a -> Scoped s a -> Bool $cmax :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Scoped s a max :: Scoped s a -> Scoped s a -> Scoped s a $cmin :: forall k (s :: k) a. Ord a => Scoped s a -> Scoped s a -> Scoped s a min :: Scoped s a -> Scoped s a -> Scoped s a Ord, Scoped s a -> () (Scoped s a -> ()) -> NFData (Scoped s a) forall a. (a -> ()) -> NFData a forall k (s :: k) a. NFData a => Scoped s a -> () $crnf :: forall k (s :: k) a. NFData a => Scoped s a -> () rnf :: Scoped s a -> () NFData, NonEmpty (Scoped s a) -> Scoped s a Scoped s a -> Scoped s a -> Scoped s a (Scoped s a -> Scoped s a -> Scoped s a) -> (NonEmpty (Scoped s a) -> Scoped s a) -> (forall b. Integral b => b -> Scoped s a -> Scoped s a) -> Semigroup (Scoped s a) forall b. Integral b => b -> Scoped s a -> Scoped s a forall a. (a -> a -> a) -> (NonEmpty a -> a) -> (forall b. Integral b => b -> a -> a) -> Semigroup a forall k (s :: k) a. Semigroup a => NonEmpty (Scoped s a) -> Scoped s a forall k (s :: k) a. Semigroup a => Scoped s a -> Scoped s a -> Scoped s a forall k (s :: k) a b. (Semigroup a, Integral b) => b -> Scoped s a -> Scoped s a $c<> :: forall k (s :: k) a. Semigroup a => Scoped s a -> Scoped s a -> Scoped s a <> :: Scoped s a -> Scoped s a -> Scoped s a $csconcat :: forall k (s :: k) a. Semigroup a => NonEmpty (Scoped s a) -> Scoped s a sconcat :: NonEmpty (Scoped s a) -> Scoped s a $cstimes :: forall k (s :: k) a b. (Semigroup a, Integral b) => b -> Scoped s a -> Scoped s a stimes :: forall b. Integral b => b -> Scoped s a -> Scoped s a Semigroup, String -> Scoped s a (String -> Scoped s a) -> IsString (Scoped s a) forall a. (String -> a) -> IsString a forall k (s :: k) a. IsString a => String -> Scoped s a $cfromString :: forall k (s :: k) a. IsString a => String -> Scoped s a fromString :: String -> Scoped s a IsString, Semigroup (Scoped s a) Scoped s a Semigroup (Scoped s a) => Scoped s a -> (Scoped s a -> Scoped s a -> Scoped s a) -> ([Scoped s a] -> Scoped s a) -> Monoid (Scoped s a) [Scoped s a] -> Scoped s a Scoped s a -> Scoped s a -> Scoped s a forall a. Semigroup a => a -> (a -> a -> a) -> ([a] -> a) -> Monoid a forall k (s :: k) a. Monoid a => Semigroup (Scoped s a) forall k (s :: k) a. Monoid a => Scoped s a forall k (s :: k) a. Monoid a => [Scoped s a] -> Scoped s a forall k (s :: k) a. Monoid a => Scoped s a -> Scoped s a -> Scoped s a $cmempty :: forall k (s :: k) a. Monoid a => Scoped s a mempty :: Scoped s a $cmappend :: forall k (s :: k) a. Monoid a => Scoped s a -> Scoped s a -> Scoped s a mappend :: Scoped s a -> Scoped s a -> Scoped s a $cmconcat :: forall k (s :: k) a. Monoid a => [Scoped s a] -> Scoped s a mconcat :: [Scoped s a] -> Scoped s a Monoid, Integer -> Scoped s a Scoped s a -> Scoped s a Scoped s a -> Scoped s a -> Scoped s a (Scoped s a -> Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a) -> (Scoped s a -> Scoped s a) -> (Integer -> Scoped s a) -> Num (Scoped s a) forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a forall k (s :: k) a. Num a => Integer -> Scoped s a forall k (s :: k) a. Num a => Scoped s a -> Scoped s a forall k (s :: k) a. Num a => Scoped s a -> Scoped s a -> Scoped s a $c+ :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a -> Scoped s a + :: Scoped s a -> Scoped s a -> Scoped s a $c- :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a -> Scoped s a - :: Scoped s a -> Scoped s a -> Scoped s a $c* :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a -> Scoped s a * :: Scoped s a -> Scoped s a -> Scoped s a $cnegate :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a negate :: Scoped s a -> Scoped s a $cabs :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a abs :: Scoped s a -> Scoped s a $csignum :: forall k (s :: k) a. Num a => Scoped s a -> Scoped s a signum :: Scoped s a -> Scoped s a $cfromInteger :: forall k (s :: k) a. Num a => Integer -> Scoped s a fromInteger :: Integer -> Scoped s a Num, Scoped s a Scoped s a -> Scoped s a -> Bounded (Scoped s a) forall a. a -> a -> Bounded a forall k (s :: k) a. Bounded a => Scoped s a $cminBound :: forall k (s :: k) a. Bounded a => Scoped s a minBound :: Scoped s a $cmaxBound :: forall k (s :: k) a. Bounded a => Scoped s a maxBound :: Scoped s a Bounded) deriving ((forall a b. (a -> b) -> Scoped s a -> Scoped s b) -> (forall a b. a -> Scoped s b -> Scoped s a) -> Functor (Scoped s) forall k (s :: k) a b. a -> Scoped s b -> Scoped s a forall k (s :: k) a b. (a -> b) -> Scoped s a -> Scoped s b forall a b. a -> Scoped s b -> Scoped s a forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f $cfmap :: forall k (s :: k) a b. (a -> b) -> Scoped s a -> Scoped s b fmap :: forall a b. (a -> b) -> Scoped s a -> Scoped s b $c<$ :: forall k (s :: k) a b. a -> Scoped s b -> Scoped s a <$ :: forall a b. a -> Scoped s b -> Scoped s a Functor) instance Applicative (Scoped s) where pure :: forall a. a -> Scoped s a pure = a -> Scoped s a forall k (s :: k) a. a -> Scoped s a Scoped {-# INLINE pure #-} liftA2 :: forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c liftA2 a -> b -> c f (Scoped a a) (Scoped b b) = c -> Scoped s c forall k (s :: k) a. a -> Scoped s a Scoped (c -> Scoped s c) -> c -> Scoped s c forall a b. (a -> b) -> a -> b $ a -> b -> c f a a b b {-# INLINE liftA2 #-} type Bs s = Scoped s LByteString type I64 s = Scoped s Int64 type B s = Scoped s Bool type W8 s = Scoped s Word8 both :: (a -> b) -> (a, a) -> (b, b) both :: forall a b. (a -> b) -> (a, a) -> (b, b) both a -> b f ~(a x,a y) = (a -> b f a x, a -> b f a y) {-# INLINE both #-} mapFst :: (a -> b) -> (a, c) -> (b, c) mapFst :: forall a b c. (a -> b) -> (a, c) -> (b, c) mapFst a -> b f (a x,c y) = (a -> b f a x, c y) {-# INLINE mapFst #-} mapSnd :: (a -> b) -> (c, a) -> (c, b) mapSnd :: forall a b c. (a -> b) -> (c, a) -> (c, b) mapSnd a -> b f (c x,a y) = (c x, a -> b f a y) {-# INLINE mapSnd #-} newtype Handle s = Handle IO.Handle deriving (Int -> Handle s -> ShowS [Handle s] -> ShowS Handle s -> String (Int -> Handle s -> ShowS) -> (Handle s -> String) -> ([Handle s] -> ShowS) -> Show (Handle s) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (s :: k). Int -> Handle s -> ShowS forall k (s :: k). [Handle s] -> ShowS forall k (s :: k). Handle s -> String $cshowsPrec :: forall k (s :: k). Int -> Handle s -> ShowS showsPrec :: Int -> Handle s -> ShowS $cshow :: forall k (s :: k). Handle s -> String show :: Handle s -> String $cshowList :: forall k (s :: k). [Handle s] -> ShowS showList :: [Handle s] -> ShowS Show, Handle s -> Handle s -> Bool (Handle s -> Handle s -> Bool) -> (Handle s -> Handle s -> Bool) -> Eq (Handle s) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall k (s :: k). Handle s -> Handle s -> Bool $c== :: forall k (s :: k). Handle s -> Handle s -> Bool == :: Handle s -> Handle s -> Bool $c/= :: forall k (s :: k). Handle s -> Handle s -> Bool /= :: Handle s -> Handle s -> Bool Eq) newtype HandlePosn s = HandlePosn IO.HandlePosn deriving (Int -> HandlePosn s -> ShowS [HandlePosn s] -> ShowS HandlePosn s -> String (Int -> HandlePosn s -> ShowS) -> (HandlePosn s -> String) -> ([HandlePosn s] -> ShowS) -> Show (HandlePosn s) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (s :: k). Int -> HandlePosn s -> ShowS forall k (s :: k). [HandlePosn s] -> ShowS forall k (s :: k). HandlePosn s -> String $cshowsPrec :: forall k (s :: k). Int -> HandlePosn s -> ShowS showsPrec :: Int -> HandlePosn s -> ShowS $cshow :: forall k (s :: k). HandlePosn s -> String show :: HandlePosn s -> String $cshowList :: forall k (s :: k). [HandlePosn s] -> ShowS showList :: [HandlePosn s] -> ShowS Show, HandlePosn s -> HandlePosn s -> Bool (HandlePosn s -> HandlePosn s -> Bool) -> (HandlePosn s -> HandlePosn s -> Bool) -> Eq (HandlePosn s) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall k (s :: k). HandlePosn s -> HandlePosn s -> Bool $c== :: forall k (s :: k). HandlePosn s -> HandlePosn s -> Bool == :: HandlePosn s -> HandlePosn s -> Bool $c/= :: forall k (s :: k). HandlePosn s -> HandlePosn s -> Bool /= :: HandlePosn s -> HandlePosn s -> Bool Eq) newtype LazyT s m a = LazyT { forall {k} {k} (s :: k) (m :: k -> *) (a :: k). LazyT s m a -> m a unLazy :: m a } instance Functor m => Functor (LazyT s m) where {-# INLINE fmap #-} fmap :: forall a b. (a -> b) -> LazyT s m a -> LazyT s m b fmap a -> b f (LazyT m a m) = m b -> LazyT s m b forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT ((a -> b) -> m a -> m b forall a b. (a -> b) -> m a -> m b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> b f m a m) instance Applicative m => Applicative (LazyT s m) where pure :: forall a. a -> LazyT s m a pure a a = m a -> LazyT s m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT (a -> m a forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure a a) {-# INLINE pure #-} liftA2 :: forall a b c. (a -> b -> c) -> LazyT s m a -> LazyT s m b -> LazyT s m c liftA2 a -> b -> c f (LazyT m a ma) (LazyT m b mb) = m c -> LazyT s m c forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT ((a -> b -> c) -> m a -> m b -> m c forall a b c. (a -> b -> c) -> m a -> m b -> m c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 a -> b -> c f m a ma m b mb) {-# INLINE liftA2 #-} instance Monad m => Monad (LazyT s m) where (>>=) :: LazyT s m a -> (a -> LazyT s m b) -> LazyT s m b LazyT m a m1 >>= :: forall a b. LazyT s m a -> (a -> LazyT s m b) -> LazyT s m b >>= a -> LazyT s m b fm2 = m b -> LazyT s m b forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT (m a m1 m a -> (a -> m b) -> m b forall a b. m a -> (a -> m b) -> m b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \a a -> LazyT s m b -> m b forall {k} {k} (s :: k) (m :: k -> *) (a :: k). LazyT s m a -> m a unLazy (a -> LazyT s m b fm2 a a)) {-# INLINE (>>=) #-} instance MonadFail m => MonadFail (LazyT s m) where fail :: forall a. String -> LazyT s m a fail String s = m a -> LazyT s m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT (String -> m a forall a. String -> m a forall (m :: * -> *) a. MonadFail m => String -> m a fail String s) instance MonadTrans (LazyT s) where lift :: forall (m :: * -> *) a. Monad m => m a -> LazyT s m a lift m a m = m a -> LazyT s m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT m a m instance MonadReader r m => MonadReader r (LazyT s m) where ask :: LazyT s m r ask = m r -> LazyT s m r forall (m :: * -> *) a. Monad m => m a -> LazyT s m a forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift m r forall r (m :: * -> *). MonadReader r m => m r ask {-# INLINE ask #-} local :: forall a. (r -> r) -> LazyT s m a -> LazyT s m a local r -> r f (LazyT m a m) = m a -> LazyT s m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT ((r -> r) -> m a -> m a forall a. (r -> r) -> m a -> m a forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a local r -> r f m a m) instance MonadState s' m => MonadState s' (LazyT s m) where get :: LazyT s m s' get = m s' -> LazyT s m s' forall (m :: * -> *) a. Monad m => m a -> LazyT s m a forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift m s' forall s (m :: * -> *). MonadState s m => m s get put :: s' -> LazyT s m () put s' s = m () -> LazyT s m () forall (m :: * -> *) a. Monad m => m a -> LazyT s m a forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (s' -> m () forall s (m :: * -> *). MonadState s m => s -> m () put s' s) instance MonadIO m => MonadIO (LazyT s m) where {-# INLINE liftIO #-} liftIO :: forall a. IO a -> LazyT s m a liftIO IO a io = m a -> LazyT s m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT (IO a -> m a forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO IO a io) instance MonadUnliftIO m => MonadUnliftIO (LazyT s m) where {-# INLINE withRunInIO #-} withRunInIO :: forall b. ((forall a. LazyT s m a -> IO a) -> IO b) -> LazyT s m b withRunInIO (forall a. LazyT s m a -> IO a) -> IO b inner = m b -> LazyT s m b forall {k} {k} (s :: k) (m :: k -> *) (a :: k). m a -> LazyT s m a LazyT (m b -> LazyT s m b) -> m b -> LazyT s m b forall a b. (a -> b) -> a -> b $ ((forall a. m a -> IO a) -> IO b) -> m b forall b. ((forall a. m a -> IO a) -> IO b) -> m b forall (m :: * -> *) b. MonadUnliftIO m => ((forall a. m a -> IO a) -> IO b) -> m b withRunInIO (((forall a. m a -> IO a) -> IO b) -> m b) -> ((forall a. m a -> IO a) -> IO b) -> m b forall a b. (a -> b) -> a -> b $ \forall a. m a -> IO a run -> (forall a. LazyT s m a -> IO a) -> IO b inner (m a -> IO a forall a. m a -> IO a run (m a -> IO a) -> (LazyT s m a -> m a) -> LazyT s m a -> IO a forall b c a. (b -> c) -> (a -> b) -> a -> c . LazyT s m a -> m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). LazyT s m a -> m a unLazy)