Skip to content

Instantly share code, notes, and snippets.

@jbpotonnier
Last active December 28, 2015 18:39
Show Gist options
  • Save jbpotonnier/5822c979318f9574fc98 to your computer and use it in GitHub Desktop.
Save jbpotonnier/5822c979318f9574fc98 to your computer and use it in GitHub Desktop.
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}
module Polynomial where
import Test.SmallCheck.Series (Serial)
import GHC.Generics (Generic)
import qualified Text.ParserCombinators.Parsec as Parsec
import Text.ParserCombinators.Parsec (ParseError, Parser, sepBy1)
import qualified Data.List as List
import Text.Parsec.Char (digit, string, char)
import Text.Parsec.Combinator (many1)
import Control.Applicative ((<$>), (<*>), (<*), (*>), (<|>))
data Monomial = Monomial Integer Integer
deriving (Show, Eq, Generic)
instance Monad m => Serial m Monomial
data Polynomial = Polynomial [Monomial]
deriving (Show, Eq, Generic)
instance Monad m => Serial m Polynomial
formatMonomial :: Monomial -> String
formatMonomial (Monomial a n) = concat [show a, "x^", show n]
pretty :: Polynomial -> String
pretty (Polynomial ms) = (List.intercalate " + " . map formatMonomial) ms
monomialParser :: Parser Monomial
monomialParser = Monomial <$> (integer <* string "x^") <*> integer
where
positive :: Parser Integer
positive = read <$> many1 digit
negative :: Parser Integer
negative = negate <$> (char '-' *> positive)
integer :: Parser Integer
integer = negative <|> positive
parseMonomial :: String -> Either ParseError Monomial
parseMonomial = Parsec.parse monomialParser ""
polynomialParser :: Parser Polynomial
polynomialParser = Polynomial <$> monomialParser `sepBy1` string " + "
parsePolynomial :: String -> Either ParseError Polynomial
parsePolynomial = Parsec.parse polynomialParser ""
deriveMonomial :: Monomial -> Monomial
deriveMonomial (Monomial a n) = Monomial (n * a) (n-1)
derivePolynomial :: Polynomial -> Polynomial
derivePolynomial (Polynomial ms) = Polynomial (map deriveMonomial ms)
main :: IO ()
main = do
input <- getLine
let derived = (fmap derivePolynomial . parsePolynomial) input
either print (putStrLn . pretty) derived
module PolynomialSpec where
import Polynomial (Monomial(..),
Polynomial(..),
formatMonomial,
pretty,
parseMonomial,
parsePolynomial,
deriveMonomial,
derivePolynomial)
import Test.Hspec
import Test.Hspec.SmallCheck (property)
import Test.SmallCheck ((==>))
main :: IO ()
main = hspec $ do
describe "Monomial" $ do
it "should format a Monomial" $ do
formatMonomial (Monomial 3 2) `shouldBe` "3x^2"
it "should format a Monomial with a negative coefficient" $ do
formatMonomial (Monomial (-3) 2) `shouldBe` "-3x^2"
it "should parse a Monomial" $ do
property $ \m -> case (parseMonomial . formatMonomial) m of
Left _ -> False
Right parsedMonomial -> parsedMonomial == m
it "should derive a Monomial" $ do
deriveMonomial (Monomial 3 2) `shouldBe` Monomial 6 1
describe "Polynomial" $ do
it "should format a Polynomial" $ do
pretty (Polynomial [Monomial 2 3, Monomial 3 2]) `shouldBe` "2x^3 + 3x^2"
it "should parse a Polynomial" $ do
property $ \p@(Polynomial ms) ->
(not . null) ms ==> case (parsePolynomial . pretty) p of
Left _ -> False
Right parsedPolynomial -> parsedPolynomial == p
it "should derive a Polynomial" $ do
derivePolynomial (Polynomial [Monomial 2 3, Monomial 3 2])
`shouldBe`
(Polynomial [Monomial 6 2, Monomial 6 1])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment