1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 17:04:47 +03:00

🔥 deepseq.

This commit is contained in:
Rob Rix 2017-09-08 17:35:55 +01:00
parent d1ced22ce8
commit 07bef3f75e
12 changed files with 10 additions and 30 deletions

View File

@ -92,7 +92,6 @@ library
, cmark-gfm , cmark-gfm
, comonad , comonad
, containers , containers
, deepseq
, directory , directory
, effects , effects
, filepath , filepath
@ -167,7 +166,6 @@ test-suite test
, bifunctors , bifunctors
, bytestring , bytestring
, comonad , comonad
, deepseq
, filepath , filepath
, free , free
, Glob , Glob

View File

@ -3,7 +3,6 @@
{-# OPTIONS_GHC -funbox-strict-fields #-} {-# OPTIONS_GHC -funbox-strict-fields #-}
module Category where module Category where
import Control.DeepSeq
import Data.Functor.Listable import Data.Functor.Listable
import Data.Hashable import Data.Hashable
import Data.Text (Text) import Data.Text (Text)
@ -238,7 +237,7 @@ data Category
| Ty | Ty
| ParenthesizedExpression | ParenthesizedExpression
| ParenthesizedType | ParenthesizedType
deriving (Eq, Generic, Ord, Show, NFData) deriving (Eq, Generic, Ord, Show)
{-# DEPRECATED RescueModifier "Deprecated; use Modifier Rescue instead." #-} {-# DEPRECATED RescueModifier "Deprecated; use Modifier Rescue instead." #-}

View File

@ -1,7 +1,6 @@
{-# OPTIONS_GHC -fno-warn-orphans -funbox-strict-fields #-} {-# OPTIONS_GHC -fno-warn-orphans -funbox-strict-fields #-}
module Data.Functor.Both (Both, both, runBothWith, fst, snd, module X) where module Data.Functor.Both (Both, both, runBothWith, fst, snd, module X) where
import Control.DeepSeq
import Data.Bifunctor.Join as X import Data.Bifunctor.Join as X
import Data.Semigroup import Data.Semigroup
import Prelude hiding (fst, snd) import Prelude hiding (fst, snd)
@ -33,5 +32,3 @@ instance (Semigroup a, Monoid a) => Monoid (Join (,) a) where
instance (Semigroup a) => Semigroup (Join (,) a) where instance (Semigroup a) => Semigroup (Join (,) a) where
a <> b = Join $ runJoin a <> runJoin b a <> b = Join $ runJoin a <> runJoin b
instance NFData a => NFData (Join (,) a)

View File

@ -6,7 +6,6 @@ module Data.Range
, intersectsRange , intersectsRange
) where ) where
import Control.DeepSeq
import Data.Semigroup import Data.Semigroup
import Data.Text.Prettyprint.Doc import Data.Text.Prettyprint.Doc
import GHC.Generics import GHC.Generics
@ -14,7 +13,7 @@ import Test.LeanCheck
-- | A half-open interval of integers, defined by start & end indices. -- | A half-open interval of integers, defined by start & end indices.
data Range = Range { start :: {-# UNPACK #-} !Int, end :: {-# UNPACK #-} !Int } data Range = Range { start :: {-# UNPACK #-} !Int, end :: {-# UNPACK #-} !Int }
deriving (Eq, Show, Generic, NFData) deriving (Eq, Show, Generic)
-- | Return the length of the range. -- | Return the length of the range.
rangeLength :: Range -> Int rangeLength :: Range -> Int

View File

@ -1,7 +1,6 @@
{-# LANGUAGE ConstraintKinds, DataKinds, GADTs, KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators, UndecidableInstances #-} {-# LANGUAGE ConstraintKinds, DataKinds, GADTs, KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Data.Record where module Data.Record where
import Control.DeepSeq
import Data.Kind import Data.Kind
import Data.Functor.Listable import Data.Functor.Listable
import Data.Semigroup import Data.Semigroup
@ -49,11 +48,6 @@ instance {-# OVERLAPPABLE #-} HasField (field ': fields) field where
getField (h :. _) = h getField (h :. _) = h
setField (_ :. t) f = f :. t setField (_ :. t) f = f :. t
instance (NFData h, NFData (Record t)) => NFData (Record (h ': t)) where
rnf (h :. t) = rnf h `seq` rnf t `seq` ()
instance NFData (Record '[]) where
rnf _ = ()
instance (Show h, Show (Record t)) => Show (Record (h ': t)) where instance (Show h, Show (Record t)) => Show (Record (h ': t)) where
showsPrec n (h :. t) = showParen (n > 0) $ showsPrec 1 h . (" :. " <>) . shows t showsPrec n (h :. t) = showParen (n > 0) $ showsPrec 1 h . (" :. " <>) . shows t

View File

@ -9,7 +9,6 @@ module Data.Span
, emptySpan , emptySpan
) where ) where
import Control.DeepSeq
import Data.Aeson ((.=), (.:)) import Data.Aeson ((.=), (.:))
import qualified Data.Aeson as A import qualified Data.Aeson as A
import Data.Hashable (Hashable) import Data.Hashable (Hashable)
@ -23,7 +22,7 @@ data Pos = Pos
{ posLine :: !Int { posLine :: !Int
, posColumn :: !Int , posColumn :: !Int
} }
deriving (Show, Read, Eq, Ord, Generic, Hashable, NFData) deriving (Show, Read, Eq, Ord, Generic, Hashable)
instance A.ToJSON Pos where instance A.ToJSON Pos where
toJSON Pos{..} = toJSON Pos{..} =
@ -38,7 +37,7 @@ data Span = Span
{ spanStart :: Pos { spanStart :: Pos
, spanEnd :: Pos , spanEnd :: Pos
} }
deriving (Show, Read, Eq, Ord, Generic, Hashable, NFData) deriving (Show, Read, Eq, Ord, Generic, Hashable)
emptySpan :: Span emptySpan :: Span
emptySpan = Span (Pos 1 1) (Pos 1 1) emptySpan = Span (Pos 1 1) (Pos 1 1)

View File

@ -2,7 +2,6 @@
module Language where module Language where
import Control.Comonad.Trans.Cofree hiding (cofree, (:<)) import Control.Comonad.Trans.Cofree hiding (cofree, (:<))
import Control.DeepSeq
import Data.Aeson import Data.Aeson
import Data.Foldable import Data.Foldable
import Data.Record import Data.Record
@ -21,7 +20,7 @@ data Language
| Python | Python
| Ruby | Ruby
| TypeScript | TypeScript
deriving (Show, Eq, Read, Generic, NFData, ToJSON) deriving (Show, Eq, Read, Generic, ToJSON)
-- | Returns a Language based on the file extension (including the "."). -- | Returns a Language based on the file extension (including the ".").
languageForType :: String -> Maybe Language languageForType :: String -> Maybe Language

View File

@ -14,7 +14,6 @@ module Patch
, mapPatch , mapPatch
) where ) where
import Control.DeepSeq
import Data.Align import Data.Align
import Data.Functor.Classes.Pretty.Generic import Data.Functor.Classes.Pretty.Generic
import Data.Functor.Listable import Data.Functor.Listable
@ -26,7 +25,7 @@ data Patch a
= Replace a a = Replace a a
| Insert a | Insert a
| Delete a | Delete a
deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Show, Traversable, NFData) deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Show, Traversable)
-- DSL -- DSL

View File

@ -18,7 +18,6 @@ module Renderer
, File(..) , File(..)
) where ) where
import Control.DeepSeq
import Data.Aeson (Value, (.=)) import Data.Aeson (Value, (.=))
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.Foldable (asum) import Data.Foldable (asum)
@ -93,7 +92,7 @@ identifierAlgebra (_ :<< syntax) = case syntax of
where identifier = fmap Identifier . extractLeafValue . unwrap . fst where identifier = fmap Identifier . extractLeafValue . unwrap . fst
newtype Identifier = Identifier Text newtype Identifier = Identifier Text
deriving (Eq, NFData, Show) deriving (Eq, Show)
instance ToJSONFields Identifier where instance ToJSONFields Identifier where
toJSONFields (Identifier i) = ["identifier" .= i] toJSONFields (Identifier i) = ["identifier" .= i]

View File

@ -17,7 +17,6 @@ module Renderer.TOC
, entrySummary , entrySummary
) where ) where
import Control.DeepSeq
import Control.Monad.Free (iter) import Control.Monad.Free (iter)
import Data.Aeson import Data.Aeson
import Data.Align (crosswalk) import Data.Align (crosswalk)
@ -93,7 +92,7 @@ data Declaration
| FunctionDeclaration { declarationIdentifier :: T.Text } | FunctionDeclaration { declarationIdentifier :: T.Text }
| SectionDeclaration { declarationIdentifier :: T.Text, declarationLevel :: Int } | SectionDeclaration { declarationIdentifier :: T.Text, declarationLevel :: Int }
| ErrorDeclaration { declarationIdentifier :: T.Text, declarationLanguage :: Maybe Language } | ErrorDeclaration { declarationIdentifier :: T.Text, declarationLanguage :: Maybe Language }
deriving (Eq, Generic, NFData, Show) deriving (Eq, Generic, Show)
getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe Declaration getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe Declaration
getDeclaration = getField getDeclaration = getField

View File

@ -1,7 +1,6 @@
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
module Syntax where module Syntax where
import Control.DeepSeq
import Data.Aeson import Data.Aeson
import Data.Align.Generic import Data.Align.Generic
import Data.Functor.Classes import Data.Functor.Classes
@ -111,7 +110,7 @@ data Syntax f
| Ty [f] | Ty [f]
-- | A send statement has a channel and an expression in Go. -- | A send statement has a channel and an expression in Go.
| Send f f | Send f f
deriving (Eq, Foldable, Functor, GAlign, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON, NFData) deriving (Eq, Foldable, Functor, GAlign, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)
extractLeafValue :: Syntax a -> Maybe Text extractLeafValue :: Syntax a -> Maybe Text

View File

@ -1,7 +1,6 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, OverloadedStrings #-} {-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, OverloadedStrings #-}
module IntegrationSpec where module IntegrationSpec where
import Control.DeepSeq
import qualified Data.ByteString as B import qualified Data.ByteString as B
import Data.Foldable (find, traverse_) import Data.Foldable (find, traverse_)
import Data.Functor.Both import Data.Functor.Both
@ -113,7 +112,7 @@ stripWhitespace = B.foldl' go B.empty
-- | A wrapper around 'B.ByteString' with a more readable 'Show' instance. -- | A wrapper around 'B.ByteString' with a more readable 'Show' instance.
newtype Verbatim = Verbatim B.ByteString newtype Verbatim = Verbatim B.ByteString
deriving (Eq, NFData) deriving (Eq)
instance Show Verbatim where instance Show Verbatim where
showsPrec _ (Verbatim byteString) = ('\n':) . (T.unpack (decodeUtf8 byteString) ++) showsPrec _ (Verbatim byteString) = ('\n':) . (T.unpack (decodeUtf8 byteString) ++)