Using a monadic boolean value in a guard? (PatternGuard) - haskell

I just found out about the PatternGuards language extension, which seems really nice.
I'm in a situation where I want to pattern match a value out, apply a monadic boolean function on that value, and only do something if the result is False. Otherwise I want to execute a default action (that might not be as simple as listed below).
This can be achieved by using an if after doing the pattern matching, but I would rather not duplicate the code for the default action, or move that out in a separate function (ie. keep the fall through behaviour of guards)
Is there a way to do this without the if?
{-# LANGUAGE GeneralizedNewtypeDeriving, PatternGuards #-}
import Control.Applicative
import Control.Monad.State
newtype MyM a = MyM (StateT Int (Either String) a)
deriving ( MonadState Int
, Monad, Applicative, Functor
)
--------------------------------------------------------------------------------
foo :: Int -> MyM Bool
foo = undefined
bar :: Either a Int -> MyM Int
bar (Right n)
| ok <- foo n, ok == False = return 42
bar _ = return 0
The above code gives the error message
Couldn't match expected type ‘MyM Bool’ with actual type ‘Bool’
In the second argument of ‘(==)’, namely ‘False’
In the expression: ok == False

What you're asking for is impossible, and for good reasons. Let's say that foo modifies the state, but the condition in the guard doesn't match. How would you deal with this state modification? Patterns are separate from the values, so matching a pattern can't result in altering results.
You really need to have the call to foo in the RHS that decides what to do with its output.
In some cases, where the monad is a data type you can match on, you can do things like
foo :: Int -> Maybe Bool
...
bar :: Either a Int -> MyM Int
bar (Right n)
| Just False <- foo n = ...
but only because you can match directly on the value of the monad.
Also in some cases extensions lambda-case and multi-way if-expressions can make your life somewhat easier.

Related

Dynamically pattern matching nested GADT back out of a wrapper

I recently asked how to make a homogenous list of GADT instances: Function returning result of any constructor of a GADT
tl;dr
{-#LANGUAGE GADTs, EmptyDataDecls #-}
module Main where
-- Define a contrived GADT
data TFoo
data TBar
data Thing a where
Foo :: Int -> Thing TFoo
Bar :: String -> Thing TBar
data SomeThing = forall a. SomeThing (Thing a)
combine :: [SomeThing]
combine = [Something $ Foo 1, SomeThing $ Bar "abc"]
Now, I'm having some trouble dynamically "unwrapping" them. Let's say we have this (still contrived, but closer to my real use case) code:
{-#LANGUAGE GADTs, EmptyDataDecls #-}
module Main where
-- Define a contrived GADT
data Thing a where
Thing :: TKind a -> Thing a
data TFoo
data TBar
data TKind a where
Foo :: TKind TFoo
Bar :: TKind TBar
data SomeThing = forall a. SomeThing (Thing a)
example :: SomeThing
example = SomeThing $ Thing Foo
extractThingWithTKind :: TKind a -> SomeThing -> Either String (Thing a)
extractThingWithTKind k st = case st of
SomeThing t#(Thing k) -> Right t
_ -> Left "nope"
The above doesn't work because the t in Right t doesn't have the type Thing a. Intrinsically, I understand why this doesn't work. Pattern matching on the k doesn't do what I want (only match if the k is the same as the one passed in). But this is my best stab at approximating what I want. I tried instanceing Eq on TKind a, but because (==) :: a -> a -> Bool, this won't work (the equality depends on potentially disparate types at runtime). I could wrap TKind like I did Thing, but then I'd just be pushing the problem lower.
Removing the dynamism, I tried just pattern matching out a Thing TFoo explicitly:
extractThingWithFoo :: SomeThing -> Either String (Thing TFoo)
extractThingWithFoo st = case st of
SomeThing t#(Thing Foo) -> Right t
_ -> Left "nope"
And that works! But does this mean that I can't do the dynamic matching? It would be a real pain to have to duplicate the above method for each kind TKind (in the non-contrived version, there are many). The only other solution I see is changing SomeThing to be a sum type that has one wrapper for each TKind, but then you're just moving the duplicated code to a different place (and forcing all uses of SomeThing to pattern match each).
In order to implement a function with the signature
extractThingWithTKind :: TKind a -> SomeThing -> Either String (Thing a), we need to be able to decide that what's inside SomeThing is a TKind a or not. GADT constructors are witnesses of such type equalities, but they need to be explicitly pattern-matched on to "unwrap" these assumptions in the function's local scope.
extractThingWithTKind :: TKind a -> SomeThing -> Either String (Thing a)
extractThingWithTKind Foo (SomeThing t#(Thing Foo)) = Right t
extractThingWithTKind Bar (SomeThing t#(Thing Bar)) = Right t
extractThingWithTKind _ _ = Left "nope"
Pattern matching on the first argument gives rise to the assumption that a ~ TFoo (in the first case), and further pattern matching on the second argument proves that the thing inside SomeThing is also a TFoo. Crucially, the individual cases have to be spelled out one by one, as it's the constructors themselves that provide the evidence.

Haskell custom datatype with parameter

I have a custom data type as follows:
data MyType a = Nothing
| One a
The idea is to have a function that return the data type. For example,
func (One Char) should return Char -- return the data type
I tried to implement func as follow:
func :: MyType a -> a
func (One a) = a
-- don't worry about Nothing for now
The code compiled but when I tried to run func (One Char) it gives me an error: Not in scope: data constructor ‘Char’
What is going on?
Try func (One "Hello") it will work.
The reason is that Haskell thinks you are trying to give it a data-constructor because you wrote a upper-case Char so just give it some real value ;)
BTW: In case you really want to give the type Char: that's in general not possible in Haskell as you need a dependent-type caps (see Idris for example).
That's not really how haskell works. Char is a type, so we can write
func :: MyType Char -> Char
meaning that we expect the "something" of MyType to be a Char.
Checking what type an argument has is probably valid in something like Java, but is not the way functional programming works.
I don't think there's much chance you really want this with your current level of understanding of Haskell (it's a stretch for me, and I've been at it a while), but if you really really do, you can actually get something pretty close.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PolyKinds #-} --might as well
-- I renamed Nothing to None to avoid conflicting with Maybe.
-- Since we're using DataKinds, this creates not only a type
-- constructor MyType and data constructors None and One,
-- but also a *kind* MyType and *type* constructors None and
-- One.
data MyType a = None | One a
-- We can't make a *function*, func, to take One Char and
-- produce Char, but we can make a *type function* (called
-- a type family) to do that (although I don't really know
-- why you'd want this particular one.
type family Func (a :: MyType k) :: k
type instance Func (One a) = a
Now if we write
Prelude> '3' :: Func (One Char)
GHCi is perfectly happy with it. In fact, we can make this type function even more general:
type family Func2 (a :: g) :: k where
Func2 (f a) = a
Now we can write
'c' :: Func2 (One Char)
but we can also write
'c' :: Func2 (Maybe Char)
and even
'c' :: Func2 (Either Char)
'c' :: Func2 ((Either Int) Char)
But in case you think anything goes,
'c' :: Func2 (Maybe Int)
or
'c' :: Func2 Char
will give errors.

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’

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")

Is it possible to export constructors for pattern matching, but not for construction, in Haskell Modules?

A vanilla data type in Haskell has zero or more constructors, each of which plays two roles.
In expressions, it supports introduction, its a function from zero or more arguments to the data type.
In patterns, it supports elimination, its kinda like a function from the data type to Maybe (tuple of argument types).
Is it possible for a module signature to hide the former while exposing the latter?
The use case is this: I have a type, T, whose constructors types alone can sometimes be used to construct nonsense. I have construction functions which can be used to build instances of the type that are guaranteed not to be nonsense. It would make sense to hide the constructors in this case, but it would still be useful for callers to be able to pattern match over the guaranteed-non-nonsense that they build with the construction functions.
I suspect this is impossible, but in case anyone has a way to do it, I though I would ask.
Next best thing is to hide the constructors and create a bunch of functions from T -> Maybe (This, That), T -> Maybe (The, Other, Thing), etc.
You can use a view type and view patterns to do what you want:
module ThingModule (Thing, ThingView(..), view) where
data Thing = Foo Thing | Bar Int
data ThingView = FooV Thing | BarV Int
view :: Thing -> ThingView
view (Foo x) = FooV x
view (Bar y) = BarV y
Note that ThingView is not a recursive data type: all the value constructors refer back to Thing. So now you can export the value constructors of ThingView and keep Thing abstract.
Use like this:
{-# LANGUAGE ViewPatterns #-}
module Main where
import ThingModule
doSomethingWithThing :: Thing -> Int
doSomethingWithThing(view -> FooV x) = doSomethingWithThing x
doSomethingWithThing(view -> BarV y) = y
The arrow notation stuff is GHC's View Patterns. Note that it requires a language pragma.
Of course you're not required to use view patterns, you can just do all the desugaring by hand:
doSomethingWithThing :: Thing -> Int
doSomethingWithThing = doIt . view
where doIt (FooV x) = doSomethingWithThing x
doIt (BarV y) = y
More
Actually we can do a little bit better: There is no reason to duplicate all the value constructors for both Thing and ThingView
module ThingModule (ThingView(..), Thing, view) where
newtype Thing = T {view :: ThingView Thing}
data ThingView a = Foo a | Bar Int
Continue useing it the same way as before, but now the pattern matches can use Foo and Bar.
{-# LANGUAGE ViewPatterns #-}
module Main where
import ThingModule
doSomethingWithThing :: Thing -> Int
doSomethingWithThing(view -> Foo x) = doSomethingWithThing x
doSomethingWithThing(view -> Bar y) = y
From GHC 7.8 on you can use PatternSynonyms to export patterns independent from constructors. So an analogue to #Lambdageek’s answer would be
{-# LANGUAGE PatternSynonyms #-}
module ThingModule (Thing, pattern Foo, pattern Bar) where
pattern Foo a <- RealFoo a
pattern Bar a <- RealBar a
data Thing = RealFoo Thing | RealBar Int
and
{-# LANGUAGE PatternSynonyms #-}
module Main where
import ThingModule
doSomethingWithThing :: Thing -> Int
doSomethingWithThing (Foo x) = doSomethingWithThing x
doSomethingWithThing (Bar y) = y
So it looks like normal constructors.
If you try to use Bar to construct a value, you get
Main.hs:9:32:
Bar used in an expression, but it's a non-bidirectional pattern synonym
In the expression: Bar y
You cannot. But if there are only reasonable number of constructors for your type T, you may want to hide the constructors and instead provide a function which does the pattern matching in the same spirit as maybe :: b -> (a -> b) -> Maybe a -> b.

Resources