Skip to content
Snippets Groups Projects
Commit d6595281 authored by ik1g19's avatar ik1g19
Browse files

added previous work

parents
Branches
Tags
No related merge requests found
.stack-work/
*~
\ No newline at end of file
# Changelog for cw
## Unreleased changes
Copyright ik (c) 2020
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
* Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above
copyright notice, this list of conditions and the following
disclaimer in the documentation and/or other materials provided
with the distribution.
* Neither the name of ik nor the names of other
contributors may be used to endorse or promote products derived
from this software without specific prior written permission.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
# cw
import Distribution.Simple
main = defaultMain
module Main where
import Challenges
main :: IO()
main = do putStrLn "Not Implemented"
\ No newline at end of file
cabal-version: 1.12
-- This file has been generated from package.yaml by hpack version 0.33.0.
--
-- see: https://github.com/sol/hpack
--
-- hash: fd3572af2df5b17566ae6c18bb0f88fc92d2e2f57139c9406ef8b0287c0d1985
name: cw
version: 0.1.0.0
description: Please see the README on GitHub at <https://github.com/ik1g19/cw#readme>
homepage: https://github.com/ik1g19/cw#readme
bug-reports: https://github.com/ik1g19/cw/issues
author: ik
maintainer: ik1g19@soton.ac.uk
copyright: ik
license: BSD3
license-file: LICENSE
build-type: Simple
extra-source-files:
README.md
ChangeLog.md
source-repository head
type: git
location: https://github.com/ik1g19/cw
library
exposed-modules:
Challenges
Lib
Parsing
other-modules:
Paths_cw
hs-source-dirs:
src
build-depends:
base >=4.7 && <5
, deepseq
, random
default-language: Haskell2010
executable cw-exe
main-is: Main.hs
other-modules:
Paths_cw
hs-source-dirs:
app
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
, cw
, deepseq
, random
default-language: Haskell2010
test-suite cw-test
type: exitcode-stdio-1.0
main-is: Spec.hs
other-modules:
Paths_cw
hs-source-dirs:
test
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
, cw
, deepseq
, random
default-language: Haskell2010
name: cw
version: 0.1.0.0
github: "ik1g19/cw"
license: BSD3
author: "ik"
maintainer: "ik1g19@soton.ac.uk"
copyright: "ik"
extra-source-files:
- README.md
- ChangeLog.md
# Metadata used when publishing your package
# synopsis: Short description of your package
# category: Web
# To avoid duplicated efforts in documentation and dealing with the
# complications of embedding Haddock markup inside cabal files, it is
# common to point users to the README.md file.
description: Please see the README on GitHub at <https://github.com/ik1g19/cw#readme>
dependencies:
- base >= 4.7 && < 5
- random
- deepseq
library:
source-dirs: src
executables:
cw-exe:
main: Main.hs
source-dirs: app
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- cw
tests:
cw-test:
main: Spec.hs
source-dirs: test
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- cw
{-# LANGUAGE DeriveGeneric #-}
-- comp2209 Functional Programming Challenges
-- (c) University of Southampton 2020
-- Skeleton code to be updated with your solutions
-- The dummy functions here simply return an arbitrary value that is usually wrong
-- DO NOT MODIFY THE FOLLOWING LINES OF CODE
module Challenges (WordSearchGrid,Placement,Posn,Orientation(..),solveWordSearch, createWordSearch,
LamMacroExpr(..),LamExpr(..),prettyPrint, parseLamMacro,
cpsTransform,innerRedn1,outerRedn1,compareInnerOuter,generatePos) where
-- Import standard library and parsing definitions from Hutton 2016, Chapter 13
-- We import System.Random - make sure that your installation has it installed - use stack ghci and stack ghc
import Data.Char
import Parsing
import Control.Monad
import Data.List
import GHC.Generics (Generic,Generic1)
import Control.DeepSeq
import System.IO
import System.Random
-- types for Part I
type WordSearchGrid = [[ Char ]]
type Placement = (Posn,Orientation)
type Posn = (Int,Int)
data Orientation = Forward | Back | Up | Down | UpForward | UpBack | DownForward | DownBack deriving (Eq,Ord,Show,Read)
-- types for Parts II and III
data LamMacroExpr = LamDef [ (String,LamExpr) ] LamExpr deriving (Eq,Show,Read)
data LamExpr = LamMacro String | LamApp LamExpr LamExpr |
LamAbs Int LamExpr | LamVar Int deriving (Eq,Show,Read)
-- END OF CODE YOU MUST NOT MODIFY
-- ADD YOUR OWN CODE HERE
-- Challenge 1 --
--attempts to find each string in the input list
solveWordSearch :: [ String ] -> WordSearchGrid -> [ (String,Maybe Placement) ]
solveWordSearch ss css = map (findString css) ss
findString :: WordSearchGrid -> String -> (String,Maybe Placement)
findString css s = (s,findLocation css 0 0 s)
--recursively searches grid for first char of word
--returns Nothing or Placement
findLocation :: WordSearchGrid -> Int -> Int -> String -> Maybe Placement
findLocation css x y s@(l:ls) | x > limit && y > limit = Nothing
| x > limit = findLocation css 0 (y+1) s
| (css !! y) !! x == l && result /= Nothing = result
| otherwise = findLocation css (x+1) y s
where
result = findPlacement css x y ls
limit = length css - 1
--checks for hidden word in possible directions
findPlacement :: WordSearchGrid -> Int -> Int -> String -> Maybe Placement
findPlacement css x y s | checkWordDir css (x,y) Forward s = Just ((x,y),Forward)
| checkWordDir css (x,y) Back s = Just ((x,y),Back)
| checkWordDir css (x,y) Up s = Just ((x,y),Up)
| checkWordDir css (x,y) Down s = Just ((x,y),Down)
| checkWordDir css (x,y) UpForward s = Just ((x,y),UpForward)
| checkWordDir css (x,y) UpBack s = Just ((x,y),UpBack)
| checkWordDir css (x,y) DownForward s = Just ((x,y),DownForward)
| checkWordDir css (x,y) DownBack s = Just ((x,y),DownBack)
| otherwise = Nothing
checkWordDir :: WordSearchGrid -> (Int,Int) -> Orientation -> String -> Bool
checkWordDir css (x,y) dir (l:[]) | nextLetter css x y dir == Just l = True
| otherwise = False
checkWordDir css (x,y) dir (l:ls) | nextLetter css x y dir == Just l = checkWordDir css (nextPos (x,y) dir) dir ls
| otherwise = False
--------------------pattern matching for traversing the grid--------------------
--returns position of movement in a given direction
nextPos :: (Int,Int) -> Orientation -> (Int,Int)
nextPos (x,y) Forward = (x+1,y)
nextPos (x,y) Back = (x-1,y)
nextPos (x,y) Up = (x,y-1)
nextPos (x,y) Down = (x,y+1)
nextPos (x,y) UpForward = (x+1,y-1)
nextPos (x,y) UpBack = (x-1,y-1)
nextPos (x,y) DownForward = (x+1,y+1)
nextPos (x,y) DownBack = (x-1,y+1)
--returns element
nextLetter :: WordSearchGrid -> Int -> Int -> Orientation -> Maybe Char
-- nextLetter css x y Forward | x == length css - 1 = Nothing
-- | otherwise = Just ((css !! y) !! (x + 1))
-- nextLetter css x y Back | x == 0 = Nothing
-- | otherwise = Just ((css !! y) !! (x - 1))
-- nextLetter css x y Up | y == 0 = Nothing
-- | otherwise = Just ((css !! (y - 1)) !! x)
-- nextLetter css x y Down | y == length css - 1 = Nothing
-- | otherwise = Just ((css !! (y + 1)) !! x)
-- nextLetter css x y UpForward | y == 0 || x == length css - 1 = Nothing
-- | otherwise = Just ((css !! (y - 1)) !! (x + 1))
-- nextLetter css x y UpBack | y == 0 || x == 0 = Nothing
-- | otherwise = Just ((css !! (y - 1)) !! (x - 1))
-- nextLetter css x y DownForward | y == length css - 1 || x == length css - 1 = Nothing
-- | otherwise = Just ((css !! (y + 1)) !! (x + 1))
-- nextLetter css x y DownBack | y == length css - 1 || x == 0 = Nothing
-- | otherwise = Just ((css !! (y + 1)) !! (x - 1))
nextLetter css x y dir | x' < 0 || y' < 0 || x' > length css - 1 || y' > length css - 1 = Nothing
| otherwise = Just ((css !! y') !! x')
where
(x',y') = nextPos (x,y) dir
-- Two examples for you to try out, the first of which is in the instructions
exGrid1'1 = [ "HAGNIRTSH" , "SACAGETAK", "GCSTACKEL","MGHKMILKI","EKNLETGCN","TNIRTLETE","IRAAHCLSR","MAMROSAGD","GIZKDDNRG" ]
exWords1'1 = [ "HASKELL","STRING","STACK","MAIN","METHOD"]
exGrid1'2 = ["ROBREUMBR","AURPEPSAN","UNLALMSEE","YGAUNPYYP","NLMNBGENA","NBLEALEOR","ALRYPBBLG","NREPBEBEP","YGAYAROMR"]
exWords1'2 = [ "BANANA", "ORANGE", "MELON", "RASPBERRY","APPLE","PLUM","GRAPE" ]
-- Challenge 2 --
--internal grid values are either a character or a placeholder for a random letter
data GridVals = Letter Char | Rand
type RandGrid = [[GridVals]]
-- createWordSearch :: [ String ] -> Double -> IO WordSearchGrid
-- createWordSearch ss den = return (createGrid ss dim)
-- where
-- charInInput = sum (map length ss)
-- longestWordLen = max (map length ss)
-- dim = head [x | x <- [0..], x^2 > (charInInput / den), x >= longestWordLen]
-- createGrid :: [String] -> Int -> WordSearchGrid
-- createGrid ss dim = addStrsToGrid tempGrid ss
-- where
-- tempGrid :: RandGrid
-- tempGrid = replicate dim (replicate dim Rand)
-- addStrsToGrid :: RandGrid -> [String] -> RandGrid
-- addStrsToGrid rg (s:ss) = addStrsToGrid newGrid ss
-- where
-- newGrid :: RandGrid
-- newGrid =
-- --takes a grid, string and a position
-- --returns a list of valid orientations for the string at that position
-- validDirs :: RandGrid -> String -> (Int,Int) -> [Orientation]
-- validDirs rg s (x,y) =
-- --checks whether an orientation for a string at a given position
-- --in a grid is valid
-- checkDir :: RandGrid -> String -> (Int,Int) -> Orientation -> Bool
-- checkDir rg s (x,y) dir =
-- insertString :: RandGrid -> String -> RandGrid
-- insertString rg s =
-- generatePos :: StdGen -> Int -> IO (Int,Int)
-- generatePos gen dim = do let (x,newGen) = randomR (1,dim) gen :: (Int,StdGen)
-- let (y,_) = randomR (1,dim) newGen :: (Int,StdGen)
-- return (x,y)
-- --- Convenience functions supplied for testing purposes
-- createAndSolve :: [ String ] -> Double -> IO [ (String, Maybe Placement) ]
-- createAndSolve words maxDensity = do g <- createWordSearch words maxDensity
-- let soln = solveWordSearch words g
-- printGrid g
-- return soln
-- printGrid :: WordSearchGrid -> IO ()
-- printGrid [] = return ()
-- printGrid (w:ws) = do putStrLn w
-- printGrid ws
createWordSearch :: [ String ] -> Double -> IO WordSearchGrid
createWordSearch ss den = return []
generatePos :: Int -> StdGen -> IO (Int,Int)
generatePos dim gen = do let (x,newGen) = randomR (1,dim) gen :: (Int,StdGen)
let (y,_) = randomR (1,dim) newGen :: (Int,StdGen)
return (x,y)
-- Challenge 3 --
prettyPrint :: LamMacroExpr -> String
prettyPrint _ = ""
-- examples in the instructions
ex3'1 = LamDef [] (LamApp (LamAbs 1 (LamVar 1)) (LamAbs 1 (LamVar 1)))
ex3'2 = LamDef [] (LamAbs 1 (LamApp (LamVar 1) (LamAbs 1 (LamVar 1))))
ex3'3 = LamDef [ ("F", LamAbs 1 (LamVar 1) ) ] (LamAbs 2 (LamApp (LamVar 2) (LamMacro "F")))
ex3'4 = LamDef [ ("F", LamAbs 1 (LamVar 1) ) ] (LamAbs 2 (LamApp (LamAbs 1 (LamVar 1)) (LamVar 2)))
-- Challenge 4 --
parseLamMacro :: String -> Maybe LamMacroExpr
parseLamMacro _ = Nothing
-- Challenge 5
cpsTransform :: LamMacroExpr -> LamMacroExpr
cpsTransform _ = LamDef [] (LamVar 0)
-- Examples in the instructions
exId = (LamAbs 1 (LamVar 1))
ex5'1 = LamDef [] (LamApp (LamVar 1) (LamVar 2))
ex5'2 = (LamDef [ ("F", exId) ] (LamVar 2) )
ex5'3 = (LamDef [ ("F", exId) ] (LamMacro "F") )
ex5'4 = (LamDef [ ("F", exId) ] (LamApp (LamMacro "F") (LamMacro "F")))
-- Challenge 6
innerRedn1 :: LamMacroExpr -> Maybe LamMacroExpr
innerRedn1 _ = Nothing
outerRedn1 :: LamMacroExpr -> Maybe LamMacroExpr
outerRedn1 _ = Nothing
compareInnerOuter :: LamMacroExpr -> Int -> (Maybe Int,Maybe Int,Maybe Int,Maybe Int)
compareInnerOuter _ _ = (Nothing,Nothing,Nothing,Nothing)
-- Examples in the instructions
-- (\x1 -> x1 x2)
ex6'1 = LamDef [] (LamAbs 1 (LamApp (LamVar 1) (LamVar 2)))
-- def F = \x1 -> x1 in F
ex6'2 = LamDef [ ("F",exId) ] (LamMacro "F")
-- (\x1 -> x1) (\x2 -> x2)
ex6'3 = LamDef [] ( LamApp exId (LamAbs 2 (LamVar 2)))
-- (\x1 -> x1 x1)(\x1 -> x1 x1)
wExp = (LamAbs 1 (LamApp (LamVar 1) (LamVar 1)))
ex6'4 = LamDef [] (LamApp wExp wExp)
-- def ID = \x1 -> x1 in def FST = (\x1 -> λx2 -> x1) in FST x3 (ID x4)
ex6'5 = LamDef [ ("ID",exId) , ("FST",LamAbs 1 (LamAbs 2 (LamVar 1))) ] ( LamApp (LamApp (LamMacro "FST") (LamVar 3)) (LamApp (LamMacro "ID") (LamVar 4)))
-- def FST = (\x1 -> λx2 -> x1) in FST x3 ((\x1 ->x1) x4))
ex6'6 = LamDef [ ("FST", LamAbs 1 (LamAbs 2 (LamVar 1)) ) ] ( LamApp (LamApp (LamMacro "FST") (LamVar 3)) (LamApp (exId) (LamVar 4)))
-- def ID = \x1 -> x1 in def SND = (\x1 -> λx2 -> x2) in SND ((\x1 -> x1 x1 ) (\x1 -> x1 x1)) ID
ex6'7 = LamDef [ ("ID",exId) , ("SND",LamAbs 1 (LamAbs 2 (LamVar 2))) ] (LamApp (LamApp (LamMacro "SND") (LamApp wExp wExp) ) (LamMacro "ID") )
module Lib
( someFunc
) where
someFunc :: IO ()
someFunc = putStrLn "someFunc"
-- Functional parsing library from chapter 13 of Programming in Haskell,
-- Graham Hutton, Cambridge University Press, 2016.
module Parsing (module Parsing, module Control.Applicative) where
import Control.Applicative
import Data.Char
-- Basic definitions
newtype Parser a = P (String -> [(a,String)])
parse :: Parser a -> String -> [(a,String)]
parse (P p) inp = p inp
item :: Parser Char
item = P (\inp -> case inp of
[] -> []
(x:xs) -> [(x,xs)])
-- Sequencing parsers
instance Functor Parser where
-- fmap :: (a -> b) -> Parser a -> Parser b
fmap g p = P (\inp -> case parse p inp of
[] -> []
[(v,out)] -> [(g v, out)])
instance Applicative Parser where
-- pure :: a -> Parser a
pure v = P (\inp -> [(v,inp)])
-- <*> :: Parser (a -> b) -> Parser a -> Parser b
pg <*> px = P (\inp -> case parse pg inp of
[] -> []
[(g,out)] -> parse (fmap g px) out)
instance Monad Parser where
-- (>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = P (\inp -> case parse p inp of
[] -> []
[(v,out)] -> parse (f v) out)
-- Making choices
instance Alternative Parser where
-- empty :: Parser a
empty = P (\inp -> [])
-- (<|>) :: Parser a -> Parser a -> Parser a
p <|> q = P (\inp -> case parse p inp of
[] -> parse q inp
[(v,out)] -> [(v,out)])
-- Derived primitives
sat :: (Char -> Bool) -> Parser Char
sat p = do x <- item
if p x then return x else empty
digit :: Parser Char
digit = sat isDigit
lower :: Parser Char
lower = sat isLower
upper :: Parser Char
upper = sat isUpper
letter :: Parser Char
letter = sat isAlpha
alphanum :: Parser Char
alphanum = sat isAlphaNum
char :: Char -> Parser Char
char x = sat (== x)
string :: String -> Parser String
string [] = return []
string (x:xs) = do char x
string xs
return (x:xs)
ident :: Parser String
ident = do x <- lower
xs <- many alphanum
return (x:xs)
nat :: Parser Int
nat = do xs <- some digit
return (read xs)
int :: Parser Int
int = do char '-'
n <- nat
return (-n)
<|> nat
-- Handling spacing
space :: Parser ()
space = do many (sat isSpace)
return ()
token :: Parser a -> Parser a
token p = do space
v <- p
space
return v
identifier :: Parser String
identifier = token ident
natural :: Parser Int
natural = token nat
integer :: Parser Int
integer = token int
symbol :: String -> Parser String
symbol xs = token (string xs)
\ No newline at end of file
# This file was automatically generated by 'stack init'
#
# Some commonly used options have been documented as comments in this file.
# For advanced use and comprehensive documentation of the format, please see:
# https://docs.haskellstack.org/en/stable/yaml_configuration/
# Resolver to choose a 'specific' stackage snapshot or a compiler version.
# A snapshot resolver dictates the compiler version and the set of packages
# to be used for project dependencies. For example:
#
# resolver: lts-3.5
# resolver: nightly-2015-09-21
# resolver: ghc-7.10.2
#
# The location of a snapshot can be provided as a file or url. Stack assumes
# a snapshot provided as a file might change, whereas a url resource does not.
#
# resolver: ./custom-snapshot.yaml
# resolver: https://example.com/snapshots/2018-01-01.yaml
resolver:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/26.yaml
# User packages to be built.
# Various formats can be used as shown in the example below.
#
# packages:
# - some-directory
# - https://example.com/foo/bar/baz-0.0.2.tar.gz
# subdirs:
# - auto-update
# - wai
packages:
- .
# Dependency packages to be pulled from upstream that are not in the resolver.
# These entries can reference officially published versions as well as
# forks / in-progress versions pinned to a git hash. For example:
#
# extra-deps:
# - acme-missiles-0.3
# - git: https://github.com/commercialhaskell/stack.git
# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
#
# extra-deps: []
# Override default flag values for local packages and extra-deps
# flags: {}
# Extra package databases containing global packages
# extra-package-dbs: []
# Control whether we use the GHC we find on the path
# system-ghc: true
#
# Require a specific version of stack, using version ranges
# require-stack-version: -any # Default
# require-stack-version: ">=2.5"
#
# Override the architecture used by stack, especially useful on Windows
# arch: i386
# arch: x86_64
#
# Extra directories used by stack for building
# extra-include-dirs: [/path/to/dir]
# extra-lib-dirs: [/path/to/dir]
#
# Allow a newer minor version of GHC than the snapshot specifies
# compiler-check: newer-minor
# This file was autogenerated by Stack.
# You should not edit this file by hand.
# For more information, please see the documentation at:
# https://docs.haskellstack.org/en/stable/lock_files
packages: []
snapshots:
- completed:
size: 533252
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/26.yaml
sha256: cdbc5db9c1afe80a5998247939027a0c7db92fa0f20b5cd01596ec3da628b622
original:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/26.yaml
import Challenges
main :: IO ()
main = challenge1Test
exGrid1'1 = [ "HAGNIRTSH" , "SACAGETAK", "GCSTACKEL","MGHKMILKI","EKNLETGCN","TNIRTLETE","IRAAHCLSR","MAMROSAGD","GIZKDDNRG" ]
exWords1'1 = [ "HASKELL","STRING","STACK","MAIN","METHOD"]
-- exAns1'1 = [("HASKELL",Just((0,0),DownForward)),("STRING",Just((7,0),Back)),("STACK",Just((2,2),Forward)),
-- ("MAIN", Just((2,7),Up )),("METHOD",Just((4,3),Down))]
exAns1'1 = [("HASKELL",Just((0,0),DownForward)),("STRING",Just((7,0),Back)),("STACK",Just((2,2),Forward)),("MAIN",Just((2,7),Up)),("METHOD",Just((4,3),Down))]
exGrid1'2 = ["ROBREUMBR","AURPEPSAN","UNLALMSEE","YGAUNPYYP","NLMNBGENA","NBLEALEOR","ALRYPBBLG","NREPBEBEP","YGAYAROMR"]
exWords1'2 = [ "BANANA", "ORANGE", "MELON", "RASPBERRY","APPLE","PLUM","GRAPE" ]
-- exAns1'2 = [("BANANA", Just((5,6),UpBack )),("ORANGE",Just((1,0),DownForward)),("MELON",Just((7,8),Up )),
-- ("RASPBERRY",Just((8,0),DownBack)),("APPLE", Just((2,8),UpForward )),("PLUM", Just((5,1),DownBack)),
-- ("GRAPE", Just((8,6),Up ))]
--exAns1'2 = [("BANANA",Just((5,6),UpBack)),("ORANGE",Just((1,0),DownForward)),("MELON",Just((7,8),Up)),("RASPBERRY",Just((8,0),DownBack)),("APPLE", Just((2,8),UpForward)),("PLUM", Just((5,1),DownBack)),("GRAPE",Just((8,6),Up))]
exGrid1'3 = ["TEST","ASBD","GDFI","FDGS"]
exWords1'3 = ["TEST"]
exAns1'3 = [("TEST",Just((0,0),Forward))]
assert1 :: [(String,Maybe Placement)] -> [(String,Maybe Placement)] -> IO ()
assert1 result correct | result == correct = do putStrLn ("Testing:")
putStrLn (show correct)
putStrLn "Passed! Result:"
putStrLn (show result)
putStrLn ""
| otherwise = do putStrLn ("Testing:")
putStrLn (show correct)
putStrLn "Failed! Result:"
putStrLn (show result)
putStrLn ""
challenge1Test :: IO ()
challenge1Test = do putStrLn "Challenge 1 Start Test"
putStrLn "========================================="
assert1 (solveWordSearch exWords1'3 exGrid1'3) exAns1'3
assert1 (solveWordSearch exWords1'1 exGrid1'1) exAns1'1
--assert1 (solveWordSearch exWords1'2 exGrid1'2) exAns1'2
putStrLn "========================================="
putStrLn "Challenge 1 End Test"
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment