{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE DefaultSignatures #-}
#endif
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
#if MIN_VERSION_base(4,8,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE OverlappingInstances #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Trustworthy #-}
#endif
#endif
#define HASCBOOL MIN_VERSION_base(4,10,0)
module Test.SmallCheck.Series (
cons0, cons1, cons2, cons3, cons4, cons5, cons6, newtypeCons,
alts0, alts1, alts2, alts3, alts4, alts5, alts6, newtypeAlts,
Depth, Series, Serial(..), CoSerial(..),
#if __GLASGOW_HASKELL__ >= 702
genericSeries,
genericCoseries,
#endif
Positive(..), NonNegative(..), NonZero(..), NonEmpty(..),
(\/), (><), (<~>), (>>-),
localDepth,
decDepth,
getDepth,
generate,
limit,
listSeries,
list,
listM,
fixDepth,
decDepthChecked,
constM
) where
import Control.Monad (liftM, guard, mzero, mplus, msum)
import Control.Monad.Logic (MonadLogic, (>>-), interleave, msplit, observeAllT)
import Control.Monad.Reader (ask, local)
import Control.Applicative (empty, pure, (<$>), (<|>))
import Data.Complex (Complex(..))
import Data.Foldable (Foldable)
import Data.Functor.Compose (Compose(..))
import Data.Void (Void, absurd)
import Control.Monad.Identity (Identity(..))
import Data.Int (Int, Int8, Int16, Int32, Int64)
import Data.List (intercalate)
import qualified Data.List.NonEmpty as NE
import Data.Ratio (Ratio, numerator, denominator, (%))
import Data.Traversable (Traversable)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Foreign.C.Types (CFloat(..), CDouble(..), CChar(..), CSChar(..), CUChar(..), CShort(..), CUShort(..), CInt(..), CUInt(..), CLong(..), CULong(..), CPtrdiff(..), CSize(..), CWchar(..), CSigAtomic(..), CLLong(..), CULLong(..), CIntPtr(..), CUIntPtr(..), CIntMax(..), CUIntMax(..), CClock(..), CTime(..))
#if __GLASGOW_HASKELL__ >= 702
import Foreign.C.Types (CUSeconds(..), CSUSeconds(..))
#endif
#if HASCBOOL
import Foreign.C.Types (CBool(..))
#endif
import Numeric.Natural (Natural)
import Test.SmallCheck.SeriesMonad
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic, (:+:)(..), (:*:)(..), C1, K1(..), M1(..), U1(..), V1(..), Rep, to, from)
#endif
class Monad m => Serial m a where
series :: Series m a
#if __GLASGOW_HASKELL__ >= 704
default series :: (Generic a, GSerial m (Rep a)) => Series m a
series = Series m a
forall (m :: * -> *) a.
(Monad m, Generic a, GSerial m (Rep a)) =>
Series m a
genericSeries
#endif
#if __GLASGOW_HASKELL__ >= 702
genericSeries
:: (Monad m, Generic a, GSerial m (Rep a))
=> Series m a
genericSeries :: Series m a
genericSeries = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to (Rep a Any -> a) -> Series m (Rep a Any) -> Series m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (Rep a Any)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries
#endif
class Monad m => CoSerial m a where
coseries :: Series m b -> Series m (a->b)
#if __GLASGOW_HASKELL__ >= 704
default coseries :: (Generic a, GCoSerial m (Rep a)) => Series m b -> Series m (a->b)
coseries = Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
(Monad m, Generic a, GCoSerial m (Rep a)) =>
Series m b -> Series m (a -> b)
genericCoseries
#endif
#if __GLASGOW_HASKELL__ >= 702
genericCoseries
:: (Monad m, Generic a, GCoSerial m (Rep a))
=> Series m b -> Series m (a->b)
genericCoseries :: Series m b -> Series m (a -> b)
genericCoseries Series m b
rs = ((Rep a Any -> b) -> (a -> Rep a Any) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from) ((Rep a Any -> b) -> a -> b)
-> Series m (Rep a Any -> b) -> Series m (a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (Rep a Any -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries Series m b
rs
#endif
generate :: (Depth -> [a]) -> Series m a
generate :: (Depth -> [a]) -> Series m a
generate Depth -> [a]
f = do
Depth
d <- Series m Depth
forall (m :: * -> *). Series m Depth
getDepth
[Series m a] -> Series m a
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum ([Series m a] -> Series m a) -> [Series m a] -> Series m a
forall a b. (a -> b) -> a -> b
$ (a -> Series m a) -> [a] -> [Series m a]
forall a b. (a -> b) -> [a] -> [b]
map a -> Series m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> [Series m a]) -> [a] -> [Series m a]
forall a b. (a -> b) -> a -> b
$ Depth -> [a]
f Depth
d
limit :: forall m a . Monad m => Int -> Series m a -> Series m a
limit :: Depth -> Series m a -> Series m a
limit Depth
n0 (Series ReaderT Depth (LogicT m) a
s) = ReaderT Depth (LogicT m) a -> Series m a
forall (m :: * -> *) a. ReaderT Depth (LogicT m) a -> Series m a
Series (ReaderT Depth (LogicT m) a -> Series m a)
-> ReaderT Depth (LogicT m) a -> Series m a
forall a b. (a -> b) -> a -> b
$ Depth -> ReaderT Depth (LogicT m) a -> ReaderT Depth (LogicT m) a
forall t (ml :: * -> *) b.
(Eq t, Num t, MonadLogic ml) =>
t -> ml b -> ml b
go Depth
n0 ReaderT Depth (LogicT m) a
s
where
go :: t -> ml b -> ml b
go t
0 ml b
_ = ml b
forall (f :: * -> *) a. Alternative f => f a
empty
go t
n ml b
mb1 = do
Maybe (b, ml b)
cons :: Maybe (b, ml b) <- ml b -> ml (Maybe (b, ml b))
forall (m :: * -> *) a. MonadLogic m => m a -> m (Maybe (a, m a))
msplit ml b
mb1
case Maybe (b, ml b)
cons of
Maybe (b, ml b)
Nothing -> ml b
forall (f :: * -> *) a. Alternative f => f a
empty
Just (b
b, ml b
mb2) -> b -> ml b
forall (m :: * -> *) a. Monad m => a -> m a
return b
b ml b -> ml b -> ml b
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ml b -> ml b
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) ml b
mb2
suchThat :: Series m a -> (a -> Bool) -> Series m a
suchThat :: Series m a -> (a -> Bool) -> Series m a
suchThat Series m a
s a -> Bool
p = Series m a
s Series m a -> (a -> Series m a) -> Series m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
x -> if a -> Bool
p a
x then a -> Series m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x else Series m a
forall (f :: * -> *) a. Alternative f => f a
empty
listSeries :: Serial Identity a => Depth -> [a]
listSeries :: Depth -> [a]
listSeries Depth
d = Depth -> Series Identity a -> [a]
forall a. Depth -> Series Identity a -> [a]
list Depth
d Series Identity a
forall (m :: * -> *) a. Serial m a => Series m a
series
list :: Depth -> Series Identity a -> [a]
list :: Depth -> Series Identity a -> [a]
list Depth
d Series Identity a
s = Identity [a] -> [a]
forall a. Identity a -> a
runIdentity (Identity [a] -> [a]) -> Identity [a] -> [a]
forall a b. (a -> b) -> a -> b
$ LogicT Identity a -> Identity [a]
forall (m :: * -> *) a. Monad m => LogicT m a -> m [a]
observeAllT (LogicT Identity a -> Identity [a])
-> LogicT Identity a -> Identity [a]
forall a b. (a -> b) -> a -> b
$ Depth -> Series Identity a -> LogicT Identity a
forall (m :: * -> *) a. Depth -> Series m a -> LogicT m a
runSeries Depth
d Series Identity a
s
listM :: Depth -> Series m a -> m [a]
listM Depth
d Series m a
s = LogicT m a -> m [a]
forall (m :: * -> *) a. Monad m => LogicT m a -> m [a]
observeAllT (LogicT m a -> m [a]) -> LogicT m a -> m [a]
forall a b. (a -> b) -> a -> b
$ Depth -> Series m a -> LogicT m a
forall (m :: * -> *) a. Depth -> Series m a -> LogicT m a
runSeries Depth
d Series m a
s
infixr 7 \/
(\/) :: Monad m => Series m a -> Series m a -> Series m a
\/ :: Series m a -> Series m a -> Series m a
(\/) = Series m a -> Series m a -> Series m a
forall (m :: * -> *) a. MonadLogic m => m a -> m a -> m a
interleave
infixr 8 ><
(><) :: Monad m => Series m a -> Series m b -> Series m (a,b)
Series m a
a >< :: Series m a -> Series m b -> Series m (a, b)
>< Series m b
b = (,) (a -> b -> (a, b)) -> Series m a -> Series m (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
a Series m (b -> (a, b)) -> Series m b -> Series m (a, b)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
b
infixl 4 <~>
(<~>) :: Monad m => Series m (a -> b) -> Series m a -> Series m b
Series m (a -> b)
a <~> :: Series m (a -> b) -> Series m a -> Series m b
<~> Series m a
b = Series m (a -> b)
a Series m (a -> b) -> ((a -> b) -> Series m b) -> Series m b
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- ((a -> b) -> Series m a -> Series m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
b)
uncurry3 :: (a->b->c->d) -> ((a,b,c)->d)
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 a -> b -> c -> d
f (a
x,b
y,c
z) = a -> b -> c -> d
f a
x b
y c
z
uncurry4 :: (a->b->c->d->e) -> ((a,b,c,d)->e)
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 a -> b -> c -> d -> e
f (a
w,b
x,c
y,d
z) = a -> b -> c -> d -> e
f a
w b
x c
y d
z
uncurry5 :: (a->b->c->d->e->f) -> ((a,b,c,d,e)->f)
uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
uncurry5 a -> b -> c -> d -> e -> f
f (a
v,b
w,c
x,d
y,e
z) = a -> b -> c -> d -> e -> f
f a
v b
w c
x d
y e
z
uncurry6 :: (a->b->c->d->e->f->g) -> ((a,b,c,d,e,f)->g)
uncurry6 :: (a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
uncurry6 a -> b -> c -> d -> e -> f -> g
f (a
u,b
v,c
w,d
x,e
y,f
z) = a -> b -> c -> d -> e -> f -> g
f a
u b
v c
w d
x e
y f
z
getDepth :: Series m Depth
getDepth :: Series m Depth
getDepth = ReaderT Depth (LogicT m) Depth -> Series m Depth
forall (m :: * -> *) a. ReaderT Depth (LogicT m) a -> Series m a
Series ReaderT Depth (LogicT m) Depth
forall r (m :: * -> *). MonadReader r m => m r
ask
localDepth :: (Depth -> Depth) -> Series m a -> Series m a
localDepth :: (Depth -> Depth) -> Series m a -> Series m a
localDepth Depth -> Depth
f (Series ReaderT Depth (LogicT m) a
a) = ReaderT Depth (LogicT m) a -> Series m a
forall (m :: * -> *) a. ReaderT Depth (LogicT m) a -> Series m a
Series (ReaderT Depth (LogicT m) a -> Series m a)
-> ReaderT Depth (LogicT m) a -> Series m a
forall a b. (a -> b) -> a -> b
$ (Depth -> Depth)
-> ReaderT Depth (LogicT m) a -> ReaderT Depth (LogicT m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local Depth -> Depth
f ReaderT Depth (LogicT m) a
a
decDepth :: Series m a -> Series m a
decDepth :: Series m a -> Series m a
decDepth Series m a
a = do
Series m ()
forall (m :: * -> *). Series m ()
checkDepth
(Depth -> Depth) -> Series m a -> Series m a
forall (m :: * -> *) a.
(Depth -> Depth) -> Series m a -> Series m a
localDepth (Depth -> Depth -> Depth
forall a. Num a => a -> a -> a
subtract Depth
1) Series m a
a
checkDepth :: Series m ()
checkDepth :: Series m ()
checkDepth = do
Depth
d <- Series m Depth
forall (m :: * -> *). Series m Depth
getDepth
Bool -> Series m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Series m ()) -> Bool -> Series m ()
forall a b. (a -> b) -> a -> b
$ Depth
d Depth -> Depth -> Bool
forall a. Ord a => a -> a -> Bool
> Depth
0
constM :: Monad m => m b -> m (a -> b)
constM :: m b -> m (a -> b)
constM = (b -> a -> b) -> m b -> m (a -> b)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM b -> a -> b
forall a b. a -> b -> a
const
fixDepth :: Series m a -> Series m (Series m a)
fixDepth :: Series m a -> Series m (Series m a)
fixDepth Series m a
s = Series m Depth
forall (m :: * -> *). Series m Depth
getDepth Series m Depth
-> (Depth -> Series m (Series m a)) -> Series m (Series m a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Depth
d -> Series m a -> Series m (Series m a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Series m a -> Series m (Series m a))
-> Series m a -> Series m (Series m a)
forall a b. (a -> b) -> a -> b
$ (Depth -> Depth) -> Series m a -> Series m a
forall (m :: * -> *) a.
(Depth -> Depth) -> Series m a -> Series m a
localDepth (Depth -> Depth -> Depth
forall a b. a -> b -> a
const Depth
d) Series m a
s
decDepthChecked :: Series m a -> Series m a -> Series m a
decDepthChecked :: Series m a -> Series m a -> Series m a
decDepthChecked Series m a
b Series m a
r = do
Depth
d <- Series m Depth
forall (m :: * -> *). Series m Depth
getDepth
if Depth
d Depth -> Depth -> Bool
forall a. Ord a => a -> a -> Bool
<= Depth
0
then Series m a
b
else Series m a -> Series m a
forall (m :: * -> *) a. Series m a -> Series m a
decDepth Series m a
r
unwind :: MonadLogic m => m a -> m [a]
unwind :: m a -> m [a]
unwind m a
a =
m a -> m (Maybe (a, m a))
forall (m :: * -> *) a. MonadLogic m => m a -> m (Maybe (a, m a))
msplit m a
a m (Maybe (a, m a)) -> (Maybe (a, m a) -> m [a]) -> m [a]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
m [a] -> ((a, m a) -> m [a]) -> Maybe (a, m a) -> m [a]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([a] -> m [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []) (\(a
x,m a
a') -> (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:) ([a] -> [a]) -> m [a] -> m [a]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` m a -> m [a]
forall (m :: * -> *) a. MonadLogic m => m a -> m [a]
unwind m a
a')
cons0 :: a -> Series m a
cons0 :: a -> Series m a
cons0 a
x = Series m a -> Series m a
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m a -> Series m a) -> Series m a -> Series m a
forall a b. (a -> b) -> a -> b
$ a -> Series m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
cons1 :: Serial m a => (a->b) -> Series m b
cons1 :: (a -> b) -> Series m b
cons1 a -> b
f = Series m b -> Series m b
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m b -> Series m b) -> Series m b -> Series m b
forall a b. (a -> b) -> a -> b
$ a -> b
f (a -> b) -> Series m a -> Series m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
newtypeCons :: Serial m a => (a->b) -> Series m b
newtypeCons :: (a -> b) -> Series m b
newtypeCons a -> b
f = a -> b
f (a -> b) -> Series m a -> Series m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
cons2 :: (Serial m a, Serial m b) => (a->b->c) -> Series m c
cons2 :: (a -> b -> c) -> Series m c
cons2 a -> b -> c
f = Series m c -> Series m c
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m c -> Series m c) -> Series m c -> Series m c
forall a b. (a -> b) -> a -> b
$ a -> b -> c
f (a -> b -> c) -> Series m a -> Series m (b -> c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series Series m (b -> c) -> Series m b -> Series m c
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
cons3 :: (Serial m a, Serial m b, Serial m c) =>
(a->b->c->d) -> Series m d
cons3 :: (a -> b -> c -> d) -> Series m d
cons3 a -> b -> c -> d
f = Series m d -> Series m d
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m d -> Series m d) -> Series m d -> Series m d
forall a b. (a -> b) -> a -> b
$
a -> b -> c -> d
f (a -> b -> c -> d) -> Series m a -> Series m (b -> c -> d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (b -> c -> d) -> Series m b -> Series m (c -> d)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (c -> d) -> Series m c -> Series m d
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m c
forall (m :: * -> *) a. Serial m a => Series m a
series
cons4 :: (Serial m a, Serial m b, Serial m c, Serial m d) =>
(a->b->c->d->e) -> Series m e
cons4 :: (a -> b -> c -> d -> e) -> Series m e
cons4 a -> b -> c -> d -> e
f = Series m e -> Series m e
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m e -> Series m e) -> Series m e -> Series m e
forall a b. (a -> b) -> a -> b
$
a -> b -> c -> d -> e
f (a -> b -> c -> d -> e)
-> Series m a -> Series m (b -> c -> d -> e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (b -> c -> d -> e) -> Series m b -> Series m (c -> d -> e)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (c -> d -> e) -> Series m c -> Series m (d -> e)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m c
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (d -> e) -> Series m d -> Series m e
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m d
forall (m :: * -> *) a. Serial m a => Series m a
series
cons5 :: (Serial m a, Serial m b, Serial m c, Serial m d, Serial m e) =>
(a->b->c->d->e->f) -> Series m f
cons5 :: (a -> b -> c -> d -> e -> f) -> Series m f
cons5 a -> b -> c -> d -> e -> f
f = Series m f -> Series m f
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m f -> Series m f) -> Series m f -> Series m f
forall a b. (a -> b) -> a -> b
$
a -> b -> c -> d -> e -> f
f (a -> b -> c -> d -> e -> f)
-> Series m a -> Series m (b -> c -> d -> e -> f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (b -> c -> d -> e -> f)
-> Series m b -> Series m (c -> d -> e -> f)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (c -> d -> e -> f) -> Series m c -> Series m (d -> e -> f)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m c
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (d -> e -> f) -> Series m d -> Series m (e -> f)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m d
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (e -> f) -> Series m e -> Series m f
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m e
forall (m :: * -> *) a. Serial m a => Series m a
series
cons6 :: (Serial m a, Serial m b, Serial m c, Serial m d, Serial m e, Serial m f) =>
(a->b->c->d->e->f->g) -> Series m g
cons6 :: (a -> b -> c -> d -> e -> f -> g) -> Series m g
cons6 a -> b -> c -> d -> e -> f -> g
f = Series m g -> Series m g
forall (m :: * -> *) a. Series m a -> Series m a
decDepth (Series m g -> Series m g) -> Series m g -> Series m g
forall a b. (a -> b) -> a -> b
$
a -> b -> c -> d -> e -> f -> g
f (a -> b -> c -> d -> e -> f -> g)
-> Series m a -> Series m (b -> c -> d -> e -> f -> g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (b -> c -> d -> e -> f -> g)
-> Series m b -> Series m (c -> d -> e -> f -> g)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (c -> d -> e -> f -> g)
-> Series m c -> Series m (d -> e -> f -> g)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m c
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (d -> e -> f -> g) -> Series m d -> Series m (e -> f -> g)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m d
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (e -> f -> g) -> Series m e -> Series m (f -> g)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m e
forall (m :: * -> *) a. Serial m a => Series m a
series
Series m (f -> g) -> Series m f -> Series m g
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m f
forall (m :: * -> *) a. Serial m a => Series m a
series
alts0 :: Series m a -> Series m a
alts0 :: Series m a -> Series m a
alts0 Series m a
s = Series m a
s
alts1 :: CoSerial m a => Series m b -> Series m (a->b)
alts1 :: Series m b -> Series m (a -> b)
alts1 Series m b
rs = do
Series m b
rs <- Series m b -> Series m (Series m b)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m b
rs
Series m (a -> b) -> Series m (a -> b) -> Series m (a -> b)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked (Series m b -> Series m (a -> b)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m b
rs) (Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs)
alts2
:: (CoSerial m a, CoSerial m b)
=> Series m c -> Series m (a->b->c)
alts2 :: Series m c -> Series m (a -> b -> c)
alts2 Series m c
rs = do
Series m c
rs <- Series m c -> Series m (Series m c)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m c
rs
Series m (a -> b -> c)
-> Series m (a -> b -> c) -> Series m (a -> b -> c)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked
(Series m (b -> c) -> Series m (a -> b -> c)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (b -> c) -> Series m (a -> b -> c))
-> Series m (b -> c) -> Series m (a -> b -> c)
forall a b. (a -> b) -> a -> b
$ Series m c -> Series m (b -> c)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m c
rs)
(Series m (b -> c) -> Series m (a -> b -> c)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (b -> c) -> Series m (a -> b -> c))
-> Series m (b -> c) -> Series m (a -> b -> c)
forall a b. (a -> b) -> a -> b
$ Series m c -> Series m (b -> c)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m c
rs)
alts3 :: (CoSerial m a, CoSerial m b, CoSerial m c) =>
Series m d -> Series m (a->b->c->d)
alts3 :: Series m d -> Series m (a -> b -> c -> d)
alts3 Series m d
rs = do
Series m d
rs <- Series m d -> Series m (Series m d)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m d
rs
Series m (a -> b -> c -> d)
-> Series m (a -> b -> c -> d) -> Series m (a -> b -> c -> d)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked
(Series m (b -> c -> d) -> Series m (a -> b -> c -> d)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (b -> c -> d) -> Series m (a -> b -> c -> d))
-> Series m (b -> c -> d) -> Series m (a -> b -> c -> d)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d) -> Series m (b -> c -> d)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (c -> d) -> Series m (b -> c -> d))
-> Series m (c -> d) -> Series m (b -> c -> d)
forall a b. (a -> b) -> a -> b
$ Series m d -> Series m (c -> d)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m d
rs)
(Series m (b -> c -> d) -> Series m (a -> b -> c -> d)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (b -> c -> d) -> Series m (a -> b -> c -> d))
-> Series m (b -> c -> d) -> Series m (a -> b -> c -> d)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d) -> Series m (b -> c -> d)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (c -> d) -> Series m (b -> c -> d))
-> Series m (c -> d) -> Series m (b -> c -> d)
forall a b. (a -> b) -> a -> b
$ Series m d -> Series m (c -> d)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m d
rs)
alts4 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) =>
Series m e -> Series m (a->b->c->d->e)
alts4 :: Series m e -> Series m (a -> b -> c -> d -> e)
alts4 Series m e
rs = do
Series m e
rs <- Series m e -> Series m (Series m e)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m e
rs
Series m (a -> b -> c -> d -> e)
-> Series m (a -> b -> c -> d -> e)
-> Series m (a -> b -> c -> d -> e)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked
(Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e))
-> Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e) -> Series m (b -> c -> d -> e)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (c -> d -> e) -> Series m (b -> c -> d -> e))
-> Series m (c -> d -> e) -> Series m (b -> c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e) -> Series m (c -> d -> e)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (d -> e) -> Series m (c -> d -> e))
-> Series m (d -> e) -> Series m (c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m e -> Series m (d -> e)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m e
rs)
(Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e))
-> Series m (b -> c -> d -> e) -> Series m (a -> b -> c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e) -> Series m (b -> c -> d -> e)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (c -> d -> e) -> Series m (b -> c -> d -> e))
-> Series m (c -> d -> e) -> Series m (b -> c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e) -> Series m (c -> d -> e)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (d -> e) -> Series m (c -> d -> e))
-> Series m (d -> e) -> Series m (c -> d -> e)
forall a b. (a -> b) -> a -> b
$ Series m e -> Series m (d -> e)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m e
rs)
alts5 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d, CoSerial m e) =>
Series m f -> Series m (a->b->c->d->e->f)
alts5 :: Series m f -> Series m (a -> b -> c -> d -> e -> f)
alts5 Series m f
rs = do
Series m f
rs <- Series m f -> Series m (Series m f)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m f
rs
Series m (a -> b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked
(Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f))
-> Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f))
-> Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e -> f) -> Series m (c -> d -> e -> f)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (d -> e -> f) -> Series m (c -> d -> e -> f))
-> Series m (d -> e -> f) -> Series m (c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (e -> f) -> Series m (d -> e -> f)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (e -> f) -> Series m (d -> e -> f))
-> Series m (e -> f) -> Series m (d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m f -> Series m (e -> f)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m f
rs)
(Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f))
-> Series m (b -> c -> d -> e -> f)
-> Series m (a -> b -> c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f))
-> Series m (c -> d -> e -> f) -> Series m (b -> c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e -> f) -> Series m (c -> d -> e -> f)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (d -> e -> f) -> Series m (c -> d -> e -> f))
-> Series m (d -> e -> f) -> Series m (c -> d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m (e -> f) -> Series m (d -> e -> f)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (e -> f) -> Series m (d -> e -> f))
-> Series m (e -> f) -> Series m (d -> e -> f)
forall a b. (a -> b) -> a -> b
$ Series m f -> Series m (e -> f)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m f
rs)
alts6 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d, CoSerial m e, CoSerial m f) =>
Series m g -> Series m (a->b->c->d->e->f->g)
alts6 :: Series m g -> Series m (a -> b -> c -> d -> e -> f -> g)
alts6 Series m g
rs = do
Series m g
rs <- Series m g -> Series m (Series m g)
forall (m :: * -> *) a. Series m a -> Series m (Series m a)
fixDepth Series m g
rs
Series m (a -> b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
forall (m :: * -> *) a. Series m a -> Series m a -> Series m a
decDepthChecked
(Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g))
-> Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g))
-> Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g))
-> Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (e -> f -> g) -> Series m (d -> e -> f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (e -> f -> g) -> Series m (d -> e -> f -> g))
-> Series m (e -> f -> g) -> Series m (d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (f -> g) -> Series m (e -> f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM (Series m (f -> g) -> Series m (e -> f -> g))
-> Series m (f -> g) -> Series m (e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m g -> Series m (f -> g)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m g
rs)
(Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g))
-> Series m (b -> c -> d -> e -> f -> g)
-> Series m (a -> b -> c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g))
-> Series m (c -> d -> e -> f -> g)
-> Series m (b -> c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g))
-> Series m (d -> e -> f -> g) -> Series m (c -> d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (e -> f -> g) -> Series m (d -> e -> f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (e -> f -> g) -> Series m (d -> e -> f -> g))
-> Series m (e -> f -> g) -> Series m (d -> e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m (f -> g) -> Series m (e -> f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m (f -> g) -> Series m (e -> f -> g))
-> Series m (f -> g) -> Series m (e -> f -> g)
forall a b. (a -> b) -> a -> b
$ Series m g -> Series m (f -> g)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m g
rs)
newtypeAlts :: CoSerial m a => Series m b -> Series m (a->b)
newtypeAlts :: Series m b -> Series m (a -> b)
newtypeAlts = Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
class GSerial m f where
gSeries :: Series m (f a)
class GCoSerial m f where
gCoseries :: Series m b -> Series m (f a -> b)
#if __GLASGOW_HASKELL__ >= 702
instance {-# OVERLAPPABLE #-} GSerial m f => GSerial m (M1 i c f) where
gSeries :: Series m (M1 i c f a)
gSeries = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f a -> M1 i c f a) -> Series m (f a) -> Series m (M1 i c f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (f a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries
{-# INLINE gSeries #-}
instance GCoSerial m f => GCoSerial m (M1 i c f) where
gCoseries :: Series m b -> Series m (M1 i c f a -> b)
gCoseries Series m b
rs = ((f a -> b) -> (M1 i c f a -> f a) -> M1 i c f a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. M1 i c f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1) ((f a -> b) -> M1 i c f a -> b)
-> Series m (f a -> b) -> Series m (M1 i c f a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (f a -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries Series m b
rs
{-# INLINE gCoseries #-}
instance Serial m c => GSerial m (K1 i c) where
gSeries :: Series m (K1 i c a)
gSeries = c -> K1 i c a
forall k i c (p :: k). c -> K1 i c p
K1 (c -> K1 i c a) -> Series m c -> Series m (K1 i c a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m c
forall (m :: * -> *) a. Serial m a => Series m a
series
{-# INLINE gSeries #-}
instance CoSerial m c => GCoSerial m (K1 i c) where
gCoseries :: Series m b -> Series m (K1 i c a -> b)
gCoseries Series m b
rs = ((c -> b) -> (K1 i c a -> c) -> K1 i c a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. K1 i c a -> c
forall i c k (p :: k). K1 i c p -> c
unK1) ((c -> b) -> K1 i c a -> b)
-> Series m (c -> b) -> Series m (K1 i c a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (c -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs
{-# INLINE gCoseries #-}
instance GSerial m U1 where
gSeries :: Series m (U1 a)
gSeries = U1 a -> Series m (U1 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
U1
{-# INLINE gSeries #-}
instance GCoSerial m U1 where
gCoseries :: Series m b -> Series m (U1 a -> b)
gCoseries Series m b
rs = Series m b -> Series m (U1 a -> b)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m b
rs
{-# INLINE gCoseries #-}
instance GSerial m V1 where
gSeries :: Series m (V1 a)
gSeries = Series m (V1 a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
{-# INLINE gSeries #-}
instance GCoSerial m V1 where
gCoseries :: Series m b -> Series m (V1 a -> b)
gCoseries = Series m (V1 a -> b) -> Series m b -> Series m (V1 a -> b)
forall a b. a -> b -> a
const (Series m (V1 a -> b) -> Series m b -> Series m (V1 a -> b))
-> Series m (V1 a -> b) -> Series m b -> Series m (V1 a -> b)
forall a b. (a -> b) -> a -> b
$ (V1 a -> b) -> Series m (V1 a -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (\V1 a
a -> V1 a
a V1 a -> b -> b
`seq` let x :: t
x = t
x in b
forall t. t
x)
{-# INLINE gCoseries #-}
instance (Monad m, GSerial m a, GSerial m b) => GSerial m (a :*: b) where
gSeries :: Series m ((:*:) a b a)
gSeries = a a -> b a -> (:*:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (a a -> b a -> (:*:) a b a)
-> Series m (a a) -> Series m (b a -> (:*:) a b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (a a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries Series m (b a -> (:*:) a b a)
-> Series m (b a) -> Series m ((:*:) a b a)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m (b a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries
{-# INLINE gSeries #-}
instance (Monad m, GCoSerial m a, GCoSerial m b) => GCoSerial m (a :*: b) where
gCoseries :: Series m b -> Series m ((:*:) a b a -> b)
gCoseries Series m b
rs = (a a -> b a -> b) -> (:*:) a b a -> b
forall (f :: * -> *) p (g :: * -> *) t.
(f p -> g p -> t) -> (:*:) f g p -> t
uncur ((a a -> b a -> b) -> (:*:) a b a -> b)
-> Series m (a a -> b a -> b) -> Series m ((:*:) a b a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (b a -> b) -> Series m (a a -> b a -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries (Series m b -> Series m (b a -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries Series m b
rs)
where
uncur :: (f p -> g p -> t) -> (:*:) f g p -> t
uncur f p -> g p -> t
f (f p
x :*: g p
y) = f p -> g p -> t
f f p
x g p
y
{-# INLINE gCoseries #-}
instance (Monad m, GSerial m a, GSerial m b) => GSerial m (a :+: b) where
gSeries :: Series m ((:+:) a b a)
gSeries = (a a -> (:+:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (a a -> (:+:) a b a) -> Series m (a a) -> Series m ((:+:) a b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (a a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries) Series m ((:+:) a b a)
-> Series m ((:+:) a b a) -> Series m ((:+:) a b a)
forall (m :: * -> *) a. MonadLogic m => m a -> m a -> m a
`interleave` (b a -> (:+:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (b a -> (:+:) a b a) -> Series m (b a) -> Series m ((:+:) a b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (b a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries)
{-# INLINE gSeries #-}
instance (Monad m, GCoSerial m a, GCoSerial m b) => GCoSerial m (a :+: b) where
gCoseries :: Series m b -> Series m ((:+:) a b a -> b)
gCoseries Series m b
rs =
Series m b -> Series m (a a -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries Series m b
rs Series m (a a -> b)
-> ((a a -> b) -> Series m ((:+:) a b a -> b))
-> Series m ((:+:) a b a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \a a -> b
f ->
Series m b -> Series m (b a -> b)
forall (m :: * -> *) (f :: * -> *) b a.
GCoSerial m f =>
Series m b -> Series m (f a -> b)
gCoseries Series m b
rs Series m (b a -> b)
-> ((b a -> b) -> Series m ((:+:) a b a -> b))
-> Series m ((:+:) a b a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b a -> b
g ->
((:+:) a b a -> b) -> Series m ((:+:) a b a -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (((:+:) a b a -> b) -> Series m ((:+:) a b a -> b))
-> ((:+:) a b a -> b) -> Series m ((:+:) a b a -> b)
forall a b. (a -> b) -> a -> b
$
\(:+:) a b a
e -> case (:+:) a b a
e of
L1 a a
x -> a a -> b
f a a
x
R1 b a
y -> b a -> b
g b a
y
{-# INLINE gCoseries #-}
instance {-# OVERLAPPING #-} GSerial m f => GSerial m (C1 c f) where
gSeries :: Series m (C1 c f a)
gSeries = f a -> C1 c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f a -> C1 c f a) -> Series m (f a) -> Series m (C1 c f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (f a) -> Series m (f a)
forall (m :: * -> *) a. Series m a -> Series m a
decDepth Series m (f a)
forall (m :: * -> *) (f :: * -> *) a. GSerial m f => Series m (f a)
gSeries
{-# INLINE gSeries #-}
#endif
instance Monad m => Serial m () where
series :: Series m ()
series = () -> Series m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance Monad m => CoSerial m () where
coseries :: Series m b -> Series m (() -> b)
coseries Series m b
rs = Series m b -> Series m (() -> b)
forall (m :: * -> *) b a. Monad m => m b -> m (a -> b)
constM Series m b
rs
instance Monad m => Serial m Integer where series :: Series m Integer
series = M Integer -> Integer
forall a. M a -> a
unM (M Integer -> Integer) -> Series m (M Integer) -> Series m Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Integer)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Integer where coseries :: Series m b -> Series m (Integer -> b)
coseries = ((M Integer -> b) -> Integer -> b)
-> Series m (M Integer -> b) -> Series m (Integer -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Integer -> b) -> (Integer -> M Integer) -> Integer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> M Integer
forall a. a -> M a
M) (Series m (M Integer -> b) -> Series m (Integer -> b))
-> (Series m b -> Series m (M Integer -> b))
-> Series m b
-> Series m (Integer -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Integer -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Natural where series :: Series m Natural
series = N Natural -> Natural
forall a. N a -> a
unN (N Natural -> Natural) -> Series m (N Natural) -> Series m Natural
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Natural)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Natural where coseries :: Series m b -> Series m (Natural -> b)
coseries = ((N Natural -> b) -> Natural -> b)
-> Series m (N Natural -> b) -> Series m (Natural -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Natural -> b) -> (Natural -> N Natural) -> Natural -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> N Natural
forall a. a -> N a
N) (Series m (N Natural -> b) -> Series m (Natural -> b))
-> (Series m b -> Series m (N Natural -> b))
-> Series m b
-> Series m (Natural -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Natural -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Int where series :: Series m Depth
series = M Depth -> Depth
forall a. M a -> a
unM (M Depth -> Depth) -> Series m (M Depth) -> Series m Depth
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Depth)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Int where coseries :: Series m b -> Series m (Depth -> b)
coseries = ((M Depth -> b) -> Depth -> b)
-> Series m (M Depth -> b) -> Series m (Depth -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Depth -> b) -> (Depth -> M Depth) -> Depth -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Depth -> M Depth
forall a. a -> M a
M) (Series m (M Depth -> b) -> Series m (Depth -> b))
-> (Series m b -> Series m (M Depth -> b))
-> Series m b
-> Series m (Depth -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Depth -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Word where series :: Series m Word
series = N Word -> Word
forall a. N a -> a
unN (N Word -> Word) -> Series m (N Word) -> Series m Word
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Word)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Word where coseries :: Series m b -> Series m (Word -> b)
coseries = ((N Word -> b) -> Word -> b)
-> Series m (N Word -> b) -> Series m (Word -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Word -> b) -> (Word -> N Word) -> Word -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> N Word
forall a. a -> N a
N) (Series m (N Word -> b) -> Series m (Word -> b))
-> (Series m b -> Series m (N Word -> b))
-> Series m b
-> Series m (Word -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Word -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Int8 where series :: Series m Int8
series = M Int8 -> Int8
forall a. M a -> a
unM (M Int8 -> Int8) -> Series m (M Int8) -> Series m Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Int8)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Int8 where coseries :: Series m b -> Series m (Int8 -> b)
coseries = ((M Int8 -> b) -> Int8 -> b)
-> Series m (M Int8 -> b) -> Series m (Int8 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Int8 -> b) -> (Int8 -> M Int8) -> Int8 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> M Int8
forall a. a -> M a
M) (Series m (M Int8 -> b) -> Series m (Int8 -> b))
-> (Series m b -> Series m (M Int8 -> b))
-> Series m b
-> Series m (Int8 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Int8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Word8 where series :: Series m Word8
series = N Word8 -> Word8
forall a. N a -> a
unN (N Word8 -> Word8) -> Series m (N Word8) -> Series m Word8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Word8)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Word8 where coseries :: Series m b -> Series m (Word8 -> b)
coseries = ((N Word8 -> b) -> Word8 -> b)
-> Series m (N Word8 -> b) -> Series m (Word8 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Word8 -> b) -> (Word8 -> N Word8) -> Word8 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> N Word8
forall a. a -> N a
N) (Series m (N Word8 -> b) -> Series m (Word8 -> b))
-> (Series m b -> Series m (N Word8 -> b))
-> Series m b
-> Series m (Word8 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Word8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Int16 where series :: Series m Int16
series = M Int16 -> Int16
forall a. M a -> a
unM (M Int16 -> Int16) -> Series m (M Int16) -> Series m Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Int16)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Int16 where coseries :: Series m b -> Series m (Int16 -> b)
coseries = ((M Int16 -> b) -> Int16 -> b)
-> Series m (M Int16 -> b) -> Series m (Int16 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Int16 -> b) -> (Int16 -> M Int16) -> Int16 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> M Int16
forall a. a -> M a
M) (Series m (M Int16 -> b) -> Series m (Int16 -> b))
-> (Series m b -> Series m (M Int16 -> b))
-> Series m b
-> Series m (Int16 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Int16 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Word16 where series :: Series m Word16
series = N Word16 -> Word16
forall a. N a -> a
unN (N Word16 -> Word16) -> Series m (N Word16) -> Series m Word16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Word16)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Word16 where coseries :: Series m b -> Series m (Word16 -> b)
coseries = ((N Word16 -> b) -> Word16 -> b)
-> Series m (N Word16 -> b) -> Series m (Word16 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Word16 -> b) -> (Word16 -> N Word16) -> Word16 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> N Word16
forall a. a -> N a
N) (Series m (N Word16 -> b) -> Series m (Word16 -> b))
-> (Series m b -> Series m (N Word16 -> b))
-> Series m b
-> Series m (Word16 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Word16 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Int32 where series :: Series m Int32
series = M Int32 -> Int32
forall a. M a -> a
unM (M Int32 -> Int32) -> Series m (M Int32) -> Series m Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Int32)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Int32 where coseries :: Series m b -> Series m (Int32 -> b)
coseries = ((M Int32 -> b) -> Int32 -> b)
-> Series m (M Int32 -> b) -> Series m (Int32 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Int32 -> b) -> (Int32 -> M Int32) -> Int32 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> M Int32
forall a. a -> M a
M) (Series m (M Int32 -> b) -> Series m (Int32 -> b))
-> (Series m b -> Series m (M Int32 -> b))
-> Series m b
-> Series m (Int32 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Int32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Word32 where series :: Series m Word32
series = N Word32 -> Word32
forall a. N a -> a
unN (N Word32 -> Word32) -> Series m (N Word32) -> Series m Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Word32)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Word32 where coseries :: Series m b -> Series m (Word32 -> b)
coseries = ((N Word32 -> b) -> Word32 -> b)
-> Series m (N Word32 -> b) -> Series m (Word32 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Word32 -> b) -> (Word32 -> N Word32) -> Word32 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> N Word32
forall a. a -> N a
N) (Series m (N Word32 -> b) -> Series m (Word32 -> b))
-> (Series m b -> Series m (N Word32 -> b))
-> Series m b
-> Series m (Word32 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Word32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Int64 where series :: Series m Int64
series = M Int64 -> Int64
forall a. M a -> a
unM (M Int64 -> Int64) -> Series m (M Int64) -> Series m Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (M Int64)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Int64 where coseries :: Series m b -> Series m (Int64 -> b)
coseries = ((M Int64 -> b) -> Int64 -> b)
-> Series m (M Int64 -> b) -> Series m (Int64 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((M Int64 -> b) -> (Int64 -> M Int64) -> Int64 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> M Int64
forall a. a -> M a
M) (Series m (M Int64 -> b) -> Series m (Int64 -> b))
-> (Series m b -> Series m (M Int64 -> b))
-> Series m b
-> Series m (Int64 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (M Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
instance Monad m => Serial m Word64 where series :: Series m Word64
series = N Word64 -> Word64
forall a. N a -> a
unN (N Word64 -> Word64) -> Series m (N Word64) -> Series m Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (N Word64)
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Word64 where coseries :: Series m b -> Series m (Word64 -> b)
coseries = ((N Word64 -> b) -> Word64 -> b)
-> Series m (N Word64 -> b) -> Series m (Word64 -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((N Word64 -> b) -> (Word64 -> N Word64) -> Word64 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> N Word64
forall a. a -> N a
N) (Series m (N Word64 -> b) -> Series m (Word64 -> b))
-> (Series m b -> Series m (N Word64 -> b))
-> Series m b
-> Series m (Word64 -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (N Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
newtype N a = N { N a -> a
unN :: a } deriving (N a -> N a -> Bool
(N a -> N a -> Bool) -> (N a -> N a -> Bool) -> Eq (N a)
forall a. Eq a => N a -> N a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: N a -> N a -> Bool
$c/= :: forall a. Eq a => N a -> N a -> Bool
== :: N a -> N a -> Bool
$c== :: forall a. Eq a => N a -> N a -> Bool
Eq, Eq (N a)
Eq (N a)
-> (N a -> N a -> Ordering)
-> (N a -> N a -> Bool)
-> (N a -> N a -> Bool)
-> (N a -> N a -> Bool)
-> (N a -> N a -> Bool)
-> (N a -> N a -> N a)
-> (N a -> N a -> N a)
-> Ord (N a)
N a -> N a -> Bool
N a -> N a -> Ordering
N a -> N a -> N 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 a. Ord a => Eq (N a)
forall a. Ord a => N a -> N a -> Bool
forall a. Ord a => N a -> N a -> Ordering
forall a. Ord a => N a -> N a -> N a
min :: N a -> N a -> N a
$cmin :: forall a. Ord a => N a -> N a -> N a
max :: N a -> N a -> N a
$cmax :: forall a. Ord a => N a -> N a -> N a
>= :: N a -> N a -> Bool
$c>= :: forall a. Ord a => N a -> N a -> Bool
> :: N a -> N a -> Bool
$c> :: forall a. Ord a => N a -> N a -> Bool
<= :: N a -> N a -> Bool
$c<= :: forall a. Ord a => N a -> N a -> Bool
< :: N a -> N a -> Bool
$c< :: forall a. Ord a => N a -> N a -> Bool
compare :: N a -> N a -> Ordering
$ccompare :: forall a. Ord a => N a -> N a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (N a)
Ord, Depth -> N a -> ShowS
[N a] -> ShowS
N a -> String
(Depth -> N a -> ShowS)
-> (N a -> String) -> ([N a] -> ShowS) -> Show (N a)
forall a. Show a => Depth -> N a -> ShowS
forall a. Show a => [N a] -> ShowS
forall a. Show a => N a -> String
forall a.
(Depth -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [N a] -> ShowS
$cshowList :: forall a. Show a => [N a] -> ShowS
show :: N a -> String
$cshow :: forall a. Show a => N a -> String
showsPrec :: Depth -> N a -> ShowS
$cshowsPrec :: forall a. Show a => Depth -> N a -> ShowS
Show)
instance Real a => Real (N a) where
toRational :: N a -> Rational
toRational (N a
x) = a -> Rational
forall a. Real a => a -> Rational
toRational a
x
instance Enum a => Enum (N a) where
toEnum :: Depth -> N a
toEnum Depth
x = a -> N a
forall a. a -> N a
N (Depth -> a
forall a. Enum a => Depth -> a
toEnum Depth
x)
fromEnum :: N a -> Depth
fromEnum (N a
x) = a -> Depth
forall a. Enum a => a -> Depth
fromEnum a
x
instance Num a => Num (N a) where
N a
x + :: N a -> N a -> N a
+ N a
y = a -> N a
forall a. a -> N a
N (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y)
N a
x * :: N a -> N a -> N a
* N a
y = a -> N a
forall a. a -> N a
N (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
negate :: N a -> N a
negate (N a
x) = a -> N a
forall a. a -> N a
N (a -> a
forall a. Num a => a -> a
negate a
x)
abs :: N a -> N a
abs (N a
x) = a -> N a
forall a. a -> N a
N (a -> a
forall a. Num a => a -> a
abs a
x)
signum :: N a -> N a
signum (N a
x) = a -> N a
forall a. a -> N a
N (a -> a
forall a. Num a => a -> a
signum a
x)
fromInteger :: Integer -> N a
fromInteger Integer
x = a -> N a
forall a. a -> N a
N (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x)
instance Integral a => Integral (N a) where
quotRem :: N a -> N a -> (N a, N a)
quotRem (N a
x) (N a
y) = (a -> N a
forall a. a -> N a
N a
q, a -> N a
forall a. a -> N a
N a
r)
where
(a
q, a
r) = a
x a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
y
toInteger :: N a -> Integer
toInteger (N a
x) = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x
instance (Num a, Enum a, Serial m a) => Serial m (N a) where
series :: Series m (N a)
series = (Depth -> [N a]) -> Series m (N a)
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [N a]) -> Series m (N a))
-> (Depth -> [N a]) -> Series m (N a)
forall a b. (a -> b) -> a -> b
$ \Depth
d -> Depth -> [N a] -> [N a]
forall a. Depth -> [a] -> [a]
take (Depth
dDepth -> Depth -> Depth
forall a. Num a => a -> a -> a
+Depth
1) [N a
0..]
instance (Integral a, Monad m) => CoSerial m (N a) where
coseries :: Series m b -> Series m (N a -> b)
coseries Series m b
rs =
Series m b -> Series m b
forall (m :: * -> *) a. Series m a -> Series m a
alts0 Series m b
rs Series m b -> (b -> Series m (N a -> b)) -> Series m (N a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
z ->
Series m b -> Series m (N a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs Series m (N a -> b)
-> ((N a -> b) -> Series m (N a -> b)) -> Series m (N a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \N a -> b
f ->
(N a -> b) -> Series m (N a -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((N a -> b) -> Series m (N a -> b))
-> (N a -> b) -> Series m (N a -> b)
forall a b. (a -> b) -> a -> b
$ \(N a
i) ->
if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0
then N a -> b
f (a -> N a
forall a. a -> N a
N (a -> N a) -> a -> N a
forall a b. (a -> b) -> a -> b
$ a
ia -> a -> a
forall a. Num a => a -> a -> a
-a
1)
else b
z
newtype M a = M { M a -> a
unM :: a } deriving (M a -> M a -> Bool
(M a -> M a -> Bool) -> (M a -> M a -> Bool) -> Eq (M a)
forall a. Eq a => M a -> M a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: M a -> M a -> Bool
$c/= :: forall a. Eq a => M a -> M a -> Bool
== :: M a -> M a -> Bool
$c== :: forall a. Eq a => M a -> M a -> Bool
Eq, Eq (M a)
Eq (M a)
-> (M a -> M a -> Ordering)
-> (M a -> M a -> Bool)
-> (M a -> M a -> Bool)
-> (M a -> M a -> Bool)
-> (M a -> M a -> Bool)
-> (M a -> M a -> M a)
-> (M a -> M a -> M a)
-> Ord (M a)
M a -> M a -> Bool
M a -> M a -> Ordering
M a -> M a -> M 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 a. Ord a => Eq (M a)
forall a. Ord a => M a -> M a -> Bool
forall a. Ord a => M a -> M a -> Ordering
forall a. Ord a => M a -> M a -> M a
min :: M a -> M a -> M a
$cmin :: forall a. Ord a => M a -> M a -> M a
max :: M a -> M a -> M a
$cmax :: forall a. Ord a => M a -> M a -> M a
>= :: M a -> M a -> Bool
$c>= :: forall a. Ord a => M a -> M a -> Bool
> :: M a -> M a -> Bool
$c> :: forall a. Ord a => M a -> M a -> Bool
<= :: M a -> M a -> Bool
$c<= :: forall a. Ord a => M a -> M a -> Bool
< :: M a -> M a -> Bool
$c< :: forall a. Ord a => M a -> M a -> Bool
compare :: M a -> M a -> Ordering
$ccompare :: forall a. Ord a => M a -> M a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (M a)
Ord, Depth -> M a -> ShowS
[M a] -> ShowS
M a -> String
(Depth -> M a -> ShowS)
-> (M a -> String) -> ([M a] -> ShowS) -> Show (M a)
forall a. Show a => Depth -> M a -> ShowS
forall a. Show a => [M a] -> ShowS
forall a. Show a => M a -> String
forall a.
(Depth -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [M a] -> ShowS
$cshowList :: forall a. Show a => [M a] -> ShowS
show :: M a -> String
$cshow :: forall a. Show a => M a -> String
showsPrec :: Depth -> M a -> ShowS
$cshowsPrec :: forall a. Show a => Depth -> M a -> ShowS
Show)
instance Real a => Real (M a) where
toRational :: M a -> Rational
toRational (M a
x) = a -> Rational
forall a. Real a => a -> Rational
toRational a
x
instance Enum a => Enum (M a) where
toEnum :: Depth -> M a
toEnum Depth
x = a -> M a
forall a. a -> M a
M (Depth -> a
forall a. Enum a => Depth -> a
toEnum Depth
x)
fromEnum :: M a -> Depth
fromEnum (M a
x) = a -> Depth
forall a. Enum a => a -> Depth
fromEnum a
x
instance Num a => Num (M a) where
M a
x + :: M a -> M a -> M a
+ M a
y = a -> M a
forall a. a -> M a
M (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y)
M a
x * :: M a -> M a -> M a
* M a
y = a -> M a
forall a. a -> M a
M (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
negate :: M a -> M a
negate (M a
x) = a -> M a
forall a. a -> M a
M (a -> a
forall a. Num a => a -> a
negate a
x)
abs :: M a -> M a
abs (M a
x) = a -> M a
forall a. a -> M a
M (a -> a
forall a. Num a => a -> a
abs a
x)
signum :: M a -> M a
signum (M a
x) = a -> M a
forall a. a -> M a
M (a -> a
forall a. Num a => a -> a
signum a
x)
fromInteger :: Integer -> M a
fromInteger Integer
x = a -> M a
forall a. a -> M a
M (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x)
instance Integral a => Integral (M a) where
quotRem :: M a -> M a -> (M a, M a)
quotRem (M a
x) (M a
y) = (a -> M a
forall a. a -> M a
M a
q, a -> M a
forall a. a -> M a
M a
r)
where
(a
q, a
r) = a
x a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
y
toInteger :: M a -> Integer
toInteger (M a
x) = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x
instance (Num a, Enum a, Monad m) => Serial m (M a) where
series :: Series m (M a)
series = Series m (M a)
forall (m :: * -> *). Series m (M a)
others Series m (M a) -> Series m (M a) -> Series m (M a)
forall (m :: * -> *) a. MonadLogic m => m a -> m a -> m a
`interleave` Series m (M a)
forall (m :: * -> *). Series m (M a)
positives
where positives :: Series m (M a)
positives = (Depth -> [M a]) -> Series m (M a)
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [M a]) -> Series m (M a))
-> (Depth -> [M a]) -> Series m (M a)
forall a b. (a -> b) -> a -> b
$ \Depth
d -> Depth -> [M a] -> [M a]
forall a. Depth -> [a] -> [a]
take Depth
d [M a
1..]
others :: Series m (M a)
others = (Depth -> [M a]) -> Series m (M a)
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [M a]) -> Series m (M a))
-> (Depth -> [M a]) -> Series m (M a)
forall a b. (a -> b) -> a -> b
$ \Depth
d -> Depth -> [M a] -> [M a]
forall a. Depth -> [a] -> [a]
take (Depth
dDepth -> Depth -> Depth
forall a. Num a => a -> a -> a
+Depth
1) [M a
0,-M a
1..]
instance (Ord a, Num a, Monad m) => CoSerial m (M a) where
coseries :: Series m b -> Series m (M a -> b)
coseries Series m b
rs =
Series m b -> Series m b
forall (m :: * -> *) a. Series m a -> Series m a
alts0 Series m b
rs Series m b -> (b -> Series m (M a -> b)) -> Series m (M a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
z ->
Series m b -> Series m (M (M a) -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs Series m (M (M a) -> b)
-> ((M (M a) -> b) -> Series m (M a -> b)) -> Series m (M a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \M (M a) -> b
f ->
Series m b -> Series m (M (M a) -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs Series m (M (M a) -> b)
-> ((M (M a) -> b) -> Series m (M a -> b)) -> Series m (M a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \M (M a) -> b
g ->
(M a -> b) -> Series m (M a -> b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((M a -> b) -> Series m (M a -> b))
-> (M a -> b) -> Series m (M a -> b)
forall a b. (a -> b) -> a -> b
$ \ M a
i -> case M a -> M a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare M a
i M a
0 of
Ordering
GT -> M (M a) -> b
f (M a -> M (M a)
forall a. a -> M a
M (M a
i M a -> M a -> M a
forall a. Num a => a -> a -> a
- M a
1))
Ordering
LT -> M (M a) -> b
g (M a -> M (M a)
forall a. a -> M a
M (M a -> M a
forall a. Num a => a -> a
abs M a
i M a -> M a -> M a
forall a. Num a => a -> a -> a
- M a
1))
Ordering
EQ -> b
z
instance Monad m => Serial m Float where
series :: Series m Float
series =
Series m (Integer, Depth)
forall (m :: * -> *) a. Serial m a => Series m a
series Series m (Integer, Depth)
-> ((Integer, Depth) -> Series m Float) -> Series m Float
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \(Integer
sig, Depth
exp) ->
Bool -> Series m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Integer -> Bool
forall a. Integral a => a -> Bool
odd Integer
sig Bool -> Bool -> Bool
|| Integer
sigInteger -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==Integer
0 Bool -> Bool -> Bool
&& Depth
expDepth -> Depth -> Bool
forall a. Eq a => a -> a -> Bool
==Depth
0) Series m () -> Series m Float -> Series m Float
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Float -> Series m Float
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> Depth -> Float
forall a. RealFloat a => Integer -> Depth -> a
encodeFloat Integer
sig Depth
exp)
instance Monad m => CoSerial m Float where
coseries :: Series m b -> Series m (Float -> b)
coseries Series m b
rs =
Series m b -> Series m ((Integer, Depth) -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs Series m ((Integer, Depth) -> b)
-> (((Integer, Depth) -> b) -> Series m (Float -> b))
-> Series m (Float -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \(Integer, Depth) -> b
f ->
(Float -> b) -> Series m (Float -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Float -> b) -> Series m (Float -> b))
-> (Float -> b) -> Series m (Float -> b)
forall a b. (a -> b) -> a -> b
$ (Integer, Depth) -> b
f ((Integer, Depth) -> b)
-> (Float -> (Integer, Depth)) -> Float -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> (Integer, Depth)
forall a. RealFloat a => a -> (Integer, Depth)
decodeFloat
instance Monad m => Serial m Double where
series :: Series m Double
series = (Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Float -> Double) (Float -> Double) -> Series m Float -> Series m Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m Float
forall (m :: * -> *) a. Serial m a => Series m a
series
instance Monad m => CoSerial m Double where
coseries :: Series m b -> Series m (Double -> b)
coseries Series m b
rs =
((Float -> b) -> (Double -> Float) -> Double -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Double -> Float)) ((Float -> b) -> Double -> b)
-> Series m (Float -> b) -> Series m (Double -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (Float -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs
instance (Integral i, Serial m i) => Serial m (Ratio i) where
series :: Series m (Ratio i)
series = (i, Positive i) -> Ratio i
forall a. Integral a => (a, Positive a) -> Ratio a
pairToRatio ((i, Positive i) -> Ratio i)
-> Series m (i, Positive i) -> Series m (Ratio i)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (i, Positive i)
forall (m :: * -> *) a. Serial m a => Series m a
series
where
pairToRatio :: (a, Positive a) -> Ratio a
pairToRatio (a
n, Positive a
d) = a
n a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% a
d
instance (Integral i, CoSerial m i) => CoSerial m (Ratio i) where
coseries :: Series m b -> Series m (Ratio i -> b)
coseries Series m b
rs = (((i, i) -> b) -> (Ratio i -> (i, i)) -> Ratio i -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio i -> (i, i)
forall b. Ratio b -> (b, b)
ratioToPair) (((i, i) -> b) -> Ratio i -> b)
-> Series m ((i, i) -> b) -> Series m (Ratio i -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m ((i, i) -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs
where
ratioToPair :: Ratio b -> (b, b)
ratioToPair Ratio b
r = (Ratio b -> b
forall a. Ratio a -> a
numerator Ratio b
r, Ratio b -> b
forall a. Ratio a -> a
denominator Ratio b
r)
instance Monad m => Serial m Char where
series :: Series m Char
series = (Depth -> String) -> Series m Char
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> String) -> Series m Char)
-> (Depth -> String) -> Series m Char
forall a b. (a -> b) -> a -> b
$ \Depth
d -> Depth -> ShowS
forall a. Depth -> [a] -> [a]
take (Depth
dDepth -> Depth -> Depth
forall a. Num a => a -> a -> a
+Depth
1) [Char
'a'..Char
'z']
instance Monad m => CoSerial m Char where
coseries :: Series m b -> Series m (Char -> b)
coseries Series m b
rs =
Series m b -> Series m (N Depth -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
rs Series m (N Depth -> b)
-> ((N Depth -> b) -> Series m (Char -> b)) -> Series m (Char -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \N Depth -> b
f ->
(Char -> b) -> Series m (Char -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Char -> b) -> Series m (Char -> b))
-> (Char -> b) -> Series m (Char -> b)
forall a b. (a -> b) -> a -> b
$ \Char
c -> N Depth -> b
f (Depth -> N Depth
forall a. a -> N a
N (Char -> Depth
forall a. Enum a => a -> Depth
fromEnum Char
c Depth -> Depth -> Depth
forall a. Num a => a -> a -> a
- Char -> Depth
forall a. Enum a => a -> Depth
fromEnum Char
'a'))
instance (Serial m a, Serial m b) => Serial m (a,b) where
series :: Series m (a, b)
series = (a -> b -> (a, b)) -> Series m (a, b)
forall (m :: * -> *) a b c.
(Serial m a, Serial m b) =>
(a -> b -> c) -> Series m c
cons2 (,)
instance (CoSerial m a, CoSerial m b) => CoSerial m (a,b) where
coseries :: Series m b -> Series m ((a, b) -> b)
coseries Series m b
rs = (a -> b -> b) -> (a, b) -> b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((a -> b -> b) -> (a, b) -> b)
-> Series m (a -> b -> b) -> Series m ((a, b) -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b -> b)
forall (m :: * -> *) a b c.
(CoSerial m a, CoSerial m b) =>
Series m c -> Series m (a -> b -> c)
alts2 Series m b
rs
instance (Serial m a, Serial m b, Serial m c) => Serial m (a,b,c) where
series :: Series m (a, b, c)
series = (a -> b -> c -> (a, b, c)) -> Series m (a, b, c)
forall (m :: * -> *) a b c d.
(Serial m a, Serial m b, Serial m c) =>
(a -> b -> c -> d) -> Series m d
cons3 (,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c) => CoSerial m (a,b,c) where
coseries :: Series m b -> Series m ((a, b, c) -> b)
coseries Series m b
rs = (a -> b -> c -> b) -> (a, b, c) -> b
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 ((a -> b -> c -> b) -> (a, b, c) -> b)
-> Series m (a -> b -> c -> b) -> Series m ((a, b, c) -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b -> c -> b)
forall (m :: * -> *) a b c d.
(CoSerial m a, CoSerial m b, CoSerial m c) =>
Series m d -> Series m (a -> b -> c -> d)
alts3 Series m b
rs
instance (Serial m a, Serial m b, Serial m c, Serial m d) => Serial m (a,b,c,d) where
series :: Series m (a, b, c, d)
series = (a -> b -> c -> d -> (a, b, c, d)) -> Series m (a, b, c, d)
forall (m :: * -> *) a b c d e.
(Serial m a, Serial m b, Serial m c, Serial m d) =>
(a -> b -> c -> d -> e) -> Series m e
cons4 (,,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) => CoSerial m (a,b,c,d) where
coseries :: Series m b -> Series m ((a, b, c, d) -> b)
coseries Series m b
rs = (a -> b -> c -> d -> b) -> (a, b, c, d) -> b
forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 ((a -> b -> c -> d -> b) -> (a, b, c, d) -> b)
-> Series m (a -> b -> c -> d -> b) -> Series m ((a, b, c, d) -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b -> c -> d -> b)
forall (m :: * -> *) a b c d e.
(CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) =>
Series m e -> Series m (a -> b -> c -> d -> e)
alts4 Series m b
rs
instance (Serial m a, Serial m b, Serial m c, Serial m d, Serial m e) => Serial m (a,b,c,d,e) where
series :: Series m (a, b, c, d, e)
series = (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Series m (a, b, c, d, e)
forall (m :: * -> *) a b c d e f.
(Serial m a, Serial m b, Serial m c, Serial m d, Serial m e) =>
(a -> b -> c -> d -> e -> f) -> Series m f
cons5 (,,,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d, CoSerial m e) => CoSerial m (a,b,c,d,e) where
coseries :: Series m b -> Series m ((a, b, c, d, e) -> b)
coseries Series m b
rs = (a -> b -> c -> d -> e -> b) -> (a, b, c, d, e) -> b
forall a b c d e f.
(a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
uncurry5 ((a -> b -> c -> d -> e -> b) -> (a, b, c, d, e) -> b)
-> Series m (a -> b -> c -> d -> e -> b)
-> Series m ((a, b, c, d, e) -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b -> c -> d -> e -> b)
forall (m :: * -> *) a b c d e f.
(CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d,
CoSerial m e) =>
Series m f -> Series m (a -> b -> c -> d -> e -> f)
alts5 Series m b
rs
instance (Serial m a, Serial m b, Serial m c, Serial m d, Serial m e, Serial m f) => Serial m (a,b,c,d,e,f) where
series :: Series m (a, b, c, d, e, f)
series = (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Series m (a, b, c, d, e, f)
forall (m :: * -> *) a b c d e f g.
(Serial m a, Serial m b, Serial m c, Serial m d, Serial m e,
Serial m f) =>
(a -> b -> c -> d -> e -> f -> g) -> Series m g
cons6 (,,,,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d, CoSerial m e, CoSerial m f) => CoSerial m (a,b,c,d,e,f) where
coseries :: Series m b -> Series m ((a, b, c, d, e, f) -> b)
coseries Series m b
rs = (a -> b -> c -> d -> e -> f -> b) -> (a, b, c, d, e, f) -> b
forall a b c d e f g.
(a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
uncurry6 ((a -> b -> c -> d -> e -> f -> b) -> (a, b, c, d, e, f) -> b)
-> Series m (a -> b -> c -> d -> e -> f -> b)
-> Series m ((a, b, c, d, e, f) -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b -> c -> d -> e -> f -> b)
forall (m :: * -> *) a b c d e f g.
(CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d,
CoSerial m e, CoSerial m f) =>
Series m g -> Series m (a -> b -> c -> d -> e -> f -> g)
alts6 Series m b
rs
instance Monad m => Serial m Bool where
series :: Series m Bool
series = Bool -> Series m Bool
forall a (m :: * -> *). a -> Series m a
cons0 Bool
True Series m Bool -> Series m Bool -> Series m Bool
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ Bool -> Series m Bool
forall a (m :: * -> *). a -> Series m a
cons0 Bool
False
instance Monad m => CoSerial m Bool where
coseries :: Series m b -> Series m (Bool -> b)
coseries Series m b
rs =
Series m b
rs Series m b -> (b -> Series m (Bool -> b)) -> Series m (Bool -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
r1 ->
Series m b
rs Series m b -> (b -> Series m (Bool -> b)) -> Series m (Bool -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
r2 ->
(Bool -> b) -> Series m (Bool -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool -> b) -> Series m (Bool -> b))
-> (Bool -> b) -> Series m (Bool -> b)
forall a b. (a -> b) -> a -> b
$ \Bool
x -> if Bool
x then b
r1 else b
r2
instance Monad m => Serial m Ordering where
series :: Series m Ordering
series = Ordering -> Series m Ordering
forall a (m :: * -> *). a -> Series m a
cons0 Ordering
LT Series m Ordering -> Series m Ordering -> Series m Ordering
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ Ordering -> Series m Ordering
forall a (m :: * -> *). a -> Series m a
cons0 Ordering
EQ Series m Ordering -> Series m Ordering -> Series m Ordering
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ Ordering -> Series m Ordering
forall a (m :: * -> *). a -> Series m a
cons0 Ordering
GT
instance Monad m => CoSerial m Ordering where
coseries :: Series m b -> Series m (Ordering -> b)
coseries Series m b
rs =
Series m b
rs Series m b
-> (b -> Series m (Ordering -> b)) -> Series m (Ordering -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
r1 ->
Series m b
rs Series m b
-> (b -> Series m (Ordering -> b)) -> Series m (Ordering -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
r2 ->
Series m b
rs Series m b
-> (b -> Series m (Ordering -> b)) -> Series m (Ordering -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
r3 ->
(Ordering -> b) -> Series m (Ordering -> b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Ordering -> b) -> Series m (Ordering -> b))
-> (Ordering -> b) -> Series m (Ordering -> b)
forall a b. (a -> b) -> a -> b
$ \Ordering
x -> case Ordering
x of
Ordering
LT -> b
r1
Ordering
EQ -> b
r2
Ordering
GT -> b
r3
instance (Serial m a) => Serial m (Maybe a) where
series :: Series m (Maybe a)
series = Maybe a -> Series m (Maybe a)
forall a (m :: * -> *). a -> Series m a
cons0 Maybe a
forall a. Maybe a
Nothing Series m (Maybe a) -> Series m (Maybe a) -> Series m (Maybe a)
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ (a -> Maybe a) -> Series m (Maybe a)
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
cons1 a -> Maybe a
forall a. a -> Maybe a
Just
instance (CoSerial m a) => CoSerial m (Maybe a) where
coseries :: Series m b -> Series m (Maybe a -> b)
coseries Series m b
rs =
b -> (a -> b) -> Maybe a -> b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (b -> (a -> b) -> Maybe a -> b)
-> Series m b -> Series m ((a -> b) -> Maybe a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m b
forall (m :: * -> *) a. Series m a -> Series m a
alts0 Series m b
rs Series m ((a -> b) -> Maybe a -> b)
-> Series m (a -> b) -> Series m (Maybe a -> b)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs
instance (Serial m a, Serial m b) => Serial m (Either a b) where
series :: Series m (Either a b)
series = (a -> Either a b) -> Series m (Either a b)
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
cons1 a -> Either a b
forall a b. a -> Either a b
Left Series m (Either a b)
-> Series m (Either a b) -> Series m (Either a b)
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ (b -> Either a b) -> Series m (Either a b)
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
cons1 b -> Either a b
forall a b. b -> Either a b
Right
instance (CoSerial m a, CoSerial m b) => CoSerial m (Either a b) where
coseries :: Series m b -> Series m (Either a b -> b)
coseries Series m b
rs =
(a -> b) -> (b -> b) -> Either a b -> b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((a -> b) -> (b -> b) -> Either a b -> b)
-> Series m (a -> b) -> Series m ((b -> b) -> Either a b -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs Series m ((b -> b) -> Either a b -> b)
-> Series m (b -> b) -> Series m (Either a b -> b)
forall (m :: * -> *) a b.
Monad m =>
Series m (a -> b) -> Series m a -> Series m b
<~> Series m b -> Series m (b -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
alts1 Series m b
rs
instance Serial m a => Serial m [a] where
series :: Series m [a]
series = [a] -> Series m [a]
forall a (m :: * -> *). a -> Series m a
cons0 [] Series m [a] -> Series m [a] -> Series m [a]
forall (m :: * -> *) a.
Monad m =>
Series m a -> Series m a -> Series m a
\/ (a -> [a] -> [a]) -> Series m [a]
forall (m :: * -> *) a b c.
(Serial m a, Serial m b) =>
(a -> b -> c) -> Series m c
cons2 (:)
instance CoSerial m a => CoSerial m [a] where
coseries :: Series m b -> Series m ([a] -> b)
coseries Series m b
rs =
Series m b -> Series m b
forall (m :: * -> *) a. Series m a -> Series m a
alts0 Series m b
rs Series m b -> (b -> Series m ([a] -> b)) -> Series m ([a] -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \b
y ->
Series m b -> Series m (a -> [a] -> b)
forall (m :: * -> *) a b c.
(CoSerial m a, CoSerial m b) =>
Series m c -> Series m (a -> b -> c)
alts2 Series m b
rs Series m (a -> [a] -> b)
-> ((a -> [a] -> b) -> Series m ([a] -> b)) -> Series m ([a] -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \a -> [a] -> b
f ->
([a] -> b) -> Series m ([a] -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (([a] -> b) -> Series m ([a] -> b))
-> ([a] -> b) -> Series m ([a] -> b)
forall a b. (a -> b) -> a -> b
$ \[a]
xs -> case [a]
xs of [] -> b
y; a
x:[a]
xs' -> a -> [a] -> b
f a
x [a]
xs'
instance Serial m a => Serial m (NE.NonEmpty a) where
series :: Series m (NonEmpty a)
series = (a -> [a] -> NonEmpty a) -> Series m (NonEmpty a)
forall (m :: * -> *) a b c.
(Serial m a, Serial m b) =>
(a -> b -> c) -> Series m c
cons2 a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
(NE.:|)
instance CoSerial m a => CoSerial m (NE.NonEmpty a) where
coseries :: Series m b -> Series m (NonEmpty a -> b)
coseries Series m b
rs =
Series m b -> Series m (a -> [a] -> b)
forall (m :: * -> *) a b c.
(CoSerial m a, CoSerial m b) =>
Series m c -> Series m (a -> b -> c)
alts2 Series m b
rs Series m (a -> [a] -> b)
-> ((a -> [a] -> b) -> Series m (NonEmpty a -> b))
-> Series m (NonEmpty a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \a -> [a] -> b
f ->
(NonEmpty a -> b) -> Series m (NonEmpty a -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((NonEmpty a -> b) -> Series m (NonEmpty a -> b))
-> (NonEmpty a -> b) -> Series m (NonEmpty a -> b)
forall a b. (a -> b) -> a -> b
$ \(a
x NE.:| [a]
xs') -> a -> [a] -> b
f a
x [a]
xs'
#if MIN_VERSION_base(4,4,0)
instance Serial m a => Serial m (Complex a) where
#else
instance (RealFloat a, Serial m a) => Serial m (Complex a) where
#endif
series :: Series m (Complex a)
series = (a -> a -> Complex a) -> Series m (Complex a)
forall (m :: * -> *) a b c.
(Serial m a, Serial m b) =>
(a -> b -> c) -> Series m c
cons2 a -> a -> Complex a
forall a. a -> a -> Complex a
(:+)
#if MIN_VERSION_base(4,4,0)
instance CoSerial m a => CoSerial m (Complex a) where
#else
instance (RealFloat a, CoSerial m a) => CoSerial m (Complex a) where
#endif
coseries :: Series m b -> Series m (Complex a -> b)
coseries Series m b
rs =
Series m b -> Series m (a -> a -> b)
forall (m :: * -> *) a b c.
(CoSerial m a, CoSerial m b) =>
Series m c -> Series m (a -> b -> c)
alts2 Series m b
rs Series m (a -> a -> b)
-> ((a -> a -> b) -> Series m (Complex a -> b))
-> Series m (Complex a -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \a -> a -> b
f ->
(Complex a -> b) -> Series m (Complex a -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Complex a -> b) -> Series m (Complex a -> b))
-> (Complex a -> b) -> Series m (Complex a -> b)
forall a b. (a -> b) -> a -> b
$ \(a
x :+ a
xs') -> a -> a -> b
f a
x a
xs'
instance Monad m => Serial m Void where
series :: Series m Void
series = Series m Void
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance Monad m => CoSerial m Void where
coseries :: Series m b -> Series m (Void -> b)
coseries = Series m (Void -> b) -> Series m b -> Series m (Void -> b)
forall a b. a -> b -> a
const (Series m (Void -> b) -> Series m b -> Series m (Void -> b))
-> Series m (Void -> b) -> Series m b -> Series m (Void -> b)
forall a b. (a -> b) -> a -> b
$ (Void -> b) -> Series m (Void -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return Void -> b
forall a. Void -> a
absurd
instance (CoSerial m a, Serial m b) => Serial m (a->b) where
series :: Series m (a -> b)
series = Series m b -> Series m (a -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries Series m b
forall (m :: * -> *) a. Serial m a => Series m a
series
instance (Serial m a, CoSerial m a, Serial m b, CoSerial m b) => CoSerial m (a->b) where
coseries :: Series m b -> Series m ((a -> b) -> b)
coseries Series m b
r = do
[a]
args <- Series m a -> Series m [a]
forall (m :: * -> *) a. MonadLogic m => m a -> m [a]
unwind Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series
[b] -> b
g <- Series m b -> [a] -> Series m ([b] -> b)
forall a b (m :: * -> *) c.
(Serial m b, CoSerial m b) =>
Series m c -> [a] -> Series m ([b] -> c)
nest Series m b
r [a]
args
((a -> b) -> b) -> Series m ((a -> b) -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (((a -> b) -> b) -> Series m ((a -> b) -> b))
-> ((a -> b) -> b) -> Series m ((a -> b) -> b)
forall a b. (a -> b) -> a -> b
$ \a -> b
f -> [b] -> b
g ([b] -> b) -> [b] -> b
forall a b. (a -> b) -> a -> b
$ (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
args
where
nest :: forall a b m c . (Serial m b, CoSerial m b) => Series m c -> [a] -> Series m ([b] -> c)
nest :: Series m c -> [a] -> Series m ([b] -> c)
nest Series m c
rs [a]
args = do
case [a]
args of
[] -> c -> [b] -> c
forall a b. a -> b -> a
const (c -> [b] -> c) -> Series m c -> Series m ([b] -> c)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Series m c
rs
a
_:[a]
rest -> do
let sf :: Series m (b -> [b] -> c)
sf = Series m ([b] -> c) -> Series m (b -> [b] -> c)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries (Series m ([b] -> c) -> Series m (b -> [b] -> c))
-> Series m ([b] -> c) -> Series m (b -> [b] -> c)
forall a b. (a -> b) -> a -> b
$ Series m c -> [a] -> Series m ([b] -> c)
forall a b (m :: * -> *) c.
(Serial m b, CoSerial m b) =>
Series m c -> [a] -> Series m ([b] -> c)
nest Series m c
rs [a]
rest
b -> [b] -> c
f <- Series m (b -> [b] -> c)
sf
([b] -> c) -> Series m ([b] -> c)
forall (m :: * -> *) a. Monad m => a -> m a
return (([b] -> c) -> Series m ([b] -> c))
-> ([b] -> c) -> Series m ([b] -> c)
forall a b. (a -> b) -> a -> b
$ \(b
b:[b]
bs) -> b -> [b] -> c
f b
b [b]
bs
instance (Serial Identity a, Show a, Show b) => Show (a -> b) where
show :: (a -> b) -> String
show a -> b
f =
if Depth
maxarheight Depth -> Depth -> Bool
forall a. Eq a => a -> a -> Bool
== Depth
1
Bool -> Bool -> Bool
&& Depth
sumarwidth Depth -> Depth -> Depth
forall a. Num a => a -> a -> a
+ [(String, String)] -> Depth
forall (t :: * -> *) a. Foldable t => t a -> Depth
length [(String, String)]
ars Depth -> Depth -> Depth
forall a. Num a => a -> a -> a
* String -> Depth
forall (t :: * -> *) a. Foldable t => t a -> Depth
length String
"->;" Depth -> Depth -> Bool
forall a. Ord a => a -> a -> Bool
< Depth
widthLimit then
String
"{"String -> ShowS
forall a. [a] -> [a] -> [a]
++
String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
";" [String
aString -> ShowS
forall a. [a] -> [a] -> [a]
++String
"->"String -> ShowS
forall a. [a] -> [a] -> [a]
++String
r | (String
a,String
r) <- [(String, String)]
ars]
String -> ShowS
forall a. [a] -> [a] -> [a]
++String
"}"
else
[String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String
aString -> ShowS
forall a. [a] -> [a] -> [a]
++String
"->\n"String -> ShowS
forall a. [a] -> [a] -> [a]
++ShowS
indent String
r | (String
a,String
r) <- [(String, String)]
ars]
where
ars :: [(String, String)]
ars = Depth -> [(String, String)] -> [(String, String)]
forall a. Depth -> [a] -> [a]
take Depth
lengthLimit [ (a -> String
forall a. Show a => a -> String
show a
x, b -> String
forall a. Show a => a -> String
show (a -> b
f a
x))
| a
x <- Depth -> Series Identity a -> [a]
forall a. Depth -> Series Identity a -> [a]
list Depth
depthLimit Series Identity a
forall (m :: * -> *) a. Serial m a => Series m a
series ]
maxarheight :: Depth
maxarheight = [Depth] -> Depth
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [ Depth -> Depth -> Depth
forall a. Ord a => a -> a -> a
max (String -> Depth
height String
a) (String -> Depth
height String
r)
| (String
a,String
r) <- [(String, String)]
ars ]
sumarwidth :: Depth
sumarwidth = [Depth] -> Depth
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [ String -> Depth
forall (t :: * -> *) a. Foldable t => t a -> Depth
length String
a Depth -> Depth -> Depth
forall a. Num a => a -> a -> a
+ String -> Depth
forall (t :: * -> *) a. Foldable t => t a -> Depth
length String
r
| (String
a,String
r) <- [(String, String)]
ars]
indent :: ShowS
indent = [String] -> String
unlines ([String] -> String) -> (String -> [String]) -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
height :: String -> Depth
height = [String] -> Depth
forall (t :: * -> *) a. Foldable t => t a -> Depth
length ([String] -> Depth) -> (String -> [String]) -> String -> Depth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
(Depth
widthLimit,Depth
lengthLimit,Depth
depthLimit) = (Depth
80,Depth
20,Depth
3)::(Int,Int,Depth)
instance (Monad m, Serial m (f (g a))) => Serial m (Compose f g a) where
series :: Series m (Compose f g a)
series = f (g a) -> Compose f g a
forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g a) -> Compose f g a)
-> Series m (f (g a)) -> Series m (Compose f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (f (g a))
forall (m :: * -> *) a. Serial m a => Series m a
series
instance (Monad m, CoSerial m (f (g a))) => CoSerial m (Compose f g a) where
coseries :: Series m b -> Series m (Compose f g a -> b)
coseries = ((f (g a) -> b) -> Compose f g a -> b)
-> Series m (f (g a) -> b) -> Series m (Compose f g a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((f (g a) -> b) -> (Compose f g a -> f (g a)) -> Compose f g a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose) (Series m (f (g a) -> b) -> Series m (Compose f g a -> b))
-> (Series m b -> Series m (f (g a) -> b))
-> Series m b
-> Series m (Compose f g a -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series m b -> Series m (f (g a) -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
coseries
newtype Positive a = Positive { Positive a -> a
getPositive :: a }
deriving (Positive a -> Positive a -> Bool
(Positive a -> Positive a -> Bool)
-> (Positive a -> Positive a -> Bool) -> Eq (Positive a)
forall a. Eq a => Positive a -> Positive a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Positive a -> Positive a -> Bool
$c/= :: forall a. Eq a => Positive a -> Positive a -> Bool
== :: Positive a -> Positive a -> Bool
$c== :: forall a. Eq a => Positive a -> Positive a -> Bool
Eq, Eq (Positive a)
Eq (Positive a)
-> (Positive a -> Positive a -> Ordering)
-> (Positive a -> Positive a -> Bool)
-> (Positive a -> Positive a -> Bool)
-> (Positive a -> Positive a -> Bool)
-> (Positive a -> Positive a -> Bool)
-> (Positive a -> Positive a -> Positive a)
-> (Positive a -> Positive a -> Positive a)
-> Ord (Positive a)
Positive a -> Positive a -> Bool
Positive a -> Positive a -> Ordering
Positive a -> Positive a -> Positive 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 a. Ord a => Eq (Positive a)
forall a. Ord a => Positive a -> Positive a -> Bool
forall a. Ord a => Positive a -> Positive a -> Ordering
forall a. Ord a => Positive a -> Positive a -> Positive a
min :: Positive a -> Positive a -> Positive a
$cmin :: forall a. Ord a => Positive a -> Positive a -> Positive a
max :: Positive a -> Positive a -> Positive a
$cmax :: forall a. Ord a => Positive a -> Positive a -> Positive a
>= :: Positive a -> Positive a -> Bool
$c>= :: forall a. Ord a => Positive a -> Positive a -> Bool
> :: Positive a -> Positive a -> Bool
$c> :: forall a. Ord a => Positive a -> Positive a -> Bool
<= :: Positive a -> Positive a -> Bool
$c<= :: forall a. Ord a => Positive a -> Positive a -> Bool
< :: Positive a -> Positive a -> Bool
$c< :: forall a. Ord a => Positive a -> Positive a -> Bool
compare :: Positive a -> Positive a -> Ordering
$ccompare :: forall a. Ord a => Positive a -> Positive a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Positive a)
Ord, a -> Positive b -> Positive a
(a -> b) -> Positive a -> Positive b
(forall a b. (a -> b) -> Positive a -> Positive b)
-> (forall a b. a -> Positive b -> Positive a) -> Functor Positive
forall a b. a -> Positive b -> Positive a
forall a b. (a -> b) -> Positive a -> Positive b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Positive b -> Positive a
$c<$ :: forall a b. a -> Positive b -> Positive a
fmap :: (a -> b) -> Positive a -> Positive b
$cfmap :: forall a b. (a -> b) -> Positive a -> Positive b
Functor, Positive a -> Bool
(a -> m) -> Positive a -> m
(a -> b -> b) -> b -> Positive a -> b
(forall m. Monoid m => Positive m -> m)
-> (forall m a. Monoid m => (a -> m) -> Positive a -> m)
-> (forall m a. Monoid m => (a -> m) -> Positive a -> m)
-> (forall a b. (a -> b -> b) -> b -> Positive a -> b)
-> (forall a b. (a -> b -> b) -> b -> Positive a -> b)
-> (forall b a. (b -> a -> b) -> b -> Positive a -> b)
-> (forall b a. (b -> a -> b) -> b -> Positive a -> b)
-> (forall a. (a -> a -> a) -> Positive a -> a)
-> (forall a. (a -> a -> a) -> Positive a -> a)
-> (forall a. Positive a -> [a])
-> (forall a. Positive a -> Bool)
-> (forall a. Positive a -> Depth)
-> (forall a. Eq a => a -> Positive a -> Bool)
-> (forall a. Ord a => Positive a -> a)
-> (forall a. Ord a => Positive a -> a)
-> (forall a. Num a => Positive a -> a)
-> (forall a. Num a => Positive a -> a)
-> Foldable Positive
forall a. Eq a => a -> Positive a -> Bool
forall a. Num a => Positive a -> a
forall a. Ord a => Positive a -> a
forall m. Monoid m => Positive m -> m
forall a. Positive a -> Bool
forall a. Positive a -> Depth
forall a. Positive a -> [a]
forall a. (a -> a -> a) -> Positive a -> a
forall m a. Monoid m => (a -> m) -> Positive a -> m
forall b a. (b -> a -> b) -> b -> Positive a -> b
forall a b. (a -> b -> b) -> b -> Positive a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Depth)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Positive a -> a
$cproduct :: forall a. Num a => Positive a -> a
sum :: Positive a -> a
$csum :: forall a. Num a => Positive a -> a
minimum :: Positive a -> a
$cminimum :: forall a. Ord a => Positive a -> a
maximum :: Positive a -> a
$cmaximum :: forall a. Ord a => Positive a -> a
elem :: a -> Positive a -> Bool
$celem :: forall a. Eq a => a -> Positive a -> Bool
length :: Positive a -> Depth
$clength :: forall a. Positive a -> Depth
null :: Positive a -> Bool
$cnull :: forall a. Positive a -> Bool
toList :: Positive a -> [a]
$ctoList :: forall a. Positive a -> [a]
foldl1 :: (a -> a -> a) -> Positive a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Positive a -> a
foldr1 :: (a -> a -> a) -> Positive a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Positive a -> a
foldl' :: (b -> a -> b) -> b -> Positive a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Positive a -> b
foldl :: (b -> a -> b) -> b -> Positive a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Positive a -> b
foldr' :: (a -> b -> b) -> b -> Positive a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Positive a -> b
foldr :: (a -> b -> b) -> b -> Positive a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Positive a -> b
foldMap' :: (a -> m) -> Positive a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Positive a -> m
foldMap :: (a -> m) -> Positive a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Positive a -> m
fold :: Positive m -> m
$cfold :: forall m. Monoid m => Positive m -> m
Foldable, Functor Positive
Foldable Positive
Functor Positive
-> Foldable Positive
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Positive a -> f (Positive b))
-> (forall (f :: * -> *) a.
Applicative f =>
Positive (f a) -> f (Positive a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Positive a -> m (Positive b))
-> (forall (m :: * -> *) a.
Monad m =>
Positive (m a) -> m (Positive a))
-> Traversable Positive
(a -> f b) -> Positive a -> f (Positive b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Positive (m a) -> m (Positive a)
forall (f :: * -> *) a.
Applicative f =>
Positive (f a) -> f (Positive a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Positive a -> m (Positive b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Positive a -> f (Positive b)
sequence :: Positive (m a) -> m (Positive a)
$csequence :: forall (m :: * -> *) a. Monad m => Positive (m a) -> m (Positive a)
mapM :: (a -> m b) -> Positive a -> m (Positive b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Positive a -> m (Positive b)
sequenceA :: Positive (f a) -> f (Positive a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Positive (f a) -> f (Positive a)
traverse :: (a -> f b) -> Positive a -> f (Positive b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Positive a -> f (Positive b)
$cp2Traversable :: Foldable Positive
$cp1Traversable :: Functor Positive
Traversable)
instance Real a => Real (Positive a) where
toRational :: Positive a -> Rational
toRational (Positive a
x) = a -> Rational
forall a. Real a => a -> Rational
toRational a
x
instance (Num a, Bounded a) => Bounded (Positive a) where
minBound :: Positive a
minBound = a -> Positive a
forall a. a -> Positive a
Positive a
1
maxBound :: Positive a
maxBound = a -> Positive a
forall a. a -> Positive a
Positive (a
forall a. Bounded a => a
maxBound :: a)
instance Enum a => Enum (Positive a) where
toEnum :: Depth -> Positive a
toEnum Depth
x = a -> Positive a
forall a. a -> Positive a
Positive (Depth -> a
forall a. Enum a => Depth -> a
toEnum Depth
x)
fromEnum :: Positive a -> Depth
fromEnum (Positive a
x) = a -> Depth
forall a. Enum a => a -> Depth
fromEnum a
x
instance Num a => Num (Positive a) where
Positive a
x + :: Positive a -> Positive a -> Positive a
+ Positive a
y = a -> Positive a
forall a. a -> Positive a
Positive (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y)
Positive a
x * :: Positive a -> Positive a -> Positive a
* Positive a
y = a -> Positive a
forall a. a -> Positive a
Positive (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
negate :: Positive a -> Positive a
negate (Positive a
x) = a -> Positive a
forall a. a -> Positive a
Positive (a -> a
forall a. Num a => a -> a
negate a
x)
abs :: Positive a -> Positive a
abs (Positive a
x) = a -> Positive a
forall a. a -> Positive a
Positive (a -> a
forall a. Num a => a -> a
abs a
x)
signum :: Positive a -> Positive a
signum (Positive a
x) = a -> Positive a
forall a. a -> Positive a
Positive (a -> a
forall a. Num a => a -> a
signum a
x)
fromInteger :: Integer -> Positive a
fromInteger Integer
x = a -> Positive a
forall a. a -> Positive a
Positive (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x)
instance Integral a => Integral (Positive a) where
quotRem :: Positive a -> Positive a -> (Positive a, Positive a)
quotRem (Positive a
x) (Positive a
y) = (a -> Positive a
forall a. a -> Positive a
Positive a
q, a -> Positive a
forall a. a -> Positive a
Positive a
r)
where
(a
q, a
r) = a
x a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
y
toInteger :: Positive a -> Integer
toInteger (Positive a
x) = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x
instance (Num a, Ord a, Serial m a) => Serial m (Positive a) where
series :: Series m (Positive a)
series = a -> Positive a
forall a. a -> Positive a
Positive (a -> Positive a) -> Series m a -> Series m (Positive a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series Series m a -> (a -> Bool) -> Series m a
forall (m :: * -> *) a. Series m a -> (a -> Bool) -> Series m a
`suchThat` (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0)
instance Show a => Show (Positive a) where
showsPrec :: Depth -> Positive a -> ShowS
showsPrec Depth
n (Positive a
x) = Depth -> a -> ShowS
forall a. Show a => Depth -> a -> ShowS
showsPrec Depth
n a
x
newtype NonNegative a = NonNegative { NonNegative a -> a
getNonNegative :: a }
deriving (NonNegative a -> NonNegative a -> Bool
(NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool) -> Eq (NonNegative a)
forall a. Eq a => NonNegative a -> NonNegative a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegative a -> NonNegative a -> Bool
$c/= :: forall a. Eq a => NonNegative a -> NonNegative a -> Bool
== :: NonNegative a -> NonNegative a -> Bool
$c== :: forall a. Eq a => NonNegative a -> NonNegative a -> Bool
Eq, Eq (NonNegative a)
Eq (NonNegative a)
-> (NonNegative a -> NonNegative a -> Ordering)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> NonNegative a)
-> (NonNegative a -> NonNegative a -> NonNegative a)
-> Ord (NonNegative a)
NonNegative a -> NonNegative a -> Bool
NonNegative a -> NonNegative a -> Ordering
NonNegative a -> NonNegative a -> NonNegative 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 a. Ord a => Eq (NonNegative a)
forall a. Ord a => NonNegative a -> NonNegative a -> Bool
forall a. Ord a => NonNegative a -> NonNegative a -> Ordering
forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
min :: NonNegative a -> NonNegative a -> NonNegative a
$cmin :: forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
max :: NonNegative a -> NonNegative a -> NonNegative a
$cmax :: forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
>= :: NonNegative a -> NonNegative a -> Bool
$c>= :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
> :: NonNegative a -> NonNegative a -> Bool
$c> :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
<= :: NonNegative a -> NonNegative a -> Bool
$c<= :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
< :: NonNegative a -> NonNegative a -> Bool
$c< :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
compare :: NonNegative a -> NonNegative a -> Ordering
$ccompare :: forall a. Ord a => NonNegative a -> NonNegative a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (NonNegative a)
Ord, a -> NonNegative b -> NonNegative a
(a -> b) -> NonNegative a -> NonNegative b
(forall a b. (a -> b) -> NonNegative a -> NonNegative b)
-> (forall a b. a -> NonNegative b -> NonNegative a)
-> Functor NonNegative
forall a b. a -> NonNegative b -> NonNegative a
forall a b. (a -> b) -> NonNegative a -> NonNegative b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> NonNegative b -> NonNegative a
$c<$ :: forall a b. a -> NonNegative b -> NonNegative a
fmap :: (a -> b) -> NonNegative a -> NonNegative b
$cfmap :: forall a b. (a -> b) -> NonNegative a -> NonNegative b
Functor, NonNegative a -> Bool
(a -> m) -> NonNegative a -> m
(a -> b -> b) -> b -> NonNegative a -> b
(forall m. Monoid m => NonNegative m -> m)
-> (forall m a. Monoid m => (a -> m) -> NonNegative a -> m)
-> (forall m a. Monoid m => (a -> m) -> NonNegative a -> m)
-> (forall a b. (a -> b -> b) -> b -> NonNegative a -> b)
-> (forall a b. (a -> b -> b) -> b -> NonNegative a -> b)
-> (forall b a. (b -> a -> b) -> b -> NonNegative a -> b)
-> (forall b a. (b -> a -> b) -> b -> NonNegative a -> b)
-> (forall a. (a -> a -> a) -> NonNegative a -> a)
-> (forall a. (a -> a -> a) -> NonNegative a -> a)
-> (forall a. NonNegative a -> [a])
-> (forall a. NonNegative a -> Bool)
-> (forall a. NonNegative a -> Depth)
-> (forall a. Eq a => a -> NonNegative a -> Bool)
-> (forall a. Ord a => NonNegative a -> a)
-> (forall a. Ord a => NonNegative a -> a)
-> (forall a. Num a => NonNegative a -> a)
-> (forall a. Num a => NonNegative a -> a)
-> Foldable NonNegative
forall a. Eq a => a -> NonNegative a -> Bool
forall a. Num a => NonNegative a -> a
forall a. Ord a => NonNegative a -> a
forall m. Monoid m => NonNegative m -> m
forall a. NonNegative a -> Bool
forall a. NonNegative a -> Depth
forall a. NonNegative a -> [a]
forall a. (a -> a -> a) -> NonNegative a -> a
forall m a. Monoid m => (a -> m) -> NonNegative a -> m
forall b a. (b -> a -> b) -> b -> NonNegative a -> b
forall a b. (a -> b -> b) -> b -> NonNegative a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Depth)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: NonNegative a -> a
$cproduct :: forall a. Num a => NonNegative a -> a
sum :: NonNegative a -> a
$csum :: forall a. Num a => NonNegative a -> a
minimum :: NonNegative a -> a
$cminimum :: forall a. Ord a => NonNegative a -> a
maximum :: NonNegative a -> a
$cmaximum :: forall a. Ord a => NonNegative a -> a
elem :: a -> NonNegative a -> Bool
$celem :: forall a. Eq a => a -> NonNegative a -> Bool
length :: NonNegative a -> Depth
$clength :: forall a. NonNegative a -> Depth
null :: NonNegative a -> Bool
$cnull :: forall a. NonNegative a -> Bool
toList :: NonNegative a -> [a]
$ctoList :: forall a. NonNegative a -> [a]
foldl1 :: (a -> a -> a) -> NonNegative a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> NonNegative a -> a
foldr1 :: (a -> a -> a) -> NonNegative a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> NonNegative a -> a
foldl' :: (b -> a -> b) -> b -> NonNegative a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> NonNegative a -> b
foldl :: (b -> a -> b) -> b -> NonNegative a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> NonNegative a -> b
foldr' :: (a -> b -> b) -> b -> NonNegative a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> NonNegative a -> b
foldr :: (a -> b -> b) -> b -> NonNegative a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> NonNegative a -> b
foldMap' :: (a -> m) -> NonNegative a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> NonNegative a -> m
foldMap :: (a -> m) -> NonNegative a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> NonNegative a -> m
fold :: NonNegative m -> m
$cfold :: forall m. Monoid m => NonNegative m -> m
Foldable, Functor NonNegative
Foldable NonNegative
Functor NonNegative
-> Foldable NonNegative
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonNegative a -> f (NonNegative b))
-> (forall (f :: * -> *) a.
Applicative f =>
NonNegative (f a) -> f (NonNegative a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonNegative a -> m (NonNegative b))
-> (forall (m :: * -> *) a.
Monad m =>
NonNegative (m a) -> m (NonNegative a))
-> Traversable NonNegative
(a -> f b) -> NonNegative a -> f (NonNegative b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
NonNegative (m a) -> m (NonNegative a)
forall (f :: * -> *) a.
Applicative f =>
NonNegative (f a) -> f (NonNegative a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonNegative a -> m (NonNegative b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonNegative a -> f (NonNegative b)
sequence :: NonNegative (m a) -> m (NonNegative a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
NonNegative (m a) -> m (NonNegative a)
mapM :: (a -> m b) -> NonNegative a -> m (NonNegative b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonNegative a -> m (NonNegative b)
sequenceA :: NonNegative (f a) -> f (NonNegative a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
NonNegative (f a) -> f (NonNegative a)
traverse :: (a -> f b) -> NonNegative a -> f (NonNegative b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonNegative a -> f (NonNegative b)
$cp2Traversable :: Foldable NonNegative
$cp1Traversable :: Functor NonNegative
Traversable)
instance Real a => Real (NonNegative a) where
toRational :: NonNegative a -> Rational
toRational (NonNegative a
x) = a -> Rational
forall a. Real a => a -> Rational
toRational a
x
instance (Num a, Bounded a) => Bounded (NonNegative a) where
minBound :: NonNegative a
minBound = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative a
0
maxBound :: NonNegative a
maxBound = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a
forall a. Bounded a => a
maxBound :: a)
instance Enum a => Enum (NonNegative a) where
toEnum :: Depth -> NonNegative a
toEnum Depth
x = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (Depth -> a
forall a. Enum a => Depth -> a
toEnum Depth
x)
fromEnum :: NonNegative a -> Depth
fromEnum (NonNegative a
x) = a -> Depth
forall a. Enum a => a -> Depth
fromEnum a
x
instance Num a => Num (NonNegative a) where
NonNegative a
x + :: NonNegative a -> NonNegative a -> NonNegative a
+ NonNegative a
y = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y)
NonNegative a
x * :: NonNegative a -> NonNegative a -> NonNegative a
* NonNegative a
y = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
negate :: NonNegative a -> NonNegative a
negate (NonNegative a
x) = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a -> a
forall a. Num a => a -> a
negate a
x)
abs :: NonNegative a -> NonNegative a
abs (NonNegative a
x) = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a -> a
forall a. Num a => a -> a
abs a
x)
signum :: NonNegative a -> NonNegative a
signum (NonNegative a
x) = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a -> a
forall a. Num a => a -> a
signum a
x)
fromInteger :: Integer -> NonNegative a
fromInteger Integer
x = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x)
instance Integral a => Integral (NonNegative a) where
quotRem :: NonNegative a -> NonNegative a -> (NonNegative a, NonNegative a)
quotRem (NonNegative a
x) (NonNegative a
y) = (a -> NonNegative a
forall a. a -> NonNegative a
NonNegative a
q, a -> NonNegative a
forall a. a -> NonNegative a
NonNegative a
r)
where
(a
q, a
r) = a
x a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
y
toInteger :: NonNegative a -> Integer
toInteger (NonNegative a
x) = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x
instance (Num a, Ord a, Serial m a) => Serial m (NonNegative a) where
series :: Series m (NonNegative a)
series = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a -> NonNegative a) -> Series m a -> Series m (NonNegative a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series Series m a -> (a -> Bool) -> Series m a
forall (m :: * -> *) a. Series m a -> (a -> Bool) -> Series m a
`suchThat` (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
0)
instance Show a => Show (NonNegative a) where
showsPrec :: Depth -> NonNegative a -> ShowS
showsPrec Depth
n (NonNegative a
x) = Depth -> a -> ShowS
forall a. Show a => Depth -> a -> ShowS
showsPrec Depth
n a
x
newtype NonZero a = NonZero { NonZero a -> a
getNonZero :: a }
deriving (NonZero a -> NonZero a -> Bool
(NonZero a -> NonZero a -> Bool)
-> (NonZero a -> NonZero a -> Bool) -> Eq (NonZero a)
forall a. Eq a => NonZero a -> NonZero a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonZero a -> NonZero a -> Bool
$c/= :: forall a. Eq a => NonZero a -> NonZero a -> Bool
== :: NonZero a -> NonZero a -> Bool
$c== :: forall a. Eq a => NonZero a -> NonZero a -> Bool
Eq, Eq (NonZero a)
Eq (NonZero a)
-> (NonZero a -> NonZero a -> Ordering)
-> (NonZero a -> NonZero a -> Bool)
-> (NonZero a -> NonZero a -> Bool)
-> (NonZero a -> NonZero a -> Bool)
-> (NonZero a -> NonZero a -> Bool)
-> (NonZero a -> NonZero a -> NonZero a)
-> (NonZero a -> NonZero a -> NonZero a)
-> Ord (NonZero a)
NonZero a -> NonZero a -> Bool
NonZero a -> NonZero a -> Ordering
NonZero a -> NonZero a -> NonZero 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 a. Ord a => Eq (NonZero a)
forall a. Ord a => NonZero a -> NonZero a -> Bool
forall a. Ord a => NonZero a -> NonZero a -> Ordering
forall a. Ord a => NonZero a -> NonZero a -> NonZero a
min :: NonZero a -> NonZero a -> NonZero a
$cmin :: forall a. Ord a => NonZero a -> NonZero a -> NonZero a
max :: NonZero a -> NonZero a -> NonZero a
$cmax :: forall a. Ord a => NonZero a -> NonZero a -> NonZero a
>= :: NonZero a -> NonZero a -> Bool
$c>= :: forall a. Ord a => NonZero a -> NonZero a -> Bool
> :: NonZero a -> NonZero a -> Bool
$c> :: forall a. Ord a => NonZero a -> NonZero a -> Bool
<= :: NonZero a -> NonZero a -> Bool
$c<= :: forall a. Ord a => NonZero a -> NonZero a -> Bool
< :: NonZero a -> NonZero a -> Bool
$c< :: forall a. Ord a => NonZero a -> NonZero a -> Bool
compare :: NonZero a -> NonZero a -> Ordering
$ccompare :: forall a. Ord a => NonZero a -> NonZero a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (NonZero a)
Ord, a -> NonZero b -> NonZero a
(a -> b) -> NonZero a -> NonZero b
(forall a b. (a -> b) -> NonZero a -> NonZero b)
-> (forall a b. a -> NonZero b -> NonZero a) -> Functor NonZero
forall a b. a -> NonZero b -> NonZero a
forall a b. (a -> b) -> NonZero a -> NonZero b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> NonZero b -> NonZero a
$c<$ :: forall a b. a -> NonZero b -> NonZero a
fmap :: (a -> b) -> NonZero a -> NonZero b
$cfmap :: forall a b. (a -> b) -> NonZero a -> NonZero b
Functor, NonZero a -> Bool
(a -> m) -> NonZero a -> m
(a -> b -> b) -> b -> NonZero a -> b
(forall m. Monoid m => NonZero m -> m)
-> (forall m a. Monoid m => (a -> m) -> NonZero a -> m)
-> (forall m a. Monoid m => (a -> m) -> NonZero a -> m)
-> (forall a b. (a -> b -> b) -> b -> NonZero a -> b)
-> (forall a b. (a -> b -> b) -> b -> NonZero a -> b)
-> (forall b a. (b -> a -> b) -> b -> NonZero a -> b)
-> (forall b a. (b -> a -> b) -> b -> NonZero a -> b)
-> (forall a. (a -> a -> a) -> NonZero a -> a)
-> (forall a. (a -> a -> a) -> NonZero a -> a)
-> (forall a. NonZero a -> [a])
-> (forall a. NonZero a -> Bool)
-> (forall a. NonZero a -> Depth)
-> (forall a. Eq a => a -> NonZero a -> Bool)
-> (forall a. Ord a => NonZero a -> a)
-> (forall a. Ord a => NonZero a -> a)
-> (forall a. Num a => NonZero a -> a)
-> (forall a. Num a => NonZero a -> a)
-> Foldable NonZero
forall a. Eq a => a -> NonZero a -> Bool
forall a. Num a => NonZero a -> a
forall a. Ord a => NonZero a -> a
forall m. Monoid m => NonZero m -> m
forall a. NonZero a -> Bool
forall a. NonZero a -> Depth
forall a. NonZero a -> [a]
forall a. (a -> a -> a) -> NonZero a -> a
forall m a. Monoid m => (a -> m) -> NonZero a -> m
forall b a. (b -> a -> b) -> b -> NonZero a -> b
forall a b. (a -> b -> b) -> b -> NonZero a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Depth)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: NonZero a -> a
$cproduct :: forall a. Num a => NonZero a -> a
sum :: NonZero a -> a
$csum :: forall a. Num a => NonZero a -> a
minimum :: NonZero a -> a
$cminimum :: forall a. Ord a => NonZero a -> a
maximum :: NonZero a -> a
$cmaximum :: forall a. Ord a => NonZero a -> a
elem :: a -> NonZero a -> Bool
$celem :: forall a. Eq a => a -> NonZero a -> Bool
length :: NonZero a -> Depth
$clength :: forall a. NonZero a -> Depth
null :: NonZero a -> Bool
$cnull :: forall a. NonZero a -> Bool
toList :: NonZero a -> [a]
$ctoList :: forall a. NonZero a -> [a]
foldl1 :: (a -> a -> a) -> NonZero a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> NonZero a -> a
foldr1 :: (a -> a -> a) -> NonZero a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> NonZero a -> a
foldl' :: (b -> a -> b) -> b -> NonZero a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> NonZero a -> b
foldl :: (b -> a -> b) -> b -> NonZero a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> NonZero a -> b
foldr' :: (a -> b -> b) -> b -> NonZero a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> NonZero a -> b
foldr :: (a -> b -> b) -> b -> NonZero a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> NonZero a -> b
foldMap' :: (a -> m) -> NonZero a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> NonZero a -> m
foldMap :: (a -> m) -> NonZero a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> NonZero a -> m
fold :: NonZero m -> m
$cfold :: forall m. Monoid m => NonZero m -> m
Foldable, Functor NonZero
Foldable NonZero
Functor NonZero
-> Foldable NonZero
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonZero a -> f (NonZero b))
-> (forall (f :: * -> *) a.
Applicative f =>
NonZero (f a) -> f (NonZero a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonZero a -> m (NonZero b))
-> (forall (m :: * -> *) a.
Monad m =>
NonZero (m a) -> m (NonZero a))
-> Traversable NonZero
(a -> f b) -> NonZero a -> f (NonZero b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => NonZero (m a) -> m (NonZero a)
forall (f :: * -> *) a.
Applicative f =>
NonZero (f a) -> f (NonZero a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonZero a -> m (NonZero b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonZero a -> f (NonZero b)
sequence :: NonZero (m a) -> m (NonZero a)
$csequence :: forall (m :: * -> *) a. Monad m => NonZero (m a) -> m (NonZero a)
mapM :: (a -> m b) -> NonZero a -> m (NonZero b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NonZero a -> m (NonZero b)
sequenceA :: NonZero (f a) -> f (NonZero a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
NonZero (f a) -> f (NonZero a)
traverse :: (a -> f b) -> NonZero a -> f (NonZero b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonZero a -> f (NonZero b)
$cp2Traversable :: Foldable NonZero
$cp1Traversable :: Functor NonZero
Traversable)
instance Real a => Real (NonZero a) where
toRational :: NonZero a -> Rational
toRational (NonZero a
x) = a -> Rational
forall a. Real a => a -> Rational
toRational a
x
instance (Eq a, Num a, Bounded a) => Bounded (NonZero a) where
minBound :: NonZero a
minBound = let x :: a
x = a
forall a. Bounded a => a
minBound in a -> NonZero a
forall a. a -> NonZero a
NonZero (if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 then a
1 else a
x)
maxBound :: NonZero a
maxBound = let x :: a
x = a
forall a. Bounded a => a
maxBound in a -> NonZero a
forall a. a -> NonZero a
NonZero (if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 then -a
1 else a
x)
instance Enum a => Enum (NonZero a) where
toEnum :: Depth -> NonZero a
toEnum Depth
x = a -> NonZero a
forall a. a -> NonZero a
NonZero (Depth -> a
forall a. Enum a => Depth -> a
toEnum Depth
x)
fromEnum :: NonZero a -> Depth
fromEnum (NonZero a
x) = a -> Depth
forall a. Enum a => a -> Depth
fromEnum a
x
instance Num a => Num (NonZero a) where
NonZero a
x + :: NonZero a -> NonZero a -> NonZero a
+ NonZero a
y = a -> NonZero a
forall a. a -> NonZero a
NonZero (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y)
NonZero a
x * :: NonZero a -> NonZero a -> NonZero a
* NonZero a
y = a -> NonZero a
forall a. a -> NonZero a
NonZero (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
negate :: NonZero a -> NonZero a
negate (NonZero a
x) = a -> NonZero a
forall a. a -> NonZero a
NonZero (a -> a
forall a. Num a => a -> a
negate a
x)
abs :: NonZero a -> NonZero a
abs (NonZero a
x) = a -> NonZero a
forall a. a -> NonZero a
NonZero (a -> a
forall a. Num a => a -> a
abs a
x)
signum :: NonZero a -> NonZero a
signum (NonZero a
x) = a -> NonZero a
forall a. a -> NonZero a
NonZero (a -> a
forall a. Num a => a -> a
signum a
x)
fromInteger :: Integer -> NonZero a
fromInteger Integer
x = a -> NonZero a
forall a. a -> NonZero a
NonZero (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x)
instance Integral a => Integral (NonZero a) where
quotRem :: NonZero a -> NonZero a -> (NonZero a, NonZero a)
quotRem (NonZero a
x) (NonZero a
y) = (a -> NonZero a
forall a. a -> NonZero a
NonZero a
q, a -> NonZero a
forall a. a -> NonZero a
NonZero a
r)
where
(a
q, a
r) = a
x a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
y
toInteger :: NonZero a -> Integer
toInteger (NonZero a
x) = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x
instance (Num a, Ord a, Serial m a) => Serial m (NonZero a) where
series :: Series m (NonZero a)
series = a -> NonZero a
forall a. a -> NonZero a
NonZero (a -> NonZero a) -> Series m a -> Series m (NonZero a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m a
forall (m :: * -> *) a. Serial m a => Series m a
series Series m a -> (a -> Bool) -> Series m a
forall (m :: * -> *) a. Series m a -> (a -> Bool) -> Series m a
`suchThat` (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
0)
instance Show a => Show (NonZero a) where
showsPrec :: Depth -> NonZero a -> ShowS
showsPrec Depth
n (NonZero a
x) = Depth -> a -> ShowS
forall a. Show a => Depth -> a -> ShowS
showsPrec Depth
n a
x
newtype NonEmpty a = NonEmpty { NonEmpty a -> [a]
getNonEmpty :: [a] }
instance (Serial m a) => Serial m (NonEmpty a) where
series :: Series m (NonEmpty a)
series = [a] -> NonEmpty a
forall a. [a] -> NonEmpty a
NonEmpty ([a] -> NonEmpty a) -> Series m [a] -> Series m (NonEmpty a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> [a] -> [a]) -> Series m [a]
forall (m :: * -> *) a b c.
(Serial m a, Serial m b) =>
(a -> b -> c) -> Series m c
cons2 (:)
instance Show a => Show (NonEmpty a) where
showsPrec :: Depth -> NonEmpty a -> ShowS
showsPrec Depth
n (NonEmpty [a]
x) = Depth -> [a] -> ShowS
forall a. Show a => Depth -> a -> ShowS
showsPrec Depth
n [a]
x
#if MIN_VERSION_base(4,5,0)
instance Monad m => Serial m CFloat where
series :: Series m CFloat
series = (Float -> CFloat) -> Series m CFloat
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Float -> CFloat
CFloat
instance Monad m => CoSerial m CFloat where
coseries :: Series m b -> Series m (CFloat -> b)
coseries Series m b
rs = Series m b -> Series m (Float -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Float -> b)
-> ((Float -> b) -> Series m (CFloat -> b))
-> Series m (CFloat -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Float -> b
f -> (CFloat -> b) -> Series m (CFloat -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CFloat -> b) -> Series m (CFloat -> b))
-> (CFloat -> b) -> Series m (CFloat -> b)
forall a b. (a -> b) -> a -> b
$ \CFloat
l -> case CFloat
l of CFloat Float
x -> Float -> b
f Float
x
instance Monad m => Serial m CDouble where
series :: Series m CDouble
series = (Double -> CDouble) -> Series m CDouble
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Double -> CDouble
CDouble
instance Monad m => CoSerial m CDouble where
coseries :: Series m b -> Series m (CDouble -> b)
coseries Series m b
rs = Series m b -> Series m (Double -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Double -> b)
-> ((Double -> b) -> Series m (CDouble -> b))
-> Series m (CDouble -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Double -> b
f -> (CDouble -> b) -> Series m (CDouble -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CDouble -> b) -> Series m (CDouble -> b))
-> (CDouble -> b) -> Series m (CDouble -> b)
forall a b. (a -> b) -> a -> b
$ \CDouble
l -> case CDouble
l of CDouble Double
x -> Double -> b
f Double
x
#if HASCBOOL
instance Monad m => Serial m CBool where
series :: Series m CBool
series = (Word8 -> CBool) -> Series m CBool
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word8 -> CBool
CBool
instance Monad m => CoSerial m CBool where
coseries :: Series m b -> Series m (CBool -> b)
coseries Series m b
rs = Series m b -> Series m (Word8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word8 -> b)
-> ((Word8 -> b) -> Series m (CBool -> b)) -> Series m (CBool -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word8 -> b
f -> (CBool -> b) -> Series m (CBool -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CBool -> b) -> Series m (CBool -> b))
-> (CBool -> b) -> Series m (CBool -> b)
forall a b. (a -> b) -> a -> b
$ \CBool
l -> case CBool
l of CBool Word8
x -> Word8 -> b
f Word8
x
#endif
instance Monad m => Serial m CChar where
series :: Series m CChar
series = (Int8 -> CChar) -> Series m CChar
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int8 -> CChar
CChar
instance Monad m => CoSerial m CChar where
coseries :: Series m b -> Series m (CChar -> b)
coseries Series m b
rs = Series m b -> Series m (Int8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int8 -> b)
-> ((Int8 -> b) -> Series m (CChar -> b)) -> Series m (CChar -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int8 -> b
f -> (CChar -> b) -> Series m (CChar -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CChar -> b) -> Series m (CChar -> b))
-> (CChar -> b) -> Series m (CChar -> b)
forall a b. (a -> b) -> a -> b
$ \CChar
l -> case CChar
l of CChar Int8
x -> Int8 -> b
f Int8
x
instance Monad m => Serial m CSChar where
series :: Series m CSChar
series = (Int8 -> CSChar) -> Series m CSChar
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int8 -> CSChar
CSChar
instance Monad m => CoSerial m CSChar where
coseries :: Series m b -> Series m (CSChar -> b)
coseries Series m b
rs = Series m b -> Series m (Int8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int8 -> b)
-> ((Int8 -> b) -> Series m (CSChar -> b))
-> Series m (CSChar -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int8 -> b
f -> (CSChar -> b) -> Series m (CSChar -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CSChar -> b) -> Series m (CSChar -> b))
-> (CSChar -> b) -> Series m (CSChar -> b)
forall a b. (a -> b) -> a -> b
$ \CSChar
l -> case CSChar
l of CSChar Int8
x -> Int8 -> b
f Int8
x
instance Monad m => Serial m CUChar where
series :: Series m CUChar
series = (Word8 -> CUChar) -> Series m CUChar
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word8 -> CUChar
CUChar
instance Monad m => CoSerial m CUChar where
coseries :: Series m b -> Series m (CUChar -> b)
coseries Series m b
rs = Series m b -> Series m (Word8 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word8 -> b)
-> ((Word8 -> b) -> Series m (CUChar -> b))
-> Series m (CUChar -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word8 -> b
f -> (CUChar -> b) -> Series m (CUChar -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUChar -> b) -> Series m (CUChar -> b))
-> (CUChar -> b) -> Series m (CUChar -> b)
forall a b. (a -> b) -> a -> b
$ \CUChar
l -> case CUChar
l of CUChar Word8
x -> Word8 -> b
f Word8
x
instance Monad m => Serial m CShort where
series :: Series m CShort
series = (Int16 -> CShort) -> Series m CShort
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int16 -> CShort
CShort
instance Monad m => CoSerial m CShort where
coseries :: Series m b -> Series m (CShort -> b)
coseries Series m b
rs = Series m b -> Series m (Int16 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int16 -> b)
-> ((Int16 -> b) -> Series m (CShort -> b))
-> Series m (CShort -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int16 -> b
f -> (CShort -> b) -> Series m (CShort -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CShort -> b) -> Series m (CShort -> b))
-> (CShort -> b) -> Series m (CShort -> b)
forall a b. (a -> b) -> a -> b
$ \CShort
l -> case CShort
l of CShort Int16
x -> Int16 -> b
f Int16
x
instance Monad m => Serial m CUShort where
series :: Series m CUShort
series = (Word16 -> CUShort) -> Series m CUShort
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word16 -> CUShort
CUShort
instance Monad m => CoSerial m CUShort where
coseries :: Series m b -> Series m (CUShort -> b)
coseries Series m b
rs = Series m b -> Series m (Word16 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word16 -> b)
-> ((Word16 -> b) -> Series m (CUShort -> b))
-> Series m (CUShort -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word16 -> b
f -> (CUShort -> b) -> Series m (CUShort -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUShort -> b) -> Series m (CUShort -> b))
-> (CUShort -> b) -> Series m (CUShort -> b)
forall a b. (a -> b) -> a -> b
$ \CUShort
l -> case CUShort
l of CUShort Word16
x -> Word16 -> b
f Word16
x
instance Monad m => Serial m CInt where
series :: Series m CInt
series = (Int32 -> CInt) -> Series m CInt
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int32 -> CInt
CInt
instance Monad m => CoSerial m CInt where
coseries :: Series m b -> Series m (CInt -> b)
coseries Series m b
rs = Series m b -> Series m (Int32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int32 -> b)
-> ((Int32 -> b) -> Series m (CInt -> b)) -> Series m (CInt -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int32 -> b
f -> (CInt -> b) -> Series m (CInt -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CInt -> b) -> Series m (CInt -> b))
-> (CInt -> b) -> Series m (CInt -> b)
forall a b. (a -> b) -> a -> b
$ \CInt
l -> case CInt
l of CInt Int32
x -> Int32 -> b
f Int32
x
instance Monad m => Serial m CUInt where
series :: Series m CUInt
series = (Word32 -> CUInt) -> Series m CUInt
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word32 -> CUInt
CUInt
instance Monad m => CoSerial m CUInt where
coseries :: Series m b -> Series m (CUInt -> b)
coseries Series m b
rs = Series m b -> Series m (Word32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word32 -> b)
-> ((Word32 -> b) -> Series m (CUInt -> b))
-> Series m (CUInt -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word32 -> b
f -> (CUInt -> b) -> Series m (CUInt -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUInt -> b) -> Series m (CUInt -> b))
-> (CUInt -> b) -> Series m (CUInt -> b)
forall a b. (a -> b) -> a -> b
$ \CUInt
l -> case CUInt
l of CUInt Word32
x -> Word32 -> b
f Word32
x
instance Monad m => Serial m CLong where
series :: Series m CLong
series = (Int64 -> CLong) -> Series m CLong
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CLong
CLong
instance Monad m => CoSerial m CLong where
coseries :: Series m b -> Series m (CLong -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CLong -> b)) -> Series m (CLong -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CLong -> b) -> Series m (CLong -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CLong -> b) -> Series m (CLong -> b))
-> (CLong -> b) -> Series m (CLong -> b)
forall a b. (a -> b) -> a -> b
$ \CLong
l -> case CLong
l of CLong Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CULong where
series :: Series m CULong
series = (Word64 -> CULong) -> Series m CULong
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word64 -> CULong
CULong
instance Monad m => CoSerial m CULong where
coseries :: Series m b -> Series m (CULong -> b)
coseries Series m b
rs = Series m b -> Series m (Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word64 -> b)
-> ((Word64 -> b) -> Series m (CULong -> b))
-> Series m (CULong -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word64 -> b
f -> (CULong -> b) -> Series m (CULong -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CULong -> b) -> Series m (CULong -> b))
-> (CULong -> b) -> Series m (CULong -> b)
forall a b. (a -> b) -> a -> b
$ \CULong
l -> case CULong
l of CULong Word64
x -> Word64 -> b
f Word64
x
instance Monad m => Serial m CPtrdiff where
series :: Series m CPtrdiff
series = (Int64 -> CPtrdiff) -> Series m CPtrdiff
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CPtrdiff
CPtrdiff
instance Monad m => CoSerial m CPtrdiff where
coseries :: Series m b -> Series m (CPtrdiff -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CPtrdiff -> b))
-> Series m (CPtrdiff -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CPtrdiff -> b) -> Series m (CPtrdiff -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CPtrdiff -> b) -> Series m (CPtrdiff -> b))
-> (CPtrdiff -> b) -> Series m (CPtrdiff -> b)
forall a b. (a -> b) -> a -> b
$ \CPtrdiff
l -> case CPtrdiff
l of CPtrdiff Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CSize where
series :: Series m CSize
series = (Word64 -> CSize) -> Series m CSize
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word64 -> CSize
CSize
instance Monad m => CoSerial m CSize where
coseries :: Series m b -> Series m (CSize -> b)
coseries Series m b
rs = Series m b -> Series m (Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word64 -> b)
-> ((Word64 -> b) -> Series m (CSize -> b))
-> Series m (CSize -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word64 -> b
f -> (CSize -> b) -> Series m (CSize -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CSize -> b) -> Series m (CSize -> b))
-> (CSize -> b) -> Series m (CSize -> b)
forall a b. (a -> b) -> a -> b
$ \CSize
l -> case CSize
l of CSize Word64
x -> Word64 -> b
f Word64
x
instance Monad m => Serial m CWchar where
series :: Series m CWchar
series = (Int32 -> CWchar) -> Series m CWchar
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int32 -> CWchar
CWchar
instance Monad m => CoSerial m CWchar where
coseries :: Series m b -> Series m (CWchar -> b)
coseries Series m b
rs = Series m b -> Series m (Int32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int32 -> b)
-> ((Int32 -> b) -> Series m (CWchar -> b))
-> Series m (CWchar -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int32 -> b
f -> (CWchar -> b) -> Series m (CWchar -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CWchar -> b) -> Series m (CWchar -> b))
-> (CWchar -> b) -> Series m (CWchar -> b)
forall a b. (a -> b) -> a -> b
$ \CWchar
l -> case CWchar
l of CWchar Int32
x -> Int32 -> b
f Int32
x
instance Monad m => Serial m CSigAtomic where
series :: Series m CSigAtomic
series = (Int32 -> CSigAtomic) -> Series m CSigAtomic
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int32 -> CSigAtomic
CSigAtomic
instance Monad m => CoSerial m CSigAtomic where
coseries :: Series m b -> Series m (CSigAtomic -> b)
coseries Series m b
rs = Series m b -> Series m (Int32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int32 -> b)
-> ((Int32 -> b) -> Series m (CSigAtomic -> b))
-> Series m (CSigAtomic -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int32 -> b
f -> (CSigAtomic -> b) -> Series m (CSigAtomic -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CSigAtomic -> b) -> Series m (CSigAtomic -> b))
-> (CSigAtomic -> b) -> Series m (CSigAtomic -> b)
forall a b. (a -> b) -> a -> b
$ \CSigAtomic
l -> case CSigAtomic
l of CSigAtomic Int32
x -> Int32 -> b
f Int32
x
instance Monad m => Serial m CLLong where
series :: Series m CLLong
series = (Int64 -> CLLong) -> Series m CLLong
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CLLong
CLLong
instance Monad m => CoSerial m CLLong where
coseries :: Series m b -> Series m (CLLong -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CLLong -> b))
-> Series m (CLLong -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CLLong -> b) -> Series m (CLLong -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CLLong -> b) -> Series m (CLLong -> b))
-> (CLLong -> b) -> Series m (CLLong -> b)
forall a b. (a -> b) -> a -> b
$ \CLLong
l -> case CLLong
l of CLLong Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CULLong where
series :: Series m CULLong
series = (Word64 -> CULLong) -> Series m CULLong
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word64 -> CULLong
CULLong
instance Monad m => CoSerial m CULLong where
coseries :: Series m b -> Series m (CULLong -> b)
coseries Series m b
rs = Series m b -> Series m (Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word64 -> b)
-> ((Word64 -> b) -> Series m (CULLong -> b))
-> Series m (CULLong -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word64 -> b
f -> (CULLong -> b) -> Series m (CULLong -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CULLong -> b) -> Series m (CULLong -> b))
-> (CULLong -> b) -> Series m (CULLong -> b)
forall a b. (a -> b) -> a -> b
$ \CULLong
l -> case CULLong
l of CULLong Word64
x -> Word64 -> b
f Word64
x
instance Monad m => Serial m CIntPtr where
series :: Series m CIntPtr
series = (Int64 -> CIntPtr) -> Series m CIntPtr
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CIntPtr
CIntPtr
instance Monad m => CoSerial m CIntPtr where
coseries :: Series m b -> Series m (CIntPtr -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CIntPtr -> b))
-> Series m (CIntPtr -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CIntPtr -> b) -> Series m (CIntPtr -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CIntPtr -> b) -> Series m (CIntPtr -> b))
-> (CIntPtr -> b) -> Series m (CIntPtr -> b)
forall a b. (a -> b) -> a -> b
$ \CIntPtr
l -> case CIntPtr
l of CIntPtr Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CUIntPtr where
series :: Series m CUIntPtr
series = (Word64 -> CUIntPtr) -> Series m CUIntPtr
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word64 -> CUIntPtr
CUIntPtr
instance Monad m => CoSerial m CUIntPtr where
coseries :: Series m b -> Series m (CUIntPtr -> b)
coseries Series m b
rs = Series m b -> Series m (Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word64 -> b)
-> ((Word64 -> b) -> Series m (CUIntPtr -> b))
-> Series m (CUIntPtr -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word64 -> b
f -> (CUIntPtr -> b) -> Series m (CUIntPtr -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUIntPtr -> b) -> Series m (CUIntPtr -> b))
-> (CUIntPtr -> b) -> Series m (CUIntPtr -> b)
forall a b. (a -> b) -> a -> b
$ \CUIntPtr
l -> case CUIntPtr
l of CUIntPtr Word64
x -> Word64 -> b
f Word64
x
instance Monad m => Serial m CIntMax where
series :: Series m CIntMax
series = (Int64 -> CIntMax) -> Series m CIntMax
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CIntMax
CIntMax
instance Monad m => CoSerial m CIntMax where
coseries :: Series m b -> Series m (CIntMax -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CIntMax -> b))
-> Series m (CIntMax -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CIntMax -> b) -> Series m (CIntMax -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CIntMax -> b) -> Series m (CIntMax -> b))
-> (CIntMax -> b) -> Series m (CIntMax -> b)
forall a b. (a -> b) -> a -> b
$ \CIntMax
l -> case CIntMax
l of CIntMax Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CUIntMax where
series :: Series m CUIntMax
series = (Word64 -> CUIntMax) -> Series m CUIntMax
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word64 -> CUIntMax
CUIntMax
instance Monad m => CoSerial m CUIntMax where
coseries :: Series m b -> Series m (CUIntMax -> b)
coseries Series m b
rs = Series m b -> Series m (Word64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word64 -> b)
-> ((Word64 -> b) -> Series m (CUIntMax -> b))
-> Series m (CUIntMax -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word64 -> b
f -> (CUIntMax -> b) -> Series m (CUIntMax -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUIntMax -> b) -> Series m (CUIntMax -> b))
-> (CUIntMax -> b) -> Series m (CUIntMax -> b)
forall a b. (a -> b) -> a -> b
$ \CUIntMax
l -> case CUIntMax
l of CUIntMax Word64
x -> Word64 -> b
f Word64
x
instance Monad m => Serial m CClock where
series :: Series m CClock
series = (Int64 -> CClock) -> Series m CClock
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CClock
CClock
instance Monad m => CoSerial m CClock where
coseries :: Series m b -> Series m (CClock -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CClock -> b))
-> Series m (CClock -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CClock -> b) -> Series m (CClock -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CClock -> b) -> Series m (CClock -> b))
-> (CClock -> b) -> Series m (CClock -> b)
forall a b. (a -> b) -> a -> b
$ \CClock
l -> case CClock
l of CClock Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CTime where
series :: Series m CTime
series = (Int64 -> CTime) -> Series m CTime
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CTime
CTime
instance Monad m => CoSerial m CTime where
coseries :: Series m b -> Series m (CTime -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CTime -> b)) -> Series m (CTime -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CTime -> b) -> Series m (CTime -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CTime -> b) -> Series m (CTime -> b))
-> (CTime -> b) -> Series m (CTime -> b)
forall a b. (a -> b) -> a -> b
$ \CTime
l -> case CTime
l of CTime Int64
x -> Int64 -> b
f Int64
x
instance Monad m => Serial m CUSeconds where
series :: Series m CUSeconds
series = (Word32 -> CUSeconds) -> Series m CUSeconds
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Word32 -> CUSeconds
CUSeconds
instance Monad m => CoSerial m CUSeconds where
coseries :: Series m b -> Series m (CUSeconds -> b)
coseries Series m b
rs = Series m b -> Series m (Word32 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Word32 -> b)
-> ((Word32 -> b) -> Series m (CUSeconds -> b))
-> Series m (CUSeconds -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Word32 -> b
f -> (CUSeconds -> b) -> Series m (CUSeconds -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CUSeconds -> b) -> Series m (CUSeconds -> b))
-> (CUSeconds -> b) -> Series m (CUSeconds -> b)
forall a b. (a -> b) -> a -> b
$ \CUSeconds
l -> case CUSeconds
l of CUSeconds Word32
x -> Word32 -> b
f Word32
x
instance Monad m => Serial m CSUSeconds where
series :: Series m CSUSeconds
series = (Int64 -> CSUSeconds) -> Series m CSUSeconds
forall (m :: * -> *) a b. Serial m a => (a -> b) -> Series m b
newtypeCons Int64 -> CSUSeconds
CSUSeconds
instance Monad m => CoSerial m CSUSeconds where
coseries :: Series m b -> Series m (CSUSeconds -> b)
coseries Series m b
rs = Series m b -> Series m (Int64 -> b)
forall (m :: * -> *) a b.
CoSerial m a =>
Series m b -> Series m (a -> b)
newtypeAlts Series m b
rs Series m (Int64 -> b)
-> ((Int64 -> b) -> Series m (CSUSeconds -> b))
-> Series m (CSUSeconds -> b)
forall (m :: * -> *) a b. MonadLogic m => m a -> (a -> m b) -> m b
>>- \Int64 -> b
f -> (CSUSeconds -> b) -> Series m (CSUSeconds -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CSUSeconds -> b) -> Series m (CSUSeconds -> b))
-> (CSUSeconds -> b) -> Series m (CSUSeconds -> b)
forall a b. (a -> b) -> a -> b
$ \CSUSeconds
l -> case CSUSeconds
l of CSUSeconds Int64
x -> Int64 -> b
f Int64
x
#endif