Created
August 1, 2020 23:36
-
-
Save tfausak/7e1e128b7bccdb423276db7c0e60224a to your computer and use it in GitHub Desktop.
Minimal examples of Haskell language extensions.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
a = a :: Eq b => () -- AllowAmbiguousTypes | |
a = proc b -> id -< b -- Arrows | |
a = let !b = () in b -- BangPatterns | |
a = 0b0 -- BinaryLiterals | |
a = id do 0 -- BlockArguments | |
foreign import capi "" a :: () | |
class A b where c :: Eq b => b -- ConstrainedClassMethods | |
type A = Eq -- ConstraintKinds | |
# -- CPP | |
import Data.Proxy; a = Proxy :: Proxy True -- DataKinds | |
class C a where m :: [a]; default m :: [a]; m = [] -- DefaultSignatures | |
data X deriving Num -- DeriveAnyClass | |
import Data.Data; data X deriving Data -- DeriveDataTypeable | |
data X a deriving Foldable -- DeriveFoldable | |
data X a deriving Functor -- DeriveFunctor | |
import GHC.Generics; data X deriving Generic -- DeriveGeneric | |
import Language.Haskell.TH.Syntax; data X deriving Lift -- DeriveLift | |
data X a deriving (Functor, Foldable, Traversable) -- DeriveTraversable | |
data X deriving stock () -- DerivingStrategies | |
newtype X = X () deriving Eq via () -- DerivingVia | |
data A = A { x :: () }; data B = B { x :: () } -- DuplicateRecordFields | |
x = \ y -> case y of -- EmptyCase | |
data X deriving Eq -- EmptyDataDeriving | |
data X = forall a . X a -- ExistentialQuantification | |
x = Nothing :: forall a . Maybe a -- ExplicitForAll | |
import Data.Ix ( type Ix ) -- ExplicitNamespaces | |
default (()) -- ExtendedDefaultRules | |
a = () :: Eq () => () -- FlexibleContexts | |
instance Eq (() -> ()) -- FlexibleInstances | |
class C a | a -> a -- FunctionalDependencies | |
data X where X :: X -- GADTSyntax | |
data X a where X :: a -> X () -- GADTs | |
newtype X = X Int deriving Num -- GeneralizedNewtypeDeriving | |
a = 0x0.0 -- HexFloatLiterals | |
a | let ?b = 0 = 0 -- ImplicitParams | |
import Data.Ix qualified -- ImportQualifiedPost | |
a = Nothing :: Maybe (forall a . a) -- ImpredicativeTypes | |
instance Num () where abs :: () -> (); abs = id -- InstanceSigs | |
foreign import ccall interruptible "" a :: () -- InterruptibleFFI | |
a = () :: (() :: *) -- KindSignatures | |
x = \ case _ -> 0 -- LambdaCase | |
type X a = a; x = undefined :: X (forall a . a) -- LiberalTypeSynonyms | |
a# = () -- MagicHash | |
class C a b -- MultiParamTypeClasses | |
a = if | let -> 0 -- MultiWayIf | |
a = id -1 -- NegativeLiterals | |
a (b + 0) = 0 -- NPlusKPatterns | |
class C -- NullaryTypeClasses | |
a = 0.0 :: Int -- NumDecimals | |
a = 0_0 -- NumericUnderscores | |
import GHC.OverloadedLabels; instance IsLabel "b" () where { fromLabel = () }; a = #b :: IsLabel "b" () => () -- OverloadedLabels | |
import Data.Set; a = [] :: Set () -- OverloadedLists | |
import Data.Text; a = "" :: Text -- OverloadedStrings | |
import "base" Data.Ix -- PackageImports | |
a = [ 0 | b <- [] | c <- [] ] -- ParallelListComp | |
a = () :: _ -- PartialTypeSignatures | |
pattern X = () -- PatternSynonyms | |
a = let (%) b = b / 100 in (5 %) -- PostfixOperators | |
a = mdo () -- RecursiveDo | |
type role X nominal; data X a -- RoleAnnotations | |
a :: () = () -- ScopedTypeVariables | |
data X; deriving instance Eq X -- StandaloneDeriving | |
type T :: *; type T = () -- StandaloneKindSignatures | |
pure [] -- TemplateHaskell | |
a = '() -- TemplateHaskellQuotes | |
a = [ 0 | _ <- [], then id ] -- TransformListComp | |
a = (0, ) -- TupleSections | |
a = id @Int 0 -- TypeApplications | |
type family X -- TypeFamilies | |
type family X a = b | b -> a -- TypeFamilyDependencies | |
data a + b = C a b -- TypeOperators | |
type X = (); instance Num X -- TypeSynonymInstances | |
a = \ x -> case x of (# a | #) -> () -- UnboxedSums | |
a = let x = (# #) in 0 -- UnboxedTuples | |
a = 0 ∷ Int -- UnicodeSyntax | |
a (id -> b) = b -- ViewPatterns |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment