Is using #-patterns to get the pattern value redundant? - haskell

I'm going through Write Yourself a Scheme in 48 Hours, and in it I've come across some seemingly redundant code; they use #-patterns and then return the value itself, let me explain.
Here's the relevant code:
data LispVal = Atom String
| List [LispVal]
| DottedList [LispVal] LispVal
| Number Integer
| String String
| Bool Bool
eval :: LispVal -> LispVal -- code in question starts here
eval val#(String _) = val
eval val#(Number _) = val
eval val#(Bool _) = val
eval (List [Atom "quote", val]) = val
It seems to me that the entire eval function could just as easily be re-written as
eval :: LispVal -> LispVal
eval (List [Atom "quote", val]) = val
eval val = val
And have the bottom case account for all the #-patterns in the original code.
Am I mistaken in thinking this, and is there an actual benefit of doing it the way they did? Or is the other way more concise?

One difference is that the original code is undefined for values constructed with Atom, i.e. there is no line
eval val#(Atom _) = val
And whether this is a copy’n’paste error or not, it highlights the important difference in style:
The first style encourages you to think about each value individually, making an explicit assertion “this is the right equation for this”. If you later add more constructors t othe LispVal type, you get runtime errors (or compiler warnings with -fwarn-incomplete-patterns, which is good practice).
The second style asserts: eval will only have to look at List values, and all others can be treated individually. In particular, later additions to the data type should work just as well, and you don’t want to be bothered about this function then.
Operationally, they are equivalent.

Related

Is it possible to access a specific piece of a custom data type in Haskell?

I'm very new to haskell, and functional programming in general, I'm switching back and fourth between two different books on haskell, but I can't seem to find an answer to my question. Say I have a custom datatype like the one below
data Expr
= Let String Expr Expr
| Binary BinOp Expr Expr
| Unary UnOp Expr
| Literal Literal
| Var String
and I have an instance of this data type that is in the form of the first constructor Let String Expr Expr, is it possible to access a specific piece of that Expr? For example if I wanted to access the String within that specific instance.
Pattern matching is your answer.
Something like this should do the trick:
myfunction :: Expr -> SomeReturnType
myfunction (Let str _ _) = doSomethingWith str -- "str" here is your string
You'll want to handle the other cases as well though, so you don't cause a runtime error:
myfunction :: Expr -> SomeReturnType
myfunction (Let str _ _) = doSomethingElse str
myfunction (Binary _ _ _) = somethingEvenDifferent
myfunction (Unary _ _) = etc
--- etc...
the _ just says to ignore the value at that position in the constructor.
Also, as #Bergi mentioned, there are many other places you can use pattern matching, like let or case statements, just always be sure to handle all the cases that your value could potentially be at that point in your program.

Parsec parsing in Haskell

