Skip to content

Commit

Permalink
git ls-files | grep '\.hs$' | xargs -n 1 stylish-haskell -c misc/styl…
Browse files Browse the repository at this point in the history
…ish-haskell.yaml -i

Although I had to tweak & untweak some files so stylish-haskell / haskell-src-exts can parse them
  • Loading branch information
Mathnerd314 committed Jun 22, 2014
1 parent f257330 commit 7c02053
Show file tree
Hide file tree
Showing 74 changed files with 431 additions and 362 deletions.
2 changes: 1 addition & 1 deletion Setup.hs
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
import Distribution.Simple
import Distribution.Simple
main = defaultMain
6 changes: 3 additions & 3 deletions misc/DKSolve.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@
-- See http://en.wikipedia.org/wiki/Durand–Kerner_method


import Data.Complex
import Data.List (inits, tails)
import Data.Complex
import Data.List (inits, tails)

eps :: Double
eps = 1e-14
Expand Down Expand Up @@ -48,4 +48,4 @@ type C = Complex Double
fixedPt :: Double -> ([C] -> [C]) -> [C] -> [C]
fixedPt eps f as | all ((<eps) . realPart . abs) $ zipWith (-) as as' = as
| otherwise = fixedPt eps f as'
where as' = f as
where as' = f as
29 changes: 29 additions & 0 deletions misc/stylish-haskell.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
# stylish-haskell configuration file
# ==================================

steps:
# Import cleanup
- imports:
# global produced the smallest diff
align: global

# Language pragmas
- language_pragmas:
style: vertical
remove_redundant: true

# Align the types in record declarations
- records: {}

# Remove trailing whitespace
- trailing_whitespace: {}

# unused steps - UnicodeSyntax, tabs to spaces

# Wrap to 100 columns, because I feel like it
columns: 100

# No language extensions are enabled by default.
# language_extensions:
# - TemplateHaskell
# - QuasiQuotes
6 changes: 3 additions & 3 deletions src/Diagrams/Align.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,13 +39,13 @@ import Diagrams.Core
import Diagrams.Util (applyAll)

import Data.AffineSpace (alerp, (.-.))
import Data.VectorSpace
import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
import Data.VectorSpace

import qualified Data.Foldable as F
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Foldable as F

-- | Class of things which can be aligned.
class Alignable a where
Expand Down Expand Up @@ -165,4 +165,4 @@ snugCenter :: ( HasLinearMap (V a), Alignable a, HasOrigin a, Num (Scalar (V a))
Fractional (Scalar (V a)), Traced a) => a -> a
snugCenter d = applyAll fs d
where
fs = map snugCenterV basis
fs = map snugCenterV basis
14 changes: 7 additions & 7 deletions src/Diagrams/Angle.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
-----------------------------------------------------------------------------
-- |
-- Module : Diagrams.Angle
Expand All @@ -26,14 +26,14 @@ module Diagrams.Angle
, HasPhi(..)
) where

import Control.Lens (Iso', Lens', iso, review)
import Control.Lens (Iso', Lens', iso, review)

import Data.Monoid hiding ((<>))
import Data.Semigroup
import Data.VectorSpace
import Data.Monoid hiding ((<>))
import Data.Semigroup
import Data.VectorSpace

import Diagrams.Core.V
import Diagrams.Points
import Diagrams.Core.V
import Diagrams.Points

-- | Angles can be expressed in a variety of units. Internally,
-- they are represented in radians.
Expand Down
2 changes: 1 addition & 1 deletion src/Diagrams/Animation.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleContexts #-}
-----------------------------------------------------------------------------
-- |
-- Module : Diagrams.Animation
Expand Down
6 changes: 3 additions & 3 deletions src/Diagrams/Attributes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,8 @@ module Diagrams.Attributes (
) where

import Data.Colour
import Data.Colour.RGBSpace (RGB (..))
import Data.Colour.SRGB (toSRGB)
import Data.Colour.RGBSpace (RGB (..))
import Data.Colour.SRGB (toSRGB)
import Data.Default.Class

import Data.Semigroup
Expand Down Expand Up @@ -209,4 +209,4 @@ lineMiterLimit = applyAttr . LineMiterLimit . Last

-- | Apply a 'LineMiterLimit' attribute.
lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a
lineMiterLimitA = applyAttr
lineMiterLimitA = applyAttr
4 changes: 2 additions & 2 deletions src/Diagrams/Backend/CmdLine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -426,10 +426,10 @@ class Mainable d where
-- @
-- import Diagrams.Prelude
-- import Diagrams.Backend.TheBestBackend.CmdLine
--
--
-- d :: Diagram B R2
-- d = ...
--
--
-- main = mainWith d
-- @
--
Expand Down
10 changes: 4 additions & 6 deletions src/Diagrams/BoundingBox.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,15 +43,13 @@ module Diagrams.BoundingBox

import Control.Applicative ((<$>))
import qualified Data.Foldable as F
import Data.Map (Map, fromDistinctAscList, fromList,
toAscList, toList)
import Data.Map (Map, fromDistinctAscList, fromList, toAscList, toList)

import Data.Maybe (fromMaybe)

import Data.VectorSpace
-- (VectorSpace, Scalar, AdditiveGroup, zeroV, negateV, (^+^), (^-^))
import Data.Basis (Basis, HasBasis, basisValue,
decompose, recompose)
import Data.Basis (Basis, HasBasis, basisValue, decompose, recompose)
import Data.Monoid (Monoid (..))
import Data.Semigroup (Option (..), Semigroup (..))

Expand All @@ -61,8 +59,8 @@ import Data.Typeable (Typeable)
import Diagrams.Core.Envelope (Enveloped (..), appEnvelope)
import Diagrams.Core.HasOrigin (HasOrigin (..))
import Diagrams.Core.Points (Point (..))
import Diagrams.Core.Transform (HasLinearMap, Transformable (..),
Transformation (..), (<->))
import Diagrams.Core.Transform (HasLinearMap, Transformable (..), Transformation (..),
(<->))
import Diagrams.Core.V (V)

-- Unexported utility newtype
Expand Down
7 changes: 3 additions & 4 deletions src/Diagrams/Combinators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module Diagrams.Combinators

-- * n-ary operations
, appends
, position, atPoints
, position, atPoints
, cat, cat'
, CatOpts(_catMethod, _sep), catMethod, sep
, CatMethod(..)
Expand All @@ -41,9 +41,8 @@ module Diagrams.Combinators

import Data.Typeable

import Control.Lens (Lens', generateSignatures, lensField,
lensRules, makeLensesWith, (%~), (&),
(.~), (^.), _Wrapping)
import Control.Lens (Lens', generateSignatures, lensField, lensRules,
makeLensesWith, (%~), (&), (.~), (^.), _Wrapping)
import Data.AdditiveGroup
import Data.AffineSpace ((.+^))
import Data.Default.Class
Expand Down
4 changes: 2 additions & 2 deletions src/Diagrams/Coordinates.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,12 @@ module Diagrams.Coordinates
)
where

import Control.Lens (Lens')
import Control.Lens (Lens')
import Data.VectorSpace

import Diagrams.Points
import Data.AffineSpace.Point
import Diagrams.Core.V
import Diagrams.Points

-- | Types which are instances of the @Coordinates@ class can be
-- constructed using '^&' (for example, a three-dimensional vector
Expand Down
35 changes: 17 additions & 18 deletions src/Diagrams/CubicSpline/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE TypeFamilies
, FlexibleContexts
#-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
-----------------------------------------------------------------------------
-- |
Expand All @@ -25,10 +24,10 @@ module Diagrams.CubicSpline.Internal
, solveCubicSplineCoefficients
) where

import Data.List
import Data.List

-- | Solves a system of the form 'A*X=D' for 'x' where 'A' is an
-- 'n' by 'n' matrix with 'bs' as the main diagonal and
-- | Solves a system of the form 'A*X=D' for 'x' where 'A' is an
-- 'n' by 'n' matrix with 'bs' as the main diagonal and
-- 'as' the diagonal below and 'cs' the diagonal above.
-- See: <http://en.wikipedia.org/wiki/Tridiagonal_matrix_algorithm>
solveTriDiagonal :: Fractional a => [a] -> [a] -> [a] -> [a] -> [a]
Expand All @@ -39,11 +38,11 @@ solveTriDiagonal as (b0:bs) (c0:cs) (d0:ds) = h cs' ds'
f (c':cs') (a:as) (b:bs) (c:cs) = c / (b - c' * a) : f cs' as bs cs
f _ _ _ _ = error "solveTriDiagonal.f: impossible!"

ds' = d0 / b0 : g ds' as bs cs' ds
ds' = d0 / b0 : g ds' as bs cs' ds
g _ [] _ _ _ = []
g (d':ds') (a:as) (b:bs) (c':cs') (d:ds) = (d - d' * a)/(b - c' * a) : g ds' as bs cs' ds
g _ _ _ _ _ = error "solveTriDiagonal.g: impossible!"

h _ [d] = [d]
h (c:cs) (d:ds) = let xs@(x:_) = h cs ds in d - c * x : xs
h _ _ = error "solveTriDiagonal.h: impossible!"
Expand All @@ -58,13 +57,13 @@ modifyLast f (a:as) = a : modifyLast f as

-- Helper that builds a list of length n of the form: '[s,m,m,...,m,m,e]'
sparseVector :: Int -> a -> a -> a -> [a]
sparseVector n s m e
sparseVector n s m e
| n < 1 = []
| otherwise = s : h (n - 1)
where
where
h 1 = [e]
h n = m : h (n - 1)

-- | Solves a system similar to the tri-diagonal system using a special case
-- of the Sherman-Morrison formula <http://en.wikipedia.org/wiki/Sherman-Morrison_formula>.
-- This code is based on /Numerical Recpies in C/'s @cyclic@ function in section 2.7.
Expand All @@ -74,20 +73,20 @@ solveCyclicTriDiagonal as (b0:bs) cs ds alpha beta = zipWith ((+) . (fact *)) zs
l = length ds
gamma = -b0
us = sparseVector l gamma 0 alpha

bs' = (b0 - gamma) : modifyLast (subtract (alpha*beta/gamma)) bs

xs@(x:_) = solveTriDiagonal as bs' cs ds
zs@(z:_) = solveTriDiagonal as bs' cs us

fact = -(x + beta * last xs / gamma) / (1.0 + z + beta * last zs / gamma)

solveCyclicTriDiagonal _ _ _ _ _ _ = error "second argument to solveCyclicTriDiagonal must be nonempty"

-- | Use the tri-diagonal solver with the appropriate parameters for an open cubic spline.
solveCubicSplineDerivatives :: Fractional a => [a] -> [a]
solveCubicSplineDerivatives (x:xs) = solveTriDiagonal as bs as ds
where
where
as = replicate (l - 1) 1
bs = 2 : replicate (l - 2) 4 ++ [2]
l = length ds
Expand All @@ -99,7 +98,7 @@ solveCubicSplineDerivatives _ = error "argument to solveCubicSplineDerivatives m
-- | Use the cyclic-tri-diagonal solver with the appropriate parameters for a closed cubic spline.
solveCubicSplineDerivativesClosed :: Fractional a => [a] -> [a]
solveCubicSplineDerivativesClosed xs = solveCyclicTriDiagonal as bs as ds 1 1
where
where
as = replicate (l - 1) 1
bs = replicate l 4
l = length xs
Expand All @@ -109,11 +108,11 @@ solveCubicSplineDerivativesClosed xs = solveCyclicTriDiagonal as bs as ds 1 1

-- | Use the cyclic-tri-diagonal solver with the appropriate parameters for a closed cubic spline.
solveCubicSplineCoefficients :: Fractional a => Bool -> [a] -> [[a]]
solveCubicSplineCoefficients closed xs =
solveCubicSplineCoefficients closed xs =
[ [x,d,3*(x1-x)-2*d-d1,2*(x-x1)+d+d1]
| (x,x1,d,d1) <- zip4 xs' (tail xs') ds' (tail ds')
]
where
where
ds | closed = solveCubicSplineDerivativesClosed xs
| otherwise = solveCubicSplineDerivatives xs
close as | closed = as ++ [head as]
Expand Down
12 changes: 6 additions & 6 deletions src/Diagrams/Direction.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
-- Module : Diagrams.Direction
Expand All @@ -19,11 +19,11 @@ module Diagrams.Direction
, angleBetweenDirs
) where

