Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Constable
Description
This module provides an interface for the Const
functor which facilitates
using it safely for summarization via the applicative instance Monoid m => Applicative (Const m)
.
As an example, say we have a record of numbers and a function that sums up the fields of that record. We want to leverage the type system to ensure that if the record changes (field are added or removed), then the summing function will not compile until it is updated to match.
As a first attempt, we might write something like this:
import Data.Functor.Const import Data.Monoid data Parts = MkParts { part1 :: Int , part2 :: Int , part3 :: Int } sumParts :: Parts -> Int sumParts parts = getSum . getConst$
MkParts<$>
Const (Sum $ part1 parts)<*>
Const (Sum $ part2 parts)<*>
Const (Sum $ part3 parts)
At first glance it looks like this accomplishes our goal, but there is a
serious bug. If we remove a field from the record then sumParts
will
indeed fail to compile, but if we add a field then it will compile without
issue! This is because we didn't explicitly provide a type to the Const
expression being constructed and so the compiler infers it to be a function
type rather than the fully applied type that we expect. This means we must
always remember to add explicit type signatures or type applications
anywhere we use this pattern.
If we instead use the getConstSafe
version of getConst
exported by this
module then we don't need to worry about this issue because the compiler
will complain if the inferred type of a Const
is for a function type.
If you use HLint, you can go one step further and ban the use of the
"unsafe" getConst
in your codebase by way of an HLint rule:
- functions: - {name: getConst, within: []}
Synopsis
- getConstSafe :: FullyAppliedConst b => Const a b -> a
- mkConst :: a -> (a -> m) -> Const m a
- mkConstF :: f a -> (f a -> m) -> Const m a
- data Const a (b :: k) where
- pattern Const :: FullyAppliedConst b => a -> Const a b
- type family FullyAppliedConst (a :: Type) :: Constraint where ...
API
getConstSafe :: FullyAppliedConst b => Const a b -> a Source #
mkConst :: a -> (a -> m) -> Const m a Source #
Smart constructor for Const
that enforces that the value it contains is
built from a value of the result type. This provides an extra measure of type safety.
data Summable = MkSummable { s1 :: Int , s2 :: Double , s3 :: Integer } deriving (Show) test :: Summable test = Summable { s1 = 1 , s2 = 2 , s3 = 3 }getConstSafe
$
MkSummable<$>
mkConst (s1 test) (Sum . fromIntegral)<*>
mkConst (s2 test) Sum<*>
mkConst (s3 test) (Sum . fromIntegral)
The Const
functor.
Bundled Patterns
pattern Const :: FullyAppliedConst b => a -> Const a b | A pattern synonym for |
Instances
Generic1 (Const a :: k -> Type) | |
Foldable (Const m :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const Methods fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
Generic (Const a b) | |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int # inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods quot :: Const a b -> Const a b -> Const a b # rem :: Const a b -> Const a b -> Const a b # div :: Const a b -> Const a b -> Const a b # mod :: Const a b -> Const a b -> Const a b # quotRem :: Const a b -> Const a b -> (Const a b, Const a b) # divMod :: Const a b -> Const a b -> (Const a b, Const a b) # | |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods toRational :: Const a b -> Rational # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const |
Internal
type family FullyAppliedConst (a :: Type) :: Constraint where ... Source #
A constraint enforcing that getConstSafe
is only used with non-partially
applied constructors.
Equations
FullyAppliedConst (a -> b) = TypeError ((Text "Const used with partially applied constructor: '" :<>: ShowType (a -> b)) :<>: Text "'") | |
FullyAppliedConst a = () |