{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE Unsafe #-}
module Lens.Micro.Internal
(
traversed,
folded,
foldring,
foldrOf,
foldMapOf,
sets,
phantom,
Each(..),
Index,
IxValue,
Ixed(..),
At(..),
ixAt,
Field1(..),
Field2(..),
Field3(..),
Field4(..),
Field5(..),
Cons(..),
Snoc(..),
Strict(..),
HasCallStack,
coerce,
( #. ),
( .# ),
)
where
import Lens.Micro.Type
import Control.Applicative
import Data.Monoid
import Data.Foldable as F
import Data.Functor.Identity
import Data.Complex
#if __GLASGOW_HASKELL__ >= 800
import Data.List.NonEmpty (NonEmpty(..))
#endif
#if __GLASGOW_HASKELL__ < 710
import Data.Traversable
#endif
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
#else
import Unsafe.Coerce
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Kind (Type)
import GHC.Stack (HasCallStack)
#elif MIN_VERSION_base(4,8,1)
import qualified GHC.Stack as GHC
type HasCallStack = (?callStack :: GHC.CallStack)
#else
import GHC.Exts (Constraint)
type HasCallStack = (() :: Constraint)
#endif
traversed :: Traversable f => Traversal (f a) (f b) a b
traversed :: forall (f :: * -> *) a b.
Traversable f =>
Traversal (f a) (f b) a b
traversed = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
{-# INLINE [0] traversed #-}
{-# RULES
"traversed -> mapped"
traversed = sets fmap :: Functor f => ASetter (f a) (f b) a b;
"traversed -> folded"
traversed = folded :: Foldable f => Getting (Endo r) (f a) a;
#-}
folded :: Foldable f => SimpleFold (f a) a
folded :: forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded = forall r a s b t.
Monoid r =>
((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a)
-> (a -> Const r b) -> s -> Const r t
foldring forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr
{-# INLINE folded #-}
foldring :: Monoid r => ((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a) -> (a -> Const r b) -> s -> Const r t
foldring :: forall r a s b t.
Monoid r =>
((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a)
-> (a -> Const r b) -> s -> Const r t
foldring (a -> Const r a -> Const r a) -> Const r a -> s -> Const r a
fr a -> Const r b
f = forall r a b. Const r a -> Const r b
phantom forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const r a -> Const r a) -> Const r a -> s -> Const r a
fr (\a
a Const r a
fa -> a -> Const r b
f a
a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Const r a
fa) forall r a. Monoid r => Const r a
noEffect
{-# INLINE foldring #-}
foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
foldrOf :: forall r s a. Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
foldrOf Getting (Endo r) s a
l a -> r -> r
f r
z = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Endo a -> a -> a
appEndo r
z forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r s a. Getting r s a -> (a -> r) -> s -> r
foldMapOf Getting (Endo r) s a
l (forall a. (a -> a) -> Endo a
Endo forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. a -> r -> r
f)
{-# INLINE foldrOf #-}
foldMapOf :: Getting r s a -> (a -> r) -> s -> r
foldMapOf :: forall r s a. Getting r s a -> (a -> r) -> s -> r
foldMapOf Getting r s a
l a -> r
f = forall {k} a (b :: k). Const a b -> a
getConst forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. Getting r s a
l (forall {k} a (b :: k). a -> Const a b
Const forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. a -> r
f)
{-# INLINE foldMapOf #-}
sets :: ((a -> b) -> s -> t) -> ASetter s t a b
sets :: forall a b s t. ((a -> b) -> s -> t) -> ASetter s t a b
sets (a -> b) -> s -> t
f a -> Identity b
g = forall a. a -> Identity a
Identity forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. (a -> b) -> s -> t
f (forall a. Identity a -> a
runIdentity forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. a -> Identity b
g)
{-# INLINE sets #-}
phantom :: Const r a -> Const r b
phantom :: forall r a b. Const r a -> Const r b
phantom = forall {k} a (b :: k). a -> Const a b
Const forall c b a. Coercible c b => (b -> c) -> (a -> b) -> a -> c
#. forall {k} a (b :: k). Const a b -> a
getConst
{-# INLINE phantom #-}
noEffect :: Monoid r => Const r a
noEffect :: forall r a. Monoid r => Const r a
noEffect = forall r a b. Const r a -> Const r b
phantom (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
{-# INLINE noEffect #-}
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
each :: Traversal s t a b
instance (a~b, q~r) => Each (a,b) (q,r) a q where
each :: Traversal (a, b) (q, r) a q
each a -> f q
f ~(a
a,b
b) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f q
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f b
b
{-# INLINE each #-}
instance (a~b, a~c, q~r, q~s) => Each (a,b,c) (q,r,s) a q where
each :: Traversal (a, b, c) (q, r, s) a q
each a -> f q
f ~(a
a,b
b,c
c) = (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f q
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f b
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f c
c
{-# INLINE each #-}
instance (a~b, a~c, a~d, q~r, q~s, q~t) => Each (a,b,c,d) (q,r,s,t) a q where
each :: Traversal (a, b, c, d) (q, r, s, t) a q
each a -> f q
f ~(a
a,b
b,c
c,d
d) = (,,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f q
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f b
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f c
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f d
d
{-# INLINE each #-}
instance (a~b, a~c, a~d, a~e, q~r, q~s, q~t, q~u) => Each (a,b,c,d,e) (q,r,s,t,u) a q where
each :: Traversal (a, b, c, d, e) (q, r, s, t, u) a q
each a -> f q
f ~(a
a,b
b,c
c,d
d,e
e) = (,,,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f q
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f b
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f c
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f d
d forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f q
f e
e
{-# INLINE each #-}
instance Each (Complex a) (Complex b) a b where
each :: Traversal (Complex a) (Complex b) a b
each a -> f b
f (a
a :+ a
b) = forall a. a -> a -> Complex a
(:+) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b
{-# INLINE each #-}
instance Each [a] [b] a b where
each :: Traversal [a] [b] a b
each = forall (f :: * -> *) a b.
Traversable f =>
Traversal (f a) (f b) a b
traversed
{-# INLINE each #-}
instance Each (Maybe a) (Maybe b) a b where
each :: Traversal (Maybe a) (Maybe b) a b
each = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
{-# INLINE each #-}
instance (a~a', b~b') => Each (Either a a') (Either b b') a b where
each :: Traversal (Either a a') (Either b b') a b
each a -> f b
f (Left a
a) = forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
each a -> f b
f (Right a'
a ) = forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a'
a
{-# INLINE each #-}
#if __GLASGOW_HASKELL__ >= 800
instance Each (NonEmpty a) (NonEmpty b) a b where
each :: Traversal (NonEmpty a) (NonEmpty b) a b
each = forall (f :: * -> *) a b.
Traversable f =>
Traversal (f a) (f b) a b
traversed
{-# INLINE each #-}
#endif
#if MIN_VERSION_base(4,9,0)
type family Index (s :: Type) :: Type
type family IxValue (m :: Type) :: Type
#else
type family Index (s :: *) :: *
type family IxValue (m :: *) :: *
#endif
type instance Index (e -> a) = e
type instance IxValue (e -> a) = a
type instance Index [a] = Int
type instance IxValue [a] = a
#if __GLASGOW_HASKELL__ >= 800
type instance Index (NonEmpty a) = Int
type instance IxValue (NonEmpty a) = a
#endif
class Ixed m where
ix :: Index m -> Traversal' m (IxValue m)
class Ixed m => At m where
at :: Index m -> Lens' m (Maybe (IxValue m))
ixAt :: At m => Index m -> Traversal' m (IxValue m)
ixAt :: forall m. At m => Index m -> Traversal' m (IxValue m)
ixAt Index m
i = forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index m
i forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
{-# INLINE ixAt #-}
instance Eq e => Ixed (e -> a) where
ix :: Index (e -> a) -> Traversal' (e -> a) (IxValue (e -> a))
ix Index (e -> a)
e IxValue (e -> a) -> f (IxValue (e -> a))
p e -> a
f = (\a
a e
e' -> if Index (e -> a)
e forall a. Eq a => a -> a -> Bool
== e
e' then a
a else e -> a
f e
e') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IxValue (e -> a) -> f (IxValue (e -> a))
p (e -> a
f Index (e -> a)
e)
{-# INLINE ix #-}
instance Ixed [a] where
ix :: Index [a] -> Traversal' [a] (IxValue [a])
ix Index [a]
k IxValue [a] -> f (IxValue [a])
f [a]
xs0 | Index [a]
k forall a. Ord a => a -> a -> Bool
< Int
0 = forall (f :: * -> *) a. Applicative f => a -> f a
pure [a]
xs0
| Bool
otherwise = [a] -> Int -> f [a]
go [a]
xs0 Index [a]
k where
go :: [a] -> Int -> f [a]
go [] Int
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure []
go (a
a:[a]
as) Int
0 = (forall a. a -> [a] -> [a]
:[a]
as) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IxValue [a] -> f (IxValue [a])
f a
a
go (a
a:[a]
as) Int
i = (a
aforall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([a] -> Int -> f [a]
go [a]
as forall a b. (a -> b) -> a -> b
$! Int
i forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE ix #-}
#if __GLASGOW_HASKELL__ >= 800
instance Ixed (NonEmpty a) where
ix :: Index (NonEmpty a)
-> Traversal' (NonEmpty a) (IxValue (NonEmpty a))
ix Index (NonEmpty a)
k IxValue (NonEmpty a) -> f (IxValue (NonEmpty a))
f NonEmpty a
xs0 | Index (NonEmpty a)
k forall a. Ord a => a -> a -> Bool
< Int
0 = forall (f :: * -> *) a. Applicative f => a -> f a
pure NonEmpty a
xs0
| Bool
otherwise = NonEmpty a -> Int -> f (NonEmpty a)
go NonEmpty a
xs0 Index (NonEmpty a)
k where
go :: NonEmpty a -> Int -> f (NonEmpty a)
go (a
a:|[a]
as) Int
0 = (forall a. a -> [a] -> NonEmpty a
:|[a]
as) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IxValue (NonEmpty a) -> f (IxValue (NonEmpty a))
f a
a
go (a
a:|[a]
as) Int
i = (a
aforall a. a -> [a] -> NonEmpty a
:|) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix (Int
i forall a. Num a => a -> a -> a
- Int
1) IxValue (NonEmpty a) -> f (IxValue (NonEmpty a))
f [a]
as
{-# INLINE ix #-}
#endif
class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_1 :: Lens s t a b
instance Field1 (a,b) (a',b) a a' where
_1 :: Lens (a, b) (a', b) a a'
_1 a -> f a'
k ~(a
a,b
b) = (\a'
a' -> (a'
a',b
b)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a'
k a
a
{-# INLINE _1 #-}
instance Field1 (a,b,c) (a',b,c) a a' where
_1 :: Lens (a, b, c) (a', b, c) a a'
_1 a -> f a'
k ~(a
a,b
b,c
c) = (\a'
a' -> (a'
a',b
b,c
c)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a'
k a
a
{-# INLINE _1 #-}
instance Field1 (a,b,c,d) (a',b,c,d) a a' where
_1 :: Lens (a, b, c, d) (a', b, c, d) a a'
_1 a -> f a'
k ~(a
a,b
b,c
c,d
d) = (\a'
a' -> (a'
a',b
b,c
c,d
d)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a'
k a
a
{-# INLINE _1 #-}
instance Field1 (a,b,c,d,e) (a',b,c,d,e) a a' where
_1 :: Lens (a, b, c, d, e) (a', b, c, d, e) a a'
_1 a -> f a'
k ~(a
a,b
b,c
c,d
d,e
e) = (\a'
a' -> (a'
a',b
b,c
c,d
d,e
e)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a'
k a
a
{-# INLINE _1 #-}
class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_2 :: Lens s t a b
instance Field2 (a,b) (a,b') b b' where
_2 :: Lens (a, b) (a, b') b b'
_2 b -> f b'
k ~(a
a,b
b) = (\b'
b' -> (a
a,b'
b')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f b'
k b
b
{-# INLINE _2 #-}
instance Field2 (a,b,c) (a,b',c) b b' where
_2 :: Lens (a, b, c) (a, b', c) b b'
_2 b -> f b'
k ~(a
a,b
b,c
c) = (\b'
b' -> (a
a,b'
b',c
c)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f b'
k b
b
{-# INLINE _2 #-}
instance Field2 (a,b,c,d) (a,b',c,d) b b' where
_2 :: Lens (a, b, c, d) (a, b', c, d) b b'
_2 b -> f b'
k ~(a
a,b
b,c
c,d
d) = (\b'
b' -> (a
a,b'
b',c
c,d
d)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f b'
k b
b
{-# INLINE _2 #-}
instance Field2 (a,b,c,d,e) (a,b',c,d,e) b b' where
_2 :: Lens (a, b, c, d, e) (a, b', c, d, e) b b'
_2 b -> f b'
k ~(a
a,b
b,c
c,d
d,e
e) = (\b'
b' -> (a
a,b'
b',c
c,d
d,e
e)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f b'
k b
b
{-# INLINE _2 #-}
class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_3 :: Lens s t a b
instance Field3 (a,b,c) (a,b,c') c c' where
_3 :: Lens (a, b, c) (a, b, c') c c'
_3 c -> f c'
k ~(a
a,b
b,c
c) = (\c'
c' -> (a
a,b
b,c'
c')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> f c'
k c
c
{-# INLINE _3 #-}
instance Field3 (a,b,c,d) (a,b,c',d) c c' where
_3 :: Lens (a, b, c, d) (a, b, c', d) c c'
_3 c -> f c'
k ~(a
a,b
b,c
c,d
d) = (\c'
c' -> (a
a,b
b,c'
c',d
d)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> f c'
k c
c
{-# INLINE _3 #-}
instance Field3 (a,b,c,d,e) (a,b,c',d,e) c c' where
_3 :: Lens (a, b, c, d, e) (a, b, c', d, e) c c'
_3 c -> f c'
k ~(a
a,b
b,c
c,d
d,e
e) = (\c'
c' -> (a
a,b
b,c'
c',d
d,e
e)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> f c'
k c
c
{-# INLINE _3 #-}
class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_4 :: Lens s t a b
instance Field4 (a,b,c,d) (a,b,c,d') d d' where
_4 :: Lens (a, b, c, d) (a, b, c, d') d d'
_4 d -> f d'
k ~(a
a,b
b,c
c,d
d) = (\d'
d' -> (a
a,b
b,c
c,d'
d')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> d -> f d'
k d
d
{-# INLINE _4 #-}
instance Field4 (a,b,c,d,e) (a,b,c,d',e) d d' where
_4 :: Lens (a, b, c, d, e) (a, b, c, d', e) d d'
_4 d -> f d'
k ~(a
a,b
b,c
c,d
d,e
e) = (\d'
d' -> (a
a,b
b,c
c,d'
d',e
e)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> d -> f d'
k d
d
{-# INLINE _4 #-}
class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_5 :: Lens s t a b
instance Field5 (a,b,c,d,e) (a,b,c,d,e') e e' where
_5 :: Lens (a, b, c, d, e) (a, b, c, d, e') e e'
_5 e -> f e'
k ~(a
a,b
b,c
c,d
d,e
e) = (\e'
e' -> (a
a,b
b,c
c,d
d,e'
e')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> e -> f e'
k e
e
{-# INLINE _5 #-}
class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
_Cons :: Traversal s t (a,s) (b,t)
instance Cons [a] [b] a b where
_Cons :: Traversal [a] [b] (a, [a]) (b, [b])
_Cons (a, [a]) -> f (b, [b])
f (a
a:[a]
as) = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a, [a]) -> f (b, [b])
f (a
a, [a]
as)
_Cons (a, [a]) -> f (b, [b])
_ [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure []
{-# INLINE _Cons #-}
class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
_Snoc :: Traversal s t (s,a) (t,b)
instance Snoc [a] [b] a b where
_Snoc :: Traversal [a] [b] ([a], a) ([b], b)
_Snoc ([a], a) -> f ([b], b)
_ [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure []
_Snoc ([a], a) -> f ([b], b)
f [a]
xs = (\([b]
as,b
a) -> [b]
as forall a. [a] -> [a] -> [a]
++ [b
a]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([a], a) -> f ([b], b)
f (forall a. [a] -> [a]
init [a]
xs, forall a. [a] -> a
last [a]
xs)
{-# INLINE _Snoc #-}
class Strict lazy strict | lazy -> strict, strict -> lazy where
strict :: Lens' lazy strict
lazy :: Lens' strict lazy
#if __GLASGOW_HASKELL__ < 708
coerce :: a -> b
coerce = unsafeCoerce
{-# INLINE coerce #-}
#endif
#if __GLASGOW_HASKELL__ >= 708
( #. ) :: Coercible c b => (b -> c) -> (a -> b) -> (a -> c)
( #. ) b -> c
_ = coerce :: forall a b. Coercible a b => a -> b
coerce (\b
x -> b
x :: b) :: forall a b. Coercible b a => a -> b
( .# ) :: Coercible b a => (b -> c) -> (a -> b) -> (a -> c)
( .# ) b -> c
pbc a -> b
_ = coerce :: forall a b. Coercible a b => a -> b
coerce b -> c
pbc
#else
( #. ) :: (b -> c) -> (a -> b) -> (a -> c)
( #. ) _ = unsafeCoerce
( .# ) :: (b -> c) -> (a -> b) -> (a -> c)
( .# ) pbc _ = unsafeCoerce pbc
#endif
{-# INLINE ( #. ) #-}
{-# INLINE ( .# ) #-}
infixr 9 #.
infixl 8 .#