Skip to content

Commit

Permalink
Format all code with Fourmolu
Browse files Browse the repository at this point in the history
  • Loading branch information
ad-si committed Nov 23, 2024
1 parent da74339 commit a28a0f7
Show file tree
Hide file tree
Showing 9 changed files with 263 additions and 183 deletions.
2 changes: 2 additions & 0 deletions Setup.hs
Original file line number Diff line number Diff line change
@@ -1,2 +1,4 @@
import Distribution.Simple


main = defaultMain
5 changes: 5 additions & 0 deletions makefile
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,11 @@ help: makefile
@tail -n +4 makefile | grep ".PHONY"


.PHONY: test
test:
stack test


Perspec.app: ~/.local/bin/perspec imagemagick
platypus \
--name Perspec \
Expand Down
35 changes: 24 additions & 11 deletions source/Correct.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,45 @@
{-# language ApplicativeDo #-}
{-# language RecordWildCards #-}
{-# language NamedFieldPuns #-}
{-# language DataKinds #-}

module Correct where

import Protolude as P
import Protolude as P (
Double,
Fractional ((/)),
Num (abs, negate, (*)),
RealFrac (round),
fromMaybe,
(.),
)

-- hip
import Graphics.Image hiding ((!))
import Graphics.Image (Ix2 ((:.)), Sz (Sz), Sz2)

-- hmatrix
import Numeric.LinearAlgebra (linearSolve, linearSolveSVD, (!), (><))

-- lens
import Control.Lens hiding (transform)
import Control.Lens ((^.))

-- linear
import Linear
import Linear (
Additive ((^+^), (^-^)),
M33,
R1 (_x),
R2 (_y),
R3 (_z),
R4 (_w),
V2 (..),
V3 (V3),
V4 (..),
)


determineSize :: V4 (V2 Double) -> Sz2
determineSize (V4 c1 c2 c3 c4) = Sz ((round height) :. (round width))
determineSize (V4 c1 c2 c3 c4) = Sz (round height :. round width)
where
diagonalA = c3 ^-^ c1
diagonalB = c4 ^-^ c2
V2 width height = (abs diagonalA ^+^ abs diagonalB) / 2


{- FOURMOLU_DISABLE -}
-- /* Calculates coefficients of perspective transformation
-- * which maps (xi,yi) to (ui,vi), (i=1,2,3,4):
-- *
Expand Down Expand Up @@ -81,3 +93,4 @@ calculatePerspectiveTransform s d =
(V3 (m ! 0 ! 0) (m ! 1 ! 0) (m ! 2 ! 0))
(V3 (m ! 3 ! 0) (m ! 4 ! 0) (m ! 5 ! 0))
(V3 (m ! 6 ! 0) (m ! 7 ! 0) 1)
{- FOURMOLU_ENABLE -}
9 changes: 4 additions & 5 deletions source/Home.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,16 +11,16 @@ import Protolude (
putText,
)

import Data.Text qualified as T
import Brillo.Interface.IO.Game as Gl (
Event (..),
Key (MouseButton),
KeyState (Down),
MouseButton (LeftButton),
)
import Data.Text qualified as T

import TinyFileDialogs (openFileDialog)
import Types (AppState(..), View(..))
import Types (AppState (..), View (..))
import Utils (isInRect, loadFileIntoState)


Expand Down Expand Up @@ -50,10 +50,9 @@ handleMsg msg appState =

case selectedFiles of
Just [filePath] -> do
stateWithFile <- loadFileIntoState
appState{ currentView = ImageView }
loadFileIntoState
appState{currentView = ImageView}
(T.unpack filePath)
pure stateWithFile
Just _files -> do
putText "Selecting several files is not supported yet!"
-- TODO
Expand Down
61 changes: 33 additions & 28 deletions source/Lib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,16 +6,16 @@ import Protolude (
Applicative (pure),
Bool (..),
Double,
Either(Left, Right),
Either (Left, Right),
Eq ((==)),
FilePath,
Float,
Floating (sqrt),
Fractional ((/)),
Functor (fmap),
Int,
IO,
IOException,
Int,
Maybe (Just, Nothing),
Monoid (mempty),
Num ((*), (+), (-)),
Expand Down Expand Up @@ -46,16 +46,9 @@ import Protolude (
)
import Protolude qualified as P

import Codec.BMP (parseBMP)
import Data.Aeson qualified as Aeson
import Data.ByteString.Lazy qualified as BL
import Data.FileEmbed (embedFile)
import Data.List as DL (elemIndex, minimum)
import Data.Text qualified as T
import Data.Text.Encoding qualified as TSE
import Brillo (
Display (InWindow),
Picture ( Line, Pictures, Scale, ThickArc, ThickCircle, Translate ),
Picture (Line, Pictures, Scale, ThickArc, ThickCircle, Translate),
Point,
bitmapOfBMP,
black,
Expand All @@ -76,10 +69,17 @@ import Brillo.Interface.IO.Game as Gl (
SpecialKey (KeyEnter, KeyEsc),
playIO,
)
import Codec.BMP (parseBMP)
import Data.Aeson qualified as Aeson
import Data.ByteString.Lazy qualified as BL
import Data.FileEmbed (embedFile)
import Data.List as DL (elemIndex, minimum)
import Data.Text qualified as T
import Data.Text.Encoding qualified as TSE
import Home (handleHomeEvent)
import System.Directory (getCurrentDirectory)
import System.Environment (setEnv)
import System.FilePath ( replaceExtension, (</>), )
import System.FilePath (replaceExtension, (</>))
import System.Info (os)
import System.Process (callProcess, readProcessWithExitCode, spawnProcess)

Expand Down Expand Up @@ -117,10 +117,14 @@ import Types (
initialState,
)
import Utils (
getWordSprite, calcInitWindowPos,
calcInitWindowPos,
calculateSizes,
getCorners,
getWordSprite,
loadFileIntoState,
scalePoints, originTopLeft, getCorners, calculateSizes
)
originTopLeft,
scalePoints,
)


-- | This is replaced with valid licenses during CI build
Expand Down Expand Up @@ -233,9 +237,10 @@ appStateToWindow screenSize appState = do

case appState.currentView of
HomeView -> do
InWindow "Perspec - Select a file" appSize
InWindow
"Perspec - Select a file"
appSize
(calcInitWindowPos screenSize appSize)

ImageView -> do
case appState.inputPath of
Nothing -> InWindow "SHOULD NOT BE POSSIBLE" (100, 100) (0, 0)
Expand All @@ -249,7 +254,6 @@ appStateToWindow screenSize appState = do
)
appSize
(calcInitWindowPos screenSize appSize)

BannerView ->
InWindow "Perspec - Banner" (800, 600) (10, 10)

Expand All @@ -273,7 +277,6 @@ startApp appState = do
makePicture
handleEvent
stepWorld

(_, _) -> do
playIO
(appStateToWindow screenSize appState)
Expand Down Expand Up @@ -623,8 +626,10 @@ submitSelection appState exportMode = do
exportMode

if appState.transformApp == ImageMagick
then putText $ "Arguments for convert command:\n"
<> T.unlines convertArgs
then
putText $
"Arguments for convert command:\n"
<> T.unlines convertArgs
else putText $ "Write file to " <> show appState.outputPath

correctAndWrite
Expand All @@ -636,7 +641,6 @@ submitSelection appState exportMode = do
convertArgs

exitSuccess

(_, _) -> do
P.die "Input path and output path must be set before submitting"

Expand Down Expand Up @@ -819,7 +823,7 @@ correctAndWrite transformApp inPath outPath ((bl, _), (tl, _), (tr, _), (br, _))
argsNorm = ("magick" : args) <&> T.unpack
successMessage =
"✅ Successfully saved converted image at "
<> fixOutputPath exportMode outPath
<> fixOutputPath exportMode outPath

-- TODO: Add CLI flag to switch between them
case conversionMode of
Expand Down Expand Up @@ -891,16 +895,17 @@ correctAndWrite transformApp inPath outPath ((bl, _), (tl, _), (tr, _), (br, _))

pure ()


loadAndStart :: Config -> Maybe FilePath -> IO ()
loadAndStart config filePathMb= do
loadAndStart config filePathMb = do
let
isRegistered = True -- (config&licenseKey) `elem` licenses
stateDraft =
initialState
{ transformApp = config.transformAppFlag
, isRegistered = isRegistered
, bannerIsVisible = not isRegistered
}
initialState
{ transformApp = config.transformAppFlag
, isRegistered = isRegistered
, bannerIsVisible = not isRegistered
}

case filePathMb of
Nothing -> startApp stateDraft
Expand Down
Loading

0 comments on commit a28a0f7

Please sign in to comment.