Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data NumberAbstract a
- data TypedNumber v a
- unsafeTypedNumber :: NumberAbstract v -> TypedNumber v a
- untypeNumber :: TypedNumber v a -> NumberAbstract v
- data Attribute' v = Attribute' !(NumberAbstract v) !ByteString
- data Attribute v a = Attribute !(TypedNumber v a) !a
- value :: Attribute v a -> a
- type TypedNumberSet v a = Set (TypedNumber v a)
- typed :: (Monad m, Functor m, Ord v) => TypedNumberSet v a -> (ByteString -> m b) -> Attribute' v -> MaybeT m (Attribute v b)
- class TypedNumberSets v where
Documentation
data NumberAbstract a Source #
Instances
Show a => Show (NumberAbstract a) Source # | |
Defined in Data.Radius.Attribute.Pair showsPrec :: Int -> NumberAbstract a -> ShowS # show :: NumberAbstract a -> String # showList :: [NumberAbstract a] -> ShowS # | |
Eq a => Eq (NumberAbstract a) Source # | |
Defined in Data.Radius.Attribute.Pair (==) :: NumberAbstract a -> NumberAbstract a -> Bool # (/=) :: NumberAbstract a -> NumberAbstract a -> Bool # | |
Ord a => Ord (NumberAbstract a) Source # | |
Defined in Data.Radius.Attribute.Pair compare :: NumberAbstract a -> NumberAbstract a -> Ordering # (<) :: NumberAbstract a -> NumberAbstract a -> Bool # (<=) :: NumberAbstract a -> NumberAbstract a -> Bool # (>) :: NumberAbstract a -> NumberAbstract a -> Bool # (>=) :: NumberAbstract a -> NumberAbstract a -> Bool # max :: NumberAbstract a -> NumberAbstract a -> NumberAbstract a # min :: NumberAbstract a -> NumberAbstract a -> NumberAbstract a # |
data TypedNumber v a Source #
Instances
Show v => Show (TypedNumber v a) Source # | |
Defined in Data.Radius.Attribute.Pair showsPrec :: Int -> TypedNumber v a -> ShowS # show :: TypedNumber v a -> String # showList :: [TypedNumber v a] -> ShowS # | |
Eq v => Eq (TypedNumber v a) Source # | |
Defined in Data.Radius.Attribute.Pair (==) :: TypedNumber v a -> TypedNumber v a -> Bool # (/=) :: TypedNumber v a -> TypedNumber v a -> Bool # | |
Ord v => Ord (TypedNumber v a) Source # | |
Defined in Data.Radius.Attribute.Pair compare :: TypedNumber v a -> TypedNumber v a -> Ordering # (<) :: TypedNumber v a -> TypedNumber v a -> Bool # (<=) :: TypedNumber v a -> TypedNumber v a -> Bool # (>) :: TypedNumber v a -> TypedNumber v a -> Bool # (>=) :: TypedNumber v a -> TypedNumber v a -> Bool # max :: TypedNumber v a -> TypedNumber v a -> TypedNumber v a # min :: TypedNumber v a -> TypedNumber v a -> TypedNumber v a # |
unsafeTypedNumber :: NumberAbstract v -> TypedNumber v a Source #
untypeNumber :: TypedNumber v a -> NumberAbstract v Source #
data Attribute' v Source #
Instances
Show v => Show (Attribute' v) Source # | |
Defined in Data.Radius.Attribute.Pair showsPrec :: Int -> Attribute' v -> ShowS # show :: Attribute' v -> String # showList :: [Attribute' v] -> ShowS # | |
Eq v => Eq (Attribute' v) Source # | |
Defined in Data.Radius.Attribute.Pair (==) :: Attribute' v -> Attribute' v -> Bool # (/=) :: Attribute' v -> Attribute' v -> Bool # | |
Ord v => Ord (Attribute' v) Source # | |
Defined in Data.Radius.Attribute.Pair compare :: Attribute' v -> Attribute' v -> Ordering # (<) :: Attribute' v -> Attribute' v -> Bool # (<=) :: Attribute' v -> Attribute' v -> Bool # (>) :: Attribute' v -> Attribute' v -> Bool # (>=) :: Attribute' v -> Attribute' v -> Bool # max :: Attribute' v -> Attribute' v -> Attribute' v # min :: Attribute' v -> Attribute' v -> Attribute' v # |
Attribute !(TypedNumber v a) !a |
Instances
(Show v, Show a) => Show (Attribute v a) Source # | |
(Eq v, Eq a) => Eq (Attribute v a) Source # | |
(Ord v, Ord a) => Ord (Attribute v a) Source # | |
Defined in Data.Radius.Attribute.Pair compare :: Attribute v a -> Attribute v a -> Ordering # (<) :: Attribute v a -> Attribute v a -> Bool # (<=) :: Attribute v a -> Attribute v a -> Bool # (>) :: Attribute v a -> Attribute v a -> Bool # (>=) :: Attribute v a -> Attribute v a -> Bool # |
type TypedNumberSet v a = Set (TypedNumber v a) Source #
typed :: (Monad m, Functor m, Ord v) => TypedNumberSet v a -> (ByteString -> m b) -> Attribute' v -> MaybeT m (Attribute v b) Source #
Retryable error context with anthor attirbute value type MaybeT
m, and parse error context m.