Skip to content
Snippets Groups Projects
Commit 2a7afae8 authored by Bodigrim's avatar Bodigrim Committed by Mergify
Browse files

Avoid Data.List.{head,tail} in Cabal-syntax

parent 050c3c53
No related branches found
No related tags found
No related merge requests found
......@@ -25,7 +25,6 @@ module Language.Haskell.Extension (
knownExtensions
) where
import qualified Prelude (head)
import Distribution.Compat.Prelude
import Data.Array (Array, accumArray, bounds, Ix(inRange), (!))
......@@ -752,9 +751,9 @@ classifyKnownExtension string@(c : _)
knownExtensionTable :: Array Char [(String, KnownExtension)]
knownExtensionTable =
accumArray (flip (:)) [] ('A', 'Z')
[ (Prelude.head str, (str, extension)) -- assume KnownExtension's Show returns a non-empty string
| extension <- [toEnum 0 ..]
, let str = show extension ]
[ (hd, (str, extension)) -- assume KnownExtension's Show returns a non-empty string
| (extension, str@(hd : _)) <- map (\e -> (e, show e)) [toEnum 0 ..]
]
knownExtensions :: [KnownExtension]
knownExtensions = [minBound .. maxBound]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment