Skip to content

Commit

Permalink
Use unsnocNE for HLint
Browse files Browse the repository at this point in the history
  • Loading branch information
xsebek committed Oct 7, 2023
1 parent f5dd56d commit 1c4cc21
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 4 deletions.
6 changes: 2 additions & 4 deletions src/Swarm/Language/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,13 @@
-- Pretty-printing for the Swarm language.
module Swarm.Language.Pretty where

import Control.Lens (unsnoc)
import Control.Lens.Combinators (pattern Empty)
import Control.Unification
import Control.Unification.IntVar
import Data.Bool (bool)
import Data.Functor.Fixedpoint (Fix, unFix)
import Data.List.NonEmpty qualified as NE
import Data.Map.Strict qualified as M
import Data.Maybe (fromJust)
import Data.Set (Set)
import Data.Set qualified as S
import Data.String (fromString)
Expand All @@ -32,7 +30,7 @@ import Swarm.Language.Parse (getLocRange)
import Swarm.Language.Syntax
import Swarm.Language.Typecheck
import Swarm.Language.Types
import Swarm.Util (showEnum, showLowT)
import Swarm.Util (showEnum, showLowT, unsnocNE)
import Witch

------------------------------------------------------------
Expand Down Expand Up @@ -160,7 +158,7 @@ instance ((UnchainableFun t), (PrettyPrec t)) => PrettyPrec (TypeF t) where
prettyPrec p (TyCmdF ty) = pparens (p > 9) $ "cmd" <+> prettyPrec 10 ty
prettyPrec _ (TyDelayF ty) = braces $ ppr ty
prettyPrec p (TyFunF ty1 ty2) =
let (iniF, lastF) = fromJust . unsnoc $ ty1 : unchainFun ty2
let (iniF, lastF) = unsnocNE $ ty1 NE.:| unchainFun ty2
funs = (prettyPrec 1 <$> iniF) <> [ppr lastF]
inLine l r = l <+> "->" <+> r
multiLine l r = l <+> "->" <> hardline <> r
Expand Down
18 changes: 18 additions & 0 deletions src/Swarm/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Swarm.Util (
surfaceEmpty,
applyWhen,
hoistMaybe,
unsnocNE,

-- * Directory utilities
readFileMay,
Expand Down Expand Up @@ -239,6 +240,23 @@ applyWhen False _ x = x
hoistMaybe :: (Applicative m) => Maybe b -> MaybeT m b
hoistMaybe = MaybeT . pure

-- | Like 'unsnoc', but for 'NonEmpty' so without the 'Maybe'
--
-- Taken from Cabal-syntax Distribution.Utils.Generic.
--
-- Example:
--
-- >>> unsnocNE (1 :| [2, 3])
-- ([1,2],3)
--
-- >>> unsnocNE (1 :| [])
-- ([],1)
unsnocNE :: NonEmpty a -> ([a], a)
unsnocNE (x :| xs) = go x xs
where
go y [] = ([], y)
go y (z : zs) = let ~(ws, w) = go z zs in (y : ws, w)

------------------------------------------------------------
-- Directory stuff

Expand Down

0 comments on commit 1c4cc21

Please sign in to comment.