{-# LANGUAGE
DataKinds
, ScopedTypeVariables
, FlexibleContexts
, FlexibleInstances
, KindSignatures
, GeneralizedNewtypeDeriving
, ConstraintKinds
, UndecidableInstances
, DeriveDataTypeable
, DeriveGeneric
, DeriveFunctor
, DeriveFoldable
, DeriveTraversable
, MonoLocalBinds
#-}
module Test.QuickCheck.Combinators where
import GHC.TypeLits (Nat, KnownNat, natVal)
import Data.Proxy (Proxy (..))
import Data.Maybe (fromMaybe)
import Data.Unfoldable.Restricted (UnfoldableR, fromList)
import Data.Constraint.Unit (Unit)
import Control.Monad (replicateM)
import Test.QuickCheck (OrderedList (..), Arbitrary (..), choose, sized)
import qualified Data.List as L (sort)
import Data.Data (Data, Typeable)
import GHC.Generics (Generic)
newtype AtLeast (n :: Nat) t a = AtLeast
{ forall (n :: Nat) (t :: * -> *) a. AtLeast n t a -> t a
getAtLeast :: t a
} deriving (Int -> AtLeast n t a -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> AtLeast n t a -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
[AtLeast n t a] -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
AtLeast n t a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AtLeast n t a] -> ShowS
$cshowList :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
[AtLeast n t a] -> ShowS
show :: AtLeast n t a -> String
$cshow :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
AtLeast n t a -> String
showsPrec :: Int -> AtLeast n t a -> ShowS
$cshowsPrec :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> AtLeast n t a -> ShowS
Show, ReadPrec [AtLeast n t a]
ReadPrec (AtLeast n t a)
ReadS [AtLeast n t a]
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [AtLeast n t a]
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [AtLeast n t a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AtLeast n t a]
$creadListPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [AtLeast n t a]
readPrec :: ReadPrec (AtLeast n t a)
$creadPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (AtLeast n t a)
readList :: ReadS [AtLeast n t a]
$creadList :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [AtLeast n t a]
readsPrec :: Int -> ReadS (AtLeast n t a)
$creadsPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (AtLeast n t a)
Read, AtLeast n t a -> AtLeast n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtLeast n t a -> AtLeast n t a -> Bool
$c/= :: forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
== :: AtLeast n t a -> AtLeast n t a -> Bool
$c== :: forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
Eq, AtLeast n t a -> AtLeast n t a -> Bool
AtLeast n t a -> AtLeast n t a -> Ordering
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
forall {n :: Nat} {t :: * -> *} {a}.
Ord (t a) =>
Eq (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Ordering
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t 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
min :: AtLeast n t a -> AtLeast n t a -> AtLeast n t a
$cmin :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
max :: AtLeast n t a -> AtLeast n t a -> AtLeast n t a
$cmax :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
>= :: AtLeast n t a -> AtLeast n t a -> Bool
$c>= :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
> :: AtLeast n t a -> AtLeast n t a -> Bool
$c> :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
<= :: AtLeast n t a -> AtLeast n t a -> Bool
$c<= :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
< :: AtLeast n t a -> AtLeast n t a -> Bool
$c< :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Bool
compare :: AtLeast n t a -> AtLeast n t a -> Ordering
$ccompare :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtLeast n t a -> AtLeast n t a -> Ordering
Ord, Int -> AtLeast n t a
AtLeast n t a -> Int
AtLeast n t a -> [AtLeast n t a]
AtLeast n t a -> AtLeast n t a
AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
AtLeast n t a -> AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> Int
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> [AtLeast n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AtLeast n t a -> AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
$cenumFromThenTo :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
enumFromTo :: AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
$cenumFromTo :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
enumFromThen :: AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
$cenumFromThen :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a -> [AtLeast n t a]
enumFrom :: AtLeast n t a -> [AtLeast n t a]
$cenumFrom :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> [AtLeast n t a]
fromEnum :: AtLeast n t a -> Int
$cfromEnum :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> Int
toEnum :: Int -> AtLeast n t a
$ctoEnum :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> AtLeast n t a
pred :: AtLeast n t a -> AtLeast n t a
$cpred :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a
succ :: AtLeast n t a -> AtLeast n t a
$csucc :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtLeast n t a -> AtLeast n t a
Enum, AtLeast n t a -> DataType
AtLeast n t a -> Constr
forall {n :: Nat} {t :: * -> *} {a}.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Typeable (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtLeast n t a -> DataType
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtLeast n t a -> Constr
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> AtLeast n t a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> AtLeast n t a -> u
forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> AtLeast n t a -> [u]
forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Monad m) =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtLeast n t a -> c (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AtLeast n t a))
forall (n :: Nat) (t :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtLeast n t a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtLeast n t a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtLeast n t a -> c (AtLeast n t a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
$cgmapMo :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
$cgmapMp :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
$cgmapM :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Monad m) =>
(forall d. Data d => d -> m d)
-> AtLeast n t a -> m (AtLeast n t a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AtLeast n t a -> u
$cgmapQi :: forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> AtLeast n t a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> AtLeast n t a -> [u]
$cgmapQ :: forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> AtLeast n t a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
$cgmapQr :: forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
$cgmapQl :: forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtLeast n t a -> r
gmapT :: (forall b. Data b => b -> b) -> AtLeast n t a -> AtLeast n t a
$cgmapT :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> AtLeast n t a -> AtLeast n t a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtLeast n t a))
$cdataCast2 :: forall (n :: Nat) (t :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtLeast n t a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (AtLeast n t a))
$cdataCast1 :: forall (n :: Nat) (t :: * -> *) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AtLeast n t a))
dataTypeOf :: AtLeast n t a -> DataType
$cdataTypeOf :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtLeast n t a -> DataType
toConstr :: AtLeast n t a -> Constr
$ctoConstr :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtLeast n t a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtLeast n t a)
$cgunfold :: forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtLeast n t a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtLeast n t a -> c (AtLeast n t a)
$cgfoldl :: forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtLeast n t a -> c (AtLeast n t a)
Data, Typeable, forall (n :: Nat) (t :: * -> *) a x.
Rep (AtLeast n t a) x -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a x.
AtLeast n t a -> Rep (AtLeast n t a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (n :: Nat) (t :: * -> *) a x.
Rep (AtLeast n t a) x -> AtLeast n t a
$cfrom :: forall (n :: Nat) (t :: * -> *) a x.
AtLeast n t a -> Rep (AtLeast n t a) x
Generic, forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
a -> AtLeast n t b -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> AtLeast n t a -> AtLeast n t b
forall a b. a -> AtLeast n t b -> AtLeast n t a
forall a b. (a -> b) -> AtLeast n t a -> AtLeast n t b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> AtLeast n t b -> AtLeast n t a
$c<$ :: forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
a -> AtLeast n t b -> AtLeast n t a
fmap :: forall a b. (a -> b) -> AtLeast n t a -> AtLeast n t b
$cfmap :: forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> AtLeast n t a -> AtLeast n t b
Functor
, forall {n :: Nat} {t :: * -> *}.
Applicative t =>
Functor (AtLeast n t)
forall (n :: Nat) (t :: * -> *) a.
Applicative t =>
a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t b
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t (a -> b) -> AtLeast n t a -> AtLeast n t b
forall (n :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c) -> AtLeast n t a -> AtLeast n t b -> AtLeast n t c
forall a. a -> AtLeast n t a
forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t a
forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t b
forall a b. AtLeast n t (a -> b) -> AtLeast n t a -> AtLeast n t b
forall a b c.
(a -> b -> c) -> AtLeast n t a -> AtLeast n t b -> AtLeast n t c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t a
$c<* :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t a
*> :: forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t b
$c*> :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t b
liftA2 :: forall a b c.
(a -> b -> c) -> AtLeast n t a -> AtLeast n t b -> AtLeast n t c
$cliftA2 :: forall (n :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c) -> AtLeast n t a -> AtLeast n t b -> AtLeast n t c
<*> :: forall a b. AtLeast n t (a -> b) -> AtLeast n t a -> AtLeast n t b
$c<*> :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtLeast n t (a -> b) -> AtLeast n t a -> AtLeast n t b
pure :: forall a. a -> AtLeast n t a
$cpure :: forall (n :: Nat) (t :: * -> *) a.
Applicative t =>
a -> AtLeast n t a
Applicative, forall {n :: Nat} {t :: * -> *}.
Monad t =>
Applicative (AtLeast n t)
forall (n :: Nat) (t :: * -> *) a. Monad t => a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t b
forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtLeast n t a -> (a -> AtLeast n t b) -> AtLeast n t b
forall a. a -> AtLeast n t a
forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t b
forall a b. AtLeast n t a -> (a -> AtLeast n t b) -> AtLeast n t b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> AtLeast n t a
$creturn :: forall (n :: Nat) (t :: * -> *) a. Monad t => a -> AtLeast n t a
>> :: forall a b. AtLeast n t a -> AtLeast n t b -> AtLeast n t b
$c>> :: forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtLeast n t a -> AtLeast n t b -> AtLeast n t b
>>= :: forall a b. AtLeast n t a -> (a -> AtLeast n t b) -> AtLeast n t b
$c>>= :: forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtLeast n t a -> (a -> AtLeast n t b) -> AtLeast n t b
Monad, forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> AtLeast n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtLeast n t a -> a
forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtLeast n t a -> a
forall (n :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
AtLeast n t m -> m
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> Int
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> [a]
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtLeast n t a -> a
forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtLeast n t a -> m
forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtLeast n t a -> b
forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtLeast n t a -> b
forall a. Eq a => a -> AtLeast n t a -> Bool
forall a. Num a => AtLeast n t a -> a
forall a. Ord a => AtLeast n t a -> a
forall m. Monoid m => AtLeast n t m -> m
forall a. AtLeast n t a -> Bool
forall a. AtLeast n t a -> Int
forall a. AtLeast n t a -> [a]
forall a. (a -> a -> a) -> AtLeast n t a -> a
forall m a. Monoid m => (a -> m) -> AtLeast n t a -> m
forall b a. (b -> a -> b) -> b -> AtLeast n t a -> b
forall a b. (a -> b -> b) -> b -> AtLeast n t 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 -> Int)
-> (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 :: forall a. Num a => AtLeast n t a -> a
$cproduct :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtLeast n t a -> a
sum :: forall a. Num a => AtLeast n t a -> a
$csum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtLeast n t a -> a
minimum :: forall a. Ord a => AtLeast n t a -> a
$cminimum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtLeast n t a -> a
maximum :: forall a. Ord a => AtLeast n t a -> a
$cmaximum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtLeast n t a -> a
elem :: forall a. Eq a => a -> AtLeast n t a -> Bool
$celem :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> AtLeast n t a -> Bool
length :: forall a. AtLeast n t a -> Int
$clength :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> Int
null :: forall a. AtLeast n t a -> Bool
$cnull :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> Bool
toList :: forall a. AtLeast n t a -> [a]
$ctoList :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtLeast n t a -> [a]
foldl1 :: forall a. (a -> a -> a) -> AtLeast n t a -> a
$cfoldl1 :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtLeast n t a -> a
foldr1 :: forall a. (a -> a -> a) -> AtLeast n t a -> a
$cfoldr1 :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtLeast n t a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> AtLeast n t a -> b
$cfoldl' :: forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtLeast n t a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AtLeast n t a -> b
$cfoldl :: forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtLeast n t a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AtLeast n t a -> b
$cfoldr' :: forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtLeast n t a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AtLeast n t a -> b
$cfoldr :: forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtLeast n t a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> AtLeast n t a -> m
$cfoldMap' :: forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtLeast n t a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AtLeast n t a -> m
$cfoldMap :: forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtLeast n t a -> m
fold :: forall m. Monoid m => AtLeast n t m -> m
$cfold :: forall (n :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
AtLeast n t m -> m
Foldable, forall {n :: Nat} {t :: * -> *}.
Traversable t =>
Functor (AtLeast n t)
forall {n :: Nat} {t :: * -> *}.
Traversable t =>
Foldable (AtLeast n t)
forall (n :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
AtLeast n t (m a) -> m (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
AtLeast n t (f a) -> f (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> AtLeast n t a -> m (AtLeast n t b)
forall (n :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> AtLeast n t a -> f (AtLeast n t 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 (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtLeast n t a -> f (AtLeast n t b)
sequence :: forall (m :: * -> *) a.
Monad m =>
AtLeast n t (m a) -> m (AtLeast n t a)
$csequence :: forall (n :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
AtLeast n t (m a) -> m (AtLeast n t a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AtLeast n t a -> m (AtLeast n t b)
$cmapM :: forall (n :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> AtLeast n t a -> m (AtLeast n t b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AtLeast n t (f a) -> f (AtLeast n t a)
$csequenceA :: forall (n :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
AtLeast n t (f a) -> f (AtLeast n t a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtLeast n t a -> f (AtLeast n t b)
$ctraverse :: forall (n :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> AtLeast n t a -> f (AtLeast n t b)
Traversable, NonEmpty (AtLeast n t a) -> AtLeast n t a
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (AtLeast n t a) -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> AtLeast n t a -> AtLeast n t a
forall b. Integral b => b -> AtLeast n t a -> AtLeast n t a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> AtLeast n t a -> AtLeast n t a
$cstimes :: forall (n :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> AtLeast n t a -> AtLeast n t a
sconcat :: NonEmpty (AtLeast n t a) -> AtLeast n t a
$csconcat :: forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (AtLeast n t a) -> AtLeast n t a
<> :: AtLeast n t a -> AtLeast n t a -> AtLeast n t a
$c<> :: forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
Semigroup, AtLeast n t a
[AtLeast n t a] -> AtLeast n t a
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
forall {n :: Nat} {t :: * -> *} {a}.
Monoid (t a) =>
Semigroup (AtLeast n t a)
forall (n :: Nat) (t :: * -> *) a. Monoid (t a) => AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[AtLeast n t a] -> AtLeast n t a
forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [AtLeast n t a] -> AtLeast n t a
$cmconcat :: forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[AtLeast n t a] -> AtLeast n t a
mappend :: AtLeast n t a -> AtLeast n t a -> AtLeast n t a
$cmappend :: forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
AtLeast n t a -> AtLeast n t a -> AtLeast n t a
mempty :: AtLeast n t a
$cmempty :: forall (n :: Nat) (t :: * -> *) a. Monoid (t a) => AtLeast n t a
Monoid)
instance
( UnfoldableR p t
, Monoid (t a)
, Arbitrary a
, KnownNat n
, p a
) => Arbitrary (AtLeast (n :: Nat) t a) where
arbitrary :: Gen (AtLeast n t a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let n' :: Int
n' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
n', forall a. Ord a => a -> a -> a
max Int
s Int
n')
t a
ts <- forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (t :: * -> *) a. t a -> AtLeast n t a
AtLeast t a
ts)
instance {-# OVERLAPPING #-}
( Arbitrary a
, Ord a
, UnfoldableR Unit []
, Unit a
, KnownNat n) => Arbitrary (AtLeast (n :: Nat) OrderedList a) where
arbitrary :: Gen (AtLeast n OrderedList a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let n' :: Int
n' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
mkOrd :: [a] -> OrderedList a
mkOrd = forall a. [a] -> OrderedList a
Ordered forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
L.sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
n', forall a. Ord a => a -> a -> a
max Int
s Int
n')
OrderedList a
ts <- [a] -> OrderedList a
mkOrd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (t :: * -> *) a. t a -> AtLeast n t a
AtLeast OrderedList a
ts)
newtype AtMost (n :: Nat) t a = AtMost
{ forall (n :: Nat) (t :: * -> *) a. AtMost n t a -> t a
getAtMost :: t a
} deriving (Int -> AtMost n t a -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> AtMost n t a -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
[AtMost n t a] -> ShowS
forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
AtMost n t a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AtMost n t a] -> ShowS
$cshowList :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
[AtMost n t a] -> ShowS
show :: AtMost n t a -> String
$cshow :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
AtMost n t a -> String
showsPrec :: Int -> AtMost n t a -> ShowS
$cshowsPrec :: forall (n :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> AtMost n t a -> ShowS
Show, ReadPrec [AtMost n t a]
ReadPrec (AtMost n t a)
ReadS [AtMost n t a]
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [AtMost n t a]
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [AtMost n t a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AtMost n t a]
$creadListPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [AtMost n t a]
readPrec :: ReadPrec (AtMost n t a)
$creadPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (AtMost n t a)
readList :: ReadS [AtMost n t a]
$creadList :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [AtMost n t a]
readsPrec :: Int -> ReadS (AtMost n t a)
$creadsPrec :: forall (n :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (AtMost n t a)
Read, AtMost n t a -> AtMost n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtMost n t a -> AtMost n t a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtMost n t a -> AtMost n t a -> Bool
$c/= :: forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtMost n t a -> AtMost n t a -> Bool
== :: AtMost n t a -> AtMost n t a -> Bool
$c== :: forall (n :: Nat) (t :: * -> *) a.
Eq (t a) =>
AtMost n t a -> AtMost n t a -> Bool
Eq, AtMost n t a -> AtMost n t a -> Bool
AtMost n t a -> AtMost n t a -> Ordering
AtMost n t a -> AtMost n t a -> AtMost n t a
forall {n :: Nat} {t :: * -> *} {a}. Ord (t a) => Eq (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Ordering
forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t 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
min :: AtMost n t a -> AtMost n t a -> AtMost n t a
$cmin :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
max :: AtMost n t a -> AtMost n t a -> AtMost n t a
$cmax :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
>= :: AtMost n t a -> AtMost n t a -> Bool
$c>= :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Bool
> :: AtMost n t a -> AtMost n t a -> Bool
$c> :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Bool
<= :: AtMost n t a -> AtMost n t a -> Bool
$c<= :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Bool
< :: AtMost n t a -> AtMost n t a -> Bool
$c< :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Bool
compare :: AtMost n t a -> AtMost n t a -> Ordering
$ccompare :: forall (n :: Nat) (t :: * -> *) a.
Ord (t a) =>
AtMost n t a -> AtMost n t a -> Ordering
Ord, Int -> AtMost n t a
AtMost n t a -> Int
AtMost n t a -> [AtMost n t a]
AtMost n t a -> AtMost n t a
AtMost n t a -> AtMost n t a -> [AtMost n t a]
AtMost n t a -> AtMost n t a -> AtMost n t a -> [AtMost n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> Int
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> [AtMost n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a -> [AtMost n t a]
forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a -> [AtMost n t a]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AtMost n t a -> AtMost n t a -> AtMost n t a -> [AtMost n t a]
$cenumFromThenTo :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a -> [AtMost n t a]
enumFromTo :: AtMost n t a -> AtMost n t a -> [AtMost n t a]
$cenumFromTo :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a -> [AtMost n t a]
enumFromThen :: AtMost n t a -> AtMost n t a -> [AtMost n t a]
$cenumFromThen :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a -> [AtMost n t a]
enumFrom :: AtMost n t a -> [AtMost n t a]
$cenumFrom :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> [AtMost n t a]
fromEnum :: AtMost n t a -> Int
$cfromEnum :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> Int
toEnum :: Int -> AtMost n t a
$ctoEnum :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> AtMost n t a
pred :: AtMost n t a -> AtMost n t a
$cpred :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a
succ :: AtMost n t a -> AtMost n t a
$csucc :: forall (n :: Nat) (t :: * -> *) a.
Enum (t a) =>
AtMost n t a -> AtMost n t a
Enum, AtMost n t a -> DataType
AtMost n t a -> Constr
forall {n :: Nat} {t :: * -> *} {a}.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Typeable (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtMost n t a -> DataType
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtMost n t a -> Constr
forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> AtMost n t a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> AtMost n t a -> u
forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> AtMost n t a -> [u]
forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Monad m) =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtMost n t a -> c (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AtMost n t a))
forall (n :: Nat) (t :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtMost n t a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtMost n t a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtMost n t a -> c (AtMost n t a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
$cgmapMo :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
$cgmapMp :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
$cgmapM :: forall (n :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Monad m) =>
(forall d. Data d => d -> m d) -> AtMost n t a -> m (AtMost n t a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AtMost n t a -> u
$cgmapQi :: forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> AtMost n t a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> AtMost n t a -> [u]
$cgmapQ :: forall (n :: Nat) (t :: * -> *) a u.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> AtMost n t a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
$cgmapQr :: forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
$cgmapQl :: forall (n :: Nat) (t :: * -> *) a r r'.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AtMost n t a -> r
gmapT :: (forall b. Data b => b -> b) -> AtMost n t a -> AtMost n t a
$cgmapT :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> AtMost n t a -> AtMost n t a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtMost n t a))
$cdataCast2 :: forall (n :: Nat) (t :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AtMost n t a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (AtMost n t a))
$cdataCast1 :: forall (n :: Nat) (t :: * -> *) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AtMost n t a))
dataTypeOf :: AtMost n t a -> DataType
$cdataTypeOf :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtMost n t a -> DataType
toConstr :: AtMost n t a -> Constr
$ctoConstr :: forall (n :: Nat) (t :: * -> *) a.
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
AtMost n t a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtMost n t a)
$cgunfold :: forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AtMost n t a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtMost n t a -> c (AtMost n t a)
$cgfoldl :: forall (n :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AtMost n t a -> c (AtMost n t a)
Data, Typeable, forall (n :: Nat) (t :: * -> *) a x.
Rep (AtMost n t a) x -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a x.
AtMost n t a -> Rep (AtMost n t a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (n :: Nat) (t :: * -> *) a x.
Rep (AtMost n t a) x -> AtMost n t a
$cfrom :: forall (n :: Nat) (t :: * -> *) a x.
AtMost n t a -> Rep (AtMost n t a) x
Generic, forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
a -> AtMost n t b -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> AtMost n t a -> AtMost n t b
forall a b. a -> AtMost n t b -> AtMost n t a
forall a b. (a -> b) -> AtMost n t a -> AtMost n t b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> AtMost n t b -> AtMost n t a
$c<$ :: forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
a -> AtMost n t b -> AtMost n t a
fmap :: forall a b. (a -> b) -> AtMost n t a -> AtMost n t b
$cfmap :: forall (n :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> AtMost n t a -> AtMost n t b
Functor
, forall {n :: Nat} {t :: * -> *}.
Applicative t =>
Functor (AtMost n t)
forall (n :: Nat) (t :: * -> *) a.
Applicative t =>
a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t a -> AtMost n t b -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t a -> AtMost n t b -> AtMost n t b
forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t (a -> b) -> AtMost n t a -> AtMost n t b
forall (n :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c) -> AtMost n t a -> AtMost n t b -> AtMost n t c
forall a. a -> AtMost n t a
forall a b. AtMost n t a -> AtMost n t b -> AtMost n t a
forall a b. AtMost n t a -> AtMost n t b -> AtMost n t b
forall a b. AtMost n t (a -> b) -> AtMost n t a -> AtMost n t b
forall a b c.
(a -> b -> c) -> AtMost n t a -> AtMost n t b -> AtMost n t c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. AtMost n t a -> AtMost n t b -> AtMost n t a
$c<* :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t a -> AtMost n t b -> AtMost n t a
*> :: forall a b. AtMost n t a -> AtMost n t b -> AtMost n t b
$c*> :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t a -> AtMost n t b -> AtMost n t b
liftA2 :: forall a b c.
(a -> b -> c) -> AtMost n t a -> AtMost n t b -> AtMost n t c
$cliftA2 :: forall (n :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c) -> AtMost n t a -> AtMost n t b -> AtMost n t c
<*> :: forall a b. AtMost n t (a -> b) -> AtMost n t a -> AtMost n t b
$c<*> :: forall (n :: Nat) (t :: * -> *) a b.
Applicative t =>
AtMost n t (a -> b) -> AtMost n t a -> AtMost n t b
pure :: forall a. a -> AtMost n t a
$cpure :: forall (n :: Nat) (t :: * -> *) a.
Applicative t =>
a -> AtMost n t a
Applicative, forall {n :: Nat} {t :: * -> *}.
Monad t =>
Applicative (AtMost n t)
forall (n :: Nat) (t :: * -> *) a. Monad t => a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtMost n t a -> AtMost n t b -> AtMost n t b
forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtMost n t a -> (a -> AtMost n t b) -> AtMost n t b
forall a. a -> AtMost n t a
forall a b. AtMost n t a -> AtMost n t b -> AtMost n t b
forall a b. AtMost n t a -> (a -> AtMost n t b) -> AtMost n t b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> AtMost n t a
$creturn :: forall (n :: Nat) (t :: * -> *) a. Monad t => a -> AtMost n t a
>> :: forall a b. AtMost n t a -> AtMost n t b -> AtMost n t b
$c>> :: forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtMost n t a -> AtMost n t b -> AtMost n t b
>>= :: forall a b. AtMost n t a -> (a -> AtMost n t b) -> AtMost n t b
$c>>= :: forall (n :: Nat) (t :: * -> *) a b.
Monad t =>
AtMost n t a -> (a -> AtMost n t b) -> AtMost n t b
Monad, forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> AtMost n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtMost n t a -> a
forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtMost n t a -> a
forall (n :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
AtMost n t m -> m
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> Bool
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> Int
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> [a]
forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtMost n t a -> a
forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtMost n t a -> m
forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtMost n t a -> b
forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtMost n t a -> b
forall a. Eq a => a -> AtMost n t a -> Bool
forall a. Num a => AtMost n t a -> a
forall a. Ord a => AtMost n t a -> a
forall m. Monoid m => AtMost n t m -> m
forall a. AtMost n t a -> Bool
forall a. AtMost n t a -> Int
forall a. AtMost n t a -> [a]
forall a. (a -> a -> a) -> AtMost n t a -> a
forall m a. Monoid m => (a -> m) -> AtMost n t a -> m
forall b a. (b -> a -> b) -> b -> AtMost n t a -> b
forall a b. (a -> b -> b) -> b -> AtMost n t 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 -> Int)
-> (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 :: forall a. Num a => AtMost n t a -> a
$cproduct :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtMost n t a -> a
sum :: forall a. Num a => AtMost n t a -> a
$csum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
AtMost n t a -> a
minimum :: forall a. Ord a => AtMost n t a -> a
$cminimum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtMost n t a -> a
maximum :: forall a. Ord a => AtMost n t a -> a
$cmaximum :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
AtMost n t a -> a
elem :: forall a. Eq a => a -> AtMost n t a -> Bool
$celem :: forall (n :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> AtMost n t a -> Bool
length :: forall a. AtMost n t a -> Int
$clength :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> Int
null :: forall a. AtMost n t a -> Bool
$cnull :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> Bool
toList :: forall a. AtMost n t a -> [a]
$ctoList :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
AtMost n t a -> [a]
foldl1 :: forall a. (a -> a -> a) -> AtMost n t a -> a
$cfoldl1 :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtMost n t a -> a
foldr1 :: forall a. (a -> a -> a) -> AtMost n t a -> a
$cfoldr1 :: forall (n :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> AtMost n t a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> AtMost n t a -> b
$cfoldl' :: forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtMost n t a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AtMost n t a -> b
$cfoldl :: forall (n :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> AtMost n t a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AtMost n t a -> b
$cfoldr' :: forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtMost n t a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AtMost n t a -> b
$cfoldr :: forall (n :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> AtMost n t a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> AtMost n t a -> m
$cfoldMap' :: forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtMost n t a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AtMost n t a -> m
$cfoldMap :: forall (n :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> AtMost n t a -> m
fold :: forall m. Monoid m => AtMost n t m -> m
$cfold :: forall (n :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
AtMost n t m -> m
Foldable, forall {n :: Nat} {t :: * -> *}.
Traversable t =>
Functor (AtMost n t)
forall {n :: Nat} {t :: * -> *}.
Traversable t =>
Foldable (AtMost n t)
forall (n :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
AtMost n t (m a) -> m (AtMost n t a)
forall (n :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
AtMost n t (f a) -> f (AtMost n t a)
forall (n :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> AtMost n t a -> m (AtMost n t b)
forall (n :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> AtMost n t a -> f (AtMost n t 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 (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtMost n t a -> f (AtMost n t b)
sequence :: forall (m :: * -> *) a.
Monad m =>
AtMost n t (m a) -> m (AtMost n t a)
$csequence :: forall (n :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
AtMost n t (m a) -> m (AtMost n t a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AtMost n t a -> m (AtMost n t b)
$cmapM :: forall (n :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> AtMost n t a -> m (AtMost n t b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AtMost n t (f a) -> f (AtMost n t a)
$csequenceA :: forall (n :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
AtMost n t (f a) -> f (AtMost n t a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtMost n t a -> f (AtMost n t b)
$ctraverse :: forall (n :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> AtMost n t a -> f (AtMost n t b)
Traversable, NonEmpty (AtMost n t a) -> AtMost n t a
AtMost n t a -> AtMost n t a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (AtMost n t a) -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> AtMost n t a -> AtMost n t a
forall b. Integral b => b -> AtMost n t a -> AtMost n t a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> AtMost n t a -> AtMost n t a
$cstimes :: forall (n :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> AtMost n t a -> AtMost n t a
sconcat :: NonEmpty (AtMost n t a) -> AtMost n t a
$csconcat :: forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (AtMost n t a) -> AtMost n t a
<> :: AtMost n t a -> AtMost n t a -> AtMost n t a
$c<> :: forall (n :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
Semigroup, AtMost n t a
[AtMost n t a] -> AtMost n t a
AtMost n t a -> AtMost n t a -> AtMost n t a
forall {n :: Nat} {t :: * -> *} {a}.
Monoid (t a) =>
Semigroup (AtMost n t a)
forall (n :: Nat) (t :: * -> *) a. Monoid (t a) => AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[AtMost n t a] -> AtMost n t a
forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [AtMost n t a] -> AtMost n t a
$cmconcat :: forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[AtMost n t a] -> AtMost n t a
mappend :: AtMost n t a -> AtMost n t a -> AtMost n t a
$cmappend :: forall (n :: Nat) (t :: * -> *) a.
Monoid (t a) =>
AtMost n t a -> AtMost n t a -> AtMost n t a
mempty :: AtMost n t a
$cmempty :: forall (n :: Nat) (t :: * -> *) a. Monoid (t a) => AtMost n t a
Monoid)
instance ( UnfoldableR p t
, Monoid (t a)
, Arbitrary a
, KnownNat m
, p a
) => Arbitrary (AtMost (m :: Nat) t a) where
arbitrary :: Gen (AtMost m t a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let m' :: Int
m' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy m))
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
0, forall a. Ord a => a -> a -> a
min Int
m' Int
s)
t a
ts <- forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (t :: * -> *) a. t a -> AtMost n t a
AtMost t a
ts)
instance {-# OVERLAPPING #-}
( Arbitrary a
, Ord a
, UnfoldableR Unit []
, Unit a
, KnownNat n) => Arbitrary (AtMost (n :: Nat) OrderedList a) where
arbitrary :: Gen (AtMost n OrderedList a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let m' :: Int
m' = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n)
mkOrd :: [a] -> OrderedList a
mkOrd = forall a. [a] -> OrderedList a
Ordered forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
L.sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
0, forall a. Ord a => a -> a -> a
min Int
m' Int
s)
OrderedList a
ts <- [a] -> OrderedList a
mkOrd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (t :: * -> *) a. t a -> AtMost n t a
AtMost OrderedList a
ts)
newtype Between (n :: Nat) (m :: Nat) t a = Between
{ forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Between n m t a -> t a
getBetween :: t a
} deriving (Int -> Between n m t a -> ShowS
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> Between n m t a -> ShowS
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
[Between n m t a] -> ShowS
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
Between n m t a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Between n m t a] -> ShowS
$cshowList :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
[Between n m t a] -> ShowS
show :: Between n m t a -> String
$cshow :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
Between n m t a -> String
showsPrec :: Int -> Between n m t a -> ShowS
$cshowsPrec :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Show (t a) =>
Int -> Between n m t a -> ShowS
Show, ReadPrec [Between n m t a]
ReadPrec (Between n m t a)
ReadS [Between n m t a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [Between n m t a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [Between n m t a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Between n m t a]
$creadListPrec :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec [Between n m t a]
readPrec :: ReadPrec (Between n m t a)
$creadPrec :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadPrec (Between n m t a)
readList :: ReadS [Between n m t a]
$creadList :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
ReadS [Between n m t a]
readsPrec :: Int -> ReadS (Between n m t a)
$creadsPrec :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Read (t a) =>
Int -> ReadS (Between n m t a)
Read, Between n m t a -> Between n m t a -> Bool
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Eq (t a) =>
Between n m t a -> Between n m t a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Between n m t a -> Between n m t a -> Bool
$c/= :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Eq (t a) =>
Between n m t a -> Between n m t a -> Bool
== :: Between n m t a -> Between n m t a -> Bool
$c== :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Eq (t a) =>
Between n m t a -> Between n m t a -> Bool
Eq, Between n m t a -> Between n m t a -> Bool
Between n m t a -> Between n m t a -> Ordering
Between n m t a -> Between n m t a -> Between n m t a
forall {n :: Nat} {m :: Nat} {t :: * -> *} {a}.
Ord (t a) =>
Eq (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Bool
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Ordering
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Between n m t 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
min :: Between n m t a -> Between n m t a -> Between n m t a
$cmin :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
max :: Between n m t a -> Between n m t a -> Between n m t a
$cmax :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
>= :: Between n m t a -> Between n m t a -> Bool
$c>= :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Bool
> :: Between n m t a -> Between n m t a -> Bool
$c> :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Bool
<= :: Between n m t a -> Between n m t a -> Bool
$c<= :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Bool
< :: Between n m t a -> Between n m t a -> Bool
$c< :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Bool
compare :: Between n m t a -> Between n m t a -> Ordering
$ccompare :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Ord (t a) =>
Between n m t a -> Between n m t a -> Ordering
Ord, Int -> Between n m t a
Between n m t a -> Int
Between n m t a -> [Between n m t a]
Between n m t a -> Between n m t a
Between n m t a -> Between n m t a -> [Between n m t a]
Between n m t a
-> Between n m t a -> Between n m t a -> [Between n m t a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Int
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> [Between n m t a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a -> [Between n m t a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a
-> Between n m t a -> Between n m t a -> [Between n m t a]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Between n m t a
-> Between n m t a -> Between n m t a -> [Between n m t a]
$cenumFromThenTo :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a
-> Between n m t a -> Between n m t a -> [Between n m t a]
enumFromTo :: Between n m t a -> Between n m t a -> [Between n m t a]
$cenumFromTo :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a -> [Between n m t a]
enumFromThen :: Between n m t a -> Between n m t a -> [Between n m t a]
$cenumFromThen :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a -> [Between n m t a]
enumFrom :: Between n m t a -> [Between n m t a]
$cenumFrom :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> [Between n m t a]
fromEnum :: Between n m t a -> Int
$cfromEnum :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Int
toEnum :: Int -> Between n m t a
$ctoEnum :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Int -> Between n m t a
pred :: Between n m t a -> Between n m t a
$cpred :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a
succ :: Between n m t a -> Between n m t a
$csucc :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Enum (t a) =>
Between n m t a -> Between n m t a
Enum, Between n m t a -> DataType
Between n m t a -> Constr
forall {n :: Nat} {m :: Nat} {t :: * -> *} {a}.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Typeable (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Between n m t a -> DataType
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Between n m t a -> Constr
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> Between n m t a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a u.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> Between n m t a -> u
forall (n :: Nat) (m :: Nat) (t :: * -> *) a u.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> Between n m t a -> [u]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a r r'.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
forall (n :: Nat) (m :: Nat) (t :: * -> *) a r r'.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Monad m) =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Between n m t a -> c (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (t :: * -> *)
(c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Between n m t a))
forall (n :: Nat) (m :: Nat) (t :: * -> *) a (t :: * -> * -> *)
(c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Between n m t a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Between n m t a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Between n m t a -> c (Between n m t a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
$cgmapMo :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
$cgmapMp :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
$cgmapM :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (m :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Monad m) =>
(forall d. Data d => d -> m d)
-> Between n m t a -> m (Between n m t a)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> Between n m t a -> u
$cgmapQi :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a u.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Int -> (forall d. Data d => d -> u) -> Between n m t a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Between n m t a -> [u]
$cgmapQ :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a u.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall d. Data d => d -> u) -> Between n m t a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
$cgmapQr :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a r r'.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
$cgmapQl :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a r r'.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Between n m t a -> r
gmapT :: (forall b. Data b => b -> b) -> Between n m t a -> Between n m t a
$cgmapT :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall b. Data b => b -> b) -> Between n m t a -> Between n m t a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Between n m t a))
$cdataCast2 :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (t :: * -> * -> *)
(c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Between n m t a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Between n m t a))
$cdataCast1 :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (t :: * -> *)
(c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a),
Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Between n m t a))
dataTypeOf :: Between n m t a -> DataType
$cdataTypeOf :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Between n m t a -> DataType
toConstr :: Between n m t a -> Constr
$ctoConstr :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
Between n m t a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Between n m t a)
$cgunfold :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Between n m t a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Between n m t a -> c (Between n m t a)
$cgfoldl :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a (c :: * -> *).
(KnownNat n, KnownNat m, Typeable t, Typeable a, Data (t a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Between n m t a -> c (Between n m t a)
Data, Typeable, forall (n :: Nat) (m :: Nat) (t :: * -> *) a x.
Rep (Between n m t a) x -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a x.
Between n m t a -> Rep (Between n m t a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a x.
Rep (Between n m t a) x -> Between n m t a
$cfrom :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a x.
Between n m t a -> Rep (Between n m t a) x
Generic, forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Functor t =>
a -> Between n m t b -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> Between n m t a -> Between n m t b
forall a b. a -> Between n m t b -> Between n m t a
forall a b. (a -> b) -> Between n m t a -> Between n m t b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Between n m t b -> Between n m t a
$c<$ :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Functor t =>
a -> Between n m t b -> Between n m t a
fmap :: forall a b. (a -> b) -> Between n m t a -> Between n m t b
$cfmap :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Functor t =>
(a -> b) -> Between n m t a -> Between n m t b
Functor
, forall {n :: Nat} {m :: Nat} {t :: * -> *}.
Applicative t =>
Functor (Between n m t)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Applicative t =>
a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t a -> Between n m t b -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t a -> Between n m t b -> Between n m t b
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t (a -> b) -> Between n m t a -> Between n m t b
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c)
-> Between n m t a -> Between n m t b -> Between n m t c
forall a. a -> Between n m t a
forall a b. Between n m t a -> Between n m t b -> Between n m t a
forall a b. Between n m t a -> Between n m t b -> Between n m t b
forall a b.
Between n m t (a -> b) -> Between n m t a -> Between n m t b
forall a b c.
(a -> b -> c)
-> Between n m t a -> Between n m t b -> Between n m t c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Between n m t a -> Between n m t b -> Between n m t a
$c<* :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t a -> Between n m t b -> Between n m t a
*> :: forall a b. Between n m t a -> Between n m t b -> Between n m t b
$c*> :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t a -> Between n m t b -> Between n m t b
liftA2 :: forall a b c.
(a -> b -> c)
-> Between n m t a -> Between n m t b -> Between n m t c
$cliftA2 :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b c.
Applicative t =>
(a -> b -> c)
-> Between n m t a -> Between n m t b -> Between n m t c
<*> :: forall a b.
Between n m t (a -> b) -> Between n m t a -> Between n m t b
$c<*> :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Applicative t =>
Between n m t (a -> b) -> Between n m t a -> Between n m t b
pure :: forall a. a -> Between n m t a
$cpure :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Applicative t =>
a -> Between n m t a
Applicative, forall {n :: Nat} {m :: Nat} {t :: * -> *}.
Monad t =>
Applicative (Between n m t)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monad t =>
a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Monad t =>
Between n m t a -> Between n m t b -> Between n m t b
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Monad t =>
Between n m t a -> (a -> Between n m t b) -> Between n m t b
forall a. a -> Between n m t a
forall a b. Between n m t a -> Between n m t b -> Between n m t b
forall a b.
Between n m t a -> (a -> Between n m t b) -> Between n m t b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Between n m t a
$creturn :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monad t =>
a -> Between n m t a
>> :: forall a b. Between n m t a -> Between n m t b -> Between n m t b
$c>> :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Monad t =>
Between n m t a -> Between n m t b -> Between n m t b
>>= :: forall a b.
Between n m t a -> (a -> Between n m t b) -> Between n m t b
$c>>= :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Monad t =>
Between n m t a -> (a -> Between n m t b) -> Between n m t b
Monad, forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> Between n m t a -> Bool
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
Between n m t a -> a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
Between n m t a -> a
forall (n :: Nat) (m :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
Between n m t m -> m
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> Bool
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> Int
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> [a]
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> Between n m t a -> a
forall (n :: Nat) (m :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> Between n m t a -> m
forall (n :: Nat) (m :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> Between n m t a -> b
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> Between n m t a -> b
forall a. Eq a => a -> Between n m t a -> Bool
forall a. Num a => Between n m t a -> a
forall a. Ord a => Between n m t a -> a
forall m. Monoid m => Between n m t m -> m
forall a. Between n m t a -> Bool
forall a. Between n m t a -> Int
forall a. Between n m t a -> [a]
forall a. (a -> a -> a) -> Between n m t a -> a
forall m a. Monoid m => (a -> m) -> Between n m t a -> m
forall b a. (b -> a -> b) -> b -> Between n m t a -> b
forall a b. (a -> b -> b) -> b -> Between n m t 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 -> Int)
-> (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 :: forall a. Num a => Between n m t a -> a
$cproduct :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
Between n m t a -> a
sum :: forall a. Num a => Between n m t a -> a
$csum :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Num a) =>
Between n m t a -> a
minimum :: forall a. Ord a => Between n m t a -> a
$cminimum :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
Between n m t a -> a
maximum :: forall a. Ord a => Between n m t a -> a
$cmaximum :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Ord a) =>
Between n m t a -> a
elem :: forall a. Eq a => a -> Between n m t a -> Bool
$celem :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> Between n m t a -> Bool
length :: forall a. Between n m t a -> Int
$clength :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> Int
null :: forall a. Between n m t a -> Bool
$cnull :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> Bool
toList :: forall a. Between n m t a -> [a]
$ctoList :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
Between n m t a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Between n m t a -> a
$cfoldl1 :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> Between n m t a -> a
foldr1 :: forall a. (a -> a -> a) -> Between n m t a -> a
$cfoldr1 :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Foldable t =>
(a -> a -> a) -> Between n m t a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Between n m t a -> b
$cfoldl' :: forall (n :: Nat) (m :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> Between n m t a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Between n m t a -> b
$cfoldl :: forall (n :: Nat) (m :: Nat) (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> Between n m t a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Between n m t a -> b
$cfoldr' :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> Between n m t a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Between n m t a -> b
$cfoldr :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> Between n m t a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Between n m t a -> m
$cfoldMap' :: forall (n :: Nat) (m :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> Between n m t a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Between n m t a -> m
$cfoldMap :: forall (n :: Nat) (m :: Nat) (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> Between n m t a -> m
fold :: forall m. Monoid m => Between n m t m -> m
$cfold :: forall (n :: Nat) (m :: Nat) (t :: * -> *) m.
(Foldable t, Monoid m) =>
Between n m t m -> m
Foldable, forall {n :: Nat} {m :: Nat} {t :: * -> *}.
Traversable t =>
Functor (Between n m t)
forall {n :: Nat} {m :: Nat} {t :: * -> *}.
Traversable t =>
Foldable (Between n m t)
forall (n :: Nat) (m :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
Between n m t (m a) -> m (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
Between n m t (f a) -> f (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> Between n m t a -> m (Between n m t b)
forall (n :: Nat) (m :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> Between n m t a -> f (Between n m t 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 (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Between n m t a -> f (Between n m t b)
sequence :: forall (m :: * -> *) a.
Monad m =>
Between n m t (m a) -> m (Between n m t a)
$csequence :: forall (n :: Nat) (m :: Nat) (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
Between n m t (m a) -> m (Between n m t a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Between n m t a -> m (Between n m t b)
$cmapM :: forall (n :: Nat) (m :: Nat) (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> Between n m t a -> m (Between n m t b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Between n m t (f a) -> f (Between n m t a)
$csequenceA :: forall (n :: Nat) (m :: Nat) (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
Between n m t (f a) -> f (Between n m t a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Between n m t a -> f (Between n m t b)
$ctraverse :: forall (n :: Nat) (m :: Nat) (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> Between n m t a -> f (Between n m t b)
Traversable, NonEmpty (Between n m t a) -> Between n m t a
Between n m t a -> Between n m t a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (Between n m t a) -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> Between n m t a -> Between n m t a
forall b. Integral b => b -> Between n m t a -> Between n m t a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Between n m t a -> Between n m t a
$cstimes :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a b.
(Semigroup (t a), Integral b) =>
b -> Between n m t a -> Between n m t a
sconcat :: NonEmpty (Between n m t a) -> Between n m t a
$csconcat :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
NonEmpty (Between n m t a) -> Between n m t a
<> :: Between n m t a -> Between n m t a -> Between n m t a
$c<> :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Semigroup (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
Semigroup, Between n m t a
[Between n m t a] -> Between n m t a
Between n m t a -> Between n m t a -> Between n m t a
forall {n :: Nat} {m :: Nat} {t :: * -> *} {a}.
Monoid (t a) =>
Semigroup (Between n m t a)
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[Between n m t a] -> Between n m t a
forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Between n m t a] -> Between n m t a
$cmconcat :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
[Between n m t a] -> Between n m t a
mappend :: Between n m t a -> Between n m t a -> Between n m t a
$cmappend :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
Between n m t a -> Between n m t a -> Between n m t a
mempty :: Between n m t a
$cmempty :: forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
Monoid (t a) =>
Between n m t a
Monoid)
instance ( UnfoldableR p t
, Monoid (t a)
, Arbitrary a
, KnownNat n
, KnownNat m
, p a
) => Arbitrary (Between (n :: Nat) (m :: Nat) t a) where
arbitrary :: Gen (Between n m t a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let n' :: Int
n' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
m' :: Int
m' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy m))
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
n', forall a. Ord a => a -> a -> a
max Int
n' (forall a. Ord a => a -> a -> a
min Int
m' Int
s))
t a
ts <- forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
t a -> Between n m t a
Between t a
ts)
instance {-# OVERLAPPING #-}
( Arbitrary a
, Ord a
, KnownNat n
, UnfoldableR Unit []
, Unit a
, KnownNat m) => Arbitrary (Between (n :: Nat) (m :: Nat) OrderedList a) where
arbitrary :: Gen (Between n m OrderedList a)
arbitrary = forall a. (Int -> Gen a) -> Gen a
sized forall a b. (a -> b) -> a -> b
$ \Int
s -> do
let n' :: Int
n' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
m' :: Int
m' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy m))
mkOrd :: [a] -> OrderedList a
mkOrd = forall a. [a] -> OrderedList a
Ordered forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
L.sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> Constraint) (t :: * -> *) a.
(UnfoldableR p t, p a) =>
[a] -> Maybe (t a)
fromList
Int
k <- forall a. Random a => (a, a) -> Gen a
choose (Int
n', forall a. Ord a => a -> a -> a
max Int
n' (forall a. Ord a => a -> a -> a
min Int
m' Int
s))
OrderedList a
ts <- [a] -> OrderedList a
mkOrd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
k forall a. Arbitrary a => Gen a
arbitrary
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) (m :: Nat) (t :: * -> *) a.
t a -> Between n m t a
Between OrderedList a
ts)
type NonMempty = AtLeast 1