Skip to content

Commit c474a94

Browse files
author
Benjamin Summers
committed
stylish-haskell
1 parent 2d20291 commit c474a94

File tree

22 files changed

+168
-89
lines changed

22 files changed

+168
-89
lines changed

.stylish-haskell.yaml

Lines changed: 84 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,84 @@
1+
steps:
2+
# Convert some ASCII sequences to their Unicode equivalents. This is disabled
3+
# by default.
4+
# - unicode_syntax:
5+
# # In order to make this work, we also need to insert the UnicodeSyntax
6+
# # language pragma. If this flag is set to true, we insert it when it's
7+
# # not already present. You may want to disable it if you configure
8+
# # language extensions using some other method than pragmas. Default:
9+
# # true.
10+
# add_language_pragma: true
11+
12+
- simple_align:
13+
cases: true
14+
top_level_patterns: true
15+
records: true
16+
17+
# Import cleanup
18+
- imports:
19+
align: group
20+
list_align: after_alias
21+
pad_module_names: true
22+
long_list_align: inline
23+
empty_list_align: inherit
24+
list_padding: 4
25+
separate_lists: false
26+
space_surround: false
27+
28+
- language_pragmas:
29+
style: vertical
30+
align: true
31+
remove_redundant: true
32+
33+
- tabs:
34+
spaces: 4
35+
36+
- trailing_whitespace: {}
37+
38+
# squash: {}
39+
40+
columns: 80
41+
42+
newline: lf
43+
44+
language_extensions:
45+
- ApplicativeDo
46+
- BangPatterns
47+
- BlockArguments
48+
- DataKinds
49+
- DefaultSignatures
50+
- DeriveAnyClass
51+
- DeriveDataTypeable
52+
- DeriveFoldable
53+
- DeriveGeneric
54+
- DeriveTraversable
55+
- DerivingStrategies
56+
- EmptyDataDecls
57+
- FlexibleContexts
58+
- FlexibleInstances
59+
- FunctionalDependencies
60+
- GADTs
61+
- GeneralizedNewtypeDeriving
62+
- LambdaCase
63+
- MagicHash
64+
- MultiParamTypeClasses
65+
- NamedFieldPuns
66+
- NoImplicitPrelude
67+
- NumericUnderscores
68+
- OverloadedStrings
69+
- PartialTypeSignatures
70+
- PatternSynonyms
71+
- QuasiQuotes
72+
- Rank2Types
73+
- RankNTypes
74+
- RecordWildCards
75+
- ScopedTypeVariables
76+
- StandaloneDeriving
77+
- TemplateHaskell
78+
- TupleSections
79+
- TypeApplications
80+
- TypeFamilies
81+
- TypeOperators
82+
- UnboxedTuples
83+
- UnicodeSyntax
84+
- ViewPatterns

pkg/hs-urbit/lib/Noun.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,12 +12,12 @@ module Noun
1212
import ClassyPrelude
1313
import Control.Lens
1414

15-
import Noun.Core
16-
import Noun.Convert
17-
import Noun.Conversions
1815
import Noun.Atom
19-
import Noun.Jam
16+
import Noun.Conversions
17+
import Noun.Convert
18+
import Noun.Core
2019
import Noun.Cue
20+
import Noun.Jam
2121
import Noun.TH
2222

2323
--------------------------------------------------------------------------------

pkg/hs-urbit/lib/Noun/Atom.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -13,25 +13,25 @@ module Noun.Atom
1313
) where
1414

1515
import ClassyPrelude
16-
import Control.Lens hiding (Index)
16+
import Control.Lens hiding (Index)
1717

