Difficulties with 'Either e` instance of `Failure` from "failure" package - haskell

This is more or less a simplified version of the issue I'm trying to understand in my own code. I'm working with functions that are polymorphic in the Failure class from this package.
{-# LANGUAGE FlexibleContexts #-}
import Data.Maybe
import Data.Either
import Control.Failure
data FookError = FookError deriving Show
fook :: (Failure FookError m)=> Int -> m Int
fook = undefined
fooks :: (Failure FookError m)=> Int -> m Int
-- DOES NOT TYPE-CHECK:
--fooks n = return $ head $ rights $ map fook [1..]
-- OKAY:
fooks n = return $ head $ catMaybes $ map fook [1..]
You can see in the above code, that when I treat the return type of fook as Maybe Int the module compiles fine, however treating it as Either Fook Int fails.
What is going on here?

This is because, in the non-working definition of fooks, fook's type is ambiguous. When you use catMaybes, it disambiguates as Maybe Int, but when you use rights, it can be Either e Int for any e, and the compiler doesn't necessarily know which. Sure, by default the only Failure instance for Either is instance Failure e (Either e), but there's nothing stopping you defining, e.g. instance Failure String (Either Int).
If you explicitly specify the type by defining fooks as
fooks n =
return $ head $ rights $ map (fook :: Int -> Either FookError Int) [1..]
then it works fine.
However, I suspect that you're not doing what you really want here; fooks never actually uses the failure capability of the underlying monad; indeed, even if there are no non-failing results, the monadic action still succeeds and returns a value. The value just so happens to be an error, but that's still probably not what you want :)
If you want fooks to try a bunch of individual fooks in turn, and return the first one that succeeds, then something like:
fooks :: (Failure FookError m, MonadPlus m) => Int -> m Int
fooks n = foldr mplus (failure FookError) $ map fook [1..]
should do the trick. The plain Failure class by itself offers no way to recover from errors, so you need to require MonadPlus too. Note that the failure FookError here will never actually be used, since [1..] is infinite, but presumably you're planning to change the definition; say to one that actually uses n :)
Unfortunately, that isn't all! Either e doesn't have a MonadPlus instance, presumably because there's no reasonable value of mzero (although another potential problem is that mplus (Left e) (Left e') could be either Left e or Left e').
Thankfully, it's easy to define an instance for our specific type:
instance MonadPlus (Either FookError) where
mzero = failure FookError
mplus a#(Right _) _ = a
mplus (Left _) a = a
You'll need {-# LANGUAGE FlexibleInstances #-} at the top of your file to do this.

Related

Set specific properties for data in Haskell

