Add remaining haskell book exercises

This commit is contained in:
2025-12-11 10:28:11 +01:00
parent 3624c712d7
commit 98329e0a3d
221 changed files with 8033 additions and 2 deletions

View File

@@ -0,0 +1,16 @@
{-# LANGUAGE DeriveGeneric #-}
module CoArbitrary where
import GHC.Generics
import Test.QuickCheck
data Bool' = True' | False' deriving (Generic)
instance CoArbitrary Bool'
trueGen :: Gen Int
trueGen = coarbitrary True' arbitrary
falseGen :: Gen Int
falseGen = coarbitrary False' arbitrary

View File

@@ -0,0 +1,24 @@
module Main where
import Test.Hspec
import WordNumber (digitToWord, digits, wordNumber)
main :: IO ()
main = hspec $ do
describe "digitToWord" $ do
it "returns zero for 0" $ do
digitToWord 0 `shouldBe`"zero"
it "returns one for 1" $ do
digitToWord 1 `shouldBe` "one"
describe "digits" $ do
it "returns [1] for 1" $ do
digits 1 `shouldBe` [1]
it "returns [1, 0, 0] for 100" $ do
digits 100 `shouldBe` [1, 0, 0]
describe "wordNumber" $ do
it "one-zero-zero given 100" $ do
wordNumber 100 `shouldBe` "one-zero-zero"
it "nine-zero-zero-one for 9001" $ do
wordNumber 9001 `shouldBe` "nine-zero-zero-one"

View File

@@ -0,0 +1,86 @@
module Main where
import qualified Data.Map as M
import Morse
import Test.QuickCheck
import Test.QuickCheck.Gen (oneof)
allowedChars :: [Char]
allowedChars = M.keys letterToMorse
allowedMorse :: [Morse]
allowedMorse = M.elems letterToMorse
charGen :: Gen Char
charGen = elements allowedChars
morseGen :: Gen Morse
morseGen = elements allowedMorse
prop_thereAndBackAgain :: Property
prop_thereAndBackAgain =
forAll charGen (\c -> ((charToMorse c) >>= morseToChar) == Just c)
main' :: IO ()
main' = quickCheck prop_thereAndBackAgain
data Trivial = Trivial deriving (Eq, Show)
trivialGen :: Gen Trivial
trivialGen = return Trivial
instance Arbitrary Trivial where
arbitrary = trivialGen
main :: IO ()
main = do
sample trivialGen
data Identity a = Identity a deriving (Eq, Show)
identityGen :: Arbitrary a => Gen (Identity a)
identityGen = do
a <- arbitrary
return (Identity a)
instance Arbitrary a => Arbitrary (Identity a) where
arbitrary = identityGen
identityGenInt :: Gen (Identity Int)
identityGenInt = identityGen
data Pair a b = Pair a b deriving (Eq, Show)
pairGen :: (Arbitrary a, Arbitrary b) => Gen (Pair a b)
pairGen = do
a <- arbitrary
b <- arbitrary
return (Pair a b)
instance (Arbitrary a, Arbitrary b) => Arbitrary (Pair a b) where
arbitrary = pairGen
pairGenIntString :: Gen (Pair Int String)
pairGenIntString = pairGen
data Sum a b = First a | Second b deriving (Eq, Show)
sumGenEqual :: Gen (Sum Char Int)
sumGenEqual = do
a <- arbitrary
b <- arbitrary
oneof [return $ First a,
return $ Second b]
sumGenCharInt :: Gen (Sum Char Int)
sumGenCharInt = sumGenEqual
sumGenFirstPls :: (Arbitrary a, Arbitrary b) => Gen (Sum a b)
sumGenFirstPls = do
a <- arbitrary
b <- arbitrary
frequency [(10, return $ First a),
(1, return $ Second b)]
sumGenCharIntFirst :: Gen (Sum Char Int)
sumGenCharIntFirst = sumGenFirstPls