1818
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
1919
import GHC.Exts (sizeofByteArray#)
20+
import GHC.Int (Int(..))
2021
import GHC.Integer.GMP.Internals (BigNat(..), bigNatToWord, sizeofBigNat#)
2122
import GHC.Integer.GMP.Internals (indexBigNat#)
22-
import GHC.Integer.GMP.Internals (wordToBigNat, byteArrayToBigNat#, zeroBigNat)
23-
import GHC.Int (Int(..))
23+
import GHC.Integer.GMP.Internals (byteArrayToBigNat#, wordToBigNat, zeroBigNat)
2424
import GHC.Natural (Natural(..))
25-
import GHC.Prim (plusWord#, clz#, minusWord#)
26-
import GHC.Prim (Word#, subIntC#, timesWord#, int2Word#)
25+
import GHC.Prim (clz#, minusWord#, plusWord#)
26+
import GHC.Prim (Word#, int2Word#, subIntC#, timesWord#)
2727
import GHC.Word (Word(..))
2828
import System.IO.Unsafe (unsafePerformIO)
2929

30-
import qualified Data.Primitive.Types as Prim
31-
import qualified Data.Primitive.ByteArray as Prim
32-
import qualified Data.Vector.Primitive as VP
3330
import qualified Data.ByteString as BS
3431
import qualified Data.ByteString.Unsafe as BU
32+
import qualified Data.Primitive.ByteArray as Prim
33+
import qualified Data.Primitive.Types as Prim
34+
import qualified Data.Vector.Primitive as VP
3535

3636

3737
-- Types -----------------------------------------------------------------------

pkg/hs-urbit/lib/Noun/Convert.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,9 +7,9 @@ module Noun.Convert
77
) where
88

99
import ClassyPrelude hiding (hash)
10-
import Noun.Core
11-
import Noun.Atom
1210
import Control.Lens
11+
import Noun.Atom
12+
import Noun.Core
1313

1414
import qualified Control.Monad.Fail as Fail
1515

pkg/hs-urbit/lib/Noun/Core.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# OPTIONS_GHC -funbox-strict-fields #-}
2-
{-# LANGUAGE Strict, StrictData #-}
2+
{-# LANGUAGE Strict #-}
3+
{-# LANGUAGE StrictData #-}
34

45
module Noun.Core
56
( Noun, pattern Cell, pattern Atom, nounSize
@@ -14,7 +15,7 @@ import Data.Hashable (hash)
1415
import GHC.Natural (Natural)
1516
import GHC.Prim (reallyUnsafePtrEquality#)
1617
import Test.QuickCheck.Arbitrary (Arbitrary(arbitrary))
17-
import Test.QuickCheck.Gen (Gen, scale, resize, getSize)
18+
import Test.QuickCheck.Gen (Gen, getSize, resize, scale)
1819

1920

2021
-- Types -----------------------------------------------------------------------

pkg/hs-urbit/lib/Noun/Cue.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -2,12 +2,12 @@ module Noun.Cue (cue, cueBS) where
22

33
import ClassyPrelude
44

5-
import Noun.Core
65
import Noun.Atom
6+
import Noun.Core
77

8-
import Control.Lens (view, from)
9-
import Data.Bits (shiftL, shiftR, (.|.), (.&.))
10-
import Foreign.Ptr (Ptr, plusPtr, castPtr, ptrToWordPtr)
8+
import Control.Lens (from, view)
9+
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
10+
import Foreign.Ptr (Ptr, castPtr, plusPtr, ptrToWordPtr)
1111
import Foreign.Storable (peek)
1212
import GHC.Prim (ctz#)
1313
import GHC.Word (Word(..))
@@ -75,7 +75,7 @@ newtype Get a = Get
7575

7676
doGet :: Get a -> ByteString -> Either DecodeExn a
7777
doGet m bs =
78-
unsafePerformIO $ try $ BS.unsafeUseAsCStringLen bs \(ptr, len) -> do
78+
unsafePerformIO $ try $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) -> do
7979
let endPtr = ptr `plusPtr` len
8080
let sz = max 50
8181
$ min 10_000_000
@@ -137,19 +137,19 @@ getPos = Get $ \_ _ s ->
137137
pure (GetResult s (pos s))
138138

139139
insRef :: Word -> Noun -> Get ()
140-
insRef !pos !now = Get \_ tbl s -> do
140+
insRef !pos !now = Get $ \_ tbl s -> do
141141
H.insert tbl pos now
142142
pure $ GetResult s ()
143143

144144
getRef :: Word -> Get Noun
145-
getRef !ref = Get \x tbl s -> do
145+
getRef !ref = Get $ \x tbl s -> do
146146
H.lookup tbl ref >>= \case
147147
Nothing -> runGet (fail ("Invalid Reference: " <> show ref)) x tbl s
148148
Just no -> pure (GetResult s no)
149149

150150
advance :: Word -> Get ()
151151
advance 0 = debugM "advance: 0" >> pure ()
152-
advance !n = Get \_ _ s -> do
152+
advance !n = Get $ \_ _ s -> do
153153
debugM ("advance: " <> show n)
154154
let newUsed = n + usedBits s
155155
newS = s { pos = pos s + n
@@ -164,15 +164,15 @@ advance !n = Get \_ _ s -> do
164164

165165
-- TODO Should this be (>= end) or (> end)?
166166
peekCurWord :: Get Word
167-
peekCurWord = Get \end _ s -> do
167+
peekCurWord = Get $ \end _ s -> do
168168
debugMId "peekCurWord" $ do
169169
if ptrToWordPtr (currPtr s) >= ptrToWordPtr end
170170
then pure (GetResult s 0)
171171
else GetResult s <$> peek (currPtr s)
172172

173173
-- TODO Same question as above.
174174
peekNextWord :: Get Word
175-
peekNextWord = Get \end _ s -> do
175+
peekNextWord = Get $ \end _ s -> do
176176
debugMId "peekNextWord" $ do
177177
let pTarget = currPtr s `plusPtr` 8
178178
if ptrToWordPtr pTarget >= ptrToWordPtr end
@@ -182,7 +182,7 @@ peekNextWord = Get \end _ s -> do
182182
peekUsedBits :: Get Word
183183
peekUsedBits =
184184
debugMId "peekUsedBits" $ do
185-
Get \_ _ s -> pure (GetResult s (usedBits s))
185+
Get $ \_ _ s -> pure (GetResult s (usedBits s))
186186

187187
{-|
188188
Get a bit.
@@ -219,7 +219,7 @@ dAtomBits :: Word -> Get Atom
219219
dAtomBits !(fromIntegral -> bits) = do
220220
debugMId ("dAtomBits(" <> show bits <> ")") $ do
221221
fmap (view $ from atomWords) $
222-
VP.generateM bufSize \i -> do
222+
VP.generateM bufSize $ \i -> do
223223
debugM (show i)
224224
if (i == lastIdx && numExtraBits /= 0)
225225
then dWordBits (fromIntegral numExtraBits)

pkg/hs-urbit/lib/Noun/Jam.hs

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,18 @@ module Noun.Jam (jam, jamBS) where
22

33
import ClassyPrelude hiding (hash)
44

5-
import Noun.Core
65
import Noun.Atom
6+
import Noun.Core
77

8-
import Control.Lens (view, from)
9-
import Data.Bits (shiftL, shiftR, setBit, clearBit, (.|.))
8+
import Control.Lens (from, view)
9+
import Data.Bits (clearBit, setBit, shiftL, shiftR, (.|.))
1010
import Data.Vector.Primitive ((!))
1111
import Foreign.Marshal.Alloc (callocBytes, free)
1212
import Foreign.Ptr (Ptr, castPtr, plusPtr)
1313
import Foreign.Storable (poke)
14-
import GHC.Integer.GMP.Internals (BigNat)
1514
import GHC.Int (Int(I#))
16-
import GHC.Natural (Natural(NatS#, NatJ#))
15+
import GHC.Integer.GMP.Internals (BigNat)
16+
import GHC.Natural (Natural(NatJ#, NatS#))
1717
import GHC.Prim (Word#, plusWord#, word2Int#)
1818
import GHC.Word (Word(W#))
1919
import System.IO.Unsafe (unsafePerformIO)
@@ -64,7 +64,7 @@ newtype Put a = Put
6464

6565
{-# INLINE getRef #-}
6666
getRef :: Put (Maybe Word)
67-
getRef = Put \tbl s -> PutResult s <$> H.lookup tbl (pos s)
67+
getRef = Put $ \tbl s -> PutResult s <$> H.lookup tbl (pos s)
6868

6969
{-
7070
1. Write the register to the output, and increment the output pointer.
@@ -77,15 +77,15 @@ flush = Put $ \tbl s@S{..} -> do
7777

7878
{-# INLINE update #-}
7979
update :: (S -> S) -> Put ()
80-
update f = Put \tbl s@S{..} -> pure (PutResult (f s) ())
80+
update f = Put $ \tbl s@S{..} -> pure (PutResult (f s) ())
8181

8282
{-# INLINE setRegOff #-}
8383
setRegOff :: Word -> Int -> Put ()
84-
setRegOff r o = update \s@S{..} -> (s {reg=r, off=o})
84+
setRegOff r o = update $ \s@S{..} -> (s {reg=r, off=o})
8585

8686
{-# INLINE setReg #-}
8787
setReg :: Word -> Put ()
88-
setReg r = update \s@S{..} -> (s { reg=r })
88+
setReg r = update $ \s@S{..} -> (s { reg=r })
8989

9090
{-# INLINE getS #-}
9191
getS :: Put S
@@ -129,9 +129,9 @@ writeWord wor = do
129129
S{..} <- getS
130130
setReg (reg .|. shiftL wor off)
131131
flush
132-
update \s -> s { pos = 64 + pos
133-
, reg = shiftR wor (64 - off)
134-
}
132+
update $ \s -> s { pos = 64 + pos
133+
, reg = shiftR wor (64 - off)
134+
}
135135

136136
{-
137137
To write some bits (< 64) from a word:
@@ -182,7 +182,7 @@ writeAtomWord (W# w) = writeAtomWord# w
182182
writeAtomBigNat :: BigNat -> Put ()
183183
writeAtomBigNat !(view bigNatWords -> words) = do
184184
let lastIdx = VP.length words - 1
185-
for_ [0..(lastIdx-1)] \i ->
185+
for_ [0..(lastIdx-1)] $ \i ->
186186
writeWord (words ! i)
187187
writeAtomWord (words ! lastIdx)
188188

pkg/hs-urbit/lib/Noun/TH.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,10 @@
44

55
module Noun.TH (deriveNoun) where
66

7-
import ClassyPrelude hiding (fromList)
8-
import Noun.Convert
7+
import ClassyPrelude hiding (fromList)
98
import Language.Haskell.TH
109
import Language.Haskell.TH.Syntax
10+
import Noun.Convert
1111

1212
import RIO (decodeUtf8Lenient)
1313

pkg/hs-urbit/lib/Urbit/Ames.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,8 @@ module Urbit.Ames where
55
import ClassyPrelude
66

77
import Data.IP
8-
import Noun
98
import Network.Socket
9+
import Noun
1010

1111
import qualified Data.Vector as V
1212
import qualified Urbit.Time as Time
@@ -17,11 +17,11 @@ import qualified Vere.Ames as VA
1717
data GalaxyInfo = GalaxyInfo { ip :: IPv4, age :: Time.Unix }
1818

1919
data Ames = Ames
20-
{ live :: Bool -- ^ whether the listener is on
21-
, ourPort :: Maybe Int
20+
{ live :: Bool -- ^ whether the listener is on
21+
, ourPort :: Maybe Int
2222
-- , threadId :: Thread
2323
, globalDomain :: Maybe Text -- ^ something like "urbit.org"
24-
, imperial :: V.Vector (Maybe GalaxyInfo)
24+
, imperial :: V.Vector (Maybe GalaxyInfo)
2525
}
2626

2727
init :: Ames
@@ -52,7 +52,7 @@ ioStart ames isLocal defaultPort (Atom who) = do
5252

5353
-- TODO: set up another thread to own the recv socket, which makes the Ovums
5454
-- which get put into the computeQueue, like in _ames_recv_cb.
55-
withSocketsDo do
55+
withSocketsDo $ do
5656
s <- socket AF_INET Datagram 17
5757
-- bind s (SockAddrInet port )
5858
pure ()

pkg/hs-urbit/lib/Urbit/Behn.hs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -16,18 +16,15 @@
1616
until a new time has been set.
1717
-}
1818

19-
module Urbit.Behn (Behn, init, wait, doze) where
19+
module Urbit.Behn (Behn(..), init, wait, doze) where
2020

21-
import Prelude hiding (init)
2221
import Control.Lens
22+
import Prelude hiding (init)
2323

24-
import Control.Concurrent.MVar (MVar, takeMVar, newEmptyMVar, putMVar)
25-
import Control.Monad (void, when)
26-
import Data.IORef (IORef, writeIORef, readIORef, newIORef)
24+
import Control.Concurrent.MVar (MVar, newEmptyMVar, putMVar, takeMVar)
2725

28-
import qualified Urbit.Timer as Timer
2926
import qualified Urbit.Time as Time
30-
import qualified GHC.Event as Ev
27+
import qualified Urbit.Timer as Timer
3128

3229

3330
-- Behn Stuff ------------------------------------------------------------------

0 commit comments

Comments
 (0)