{-# LANGUAGE LambdaCase #-}
I have a bunch of functions which encode failure in various ways. For example:
f :: A -> Bool
returns False
on failureg :: B -> Maybe B'
returns Nothing
on failureh :: C -> Either Error C'
returns Left ...
on failureI want to chain these operations in the same way as the Maybe
monad, so the chaining function needs to know whether each function failed before proceeding to the next one. For this I wrote this class:
class Fail a where
isFail :: a -> Bool
instance Fail () where
isFail () = False
instance Fail Bool where -- a
isFail = not
instance Fail (Maybe a) where -- b
isFail = not . isJust
instance Fail (Either a b) where -- c
isFail (Left _) = True
isFail _ = False
However, it's possible that functions that don't conform exist:
f' :: A -> Bool
returns True
on failureg' :: B -> Maybe Error
returns Just Error
on failure (Nothing
on success)h' :: C -> Either C' Error
returns Right ...
on failureThese could be remedied by simply wrapping them with functions that transform them, for example:
f'' = not . f'
.g'' = (\case Nothing -> Right (); Just e -> Left e) . g'
h'' = (\case Left c -> Right c; Right e -> Left e) . h'
However, the user of the chaining function expects to be able to combine f
,g
,h
,f'
,g'
, and h'
and have them just work. He would not know that the return type of a function needs to be transformed unless he looks at the semantics of each function he's combining, and check if they match up with whatever Fail
instances he has in scope. This is tedious and too subtle for the average user to even notice, especially with type inference bypassing the user having to choose the right instances.
These functions weren't created with knowledge of how they'd be used. So I could make a type data Result a b = Fail a | Success b
and make wrappers around each function. For example:
fR = (\case True -> Sucess (); False -> Fail ()) . f
f'R = (\case False -> Sucess (); True -> Fail ()) . f'
gR = (\case Just a -> Sucess a; Nothing -> Fail ()) . g
g'R = (\case Nothing -> Sucess (); Just e -> Fail e) . g'
hR = (\case Left e -> Fail e; Right a -> Sucess a) . h
h'R = (\case Right e -> Fail e; Left a -> Sucess a) . h'
However, this feels dirty. What we're doing is just certifying / explaining how each of f
,g
,h
,f'
,g'
, and h'
are used in the context of the combining function. Is there are more direct way of doing this? What I want exactly is a way to say which instance of the Fail
typeclass should be used for each function, i.e, (using the names given to the typeclass instances above), f
→ a
, g
→ b
, h
→ c
, and f'
→ a'
, g'
→ b'
, h'
→ c'
for the "invalid" functions, where a'
,b'
, and c'
are defined as the following instances (which overlap the previous ones, so you'd need to be able to pick them by name somehow):
instance Fail Bool where -- a'
isFail = id
instance Fail (Maybe a) where -- b'
isFail = isJust
instance Fail (Either a b) where -- c'
isFail (Right _) = True
isFail _ = False
It doesn't necessarily have to by done via typeclasses though. Maybe there's some way to do this other than with typeclasses?
A typeclass is a sort of interface that defines some behavior. If a type is a part of a typeclass, that means that it supports and implements the behavior the typeclass describes. A lot of people coming from OOP get confused by typeclasses because they think they are like classes in object oriented languages.
An instance of a class is an individual object which belongs to that class. In Haskell, the class system is (roughly speaking) a way to group similar types. (This is the reason we call them "type classes"). An instance of a class is an individual type which belongs to that class.
An interface in the Java programming language is an abstract type that is used to specify an interface (in the generic sense of the term) that classes must implement. These two looks rather similar: type class limit a type's behavior, while interface limit a class' behavior.
What's a typeclass in Haskell? A typeclass defines a set of methods that is shared across multiple types. For a type to belong to a typeclass, it needs to implement the methods of that typeclass. These implementations are ad-hoc: methods can have different implementations for different types.
Don't do this. Haskell's static type system and referential transparency give you a tremendously useful guarantee: you can be properly sure that some particular value means the same thing1, regardless of how it was produced. There's neither mutability to interfer with this, nor dynamic-style “runtime reinterpretation” of expressions, as you'd need for the task you seem to envision.
If those functions you have there don't adhere to such a specification accordingly, well, then this is bad. Better get rid of them (at least, hide them and only export a re-defined version with unified behaviour). Or tell the users they'll have to live with looking up the specification of each. But don't try to hack some way around this particular symptom of broken definitions.
An easy change you could apply to just “flag” the functions where failure means the opposite as it otherwise does is to have them return such a wrapped result:
newtype Anti a = Anti { profail :: a }
instance (Anti a) => Fail (Anti a) where
isFail (Anti a) = not $ isFail a
1Mind: “same thing” in a possibly very abstract sense. There's no need for Left
to be universally a “fail constructor”, it's sufficient that it's clear that it's the variant constructor associated to the first type argument, which is not what the functor/monad instance operates on – from that it follows automatically that this will “mean” failure in a monadic application.
I.e., when you've chosen the right types, stuff should be unambigious pretty much automatically; obviously the opposite is true when you're just tossing around booleans, so perhaps you should get rid of those entirely...
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With