Agda-2.6.2.2.20221106: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Utils.List2

Description

Lists of length at least 2.

Import as: import Agda.Utils.List2 (List2(List2)) import qualified Agda.Utils.List2 as List2

Synopsis

Documentation

data List2 a Source #

Lists of length ≥2.

Constructors

List2 a a [a] 

Instances

Instances details
Foldable List2 Source # 
Instance details

Defined in Agda.Utils.List2

Methods

fold :: Monoid m => List2 m -> m #

foldMap :: Monoid m => (a -> m) -> List2 a -> m #

foldMap' :: Monoid m => (a -> m) -> List2 a -> m #

foldr :: (a -> b -> b) -> b -> List2 a -> b #

foldr' :: (a -> b -> b) -> b -> List2 a -> b #

foldl :: (b -> a -> b) -> b -> List2 a -> b #

foldl' :: (b -> a -> b) -> b -> List2 a -> b #

foldr1 :: (a -> a -> a) -> List2 a -> a #

foldl1 :: (a -> a -> a) -> List2 a -> a #

toList :: List2 a -> [a] #

null :: List2 a -> Bool #

length :: List2 a -> Int #

elem :: Eq a => a -> List2 a -> Bool #

maximum :: Ord a => List2 a -> a #

minimum :: Ord a => List2 a -> a #

sum :: Num a => List2 a -> a #

product :: Num a => List2 a -> a #

Traversable List2 Source # 
Instance details

Defined in Agda.Utils.List2

Methods

traverse :: Applicative f => (a -> f b) -> List2 a -> f (List2 b) #

sequenceA :: Applicative f => List2 (f a) -> f (List2 a) #

mapM :: Monad m => (a -> m b) -> List2 a -> m (List2 b) #

sequence :: Monad m => List2 (m a) -> m (List2 a) #

Functor List2 Source # 
Instance details

Defined in Agda.Utils.List2

Methods

fmap :: (a -> b) -> List2 a -> List2 b #

(<$) :: a -> List2 b -> List2 a #

ExprLike a => ExprLike (List2 a) Source # 
Instance details

Defined in Agda.Syntax.Concrete.Generic

Methods

mapExpr :: (Expr -> Expr) -> List2 a -> List2 a Source #

foldExpr :: Monoid m => (Expr -> m) -> List2 a -> m Source #

traverseExpr :: Monad m => (Expr -> m Expr) -> List2 a -> m (List2 a) Source #

CPatternLike p => CPatternLike (List2 p) Source # 
Instance details

Defined in Agda.Syntax.Concrete.Pattern

Methods

foldrCPattern :: Monoid m => (Pattern -> m -> m) -> List2 p -> m Source #

traverseCPatternA :: (Applicative m, Functor m) => (Pattern -> m Pattern -> m Pattern) -> List2 p -> m (List2 p) Source #

traverseCPatternM :: Monad m => (Pattern -> m Pattern) -> (Pattern -> m Pattern) -> List2 p -> m (List2 p) Source #

HasRange a => HasRange (List2 a) Source # 
Instance details

Defined in Agda.Syntax.Position

Methods

getRange :: List2 a -> Range Source #

KillRange a => KillRange (List2 a) Source # 
Instance details

Defined in Agda.Syntax.Position

EmbPrj a => EmbPrj (List2 a) Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Common

Methods

icode :: List2 a -> S Int32 Source #

icod_ :: List2 a -> S Int32 Source #

value :: Int32 -> R (List2 a) Source #

IsList (List2 a) Source #

fromList is unsafe.

Instance details

Defined in Agda.Utils.List2

Associated Types

type Item (List2 a) #

Methods

fromList :: [Item (List2 a)] -> List2 a #

fromListN :: Int -> [Item (List2 a)] -> List2 a #

toList :: List2 a -> [Item (List2 a)] #

Show a => Show (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

Methods

showsPrec :: Int -> List2 a -> ShowS #

show :: List2 a -> String #

showList :: [List2 a] -> ShowS #

NFData a => NFData (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

Methods

rnf :: List2 a -> () #

Eq a => Eq (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

Methods

(==) :: List2 a -> List2 a -> Bool #

(/=) :: List2 a -> List2 a -> Bool #

Ord a => Ord (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

Methods

compare :: List2 a -> List2 a -> Ordering #

(<) :: List2 a -> List2 a -> Bool #

(<=) :: List2 a -> List2 a -> Bool #

(>) :: List2 a -> List2 a -> Bool #

(>=) :: List2 a -> List2 a -> Bool #

max :: List2 a -> List2 a -> List2 a #

min :: List2 a -> List2 a -> List2 a #

type Item (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

type Item (List2 a) = a

fromList1 :: List1 a -> List2 a Source #

Unsafe! O(1).

toList1 :: List2 a -> List1 a Source #

Safe. O(1).

fromListMaybe :: [a] -> Maybe (List2 a) Source #

Safe. O(1).

fromList1Maybe :: List1 a -> Maybe (List2 a) Source #

Safe. O(1).

fromList1Either :: List1 a -> Either a (List2 a) Source #

Any List1 is either a singleton or a List2. O(1).

toList1Either :: Either a (List2 a) -> List1 a Source #

Inverse of fromList1Either. O(1).

cons :: a -> List1 a -> List2 a Source #

O(1).

append :: List1 a -> List1 a -> List2 a Source #

O(length first list).

appendList :: List2 a -> [a] -> List2 a Source #

O(length first list).

head :: List2 a -> a Source #

Safe. O(1).

tail :: List2 a -> List1 a Source #

Safe. O(1).

init :: List2 a -> List1 a Source #

Safe. O(n).

break :: (a -> Bool) -> List2 a -> ([a], [a]) Source #

toList :: IsList l => l -> [Item l] #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.