Skip to content

Commit 96c25a8

Browse files
author
matteB10
committed
hej
1 parent 866e8f2 commit 96c25a8

File tree

3 files changed

+105
-28
lines changed

3 files changed

+105
-28
lines changed

Labb4MB.hs

+40-7
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,13 @@
11
import Test.QuickCheck
2+
import Parsing
23
import Data.Maybe
4+
import Data.Char
35
import Data.List
6+
import Control.Monad
47

58

69
data Expr = Num Double
7-
| Var
10+
| Var Char
811
| BinOp String (Double -> Double -> Double) Expr Expr
912
| MonoOp String (Double -> Double) Expr
1013

@@ -14,10 +17,10 @@ instance Show Expr
1417

1518
showExpr :: Expr -> String
1619
showExpr (Num n) = show n
17-
showExpr Var = "x"
20+
showExpr (Var _) = "x"
1821
showExpr (MonoOp name _ expr) = name ++ " " ++ case expr of
1922
(Num n) -> showExpr expr
20-
Var -> showExpr expr
23+
(Var _) -> showExpr expr
2124
_ -> " (" ++ showExpr expr ++ ") "
2225
showExpr (BinOp name _ expr1 expr2) = case name of
2326
"*" -> showFactor expr1 ++ " " ++ name ++ " " ++ showFactor expr2
@@ -29,7 +32,7 @@ showExpr (BinOp name _ expr1 expr2) = case name of
2932
--------------------------------------------------------
3033

3134
x :: Expr
32-
x = Var
35+
x = Var 'x'
3336

3437
num :: Double -> Expr
3538
num d = Num d
@@ -52,17 +55,47 @@ test3 = mul (add (Num 1) (Num 2)) (add (Num 3) (Num 5)) -- = 3 * 8 = 24
5255
test4 = add (add (Num 1) (Num 2)) (add (Num 3) (Num 5)) -- = 3 + 8 = 11
5356
test5 = mul (mul (Num 1) (Num 2)) (mul (Num 3) (Num 5)) -- = 1*2 * 3*5 = 2 * 15 = 30
5457

55-
test6 = mul (mul (Var) (Num 2)) (mul (Num 3) (Num 5)) -- = 1*2 * 3*5 = 2 * 15 = 30
58+
test6 = mul (mul (Var 'x') (Num 2)) (mul (Num 3) (Num 5)) -- = 1*2 * 3*5 = 2 * 15 = 30
5659

5760
--------------------------------------------------
5861

5962
-- | Evaluates a given expression, where the second argument is the value of x
6063
eval :: Expr -> Double -> Double
61-
eval (Var) x = x
64+
eval (Var _) x = x
6265
eval (Num n) _ = n
6366
eval (BinOp _ op i j) x = (eval i x) `op` (eval j x)
6467
eval (MonoOp _ op i) x = op (eval i x)
6568

6669
-- | Tries to read a expression from a string
6770
readExpr :: String -> Maybe Expr
68-
readExpr = undefined
71+
readExpr s = undefined
72+
73+
{-}
74+
do
75+
let s' = filter (not . isSpace) s
76+
77+
-}
78+
79+
-- | Parse a number
80+
number :: Parser Double
81+
number = read <$> oneOrMore digit
82+
83+
-- | Parse an x-variable
84+
xparse :: Parser Char
85+
xparse = char 'x'
86+
87+
expr, term, factor :: Parser Expr
88+
expr = foldl1 add <$> chain term (char '+')
89+
term = foldl1 mul <$> chain factor (char '*')
90+
factor = Num <$> number <|> (Var <$> xparse <|> char '(' *> expr <* char ')')
91+
92+
93+
94+
main = do putStrLn "Welcome to the simple calculator!"
95+
readEvalPrint = do
96+
putStr "What would you like to calculate?"
97+
s <- getLine
98+
let s' = filter (not . isSpace) s
99+
case parse expr s' of
100+
Just (e, "") -> print $ eval e 1
101+
Nothing -> putStrLn "Invalid Expression!"

Parsing.hs renamed to ParsingMB.hs

+63-21
Original file line numberDiff line numberDiff line change
@@ -2,30 +2,14 @@
22
Module : Parsing
33
Description : Simple Monadic Parsing Library
44
Maintainer : Thomas Hallgren
5+
56
A Simple Monadic Parsing Library
7+
68
Used in the course Functional Programming GU/Chalmers.
7-
Original author: David Sands.
89
9-
---------------------
10-
Aim: reusable Parser combinators including
11-
a new type for the Parser,
12-
but no export of the constructor
13-
Changes (v3 2016) Thomas Hallgren
14-
Export <* and *> from class Applicative instead of the combinators <-< and >->
15-
Export <|> from class Alternative instead of +++
16-
Changes (v2 2015)
17-
For compatibility with GHC>=7.10 Parser
18-
is now also instance Applicative
19-
Removal: Class Functor, Applicative and Monad provide a number of
20-
functions that were previously exported explicitly, in particular
21-
(>*>) is available as the bind operation (>>=),
22-
success is return, pmap is fmap.
23-
Additional function:
24-
readsP :: Read a => Parser a
25-
-- satisfies
26-
-- parse readsP s == listToMaybe (reads s)
27-
---------------------
10+
Original author: David Sands.
2811
-}
12+
2913
module Parsing
3014
( -- * The Parser type
3115
Parser -- exports the type name but not the constructors
@@ -47,51 +31,94 @@ module Parsing
4731
,(*>)
4832
-- ** Return a result without consuming any input
4933
, return
50-
)
34+
)
35+
36+
{----------------------
37+
38+
Aim: reusable Parser combinators including
39+
a new type for the Parser,
40+
but no export of the constructor
41+
42+
Changes (v3 2016) Thomas Hallgren
43+
Export <* and *> from class Applicative instead of the combinators <-< and >->
44+
Export <|> from class Alternative instead of +++
45+
46+
Changes (v2 2015)
47+
For compatibility with GHC>=7.10 Parser
48+
is now also instance Applicative
49+
50+
Removal: Class Functor, Applicative and Monad provide a number of
51+
functions that were previously exported explicitly, in particular
52+
(>*>) is available as the bind operation (>>=),
53+
success is return, pmap is fmap.
54+
55+
Additional function:
56+
readsP :: Read a => Parser a
57+
-- satisfies
58+
-- parse readsP s == listToMaybe (reads s)
59+
60+
----------------------}
5161
where
62+
5263
import Data.Char
5364
import Data.Maybe(listToMaybe)
5465
-- boilerplate for GHC 10.7 compatibility:
5566
import Control.Applicative (Applicative(..),Alternative(..))
5667
import Control.Monad (liftM, ap)
68+
5769
------------------
5870

71+
72+
73+
5974
-- | The abstract data type representing a Parser
6075
newtype Parser a = P (String -> Maybe (a,String))
76+
6177
-- | Runs the parser on the given string
6278
-- to return maybe a thing and a string
6379
parse :: Parser a -> String -> Maybe(a,String)
6480
parse (P f ) s = f s
81+
6582
-- | A parser for anything in the Read class,
6683
-- satisfying
6784
--
6885
-- prop> parse readsP s == listToMaybe (reads s)
86+
6987
readsP :: Read a => Parser a
7088
readsP = P $ listToMaybe . reads
89+
7190
-------------------
7291
-- | Parser than can never succeed
7392
failure :: Parser a -- always fails
7493
failure = P $ \s ->
7594
Nothing
95+
7696
-- | Parser that succeeds without looking at the String
7797
success :: a -> Parser a
7898
success a = P $ \s ->
7999
Just (a,s)
100+
80101
-- | Parse any single character
81102
item = P $ \s ->
82103
case s of
83104
(c:s') -> Just (c,s')
84105
"" -> Nothing
106+
107+
85108
infixr 3 +++
86109
-- | Try the first parser and if it fails try the second
87110
(+++) :: Parser a -> Parser a -> Parser a
88111
p +++ q = P $ \s ->
89112
case parse p s of
90113
Nothing -> parse q s
91114
r -> r
115+
116+
92117
-- (p >*> f) parse using p to produce a.
93118
-- Then parse using f a
119+
94120
infixl 1 >*>
121+
95122
(>*>) :: Parser a -> (a -> Parser b) -> Parser b
96123
p >*> f = P $ \s ->
97124
case parse p s of
@@ -100,42 +127,57 @@ p >*> f = P $ \s ->
100127
-----------------------------------------------
101128
-- Parsers below do not depend on the internal
102129
-- representation of Parser
130+
103131
-- | parse a single character satisfying property p
104132
sat :: (Char -> Bool) -> Parser Char
105133
sat p = item >*> \a -> if p a then success a else failure
134+
106135
-- | parse a digit character
107136
digit :: Parser Char
108137
digit = sat isDigit
138+
109139
-- | Parse a specific character
110140
char c = sat (==c)
141+
111142
-- example: parse any lowercase letter
112143
-- followed by its uppercase equivalent aA or bB etc.
113144
ex1 = sat isAsciiLower >*> char . toUpper
145+
114146
-- pmap modifies the result of a parser
147+
148+
115149
-- | Parse a thing, then parse a list of things, and
116150
-- return the first thing followed by the list of things
117151
(<:>):: Parser a -> Parser [a] -> Parser [a]
118152
p <:> q = p >*> \a -> fmap (a:) q
153+
119154
-- | Parse zero or more things
120155
zeroOrMore :: Parser a -> Parser [a]
121156
zeroOrMore p = oneOrMore p +++ success []
157+
122158
-- | Parse one or more things
123159
oneOrMore :: Parser a -> Parser [a]
124160
oneOrMore p = p <:> zeroOrMore p
161+
125162
-- | Parse a list of as, separated by bs
126163
chain :: Parser a -> Parser b -> Parser [a]
127164
chain p q = p <:> zeroOrMore (q *> p)
165+
128166
-- example: comma separated digits "1,2,3"
167+
129168
-- Standard definition for Functor and Applicative for
130169
-- GHC>=7.10 compatibility
131170
instance Functor Parser where
132171
fmap = liftM
172+
133173
instance Applicative Parser where
134174
pure = success
135175
(<*>) = ap
176+
136177
instance Monad Parser where
137178
(>>=) = (>*>)
138179
return = pure
180+
139181
instance Alternative Parser where
140182
empty = failure
141183
(<|>) = (+++)

desktop.ini

+2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
[LocalizedFileNames]
2+
Parsing.hs=@Parsing,0

0 commit comments

Comments
 (0)