I have 2 parsers:
nexpr::Parser (Expr Double)
sexpr::Parser (Expr String)
How do I build a parser that tries one and then the other if it doesn't work? I can't figure out what to return. There must be a clever way to do this.
Thanks.
EDIT:
Adding a bit more info...
I'm learning Haskel, so I started with :
data Expr a where
N::Double -> Expr Double
S::String -> Expr String
Add::Expr Double -> Expr Double -> Expr Double
Cat::Expr String -> Expr String -> Expr String
then I read about F-algebra (here) and so I changed it to:
data ExprF :: (* -> *) -> * -> * where
N::Double -> ExprF r Double
S::String -> ExprF r String
Add::r Double -> r Double -> ExprF r Double
Cat::r String -> r String -> ExprF r String
with
type Expr = HFix ExprF
so my parse to:
Parser (Expr Double)
is actually:
Parser (ExprF HFix Double)
Maybe I'm biting off more than I can chew...
As noted in the comments, you can have a parser like this
nOrSexpr :: Parser (Either (Expr Double) (Expr String))
nOrSexpr = (Left <$> nexpr) <|> (Right <$> sexpr)
However, I think the reason that you are having this difficulty is because you are not representing your parse tree as a single type, which is the more usual thing to do. Something like this:
data Expr =
ExprDouble Double
| ExprInt Int
| ExprString String
That way you can have parsers for each kind of expression that are all of type Parser Expr. This is the same as using Either but more flexible and maintainable. So you might have
doubleParser :: Parser Expr
doubleParser = ...
intParser :: Parser Expr
intParser = ...
stringParser :: Parser Expr
stringParser = ...
exprParser :: Parser Expr
exprParser = intParser <|> doubleParser <|> stringParser
Note that the order of the parsers does matter and use can use Parsec's try function if backtracking is needed.
So, for example, if you want to have a sum expression now, you can add to the data type
data Expr =
ExprDouble Double
| ExprInt Int
| ExprString String
| ExprSum Expr Expr
and make the parser
sumParser :: Parser Expr
sumParser = do
a <- exprParser
string " + "
b <- exprParser
return $ ExprSum a b
UPDATE
Well, I take my hat off to you diving straight into GADTs if you are just starting with Haskell. I have been reading through the paper you linked and noticed this immediately in the first paragraph:
The jury is still out on whether the additional type-safety provided by GADTs is worth the added inconvenience of working with them.
There are three points worth taking away here I think. The first is simply that I would have a go with the simpler way of doing things first, to get an idea of how it works and why you might want to add more type safety, before trying to more complicated type theoretical stuff. That comment may not help so feel free to ignore it!
Secondly, and more importantly, your representation...
data ExprF :: (* -> *) -> * -> * where
N :: Double -> ExprF r Double
S :: String -> ExprF r String
Add :: r Double -> r Double -> ExprF r Double
Cat :: r String -> r String -> ExprF r String
...is specifically designed to not allow ill formed type expressions. Contrasted with mine which can, eg ExprSum (ExprDouble 5.0) (ExprString "test"). So the question you really want to ask is what should actually happen when the parser attempts to parse something like "5.0 + \"test\""? Do you want it to just not parse, or do you want it to return a nice message saying that this expression is the wrong type? Compilers are usually designed in multiple stages for this reason. The first pass turns the input into an abstract syntax tree (AST), and further passes annotate this tree with type judgements. This annotated AST can then be transformed into the semantic representation that you really want it in.
So in your case I would recommend two stages. first, parse into a dumb representation like mine, that will give you the correct tree shape but allow ill-typed expressions. Like
data ExprAST =
ExprASTDouble Double
| ExprASTInt Int
| ExprASTString String
| ExprASTAdd Expr Expr
Then have another function that will typecheck the ExprAST. Something like
typecheck :: ExprAST -> Maybe (ExprF HFix a)
(You could also use Either and return either the typechecked GADT or an error string saying what the problem is.) The further problem here is that you don't know what a is statically. The other answer solves this by using type tags and an existential wrapper, which you might find to be the best way to go. I feel like it might be simpler to have a top level expression in your GADT that all expressions must live in, so an entire parse will always have the same type. In the end there is usually only one program type.
My third, and last, point is related to this
The jury is still out on whether the additional type-safety provided by GADTs is worth the added inconvenience of working with them.
The more type safety, generally the more work you have to do to get it. You mention you are new to Haskell, yet this adventure has taken us right to the edge of what it is capable of doing. The type of the parsed expression cannot depend only on the input string in a Haskell function, because it does not allow for dependant types. If you want to go down this path, I might suggest you have a look at a language called Idris. A great introduction to what it is capable of can be found in this video, in which he constructs a typesafe printf.
The problem described looks to be using Parsec to parse into a GADT representation, for which probably the easiest solution would be parse into a monotype representation and then have a (likely partial) type checking phase to produce the well-typed GADT, if it can. The monotype representation could be an existential wrapper over a GADT term, with a type-tag to reify the GADT index.
EDIT: a quick example
Let's define a type for type-tags and an existential wrapper:
data Type :: * -> * where
TDouble :: Type Double
TString :: Type String
data Judgement f = forall ix. Judgement (f ix) (Type ix)
With the example GADT given in the original post, we only have a problem with the outer-most production, which we need to parse to a monotype as we don't know statically which expression type we will get at runtime:
pExpr :: Parser (Judgement Expr)
pExpr = Judgement <$> pDblExpr <*> pure TDouble
<|> Judgement <$> pStrExpr <*> pure TString
We can write a type check phase to produce a GADT or fail, depending on whether the type assertion succeeds or not:
typecheck :: Judgement Expr -> Type ix -> Maybe (Expr ix)
typecheck (Judgement e TDouble) TDouble = Just e
typecheck (Judgement e TString) TString = Just e
typecheck _ _ = Nothing

ambiguity error with `reads` in ghc-7.8