Let us say I want to make a ADT as follows in Haskell:
data Properties = Property String [String]
deriving (Show,Eq)
I want to know if it is possible to give the second list a bounded and enumerated property? Basically the first element of the list will be the minBound and the last element will be the maxBound. I am trying,
data Properties a = Property String [a]
deriving (Show, Eq)
instance Bounded (Properties a) where
minBound a = head a
maxBound a = (head . reverse) a
But not having much luck.
Well no, you can't do quite what you're asking, but maybe you'll find inspiration in this other neat trick.
{-# language ScopedTypeVariables, FlexibleContexts, UndecidableInstances #-}
import Data.Reflection -- from the reflection package
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty (..))
import Data.Proxy
-- Just the plain string part
newtype Pstring p = P String deriving Eq
-- Those properties you're interested in. It will
-- only be possible to produce bounds if there's at
-- least one property, so NonEmpty makes more sense
-- than [].
type Props = NonEmpty String
-- This is just to make a Show instance that does
-- what you seem to want easier to write. It's not really
-- necessary.
data Properties = Property String [String] deriving Show
Now we get to the key part, where we use reflection to produce class instances that can depend on run-time values. Roughly speaking, you can think of
Reifies x t => ...
as being a class-level version of
\(x :: t) -> ...
Because it operates at the class level, you can use it to parametrize instances. Since Reifies x t binds a type variable x, rather than a term variable, you need to use reflect to actually get the value back. If you happen to have a value on hand whose type ends in p, then you can just apply reflect to that value. Otherwise, you can always magic up a Proxy :: Proxy p to do the job.
-- If some Props are "in the air" tied to the type p,
-- then we can show them along with the string.
instance Reifies p Props => Show (Pstring p) where
showsPrec k p#(P str) =
showsPrec k $ Property str (NE.toList $ reflect p)
-- If some Props are "in the air" tied to the type p,
-- then we can give Pstring p a Bounded instance.
instance Reifies p Props => Bounded (Pstring p) where
minBound = P $ NE.head (reflect (Proxy :: Proxy p))
maxBound = P $ NE.last (reflect (Proxy :: Proxy p))
Now we need to have a way to actually bind types that can be passed to the type-level lambdas. This is done using the reify function. So let's throw some Props into the air and then let the butterfly nets get them back.
main :: IO ()
main = reify ("Hi" :| ["how", "are", "you"]) $
\(_ :: Proxy p) -> do
print (minBound :: Pstring p)
print (maxBound :: Pstring p)
./dfeuer#squirrel:~/src> ./WeirdBounded
Property "Hi" ["Hi","how","are","you"]
Property "you" ["Hi","how","are","you"]
You can think of reify x $ \(p :: Proxy p) -> ... as binding a type p to the value x; you can then pass the type p where you like by constraining things to have types involving p.
If you're just doing a couple of things, all this machinery is way more than necessary. Where it gets nice is when you're performing lots of operations with values that have phantom types carrying extra information. In many cases, you can avoid most of the explicit applications of reflect and the explicit proxy handling, because type inference just takes care of it all for you. For a good example of this technique in action, see the hyperloglog package. Configuration information for the HyperLogLog data structure is carried in a type parameter; this guarantees, at compile time, that only similarly configured structures are merged with each other.

How to avoid default return value when accessing a non-existent field with lenses?

