| Copyright | (c) Artem Chirkin |
|---|---|
| License | BSD3 |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.Tuple.Strict
Description
Synopsis
- newtype Id a = Id {
- runId :: a
- type Tuple = TypedList Id :: [Type] -> Type
- data TypedList (f :: k -> Type) (xs :: [k]) where
- pattern U :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs
- pattern (:*) :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs
- pattern (:$) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs
- pattern (:!) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs
- pattern Empty :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs
- pattern TypeList :: forall xs. () => RepresentableList xs => TypeList xs
- pattern Cons :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs
- pattern Snoc :: forall f xs. () => forall sy y. SnocList sy y xs => TypedList f sy -> f y -> TypedList f xs
- pattern Reverse :: forall f xs. () => forall sx. ReverseList xs sx => TypedList f sx -> TypedList f xs
- (*$) :: x -> Tuple xs -> Tuple (x :+ xs)
- ($*) :: Tuple xs -> x -> Tuple (xs +: x)
- (*!) :: x -> Tuple xs -> Tuple (x :+ xs)
- (!*) :: Tuple xs -> x -> Tuple (xs +: x)
Documentation
This is an almost complete copy of Identity
by (c) Andy Gill 2001.
Instances
| Monad Id Source # | |
| Functor Id Source # | |
| MonadFix Id Source # | |
Defined in Numeric.Tuple.Strict | |
| Applicative Id Source # | |
| Foldable Id Source # | |
Defined in Numeric.Tuple.Strict Methods fold :: Monoid m => Id m -> m # foldMap :: Monoid m => (a -> m) -> Id a -> m # foldMap' :: Monoid m => (a -> m) -> Id a -> m # foldr :: (a -> b -> b) -> b -> Id a -> b # foldr' :: (a -> b -> b) -> b -> Id a -> b # foldl :: (b -> a -> b) -> b -> Id a -> b # foldl' :: (b -> a -> b) -> b -> Id a -> b # foldr1 :: (a -> a -> a) -> Id a -> a # foldl1 :: (a -> a -> a) -> Id a -> a # elem :: Eq a => a -> Id a -> Bool # maximum :: Ord a => Id a -> a # | |
| Traversable Id Source # | |
| Eq1 Id Source # | |
| Ord1 Id Source # | |
Defined in Numeric.Tuple.Strict | |
| Read1 Id Source # | |
Defined in Numeric.Tuple.Strict | |
| Show1 Id Source # | |
| MonadZip Id Source # | |
| (RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # | |
| Bounded a => Bounded (Id a) Source # | |
| Enum a => Enum (Id a) Source # | |
| All Eq xs => Eq (Tuple xs) Source # | |
| Eq a => Eq (Id a) Source # | |
| Floating a => Floating (Id a) Source # | |
| Fractional a => Fractional (Id a) Source # | |
| Integral a => Integral (Id a) Source # | |
| Data a => Data (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id a -> c (Id a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Id a) # dataTypeOf :: Id a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Id a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Id a)) # gmapT :: (forall b. Data b => b -> b) -> Id a -> Id a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id a -> r # gmapQ :: (forall d. Data d => d -> u) -> Id a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Id a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) # | |
| Num a => Num (Id a) Source # | |
| (All Eq xs, All Ord xs) => Ord (Tuple xs) Source # | Lexicorgaphic ordering; same as normal Haskell lists. |
Defined in Numeric.Tuple.Strict | |
| Ord a => Ord (Id a) Source # | |
| (All Read xs, RepresentableList xs) => Read (Tuple xs) Source # | |
| Read a => Read (Id a) Source # | |
| Real a => Real (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods toRational :: Id a -> Rational # | |
| RealFloat a => RealFloat (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods floatRadix :: Id a -> Integer # floatDigits :: Id a -> Int # floatRange :: Id a -> (Int, Int) # decodeFloat :: Id a -> (Integer, Int) # encodeFloat :: Integer -> Int -> Id a # significand :: Id a -> Id a # scaleFloat :: Int -> Id a -> Id a # isInfinite :: Id a -> Bool # isDenormalized :: Id a -> Bool # isNegativeZero :: Id a -> Bool # | |
| RealFrac a => RealFrac (Id a) Source # | |
| All Show xs => Show (Tuple xs) Source # | |
| Show a => Show (Id a) Source # | |
| Ix a => Ix (Id a) Source # | |
| IsString a => IsString (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods fromString :: String -> Id a # | |
| Generic (Id a) Source # | |
| All Semigroup xs => Semigroup (Tuple xs) Source # | |
| Semigroup a => Semigroup (Id a) Source # | |
| (RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # | |
| Monoid a => Monoid (Id a) Source # | |
| Storable a => Storable (Id a) Source # | |
| Bits a => Bits (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods (.&.) :: Id a -> Id a -> Id a # (.|.) :: Id a -> Id a -> Id a # complement :: Id a -> Id a # shift :: Id a -> Int -> Id a # rotate :: Id a -> Int -> Id a # setBit :: Id a -> Int -> Id a # clearBit :: Id a -> Int -> Id a # complementBit :: Id a -> Int -> Id a # testBit :: Id a -> Int -> Bool # bitSizeMaybe :: Id a -> Maybe Int # shiftL :: Id a -> Int -> Id a # unsafeShiftL :: Id a -> Int -> Id a # shiftR :: Id a -> Int -> Id a # unsafeShiftR :: Id a -> Int -> Id a # rotateL :: Id a -> Int -> Id a # | |
| FiniteBits a => FiniteBits (Id a) Source # | |
Defined in Numeric.Tuple.Strict Methods finiteBitSize :: Id a -> Int # countLeadingZeros :: Id a -> Int # countTrailingZeros :: Id a -> Int # | |
| Generic1 Id Source # | |
| type Rep (Id a) Source # | |
Defined in Numeric.Tuple.Strict | |
| type Rep1 Id Source # | |
Defined in Numeric.Tuple.Strict | |
data TypedList (f :: k -> Type) (xs :: [k]) where Source #
Type-indexed list
Bundled Patterns
| pattern U :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs | Zero-length type list |
| pattern (:*) :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs infixr 5 | Constructing a type-indexed list |
| pattern (:$) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs infixr 5 | Constructing a type-indexed list |
| pattern (:!) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs infixr 5 | Constructing a type-indexed list |
| pattern Empty :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs | Zero-length type list; synonym to |
| pattern TypeList :: forall xs. () => RepresentableList xs => TypeList xs | Pattern matching against this causes |
| pattern Cons :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs | Constructing a type-indexed list in the canonical way |
| pattern Snoc :: forall f xs. () => forall sy y. SnocList sy y xs => TypedList f sy -> f y -> TypedList f xs | Constructing a type-indexed list from the other end |
| pattern Reverse :: forall f xs. () => forall sx. ReverseList xs sx => TypedList f sx -> TypedList f xs | Reverse a typed list |
Instances
| (RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # | |
| (RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # | |
| All Eq xs => Eq (Tuple xs) Source # | |
| All Eq xs => Eq (Tuple xs) Source # | |
| (All Eq xs, All Ord xs) => Ord (Tuple xs) Source # | Lexicorgaphic ordering; same as normal Haskell lists. |
Defined in Numeric.Tuple.Strict | |
| (All Eq xs, All Ord xs) => Ord (Tuple xs) Source # | Lexicorgaphic ordering; same as normal Haskell lists. |
Defined in Numeric.Tuple.Lazy | |
| (All Read xs, RepresentableList xs) => Read (Tuple xs) Source # | |
| (All Read xs, RepresentableList xs) => Read (Tuple xs) Source # | |
| All Show xs => Show (Tuple xs) Source # | |
| All Show xs => Show (Tuple xs) Source # | |
| All Semigroup xs => Semigroup (Tuple xs) Source # | |
| All Semigroup xs => Semigroup (Tuple xs) Source # | |
| (RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # | |
| (RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # | |
| BoundedDims ds => Bounded (Idxs ds) Source # | |
| Dimensions ds => Enum (Idxs ds) Source # |
|
| Eq (Dims ds) Source # | |
| Eq (Dims ds) Source # | |
| Eq (Idxs xs) Source # | |
| Ord (Dims ds) Source # | |
Defined in Numeric.Dimensions.Dim | |
| Ord (Dims ds) Source # | |
Defined in Numeric.Dimensions.Dim | |
| Ord (Idxs xs) Source # | Compare indices by their importance in lexicorgaphic order from the first dimension to the last dimension (the first dimension is the most significant one). Literally, compare a b = compare (listIdxs a) (listIdxs b) This is the same sort == sortOn fromEnum |
Defined in Numeric.Dimensions.Idx | |
| BoundedDims xs => Read (Dims xs) Source # | |
| BoundedDims xs => Read (Idxs xs) Source # | |
| Show (Dims xs) Source # | |
| Show (Idxs xs) Source # | |
| (Typeable k, Typeable f, Typeable xs, All Data (Map f xs)) => Data (TypedList f xs) Source # | Term-level structure of a |
Defined in Numeric.TypedList Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypedList f xs -> c (TypedList f xs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TypedList f xs) # toConstr :: TypedList f xs -> Constr # dataTypeOf :: TypedList f xs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TypedList f xs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypedList f xs)) # gmapT :: (forall b. Data b => b -> b) -> TypedList f xs -> TypedList f xs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r # gmapQ :: (forall d. Data d => d -> u) -> TypedList f xs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypedList f xs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) # | |
| Generic (TypedList f xs) Source # | |
| type Rep (TypedList f xs) Source # | |
Defined in Numeric.TypedList | |
($*) :: Tuple xs -> x -> Tuple (xs +: x) infixl 5 Source #
Grow a tuple on the right. Note, it traverses an element list inside O(n).