I am testing the code for Write yourself a Scheme in 48 hours with GHC-7.8.2, which gives me an error about ambiguity that I don't recall encountering in previous versions of GHC.
The excerpt is below, with the problem line marked:
data LispVal = Atom String
| List [LispVal]
| DottedList [LispVal] LispVal
| Number Integer
| String String
| Bool Bool
unpackNum :: LispVal -> Integer
unpackNum (Number n) = n
unpackNum (String n) = let parsed = reads n in --problem line
if null parsed
then 0
else fst $ parsed !! 0
unpackNum (List [n]) = unpackNum n
unpackNum _ = 0
, and the error says:
No instance for (Read a0) arising from a use of ¡®parsed¡¯
The type variable ¡®a0¡¯ is ambiguous
Note: there are several potential instances:
instance Read a => Read (Control.Applicative.ZipList a)
-- Defined in ¡®Control.Applicative¡¯
instance Read () -- Defined in ¡®GHC.Read¡¯
instance (Read a, Read b) => Read (a, b) -- Defined in ¡®GHC.Read¡¯
...plus 26 others
If I change the problem line to
unpackNum (String n) = let parsed = reads n ::[(Integer,String)] in
then everything works fine.
I don't see why GHC failed to infer the type for ReadS from the signature of unpackNum. Can someone please explain what triggered the error?
(
-- EDIT --
Just some follow-up. From what I understand, the function type unpackNum :: LispVal -> Integer and the fact that fst $ parsed !! 0 is a return value of it tells that parsed has type [(Integer,b)], and from type ReadS a = String -> [(a,String)], the parsed should be [(a, String)]. Shouldn't these two types unify to [(Integer, String)] and fix the type for parsed?
Can someone please explain why NoMonomorphismRestriction would break the above reasoning?
-- EDIT2 --
From the answers, I can understand how NoMonomorphismRestriction could cause the issue here. Still, what I don't understand is the fact that how this "two type for the same expression" behavior consistent with laziness in Haskell. In the example parsed or reads n is the same expression in one block and should be evaluated only once. How can it have type a the first time of evaluation and Integer the second time?
)
Thanks,
This is triggered if NoMonomorphismRestriction is active; which, btw, is now the case by default in GHCi since 7.8 (see release notes, Section 1.5.2.3).
If the monomorphism restriction is disabled, the definition of parsed gets a polymorphic type, namely
parsed :: Read a => [(a, String)]
and then the first use in null parsed doesn't have sufficient contextual information to resolve what a is.
This happens to be one of the few cases where the monomorphism restriction actually does some good. Because with the polymorphic type, even if both use sites had sufficient type
information to resolve the class constraint, the actual parsing would happen twice.
The best solution is still to use pattern matching as suggested in acomar's answer.
The types should unify but don't in the presence of the NoMonomorphismRestriction (as noted in the comments by #FedorGogolev and #kosmikus). However, the following more idiomatic approach removes the need for the type annotation in any case:
data LispVal = Atom String
| List [LispVal]
| DottedList [LispVal] LispVal
| Number Integer
| String String
| Bool Bool
unpackNum :: LispVal -> Integer
unpackNum (Number n) = n
unpackNum (String n) = case reads n of
[] -> 0
((x, _):xs) -> x
unpackNum (List [n]) = unpackNum n
unpackNum _ = 0
The Difference Between Case and Null
It boils down to the fact that null is a function whereas case is straight syntax.
null :: [a] -> Bool
So with -XNoMonomorphismRestriction enabled, this is left as polymorphic as possible when the argument is supplied. The function doesn't restrict the argument type in any way, and so the compiler is unable to determine the return type of reads, causing the error. At the site of the function call, the type is ambiguous. In the case of the case statement, the compiler has the entire expression to work with, and so has the pattern matches to refine the return type of reads.

Counting occurrences in an expression

I'm pretty new to Haskell and I have an assessment which involves a manipulator and evaluator of boolean expressions.
Thee expression type is:
type Variable = String
data Expr = T | Var Variable | And Expr Expr | Not Expr
I've worked through a lot of the questions but i am stuck on how to approach the following function. I need to count the occurences of all the variables in an expression
addCounter :: Expr -> Expr
addCounter = undefined
prop_addCounter1 = addCounter (And (Var "y") (And (Var "x") (Var "y"))) ==
And (Var "y1") (And (Var "x2") (Var "y1"))
prop_addCounter2 = addCounter (Not (And (Var "y") T)) ==
Not (And (Var "y1") T)
I'm not looking for an answer on exactly how to do this as it is an assessment question but I would like some tips on how I would go about approaching this?
In my head I imagine incrementing a counter so that I can get the y1, x2 part but this isn't really something that is possible in Haskell (or not advised to do anyway!) Would I go about this through recursion and if so how do I know what number to add to the variable?
As you say you cannot keep a shared counter which would be very natural in this case. What you can do instead is to pass the current counter value down the tree as you recursively visit all Expr's, and receive back the incremented counter value from the function being called. It must be a two-way communication. You pass down the current value and receive back the updated Expr and the new counter value.
If you want each unique variable name to have the same counter value you need to keep a mapping of variable names to assigned counter values. You need to pass that one around just like the current counter value.
Hope that helps.
Atomize your stateful updates
So, this is definitely a great time to use a State monad. In particular, the atomic transform you're looking for is a way to take String -> String enumerating strings by a unique id for each string. Let's call it enumerate
import Control.Monad.State
-- | This is the only function which is going to touch our 'Variable's
enumerate :: Variable -> State OurState Variable
To do this, we'll need to track state that maps Strings to counts (Ints)
import qualified Data.Map as M
type OurState = Map String Int
runOurState :: State OurState a -> a
runOurState = flip evalState M.empty
runOurState $ mapM enumerate ["x", "y", "z", "x" ,"x", "x", "y"]
-- ["x1", "y1", "z1", "x2", "x3", "x4", "y2"]
so we can implement enumerate pretty directly as a stateful action.
enumerate :: Variable -> State OurState Variable
enumerate var = do m <- get
let n = 1 + M.findWithDefault 0 var m
put $ M.insert var n m
return $ var ++ show n
Cool!
Folding generically over an expression tree
Now we really ought to write an elaborate folding apparatus which maps Expr -> State OurState Expr by applying enumerate on each Var-type leaf.
enumerateExpr :: Expr -> State OurState Expr
enumerateExpr T = return T
enumerateExpr (Var s) = fmap Var (enumerate s)
enumerateExpr (And e1 e2) = do em1 <- addCounter e1
em2 <- addCounter e2
return (Add em1 em2)
enumerateExpr (Not expr) = fmap Not (addCounter expr)
But this is pretty tedious, so we'll use the Uniplate library to keep dry.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data
import Data.Generics.Uniplate.Data
data Expr = T | Var Variable | And Expr Expr | Not Expr
deriving (Show,Eq,Ord,Data)
onVarStringM :: (Variable -> State OurState Variable) -> Expr -> State OurState Expr
onVarStringM action = transformM go
where go :: Expr -> State OurState Expr
go (Var s) = fmap Var (action s)
go x = return x
The transformM operator does just what we want—apply a monadic transformation over all the pieces of a generic tree (our Expr).
So now, we just unpack the Stateful action to make addCounter
addCounter :: Expr -> Expr
addCounter = runOurState . onVarStringM enumerate
Oh, wait!
Just noticed, this doesn't actually have the right behavior—it doesn't enumerate your variables quite right (prop_addCounter1 fails but prop_addCounter2 passes). Unfortunately, I'm not really sure how it ought to be done... but given this separation of concerns laid out here it'd be very easy to just write the appropriate enumerate Stateful action and apply it to the same generic Expr-transforming machinery.

Haskell recursive problem, tiny parser. A few things

data Expr = Var Char | Tall Int | Sum Expr Expr | Mult Expr Expr | Neg Expr | Let Expr Expr Expr
deriving(Eq, Show)
That is the datatype for Expr, I have a few questions. I'm suppose to parse expressions like *(Expr,Expr) as shown in the datatype definition. However I do have some problems with "creating" a valid Expr. I use pattern matching for recognizing the different things Expr can be. Some more code:
parseExpr :: String -> (Expr, String)
parseExpr ('*':'(':x:',':y:')':s) = (Mult (parseExpr [x] parseExpr [y]),s)
This is not working, obviously. The return type of parseExpr is to return the rest of the expression that is to be parsed an a portion of the parsed code as an Expr. The right side of this code is the problem. I can't make a valid Expr. The function is suppose to call it self recursively until the problem is solved.
ANOTHER problem is that I don't know how to do the pattern matching against Var and Tall. How can I check that Var is an uppercase character between A-Z and that Tall is 0-9 and return it as a valid Expr?
Generally I can just look at a few parts of the string to understand what part of Expr I'm dealing with.
Input like: parseProg "let X be 9 in *(X , 2)" Would spit out: Let (Var 'X') (Tall 9) (Mult (Var 'X') (Tall 2))
Your parseExpr function returns a pair, so of course you cannot use its result directly to construct an Expr. The way I would write this would be something like
parseExpr ('*':'(':s) = (Mult x y, s'')
where (x,',':s') = parseExpr s
(y,')':s'') = parseExpr s'
The basic idea is that, since parseExpr returns the leftover string as the second argument of the pair, you need to save that string in each recursive call you make, and when you've handled all the subexpressions, you need to return whatever is left over. And obviously the error handling here sucks, so you may want to think about that a bit more if this is intended to be a robust parser.
Handling Var and Tall I would do by just extracting the first character as is and have an if to construct an Expr of the appropriate type.
And if you want to write more complex parsers in Haskell, you'll want to look at the Parsec library, which lets you write a parser as pretty much the grammar of the language you're parsing.

Resources