Safe Haskell | None |
---|---|
Language | Haskell2010 |
Collection size.
For TermSize
see Agda.Syntax.Internal.
Synopsis
- class Sized a where
- data SizedThing a = SizedThing {
- theSize :: !Int
- sizedThing :: a
- sizeThing :: Sized a => a -> SizedThing a
- data Peano
Documentation
The size of a collection (i.e., its length).
Nothing
Strict size computation.
Anti-patterns: size xs == n
where n
is 0
, 1
or another number
that is likely smaller than size xs
.
Similar for size xs >= 1
etc.
Use natSize
instead.
natSize :: a -> Peano Source #
Lazily compute a (possibly infinite) size.
Use when comparing a size against a fixed number.
Instances
data SizedThing a Source #
Thing decorated with its size.
The thing should fit into main memory, thus, the size is an Int
.
SizedThing | |
|
Instances
Null a => Null (SizedThing a) Source # | |
Defined in Agda.Utils.Size empty :: SizedThing a Source # null :: SizedThing a -> Bool Source # | |
Sized (SizedThing a) Source # | Return the cached size. |
Defined in Agda.Utils.Size size :: SizedThing a -> Int Source # natSize :: SizedThing a -> Peano Source # |
sizeThing :: Sized a => a -> SizedThing a Source #
Cache the size of an object.
Instances
Data Peano | |
Defined in Data.Peano gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Peano -> c Peano gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Peano dataTypeOf :: Peano -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Peano) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Peano) gmapT :: (forall b. Data b => b -> b) -> Peano -> Peano gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Peano -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Peano -> r gmapQ :: (forall d. Data d => d -> u) -> Peano -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Peano -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Peano -> m Peano gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Peano -> m Peano gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Peano -> m Peano | |
Bounded Peano | |
Defined in Data.Peano | |
Enum Peano | |
Ix Peano | |
Num Peano | |
Read Peano | |
Defined in Data.Peano | |
Integral Peano | |
Real Peano | |
Defined in Data.Peano toRational :: Peano -> Rational | |
Show Peano | |
Eq Peano | |
Ord Peano | |