Skip to content

Commit

Permalink
Initial commit in Haskell Stack env
Browse files Browse the repository at this point in the history
  • Loading branch information
epatrizio committed Apr 8, 2022
1 parent af8fca6 commit b36835b
Show file tree
Hide file tree
Showing 11 changed files with 388 additions and 0 deletions.
3 changes: 3 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -21,3 +21,6 @@ cabal.project.local
cabal.project.local~
.HTF/
.ghc.environment.*

stack.yaml.lock
hgame.cabal
2 changes: 2 additions & 0 deletions Setup.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain
8 changes: 8 additions & 0 deletions app/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Main where

import Coord
import Hitbox
import Game

main :: IO ()
main = undefined
50 changes: 50 additions & 0 deletions package.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
name: hgame
version: 0.1.0.0
github: epatrizio/hgame
license: unlicense
author: epatrizio
maintainer: [email protected]
copyright: epatrizio

extra-source-files:
- README.md

# Metadata used when publishing your package
# synopsis: A sample game in Haskell language
# category: Game

# 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/epatrizio/hgame#readme>

dependencies:
- base >= 4.7 && < 5
- containers
- hspec
- QuickCheck

library:
source-dirs: src

executables:
paf-projet-street-fighter-exe:
main: Main.hs
source-dirs: app
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- hgame

tests:
hgame-test:
main: Spec.hs
source-dirs: test
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- hgame
64 changes: 64 additions & 0 deletions src/Coord.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
module Coord where -- ( someFunc )

data Zone = Zone Integer Integer -- Width (-w +w) and Height (0 +h)
deriving (Show, Eq)

data Coordinates = Coord Integer Integer
deriving (Show, Eq)

data Direction = U | D | R | L -- U (Up) | D (Down) | R (Right) | L (Left)
deriving (Show, Eq)

data Movement = Mov Direction Integer
deriving (Show, Eq)

-- Width & Height > 0
prop_inv_zone :: Zone -> Bool
prop_inv_zone (Zone w h) = w>0 && h>0

-- Coordinates must be inside Zone
prop_inv_zone_coord :: Zone -> Coordinates -> Bool
prop_inv_zone_coord (Zone w h) (Coord x y) = x>=(-w) && x<=w && y>=0 && y<=h

-- Int nb mvt > 0
prop_inv_movement :: Movement -> Bool
prop_inv_movement (Mov _ n) = n>=0

move :: Coordinates -> Movement -> Coordinates
move (Coord x y) (Mov U u) = Coord x (y+u)
move (Coord x y) (Mov D d) = Coord x (y-d)
move (Coord x y) (Mov R r) = Coord (x+r) y
move (Coord x y) (Mov L l) = Coord (x-l) y

prop_move_leftRight :: Coordinates -> Integer -> Bool
prop_move_leftRight (Coord x y) i = move (move (Coord x y) (Mov R i)) (Mov L i) == (Coord x y)

prop_move_upDown :: Coordinates -> Integer -> Bool
prop_move_upDown (Coord x y) i = move (move (Coord x y) (Mov U i)) (Mov D i) == (Coord x y)

-- moveSafe :: Coordinates -> Movement -> Zone -> Maybe Coordinates
-- Q: au lieu de ne pas bouger, aller au bout et s'arrêter ?
moveSafe :: Zone -> Coordinates -> Movement -> Coordinates
moveSafe (Zone _ h) (Coord x y) (Mov U u)
| y+u <= h = move (Coord x y) (Mov U u)
| otherwise = Coord x y
moveSafe _ (Coord x y) (Mov D d)
| y-d >= 0 = move (Coord x y) (Mov D d)
| otherwise = Coord x y
moveSafe (Zone w _) (Coord x y) (Mov R r)
| x+r <= w = move (Coord x y) (Mov R r)
| otherwise = Coord x y
moveSafe (Zone w _) (Coord x y) (Mov L l)
| x-l >= (-w) = move (Coord x y) (Mov L l)
| otherwise = Coord x y

-- check that movement does not go outside zone
prop_moveSafe :: Zone -> Coordinates -> Movement -> Bool
prop_moveSafe (Zone _ h) (Coord x y) (Mov U u) = y+u <= h
prop_moveSafe _ (Coord x y) (Mov D d) = y-d >= 0
prop_moveSafe (Zone w _) (Coord x y) (Mov R r) = x+r <= w
prop_moveSafe (Zone w _) (Coord x y) (Mov L l) = x-l >= (-w)

-- check that always remains in zone
prop_moveSafe_in_zone :: Zone -> Coordinates -> Movement -> Bool
prop_moveSafe_in_zone z c m = (prop_inv_zone_coord z c) && (prop_inv_zone_coord z (moveSafe z c m))
25 changes: 25 additions & 0 deletions src/Game.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module Game where

import Coord
import Hitbox

data FighterState = KO | OK Integer -- Integer > Life points

newtype FighterId = FighterId Integer
deriving (Eq,Show,Ord)

data Fighter = Fighter {
idF :: FighterId,
posF :: Coordinates,
hitboxF :: Hitbox,
faceF :: Direction,
stateF :: FighterState
}

data Game =
GameOver FighterId -- le numero du joueur vainqueur
| CurrentGame {
fighter1 :: Fighter,
fighter2 :: Fighter,
gameZone :: Zone
}
17 changes: 17 additions & 0 deletions src/Hitbox.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
module Hitbox where

import Data.Sequence (Seq (..), (!?))
import qualified Data.Sequence as S

import Coord

data Hitbox =
Rect Coordinates Integer Integer -- Rectangle Coord (point on the top left) + w / h
| Composite (Seq Hitbox)

prop_inv_hb_notEmpty :: Hitbox -> Bool
prop_inv_hb_notEmpty (Rect _ w h) = w>0 && h>0
prop_inv_hb_notEmpty (Composite s) = case s of
Empty -> False
_ -> True

66 changes: 66 additions & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,66 @@
# 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: lts-18.28

# 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.7"
#
# 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
116 changes: 116 additions & 0 deletions test/CoordSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,116 @@
module CoordSpec where

import Test.Hspec
import Test.QuickCheck

import Coord as C

-- Unit tests
coordUT = do
describe "Coord - Unit tests move" $ do
it "Up movement" $
move (Coord 0 0) (Mov U 10) `shouldBe` (Coord 0 10)
it "Down movement" $
move (Coord 0 0) (Mov D 10) `shouldBe` (Coord 0 (-10))
it "Right movement" $
move (Coord 0 0) (Mov R 10) `shouldBe` (Coord 10 0)
it "Left movement" $
move (Coord 0 0) (Mov L 10) `shouldBe` (Coord (-10) 0)
describe "Coord - Unit tests moveSafe" $ do
it "Up movement OK" $
moveSafe (Zone 50 50) (Coord 0 0) (Mov U 10) `shouldBe` (Coord 0 10)
it "Down movement OK" $
moveSafe (Zone 50 50) (Coord 0 10) (Mov D 10) `shouldBe` (Coord 0 0)
it "Right movement OK" $
moveSafe (Zone 50 50) (Coord 0 0) (Mov R 10) `shouldBe` (Coord 10 0)
it "Left movement OK" $
moveSafe (Zone 50 50) (Coord 0 0) (Mov L 10) `shouldBe` (Coord (-10) 0)
it "Up movement KO" $
moveSafe (Zone 5 5) (Coord 0 0) (Mov U 10) `shouldBe` (Coord 0 0)
it "Down movement KO" $
moveSafe (Zone 5 5) (Coord 0 0) (Mov D 10) `shouldBe` (Coord 0 0)
it "Right movement KO" $
moveSafe (Zone 5 5) (Coord 0 0) (Mov R 10) `shouldBe` (Coord 0 0)
it "Left movement OK" $
moveSafe (Zone 5 5) (Coord 0 0) (Mov L 10) `shouldBe` (Coord 0 0)

genZoneOk :: Gen Zone
genZoneOk = do
w <- choose (1, 100)
h <- choose (1, 100)
return (Zone w h)

genZoneKo :: Gen Zone
genZoneKo = do
w <- choose (-100, 0)
h <- choose (-100, 0)
return (Zone w h)

genCoordOk :: Gen Coordinates
genCoordOk = do
x <- choose (-50, 50)
y <- choose (0, 100)
return (Coord x y)

genMovUOk :: Integer -> Gen Movement
genMovUOk i = do
m <- choose (0, i)
return (Mov U m)

genMovDOk :: Integer -> Gen Movement
genMovDOk i = do
m <- choose (0, i)
return (Mov D m)

genMovROk :: Integer -> Gen Movement
genMovROk i = do
m <- choose (0, i)
return (Mov R m)

genMovLOk :: Integer -> Gen Movement
genMovLOk i = do
m <- choose (0, i)
return (Mov L m)

-- QuickCheck auto tests
coordQCT = do
describe "Coord - QuickCheck prop" $ do
it "prop_inv_zone OK" $ property $
forAll genZoneOk $ prop_inv_zone
it "prop_inv_zone KO" $ property $
forAll genZoneKo $ \z -> not (prop_inv_zone z)
it "prop_inv_zone_coord" $ property $
forAll genCoordOk $ prop_inv_zone_coord (Zone 50 100)
it "prop_inv_movement Up" $ property $
forAll (genMovUOk 100) $ prop_inv_movement
it "prop_inv_movement Down" $ property $
forAll (genMovDOk 100) $ prop_inv_movement
it "prop_inv_movement Right" $ property $
forAll (genMovROk 100) $ prop_inv_movement
it "prop_inv_movement Left" $ property $
forAll (genMovLOk 100) $ prop_inv_movement
it "prop_move_leftRight" $ property $
\x y i -> prop_move_leftRight (Coord x y) i
it "prop_move_upDown" $ property $
\x y i -> prop_move_upDown (Coord x y) i
describe "Coord - QuickCheck moveSafe" $ do
it "prop_moveSafe Up" $ property $
forAll (genMovUOk 100) $ \z -> prop_moveSafe (Zone 50 100) (Coord 0 0) z
it "prop_moveSafe Down" $ property $
forAll (genMovDOk 100) $ \z -> prop_moveSafe (Zone 50 100) (Coord 0 100) z
it "prop_moveSafe Right" $ property $
forAll (genMovROk 100) $ \z -> prop_moveSafe (Zone 50 100) (Coord (-50) 0) z
it "prop_moveSafe Left" $ property $
forAll (genMovLOk 100) $ \z -> prop_moveSafe (Zone 50 100) (Coord 50 0) z
it "prop_moveSafe_in_zone Up" $ property $
forAll (genMovUOk 1000) $ \z -> prop_moveSafe_in_zone (Zone 10 20) (Coord 0 0) z
it "prop_moveSafe_in_zone Down" $ property $
forAll (genMovDOk 1000) $ \z -> prop_moveSafe_in_zone (Zone 10 20) (Coord 0 0) z
it "prop_moveSafe_in_zone Right" $ property $
forAll (genMovROk 1000) $ \z -> prop_moveSafe_in_zone (Zone 10 20) (Coord 0 0) z
it "prop_moveSafe_in_zone Left" $ property $
forAll (genMovLOk 1000) $ \z -> prop_moveSafe_in_zone (Zone 10 20) (Coord 0 0) z

-- ToDo
-- KO tests

24 changes: 24 additions & 0 deletions test/HitboxSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
module HitboxSpec where

import Test.Hspec
import Test.QuickCheck

import Data.Sequence (Seq (..), (!?))
import qualified Data.Sequence as S

import Coord as C
import Hitbox as H

-- Unit tests
hitboxUT = do
describe "Hitbox - Unit tests" $ do
it "prop_inv_hb_notEmpty - KO null sizes" $
prop_inv_hb_notEmpty (Rect (Coord 0 0) 0 0) `shouldBe` False
it "prop_inv_hb_notEmpty - KO empty sequence" $
prop_inv_hb_notEmpty (Composite S.empty) `shouldBe` False
it "prop_inv_hb_notEmpty - OK one rectangle" $
prop_inv_hb_notEmpty (Rect (Coord 0 10) 5 5) `shouldBe` True
it "prop_inv_hb_notEmpty - OK not empty sequence" $
prop_inv_hb_notEmpty (Composite (S.fromList [(Rect (Coord 0 10) 5 5)])) `shouldBe` True


Loading

0 comments on commit b36835b

Please sign in to comment.