Haskell Symbol Search Cheatsheet Save

Haskell/GHC symbol search cheatsheet

Project README

Haskell/GHC symbol search cheatsheet

Several features of Haskell/GHC have low googleability. Because some of them are composed of symbols :)
This page is a reference collection to support search of them.

If you want to search for function symbols like ., $, >>=, <*>, ..., you can use the following search engines:

Happy Haskelling!


! : "strictness flag"

[ Haskell 2010 Language Report ]

data Vec = Vec !Int

! : "bang pattern"

[ GHC User's Guide ]

f1 !x = 

# : "MagicHash"

[ GHC User's Guide ]

data Int = I# Int#

# : "ExtendedLiterals"

[ GHC User's Guide ]

f x = case x of
        123#Int8 -> False
        _        -> True

# : "OverloadedLabels"

[ GHC User's Guide ]

example = #x (Point 1 2)

# : C pre-processor's directive

[ GHC User's Guide ]

#include "MachDeps.h"

# : hsc2hs command's operator

[ GHC User's Guide ]

flag = #const VER_MAJORVERSION

$( ) : Template Haskell’s splice syntax

[ GHC User's Guide ]

two = $(add1 1)

$$( ) : Typed Template Haskell’s splice syntax

[ GHC User's Guide ]

two = $$(add1 1)

%1 -> : "Linear types"

[ GHC User's Guide ]

f :: a %1 -> a 

' : an identifier consists of a letter followed by zero or more letters, digits, underscores, and single quotes

[ Haskell 2010 Language Report ]

xs' = f ys

' : promoted constructors are prefixed by a tick '

[ GHC User's Guide ]

type * = TYPE 'LiftedRep

' '' : Template Haskell’s quotation syntax

[ GHC User's Guide ]

makeLenses ''FooBar

() : "unit type"

[ Haskell 2010 Language Report ] [ Haskell 2010 Language Report ]

main :: IO ()

() : "unit expression"

[ Haskell 2010 Language Report ] [ Haskell 2010 Language Report ]

return ()

( ) : "section" - a convenient syntax for partial application

[ Haskell 2010 Language Report ]

add1 = (1+)

(,) : the constructor for a tuple

[ Haskell 2010 Language Report ]

f x y = liftM2 (,) x y 

(, xxx) : "TupleSections"

[ GHC User's Guide ]

f xs = fmap (, True) xs

(# #) : "unboxed tuple"

[ GHC User's Guide ]

f x y = (# x+1, y-1 #)

(# | | #) : "unboxed sum"

[ GHC User's Guide ]

f :: (# Int | Bool | Char #) -> Int
f (# x | | #)    = 1
f (# | True | #) = 2
f _              = 3

(..) : export all of its names

[ Haskell 2010 Language Report ]

module GHC.Arr (
        Ix(..),

(..) : import all of its names

[ Haskell 2010 Language Report ]

import GHC.Types (Bool(..))

* : the kind of ordinary types (synonym for Type and TYPE `LiftedRep)

[ Haskell 2010 Language Report ] [ GHC User's Guide ]

ghci> :kind Int
Int :: *

-> : case expression

[ Haskell 2010 Language Report ]

f x = case x of
        Nothing -> False
        Just _  -> True

-> : "view pattern"

[ GHC User's Guide ]

size (view -> Unit)        = 1
size (view -> Arrow t1 t2) = size t1 + size t2

-> : "function type"

[ Haskell 2010 Language Report ]

id :: a -> a

. : module names are a dot-separated sequence

[ Haskell 2010 Language Report ]

import Data.Maybe
import qualified Text.Read.Lex as L

lexP = lift L.lex

. : "OverloadedRecordDot"

[ GHC User's Guide ]

getResult c = c.result

getResults = map (.result)

. : "OverloadedRecordUpdate" (experimental)

[ GHC User's Guide ]

setYearTaken c y = c{taken.year = y}

. : universal quantification

[ GHC User's Guide ]

f :: forall a. a -> [a]

: : "list constructor" (cons)

[ Haskell 2010 Language Report ] [ Haskell 2010 Language Report ] [ Haskell 2010 Language Report ]

f x xs = x:xs

: : an operator symbol starting with a colon is a constructor

[ Haskell 2010 Language Report ]

data NonEmpty a = a :| [a]

:: : "type signature"

[ Haskell 2010 Language Report ]

id :: a -> a
id x =  x

:: : "expression type-signature" (type annotation)

[ Haskell 2010 Language Report ]

x = fromIntegral (maxBound::Int)

; : semicolon in layout rule

[ Haskell 2010 Language Report ]

f x = let a = 1; b = 2  
          g y = exp2  
      in exp1 

<- : lambda-bound in do expression

[ Haskell 2010 Language Report ]

f = do
  x <- getLine
  putStrLn x

<- : "pattern guard"

[ Haskell 2010 Language Report ]

f x
  | Just y <- g x = 

=> : context (type class constraint)

[ Haskell 2010 Language Report ]

subtract :: (Num a) => a -> a -> a
subtract x y = y - x

? : "ImplicitParams"

[ GHC User's Guide ]

sort :: (?cmp :: a -> a -> Bool) => [a] -> [a]
sort = sortBy ?cmp

@ : "as pattern"

[ Haskell 2010 Language Report ]

f s@(x:xs) = 

@ : "type application"

[ GHC User's Guide ]

f = read @Int

@ : "type abstraction"

[ GHC User's Guide ]

class C @k a where 

[] : "empty list" (nil)

[ Haskell 2010 Language Report ] [ Haskell 2010 Language Report ]

null [] = True
null _  = False

[ .. ] : "arithmetic sequence"

[ Haskell 2010 Language Report ]

xs = [1..10]

[ | <- ] : "list comprehension"

[ Haskell 2010 Language Report ]

xs = [x^2 | x <- [1..10]] 

[| |], [e| |], [d| |], [t| |], [p| |] : Template Haskell’s quotation syntax (expression, declaration, type, and pattern)

[ GHC User's Guide ]

add1 x = [| x + 1 |]

[varid| |] : Template Haskell’s quasi-quotation syntax

[ GHC User's Guide ]

greet name = [interpolate| Hello, #name! |]

[|| ||] : Typed Template Haskell’s quotation syntax

[ GHC User's Guide ]

add1 x = [|| x + 1 ||]

_ : "wildcard pattern"

[ Haskell 2010 Language Report ]

f Red  =
f Blue =
f _    =

_ : unused identifiers beginning with underscore

[ GHC User's Guide ] [ Haskell 2010 Language Report ]

_w = True                -- No warning: _w starts with an underscore

_ : "typed hole" (expression level)

[ GHC User's Guide ]

sum xs = foldr _ 0 xs

_ : "type wildcard" (type level)

[ GHC User's Guide ]

not' :: Bool -> _
not' x = not x

_ : "extra-constraints wildcard"

[ GHC User's Guide ]

arbitCs :: _ => a -> String

_ : "NumericUnderscores"

[ GHC User's Guide ]

million = 1_000_000

\ -> : "lambda abstraction"

[ Haskell 2010 Language Report ]

add1 = \x -> x + 1

\case -> : "LambdaCase"

[ GHC User's Guide ]

f = \case
      Red  -> 2
      Blue -> 1
      _    -> 0

` ` : "infix notation" - an identifier enclosed in grave accents

[ Haskell 2010 Language Report ]

div10 x = x `div` 10

{ } : brace in layout rule

[ Haskell 2010 Language Report ]

f x = case x of {Nothing -> False; Just _ -> True}

{ } : "record syntax" (datatypes with field labels)

[ Haskell 2010 Language Report ]

data MyPoint = Point { x :: Int, y :: Int }

{..} : "record wildcard"

[ GHC User's Guide ]

f Vec{..} = 

{-# #-} : "compiler pragma"

[ Haskell 2010 Language Report ] [ GHC User's Guide ] [ GHC User's Guide ]

{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTs            #-}

{-# INLINE fmap #-}

| : "boolean guard" (guard)

[ Haskell 2010 Language Report ]

clip255 x
  | x > 255   = 255
  | otherwise = x 

| : "MultiWayIf"

[ GHC User's Guide ]

if | x == ":q" -> quit
   | isError x -> errorExit x
   | otherwise -> execCommand x

| : algebraic datatype declaration

[ Haskell 2010 Language Report ]

data Maybe a = Nothing | Just a

| : "functional dependency"

[ GHC User's Guide ]

class Foo a b c | a b -> c where 

~ : "irrefutable pattern"

[ Haskell 2010 Language Report ]

f1 ~(as,bs) =

~ : lazy pattern when Strict is enabled

[ GHC User's Guide ]

{-# LANGUAGE Strict #-}

f ~x =

~ : laziness flag

[ GHC User's Guide ]

data T = C ~a

~ : "equality constraint"

[ GHC User's Guide ]

class (F a ~ b) => C a b where
Open Source Agenda is not affiliated with "Haskell Symbol Search Cheatsheet" Project. README Source: takenobu-hs/haskell-symbol-search-cheatsheet
Stars
320
Open Issues
0
Last Commit
3 days ago

Open Source Agenda Badge

Open Source Agenda Rating