I love Lens library and I love how it works, but sometimes it introduces so many problems, that I regret I ever started using it. Lets look at this simple example:
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
data Data = A { _x :: String, _y :: String }
| B { _x :: String }
makeLenses ''Data
main = do
let b = B "x"
print $ view y b
it outputs:
""
And now imagine - we've got a datatype and we refactor it - by changing some names. Instead of getting error (in runtime, like with normal accessors) that this name does not longer apply to particular data constructor, lenses use mempty from Monoid to create default object, so we get strange results instead of error. Debugging something like this is almost impossible.
Is there any way to fix this behaviour? I know there are some special operators to get the behaviour I want, but all "normal" looking functions from lenses are just horrible. Should I just override them with my custom module or is there any nicer method?
As a sidenote: I want to be able to read and set the arguments using lens syntax, but just remove the behaviour of automatic result creating when field is missing.
It sounds like you just want to recover the exception behavior. I vaguely recall that this is how view once worked. If so, I expect a reasonable choice was made with the change.
Normally I end up working with (^?) in the cases you are talking about:
> b ^? y
Nothing
If you want the exception behavior you can use ^?!
> b ^?! y
"*** Exception: (^?!): empty Fold
I prefer to use ^? to avoid partial functions and exceptions, similar to how it is commonly advised to stay away from head, last, !! and other partial functions.
Yes, I too have found it a bit odd that view works for Traversals by concatenating the targets. I think this is because of the instance Monoid m => Applicative (Const m). You can write your own view equivalent that doesn't have this behaviour by writing your own Const equivalent that doesn't have this instance.
Perhaps one workaround would be to provide a type signature for y, so know know exactly what it is. If you had this then your "pathological" use of view wouldn't compile.
data Data = A { _x :: String, _y' :: String }
| B { _x :: String }
makeLenses ''Data
y :: Lens' Data String
y = y'
You can do this by defining your own view1 operator. It doesn't exist in the lens package, but it's easy to define locally.
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
data Data = A { _x :: String, _y :: String }
| B { _x :: String }
makeLenses ''Data
newtype Get a b = Get { unGet :: a }
instance Functor (Get a) where
fmap _ (Get x) = Get x
view1 :: LensLike' (Get a) s a -> s -> a
view1 l = unGet . l Get
works :: Data -> String
works = view1 x
-- fails :: Data -> String
-- fails = view1 y
-- Bug.hs:23:15:
-- No instance for (Control.Applicative.Applicative (Get String))
-- arising from a use of ‘y’

Haskell: Type safety with logically different Boolean values

Lets say I've got the following code
type IsTall = Bool
type IsAlive = Bool
is_short_alive_person is_tall is_alive = (not is_tall) && is_alive
Say, later on, I've got the following
a :: IsAlive
a = False
b :: IsTall
b = True
And call the following, getting the two arguments around the wrong way:
is_short_alive_person a b
This successfully compiles unfortunately, and at runtime tall dead people are instead found instead of short alive people.
I would like the above example not to compile.
My first attempt was:
newtype IsAlive = IsAlive Bool
newtype IsTall = IsTall Bool
But then I can't do something like.
switch_height :: IsTall -> IsTall
switch_height h = not h
As not is not defined on IsTalls, only Bools.
I could explicitly extract the Bools all the time, but that largely defeats the purpose.
Basically, I want IsTalls to interact with other IsTalls, just like they're Bools, except they won't interact with Bools and IsAlives without an explicit cast.
What's the best way to achieve this.
p.s. I think I've achieved this with numbers by doing in GHC:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype UserID = UserID Int deriving (Eq, Ord, Num)
newtype GroupID = GroupID Int deriving (Eq, Ord, Num)
(i.e. UserID's and GroupID's shouldn't interact)
but I can't seem to do this with Bools (deriving Bool doesn't work). I'm not even sure the above is the best approach anyway.
If you change your data type slightly you can make it an instance of Functor and you can then use fmap to do operations on the Boolean
import Control.Applicative
newtype IsAliveBase a = IsAlive a
newtype IsTallBase a = IsTall a
type IsAlive = IsAliveBase Bool
type IsTall = IsTallBase Bool
instance Functor IsAliveBase where
fmap f (IsAlive b) = IsAlive (f b)
instance Functor IsTallBase where
fmap f (IsTall b) = IsTall (f b)
switch_height :: IsTall -> IsTall
switch_height h = not <$> h -- or fmap not h
-- EDIT
for operations like && you can make it an instance of Applicative
instance Applicative IsAliveBase where
pure = IsAlive
(IsAlive f) <*> (IsAlive x) = IsAlive (f x)
and then you can do (&&) using liftA2
example:
*Main> let h = IsAlive True
*Main> liftA2 (&&) h h
IsAlive True
you can read more about this at http://en.wikibooks.org/wiki/Haskell/Applicative_Functors
Your options are either to define algebraic data types like
data Height = Tall | Short
data Wiggliness = Alive | Dead
or to define new operators, e.g., &&&, |||, complement and to overload them on the type of your choice. But even with overloading you won't be able to use them with if.
I'm not sure that Boolean operations on height make sense anyway. How do you justify a conclusion that "tall and short equals short" but "tall or short equals tall"?
I suggest you look for different names for your connectives, which you can then overload.
P.S. Haskell is always getting new features, so the best I can say is that if you can overload if I'm not aware of it. To say about Haskell that "such-and-such can't be done" is always dangerous...
You can get some way towards this, using newtypes and a class if you import the Prelude hiding the boolean functions you want to use with your IsTall and IsAlive values. You redefine the boolean functions as methods in the class, for which you then make instances for all 3 of the Bool, IsTall, and IsAlive types. If you use GeneralizedNewtypeDeriving you can even get the IsTall and IsAlive instances without having to write the wrapping/unwrapping boilerplate by hand.
Here's an example script I actually tried out in ghci:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Prelude hiding ((&&), (||), not)
import qualified Prelude
class Boolish a where
(&&) :: a -> a -> a
(||) :: a -> a -> a
not :: a -> a
instance Boolish Bool where
(&&) = (Prelude.&&)
(||) = (Prelude.||)
not = Prelude.not
newtype IsTall = IsTall Bool
deriving (Eq, Ord, Show, Boolish)
newtype IsAlive = IsAlive Bool
deriving (Eq, Ord, Show, Boolish)
You can now &&, ||, and not values of any of the three types, but not together. And they're separate types, so your function signatures can now restrict which of the 3 they want to accept.
Higher order functions defined in other modules will work fine with this, as in:
*Main> map not [IsTall True, IsTall False]
[IsTall False,IsTall True]
But you won't be able to pass an IsTall to any other function defined elsewhere that expects a Bool, because the other module will still be using the Prelude version of the boolean functions. Language constructs like if ... then ... else ... will still be a problem too (although a comment by hammar on Norman Ramsey's answer says you can fix this with another GHC extension). I'd probably add a toBool method to that class to help uniformly convert back to regular Bools to help mitigate such problems.

Laziness and polymorphic values

(For the following, simplify Show and Read to
class Show a where show :: a -> String
class Read a where read :: String -> a
And assume that read never fails.)
It's well-known that one can make an existential type of the form
data ShowVal where
ShowVal :: forall a. Show a => a -> ShowVal
And then construct a "heterogeneous list" :: [ShowVal], such as
l = [ShowVal 4, ShowVal 'Q', ShowVal True]
It's also well-known that this is relatively useless, because, instead, one can
just construct a list :: [String], such as
l = [show 4, show 'Q', show True]
Which is exactly isomorphic (after all, the only thing one can do with a
ShowVal is show it).
Laziness makes this particularly nice, because for each value in the list, the
result of show is memoized automatically, so no String is computed more than
once (and Strings that aren't used aren't computed at all).
A ShowVal is equivalent to an existential tuple exists a. (a -> String, a),
where the function is the Show dictionary.
A similar construct can be made for Read:
data ReadVal where
ReadVal :: (forall a. Read a => a) -> ReadVal
Note that, because read is polymorphic in its return value, ReadVal is
universal rather than existential (which means that we don't really need it at
all, because Haskell has first-class universals; but we'll use it here to
highlight the similaries to Show).
We can also make a list :: [ReadVal]:
l = [ReadVal (read "4"), ReadVal (read "'Q'"), ReadVal (read "True")]
Just as with Show, a list :: [ReadVal] is isomorphic to a list :: [String],
such as
l = ["4", "'Q'", "True"]
(We can always get the original String back with
newtype Foo = Foo String
instance Read Foo where read = Foo
Because the Read type class is open.)
A ReadVal is equivalent to a universal function forall a. (String -> a) -> a
(a CPS-style representation). Here the Read dictionary is supplied by the user
of the ReadVal rather than by the producer, because the return value is
polymorphic rather than the argument.
However, in neither of these representations do we get the automatic
memoization that we get in the String representation with Show. Let's say that
read for our type is an expensive operation, so we don't want to compute it
on the same String for the same type more than once.
If we had a closed type, we could do something like:
data ReadVal = ReadVal { asInt :: Int, asChar :: Char, asBool :: Bool }
And then use a value
ReadVal { asInt = read s, asChar = read s, asBool = read s }
Or something along those lines.
But in this case -- even if we only ever use the ReadVal as one type -- the
String will be parsed each time the value is used. Is there a simple way to
get memoization while keeping the ReadVal polymorphic?
(Getting GHC to do it automatically, similarly to the Show case, would be
ideal, if it's somehow possible. A more explicit memoization approach --
perhaps by adding a Typeable constraint? -- would also be OK.)
Laziness makes this particularly nice, because for each value in the list, the result of show is memoized automatically, so no String is computed more than once (and Strings that aren't used aren't computed at all).
This premise is incorrect. There is no magical memo table under the hood.
Laziness means things that aren't needed, aren't computed. It does not mean that all computed values are shared. You still have to introduce explicit sharing (via a table of your own).
Here's an implementation of the more explicit approach; it requires Typeable, because otherwise there'd be nothing to key the memo table on. I based the memoisation code on uglymemo; there might be a way to get this to work with pure memoisation, but I'm not sure. It's tricky, because you have to construct the table outside of the implicit function that any forall a. (Read a, Typeable a) => ... creates, otherwise you end up constructing one table per call, which is useless.
{-# LANGUAGE GADTs, RankNTypes #-}
import Data.Dynamic
import Control.Concurrent.MVar
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import System.IO.Unsafe
data ReadVal where
ReadVal :: { useReadVal :: forall a. (Read a, Typeable a) => a } -> ReadVal
mkReadVal :: String -> ReadVal
mkReadVal s = unsafePerformIO $ do
v <- newMVar HM.empty
return $ ReadVal (readVal v)
where
readVal :: (Read a, Typeable a) => MVar (HashMap TypeRep Dynamic) -> a
readVal v = unsafePerformIO $ do
m <- readMVar v
let r = read s -- not evaluated
let typeRep = typeOf r
case HM.lookup typeRep m of
Nothing -> do
modifyMVar_ v (return . HM.insert typeRep (toDyn r))
return r
Just r' -> return $ fromDyn r' (error "impossible")

Binary instance for an existential

Given an existential data type, for example:
data Foo = forall a . (Typeable a, Binary a) => Foo a
I'd like to write instance Binary Foo. I can write the serialisation (serialise the TypeRep then serialise the value), but I can't figure out how to write the deserialisation. The basic problem is that given a TypeRep you need to map back to the type dictionary for that type - and I don't know if that can be done.
This question has been asked before on the haskell mailing list http://www.haskell.org/pipermail/haskell/2006-September/018522.html, but no answers were given.
You need some way that each Binary instance can register itself (just as in your witness version). You can do this by bundling each instance declaration with an exported foreign symbol, where the symbol name is derived from the TypeRep. Then when you want to deserialize you get the name from the TypeRep and look up that symbol dynamically (with dlsym() or something similar). The value exported by the foreign export can, e.g., be the deserializer function.
It's crazy ugly, but it works.
This can be solved in GHC 7.10 and onwards using the Static Pointers Language extension:
{-# LANGUAGE StaticPointers #-}
{-# LANGUAGE InstanceSigs #-}
data Foo = forall a . (StaticFoo a, Binary a, Show a) => Foo a
class StaticFoo a where
staticFoo :: a -> StaticPtr (Get Foo)
instance StaticFoo String where
staticFoo _ = static (Foo <$> (get :: Get String))
instance Binary Foo where
put (Foo x) = do
put $ staticKey $ staticFoo x
put x
get = do
ptr <- get
case unsafePerformIO (unsafeLookupStaticPtr ptr) of
Just value -> deRefStaticPtr value :: Get Foo
Nothing -> error "Binary Foo: unknown static pointer"
A full description of the solution can be found on this blog post, and a complete snippet here.
If you could do that, you would also be able to implement:
isValidRead :: TypeRep -> String -> Bool
This would be a function that changes its behavior due to someone defining a new type! Not very pure-ish.. I think (and hope) that one can't implement this in Haskell..
I have an answer that slightly works in some situations (not enough for my purposes), but may be the best that can be done. You can add a witness function to witness any types that you have, and then the deserialisation can lookup in the witness table. The rough idea is (untested):
witnesses :: IORef [Foo]
witnesses = unsafePerformIO $ newIORef []
witness :: (Typeable a, Binary a) => a -> IO ()
witness x = modifyIORef (Foo x :)
instance Binary Foo where
put (Foo x) = put (typeOf x) >> put x
get = do
ty <- get
wits <- unsafePerformIO $ readIORef witnesses
case [Foo x | Foo x <- wits, typeOf x == ty] of
Foo x:_ -> fmap Foo $ get `asTypeOf` return x
[] -> error $ "Could not find a witness for the type: " ++ show ty
The idea is that as you go through, you call witness on values of every type that you may plausibly encounter when deserialising. When you deserialise you search this list. The obvious problem is that if you fail to call witness before deserialisation you get a crash.

Resources