feat: better rendering
This commit is contained in:
parent
e1f2d5b5ef
commit
eeedecc9ee
1 changed files with 21 additions and 6 deletions
|
@ -1,14 +1,18 @@
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
module Sudoku.Render (unstructured, hints) where
|
module Sudoku.Render (unstructured, hints) where
|
||||||
import Sudoku (Sudoku, orderedIndices, translateIntIndex)
|
import Sudoku ( Sudoku, orderedIndices, Sudoku(..) )
|
||||||
|
import Data.Functor.Compose (Compose(..))
|
||||||
import Sudoku.Field (Field)
|
import Sudoku.Field (Field)
|
||||||
import qualified Sudoku.Field as Field
|
import qualified Sudoku.Field as Field
|
||||||
import qualified Data.Functor.Rep as Representable
|
import qualified Data.Functor.Rep as Representable
|
||||||
import Data.Set (Set)
|
import Data.Set (Set)
|
||||||
import Graphics.Text.Box (Box)
|
import Graphics.Text.Box (Box, Border (..))
|
||||||
import qualified Graphics.Text.Box as Box
|
import qualified Graphics.Text.Box as Box
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
import Sudoku.Area (Area)
|
||||||
|
import Data.Bifunctor (bimap)
|
||||||
|
import Control.Monad (join)
|
||||||
|
|
||||||
unstructured :: Sudoku (Maybe Field) -> String
|
unstructured :: Sudoku (Maybe Field) -> String
|
||||||
unstructured sudoku = let
|
unstructured sudoku = let
|
||||||
|
@ -18,10 +22,21 @@ unstructured sudoku = let
|
||||||
|
|
||||||
hints :: Sudoku (Either Field (Set Field)) -> Text
|
hints :: Sudoku (Either Field (Set Field)) -> Text
|
||||||
hints sudoku = let
|
hints sudoku = let
|
||||||
|
|
||||||
boxes = fieldBox <$> sudoku :: Sudoku Box
|
(Sudoku (Compose fieldBoxes)) = fieldBox <$> sudoku :: Sudoku Box
|
||||||
|
areaBoxes = areaBox <$> fieldBoxes
|
||||||
in Box.render $ Box.asciiGrid (9, 9) (Representable.index boxes . Sudoku.translateIntIndex)
|
translateAreaIndices = join bimap toEnum
|
||||||
|
boxStyle = Box.Border {verticalBetween=' ', topRight=' ', topLeft=' ', top=' ', right=' ', left=' ', horizontalBetween=' ', crosssection=' ', bottomRight=' ', bottomLeft=' ', bottom=' '}
|
||||||
|
|
||||||
|
in Box.render $ Box.grid (Just boxStyle) (3, 3) (Representable.index areaBoxes . translateAreaIndices)
|
||||||
|
|
||||||
|
areaBox :: Area Box -> Box
|
||||||
|
areaBox area = let
|
||||||
|
|
||||||
|
boxStyle = Box.asciiBorder {topLeft='#', topRight='#', bottomLeft='#', bottomRight='#'}
|
||||||
|
translateIndices (i, j) = Representable.index area (toEnum i, toEnum j)
|
||||||
|
|
||||||
|
in Box.grid (Just boxStyle) (3, 3) translateIndices
|
||||||
|
|
||||||
fieldBox :: Either Field (Set Field) -> Box
|
fieldBox :: Either Field (Set Field) -> Box
|
||||||
fieldBox = \case
|
fieldBox = \case
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue