Last active
April 22, 2019 07:14
-
-
Save jaymoid/5ae8d22007cc48f3939cf2201dfc48af to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE InstanceSigs #-} | |
module WriteStateForYourself where | |
import Test.Hspec (describe, hspec, shouldBe, it) | |
import Test.QuickCheck.Classes (functor, applicative, monad) | |
import Test.Hspec.Checkers (testBatch) | |
import Test.QuickCheck (Arbitrary(..), CoArbitrary(..)) | |
import Test.QuickCheck.Checkers (EqProp(..)) | |
import Text.Show.Functions () -- For generating instances of show for functions | |
import Data.Char (ord) | |
newtype Moi s a = Moi { runMoi :: s -> (a, s) } | |
deriving (Show) | |
instance Functor (Moi s) where | |
fmap :: (a -> b) -> Moi s a -> Moi s b | |
fmap f (Moi g) = Moi (\s -> let (a, s') = g s | |
in (f a, s')) | |
instance Applicative (Moi s) where | |
pure :: a -> Moi s a | |
pure a = Moi (\s -> (a, s)) | |
(<*>) :: Moi s (a -> b) -> Moi s a -> Moi s b | |
(Moi f) <*> (Moi g) = Moi (\s0 -> | |
let (a, s1) = g s0 | |
(aToB, s2) = f s1 | |
b = aToB a | |
in (b, s2)) | |
instance Monad (Moi s) where | |
return = pure | |
(>>=) :: Moi s a -> (a -> Moi s b) -> Moi s b | |
-- (Moi f) >>= g = Moi (\s0 -> | |
-- let (a, s1) = f s0 | |
-- in runMoi (g a) s1 | |
-- alternatively match the function in the Moi... | |
(Moi f) >>= g = Moi (\s0 -> | |
let (a, s1) = f s0 | |
Moi h = g a | |
in h s1) | |
instance (CoArbitrary s, Arbitrary a, Arbitrary s) => Arbitrary (Moi s a) where | |
arbitrary = Moi <$> arbitrary | |
instance ( Arbitrary s | |
, Show s | |
, EqProp s | |
, Arbitrary a | |
, Show a | |
, EqProp a ) => EqProp (Moi s a) where | |
(Moi s1) =-= (Moi s2) = s1 =-= s2 | |
main :: IO () | |
main = hspec $ do | |
describe "Moi State Functor" $ do | |
it "Example from the book" $ do | |
runMoi ((+1) <$> (Moi $ \s -> (0, s))) 0 `shouldBe` (1 :: Int, 0 :: Int) | |
it "Modified example from the book" $ do | |
let moi :: Moi Char Int | |
moi = Moi $ \s -> (0, s) | |
runMoi (fmap (+40) moi) 'c' `shouldBe` (40, 'c') | |
describe "Moi State Applicative" $ do | |
it "Example use." $ do | |
let moi1 :: Moi [Char] Int | |
moi1 = Moi (\s -> (length s * 2, s <> "moi1 ")) | |
moi2 :: Moi [Char] (Int -> Double) | |
moi2 = Moi (\s -> (\a -> 0.5 + (fromIntegral a), s <> "moi2 ")) | |
runMoi (moi2 <*> moi1) "hello " `shouldBe` (12.5, "hello moi1 moi2 ") | |
describe "Moi State Monad" $ do | |
it "Example use." $ do | |
let moi :: Moi Char Int | |
moi = Moi (\char -> (ord char, succ char)) | |
fToMoi :: Int -> Moi Char Int | |
fToMoi n = Moi (\char -> (n + (ord char), (succ . succ) char)) | |
runMoi (moi >>= fToMoi) 'a' `shouldBe` (195, 'd') | |
-- a = 97 | |
-- b = 98 | |
-- 97 + 98 = 195 | |
describe "Moi property based tests" $ do | |
let testType :: Moi Char (Int, Int, [Int]) | |
testType = undefined | |
testBatch (functor testType) | |
testBatch (applicative testType) | |
testBatch (monad testType) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
From FP Chat Slack group: Gabriel Lebec kindly helped me out:
James Pittendreigh [7:55 AM]
Hi, I’m stumped on one of the questions in ch23 - State. Well not so much the question, more testing it. The question asks you to implement the State type for yourself, and write Functor, Applicative and Monad instances for it.
I’d like to be able to test that the instances are lawful using quickcheck + checkers, like in the previous chapters, however I’m struggling to write the EqProp instance (presumably because State wraps a function). Anyone able to take a look please?
I’ve gist’ed up the code here: https://gist.github.com/jaymoid/5ae8d22007cc48f3939cf2201dfc48af
glebec [5:31 PM]
EqProp
definitely cannot beeq
because, as you point out, each state instance is a function, and extensional function equality is undecidable (in other words, no program can be written which can tell you if two functions behave identically for all inputs). (edited)However… (edited)
(checking my own work on this problem)
Yeah, I didn't attempt to write the
checkers
tests for this exerciseIn theory it seems to me like you could verify the equality (for a finite number of checks) itself through some prop testing? generate random
s
inputs and verify that the(a, s)
output is the same for your two functions? Not sure how to makecheckers
understand that though. And using a property test in your property test sounds slloooowwwww. (edited)glebec [5:56 PM]
Hm. I feel like this indicates that functions should be able to have an
EqProp
instance, because you can do random sampling:(http://hackage.haskell.org/package/checkers-0.5.0/docs/Test-QuickCheck-Checkers.html#t:EqProp)
Trying to see if I can find an example.
Yes, in fact there is an
EqProp
instance for funcs. http://hackage.haskell.org/package/checkers-0.5.0/docs/Test-QuickCheck-Checkers.html#t:EqProp@james Pittendreigh I think all you have to do is extract the functions from your
Moi
newtype and run=-=
on them?Something like
(Moi s1) =-= (Moi s2) = s1 =-= s2
Or using
Data.Function.on
to be cute:(=-=) = (=-=) `on` runMoi
You may have to add some constraints to make it all type check – specifically
EqProp s, EqProp a
glebec [6:28 PM]
Got it
Thanks for the challenge, learned a little more about
=-=
today 👍And FYI your code passes the checkers tests 😉
James Pittendreigh [9:09 PM]
@glebec Thanks very much, this worked! 😄 Apologies for my slow response (was BBQ’ing) - thanks also for explaining why functions equality is undecidable, this makes sense now. So I guess the best we can do is assert that it yields the same results for the given inputs?
I guess the only thing I don’t understand is how you worked out the required type preconditions for the EqProp instance?
I realise this is kinda beyond what the question asked, but one thing I’ve really got from this book is how awesome property based testing is, and I’m a bit of a testing nerd so I try and test everything. (p.s. for anyone else reading I have updated my gist with Glebec’s working EqProp instance)
glebec [9:14 PM]
@james Pittendreigh honestly I just kept adding whatever constraints the type checker yelled about until it worked
glebec [9:25 PM]
And yeah while there can be no
Eq
instance for functions, there can be (and is) anEqProp
instance, wherecheckers
/QuickCheck
generate many arbitrarys
values and confirm that your two functions both return the same(a, s)
tuples.That doesn’t prove they are equal functions but it does verify that they seem to be equal for a finite number of random inputs.
Which is better than nothing.
James Pittendreigh [9:36 PM]
Gotcha, thanks again.
Message Input
Message #haskellbook