Remove unused imports, minor code simplifications

This commit is contained in:
Sasha 2018-03-07 23:22:45 +01:00
parent 5b78285303
commit 7d672589b2
6 changed files with 21 additions and 25 deletions

View File

@ -8,7 +8,6 @@ import Data.Bits (
, shift , shift
, testBit , testBit
, xor , xor
, Bits
, (.&.) , (.&.)
, (.|.) , (.|.)
, countTrailingZeros , countTrailingZeros

View File

@ -2,10 +2,10 @@
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
module Hanafuda.Day where module Hanafuda.Day where
import Hanafuda.Card (Card, Pack, Flower(Pine), contains, flower, packOfCards, pair, remove) import Hanafuda.Card (Card, Pack, Flower(Pine), contains, flower, pair, remove)
import Hanafuda.Yaku (rate) import Hanafuda.Yaku (rate)
import Hanafuda.Game (Game(..), Move(..), PlayerState, meld, plays, yakus) import Hanafuda.Game (Game(..), Move(..), PlayerState(..), plays)
import Data.Map (Map, adjust, empty, fromList, insert, union, (!)) import Data.Map (union)
import Control.Monad.Reader (runReader) import Control.Monad.Reader (runReader)
data Step = ToPlay | Turned Card | Scored | Over Bool data Step = ToPlay | Turned Card | Scored | Over Bool

View File

@ -2,7 +2,7 @@
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
module Hanafuda.Game where module Hanafuda.Game where
import Data.Map (Map, empty, fromList, (!)) import Data.Map (Map, empty, fromList)
import Hanafuda.Card (Card, Pack, contains, packOfCards, remove) import Hanafuda.Card (Card, Pack, contains, packOfCards, remove)
import Hanafuda.Yaku (Score, Points) import Hanafuda.Yaku (Score, Points)

View File

@ -4,8 +4,8 @@ module Hanafuda.Month where
import Hanafuda.Card (Card, Flower(Pine), cards, shuffle, packOfCards) import Hanafuda.Card (Card, Flower(Pine), cards, shuffle, packOfCards)
import Hanafuda.Day (Day(..)) import Hanafuda.Day (Day(..))
import qualified Hanafuda.Day as Day (Step(Over), next, new) import qualified Hanafuda.Day as Day (Step(Over), new)
import Hanafuda.Game (Game(..), Move, Player, Players, PlayerState(..), initPlayers) import Hanafuda.Game (Game(..), Player, Players, PlayerState(..), initPlayers)
import qualified Hanafuda.Game as Game (next) import qualified Hanafuda.Game as Game (next)
import Data.Map ((!), insert) import Data.Map ((!), insert)
import Control.Monad.State (replicateM, runState, state) import Control.Monad.State (replicateM, runState, state)
@ -29,9 +29,11 @@ newtype Month = Month (Either Over On)
go :: On -> Month go :: On -> Month
go = Month . Right go = Month . Right
new :: Player -> [Card] -> On new :: Player -> IO On
new playing shuffled = new playing = do
On { ([hand1, hand2, river], next:stock) <- fmap (runState (replicateM 3 take8)) $ shuffle cards
let players = initPlayers [hand1, hand2]
return On {
flower = Pine flower = Pine
, players , players
, day = Day.new (packOfCards river) (players ! playing) next , day = Day.new (packOfCards river) (players ! playing) next
@ -42,13 +44,11 @@ new playing shuffled =
} }
where where
take8 = state $ splitAt 8 take8 = state $ splitAt 8
([hand1, hand2, river], next:stock) = runState (replicateM 3 take8) shuffled
players = initPlayers [hand1, hand2]
next :: On -> IO On next :: On -> IO On
next (On {flower, oyake}) = do next (On {flower, oyake}) = do
shuffled <- shuffle cards on <- new $ Game.next oyake
return $ (new (Game.next oyake) shuffled) {flower = succ flower} return $ on {flower = succ flower}
instance Game On Month where instance Game On Month where
play on@(On {flower, day, playing, players, stock = next : moreStock}) move = play on@(On {flower, day, playing, players, stock = next : moreStock}) move =

View File

@ -1,9 +1,9 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module Hanafuda.Yaku where module Hanafuda.Yaku where
import Hanafuda.Card (Card(..), Flower, Monthly, Pack, add, contains, intersection, packOfCards, size) import Hanafuda.Card (Card(..), Monthly, Pack, add, contains, intersection, packOfCards, size)
import qualified Data.Map as M (Map, empty, insert, unionWith, (!)) import qualified Data.Map as M (Map, empty, insert, unionWith, (!))
import qualified Data.Set as S (Set, empty, insert, singleton, union) import qualified Data.Set as S (Set, empty, singleton, union)
import Control.Monad.Reader (reader) import Control.Monad.Reader (reader)
data Yaku = data Yaku =
@ -70,7 +70,7 @@ finders = do
, (Akatan, akatan, fixed 5) , (Akatan, akatan, fixed 5)
, (Aotan, aotan, fixed 5) , (Aotan, aotan, fixed 5)
, (Tan, [WisteriaRed, IrisRed, BushCloverRed, WillowRed] ++ aotan ++ akatan, moreThan 4) , (Tan, [WisteriaRed, IrisRed, BushCloverRed, WillowRed] ++ aotan ++ akatan, moreThan 4)
, (Kasu, (foldl (++) [] [map toEnum [4*i, 4*i+1] | i <- [0..10]]) ++ Lightning : [Paulownia0 .. Sand], moreThan 9) , (Kasu, plains, moreThan 9)
, (TsukimiZake, [SakeCup, FullMoon], fixed 3) , (TsukimiZake, [SakeCup, FullMoon], fixed 3)
, (HanamiZake, [SakeCup, CampCurtain], fixed 3) , (HanamiZake, [SakeCup, CampCurtain], fixed 3)
, (TsukiFuda, map (toEnum . monthCardPlus) [0..3], fixed 5) , (TsukiFuda, map (toEnum . monthCardPlus) [0..3], fixed 5)
@ -79,6 +79,7 @@ finders = do
inoshikacho = [Butterflies, Boar, Deer] inoshikacho = [Butterflies, Boar, Deer]
aotan = [PeonyBlue, ChrysanthemumBlue, MapleBlue] aotan = [PeonyBlue, ChrysanthemumBlue, MapleBlue]
akatan = [PinePoetry, PlumPoetry, CherryPoetry] akatan = [PinePoetry, PlumPoetry, CherryPoetry]
plains = (foldl (++) [] [map toEnum [4*i, 4*i+1] | i <- [0..10]]) ++ Lightning : [Paulownia0 .. Sand]
rate :: Pack -> [Card] -> Monthly (Score, Pack) rate :: Pack -> [Card] -> Monthly (Score, Pack)
rate pack cards = do rate pack cards = do

View File

@ -3,11 +3,11 @@
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
module Hanafuda.Year where module Hanafuda.Year where
import Hanafuda.Card (Flower(Paulownia), cards, shuffle) import Hanafuda.Card (Flower(Paulownia))
import Hanafuda.Month (Month(..), flower, next, score, winner) import Hanafuda.Month (Month(..), flower, next, score, winner)
import qualified Hanafuda.Month as Month (On(..), Over(..), new) import qualified Hanafuda.Month as Month (On(..), Over(..), new)
import Hanafuda.Game (Game(..), Player(Player1), Scores, deal) import Hanafuda.Game (Game(..), Player(Player1), Scores, deal)
import Data.Map (Map, insert, (!)) import Data.Map (insert, (!))
import System.Random (StdGen) import System.Random (StdGen)
data Mode = FirstAt Int | WholeYear data Mode = FirstAt Int | WholeYear
@ -28,12 +28,8 @@ go = return . Year . Right
new :: Mode -> IO Year new :: Mode -> IO Year
new mode = do new mode = do
shuffled <- shuffle cards month <- Month.new Player1
go $ On { go $ On {mode , month , scores = deal $ cycle [0]}
mode
, month = Month.new Player1 shuffled
, scores = deal $ cycle [0]
}
consolidate :: On -> Player -> Int -> IO Year consolidate :: On -> Player -> Int -> IO Year
consolidate on@(On {mode, month, scores}) winner score = consolidate on@(On {mode, month, scores}) winner score =