Too few arguments to infix type operator [GHC-24180]

Language extension: TypeOperators

This error occurs when an infix operator in a type is used as a prefix or postfix operator. That is, if one writes T1 OP or OP T2 instead of T1 OP T2, for types T1 and T2 and infix operator OP.

Examples

Type operator missing an argument

Message

missing-argument/before/MissingArgument.hs:6:12: error: [GHC-24180]
    Operator applied to too few arguments: +
  |
6 | example :: + Int
  |            ^

Explanation

Infix type operators require arguments on both sides.

MissingArgument.hs
Before
{-# LANGUAGE TypeOperators #-}
module MissingArgument where

type a + b = Either a b

example :: + Int
example = Right 5
After
{-# LANGUAGE TypeOperators #-}
module MissingArgument where

type a + b = Either a b

example :: String + Int
example = Right 5
Use of ∀ without UnicodeSyntax being enabled

Message

Ident.hs:3:10: error: [GHC-24180]
    Operator applied to too few arguments: ∀
  |
3 | ident :: ∀ α.α → α
  |          ^

Explanation

The UnicodeSyntax language extension causes GHC’s parser to recognize a variety of non-ASCII mathematical symbols as representing their Haskell equivalents. The complete list is available in the documentation.

When this extension is not enabled, is instead recognized as an infix operator character that has no argument on its left side.

Ident.hs
Before

module Ident where

ident :: ∀ α.α → α
ident = λ x → x
After
{-# LANGUAGE UnicodeSyntax #-}
module Ident where

ident :: ∀ α.α → α
ident = λ x → x