import Control.Lens (Iso', iso)
import Data.VectorSpace
import Control.Lens (Iso', iso)
import Data.VectorSpace

import Diagrams.Angle
import Diagrams.Core
import Diagrams.Angle
import Diagrams.Core

--------------------------------------------------------------------------------
-- Direction
Expand Down
2 changes: 1 addition & 1 deletion src/Diagrams/Parametric.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module Diagrams.Parametric
import Diagrams.Core

import Data.VectorSpace
import qualified Numeric.Interval.Kaucher as I
import qualified Numeric.Interval.Kaucher as I

-- | Codomain of parametric classes. This is usually either @(V p)@, for relative
-- vector results, or @(Point (V p))@, for functions with absolute coordinates.
Expand Down
3 changes: 2 additions & 1 deletion src/Diagrams/Parametric/Adjust.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,8 @@ module Diagrams.Parametric.Adjust

) where

import Control.Lens (makeLensesWith, lensRules, lensField, generateSignatures, (^.), (&), (.~), Lens')
import Control.Lens (Lens', generateSignatures, lensField, lensRules,
makeLensesWith, (&), (.~), (^.))
import Data.Proxy

import Data.Default.Class
Expand Down
4 changes: 2 additions & 2 deletions src/Diagrams/Path.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,8 @@ import Diagrams.TrailLike
import Diagrams.Transform

import Control.Arrow ((***))
import Control.Lens (Rewrapped, Wrapped (..), iso, mapped, op,
over, view, (%~), _Unwrapped', _Wrapped)
import Control.Lens (Rewrapped, Wrapped (..), iso, mapped, op, over, view, (%~),
_Unwrapped', _Wrapped)
import Data.AffineSpace
import qualified Data.Foldable as F
import Data.List (partition)
Expand Down
4 changes: 2 additions & 2 deletions src/Diagrams/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -146,17 +146,17 @@ import Diagrams.Query
import Diagrams.Segment
import Diagrams.Tangent
import Diagrams.Trace
import Diagrams.Trail hiding (trailPoints, loopPoints, linePoints)
import Diagrams.Trail hiding (linePoints, loopPoints, trailPoints)
import Diagrams.TrailLike
import Diagrams.Transform
import Diagrams.TwoD
import Diagrams.Util

import Control.Applicative
import Control.Lens ((%~), (&), (.~))
import Data.Active
import Data.AffineSpace
import Data.Colour hiding (AffineSpace (..), atop, over)
import Data.Colour.Names hiding (tan)
import Data.Semigroup
import Data.VectorSpace hiding (Sum (..))
import Control.Lens ((&), (.~), (%~))
Loading

0 comments on commit 7c02053

Please sign in to comment.