Language Syntax

The Finkel language is made from Finkel kernel keywords and Finkel core keywords.

The Finkel kernel keywords are designed to be compatible with Haskell 2010, with few exceptions. The syntax for literal values and function applications are also defined in the Finkel kernel. The rest of this section will go through the Finkel kernel language syntax with small example codes. Each Finkel code is compared to an equivalent Haskell code.

The Finkel core keywords are implemented as macros. Details of the Finkel core keywords are described in the haddock API documentation of the finkel-core package.

Literals

Comments

Line contents after ; are treated as comments.

(putStrLn "foo") ; single-line comment in Finkel
putStrLn "foo" -- single-line comment in Haskell

Block style comment is supported with #; and ;#.

(putStrLn #;Finkel block comment;# "bar")
putStrLn {- Haskell block comment -} "bar"

Form after %_ is ignored:

(do (print True) ; Finkel
    %_(this list (is ignored))
    (print %_ignored False %_ "ignored"))
do print True -- Haskell, ignored forms removed
   print False

Variable identifier

Finkel accepts valid variable identifiers defined in Haskell 2010, and variable identifiers containing hyphens which starting with a non-operator character. Hyphens in variable identifiers are internally converted to underscores. For instance, foo-bar-buzz will be converted to foo_bar_buzz:

(foo-bar-buzz quux) ; Finkel
foo_bar_buzz quux -- Haskell

The hyphen conversion will be triggered only when the first letter of a variable identifier was a non-operator character. Operators like -:-, *+-, $-$, etc are kept as-is.

Numeric

As described in the Numeric Literals section of the Haskell 2010 report, decimal, octal, hexadecimal integers and float with exponent are supported.

(do (print 1)     ; decimal integer in Finkel
    (print 0o77)  ; octal integer
    (print 0xff)  ; hexadecimal integer
    (print 2.34)  ; float
    (print 1e-2)) ; float with exponent
do print 1    -- decimal integer in Haskell
   print 0o77 -- octal integer
   print 0xff -- hexadecimal integer
   print 2.34 -- float
   print 1e-2 -- float with exponent

Character And String

A character literal in Finkel starts with #' instead of surrounding with single quotes. Other than that, Finkel mostly follows the Characters and String Literals section in the Haskell 2010 report.

Following code prints single lower case character a:

(putChar #'a) ; Finkel
putChar 'a'  -- Haskell

Following code prints backslash and single quote:

(print [#'\ #'']) ; Finkel
print ['\\', '\''] -- Haskell

Some characters like newline, space, NUL, etc. are expressed with escape character and specific character sequences.

(print [#'\n #'  #'\NUL #'\^L]) ; Finkel
print ['\n', ' ', '\NUL', '\^L'] -- Haskell

Characters could be expressed with their numeric code in decimal, octal, and hexadecimal:

(print [#'\97 #'\o141 #'\x61]) ; Finkel, prints "aaa"
print ['\97', '\o141', '\x61'] -- Haskell, prints "aaa"

String literals are written between double-quotes. Special characters are escaped with \. Finkel also supports the gap feature, to ignore the string contents between two backslashes.

"Here is a backslant \\ as well as \137, \
    \a numeric escape character, and \^X, a control character." ; Finkel
"Here is a backslant \\ as well as \137, \
    \a numeric escape character, and \^X, a control character." -- Haskell

Expressions

Function Applications

Function application in Finkel is done with parentheses:

(putStrLn "hello") ; Finkel
putStrLn "hello" -- Haskell

Unlike some other lisps, extra parentheses are ignored. For instance:

(((((putStrLn)) "hello"))) ; Finkel

is simplified to:

putStrLn "hello" -- Haskell, redundant parentheses removed

Operator Applications

Finkel does not have native support for infix operator applications. However, a form applying operator function will be expanded to a form taking all of its arguments, with two operands for each. For example, adding numbers from 1 to 5 could be written as:

(+ 1 2 3 4 5) ; Finkel
1 + 2 + 3 + 4 + 5 -- Haskell

Operator expansion understands right and left associativity. Operator precedence in Finkel is explicitly specified with parentheses.

(<*> (pure foldr) (Just +) (pure 1) (pure [2 3])) ; Finkel
pure foldr <*> Just (+) <*> pure 1 <*> pure [2, 3] -- Haskell

The compiler treats the above expression as:

((pure foldr <*> Just (+)) <*> pure 1) <*> pure [2, 3] -- Haskell

because the <*> operator is left-associative.

When a single argument has been passed to operator function, the resulting expression is partial application:

(map (* 2) [1 2 3]) ; Finkel
map ((*) 2) [1, 2, 3] -- Haskell

To apply more than two arguments to an operator function, one needs to explicitly surround the operator with parenthesis. Suppose that there is an operator function *+ which takes three arguments:

((*+) 2 3 4) ; Finkel
(*+) 2 3 4 -- Haskell

Unary Operator Application

The operator - is always treated as a binary operator in Finkel. In below Finkel example, (- 1) is a partially applied function:

(map (- 1) [1 2 3]) ; Finkel
map ((-) 1) [1, 2, 3] -- Haskell

Lambda

Lambda expression starts with \. The last form in the lambda expression the body expression of entire lambda abstraction, others forms are argument patterns:

(zipWith (\x y (* x (+ y 1))) [1 2 3] [4 5 6]) ; Finkel
zipWith (\x y -> x * (y + 1)) [1, 2, 3] [4, 5, 6] -- Haskell

Conditionals

An if expression does not take then and else:

(if test true-expr false-expr) ; Finkel
if test then true_expr else false_expr -- Haskell

A guard starts with |, and supports pattern, local declaration, and boolean:

(case expr ; Finkel
  (Just y) (| ((even y) r1)
              ((odd y) (< y 10) r2)
              ((<- (Just z) (lookup y kvs))
               (let ((= z' (* z 2))))
               (r3 z'))
              (otherwise r4)))
case expr of -- Haskell
  Just y | even y -> r1
         | odd y, y < 10 -> r2
         | Just z <- lookup y kvs
         , let z' = z * 2
         -> r3 z'
         | otherwise -> r4

See also cond in finkel-core.

Tuples

Tuple constructor expression uses single comma. At least one space after the comma is required:

(print (, True #'x)) ; Finkel
print (True, 'x') -- Haskell

Single comma works for tuples with more than two elements:

(print (, True #'x 42 1.23 "foo")) ; Finkel
print (True, 'x', 42, 1.23, "foo") -- Haskell

To express tuple data and type constructor, use consecutive commas without spaces:

(<*> (pure (,,,)) (Just 1) (Just 2) (Just 3) (Just 4)) ; Finkel
pure (,,,) <*> Just 1 <*> Just 2 <*> Just 3 <*> Just 4 -- Haskell

Unit

Unit is expressed with empty parentheses:

(return ()) ; Finkel
return () -- Haskell

See also nil to express an empty form.

Lists

List expression does not take commas:

(print [1 2 3]) ; Finkel
print [1, 2, 3] -- Haskell

Arithmetic sequences use ... Space on each side of .. are required:

(print [1 3 .. 9]) ; Finkel
print [1, 3 .. 9] -- Haskell

List comprehensions use | to separate the resulting expression. Space between | and the result is required.

[x | (<- x [1 .. 10]) (even x)] ; Finkel
[x | x <- [1 .. 10], even x] -- Haskell

Let

A let expression is expressed with let without in:

(let ((:: a Int) ; Finkel
      (:: b c Int)
      (= a 10)
      (= b 4)
      (= c 2))
  (print [a b c]))
let a :: Int -- Haskell
    b, c :: Int
    a = 10
    b = 4
    c = 2
in  print [a, b, c]

Case

A case expression is expressed with case without of and ->:

(case n ; Finkel
  0 "zero"
  1 "one"
  _ "many")
case n of -- Haskell
  0 -> "zero"
  1 -> "one"
  _ -> "many"

Do

Do expression is expressed with do, and bindings inside do-expressions are expressed with <-:

(do (putStr "x: ") ; Finkel
    (<- l getLine)
    (return (words l)))
do putStr "x: " -- Haskell
   l <- getLine
   return (words l)

Datatypes with field labels

Field labels are enclosed with { and }:

(Constr1 {(= field1 1) (= field2 True) (= field3 "abc")}) ; Finkel
Constr1 {field1=1, field2=True, field3="abc"} -- Haskell

Expression Type-Signatures

Type signature uses :::

(:: 42 Int) ; Finkel
(42 :: Int) -- Haskell

Pattern Matching

A non-variable pattern requires parentheses, as in Just shown below:

(case expr ; Finkel
  (Just x) (+ x 1)
  Nothing  0)
case expr of -- Haskell
  Just x -> x + 1
  Nothing -> 0

As pattern

As pattern uses @:

(let ((= (@ x (Just n)) expr)) ; Finkel
  (+ n 1))
let x@(Just n) = expr -- Haskell
in  n + 1

Irrefutable pattern

Irrefutable patterns are expressed with ~:

(let ((= ~(, a ~(, b c)) expr)) ; Finkel
  (+ a (* b c)))
let ~(a, ~(b, c)) = expr -- Haskell
in  a + (b * c)

Operator expansion

The Operator expansion rule applies to patterns. For instance, the : constructor for a list is expanded with its pattern arguments:

(case expr ; Finkel
  (: a1 a2 _) (+ a1 a2)
  _ 0)
case expr of -- Haskell
  a1 : a2 : _ -> a1 + a2
  _ -> 0

Declarations And Bindings

Algebraic Datatype

Algebraic datatype declaration uses data. It does not use = and |. Optional deriving form may appear at the last element of the data form:

(data (D1 a b) ; Finkel
  C1
  (C2 a)
  (C3 b)
  (deriving Eq Show))
data D1 a b -- Haskell
  = C1
  | C2 a
  | C3 b
  deriving (Eq, Show)

Constructor with labeled fields are supported with { and }:

(data (D2 a b) ; Finkel
  (D2 {(:: f1 a)
       (:: f2 b)
       (:: f3 Int)}))
data D2 a b -- Haskell
 = D2 { f1 :: a
      , f2 :: b
      , f3 :: Int }

Type Synonym

Type synonym declaration uses type. It does not use =:

(type (T1 a) (Maybe (, a Bool String))) ; Finkel
type T1 a = Maybe (a, Bool, String) -- Haskell

Datatype Renamings

Newtype declaration uses newtype:

(newtype N (N {(:: unN Int)})) ; Finkel
newtype N = N {unN :: Int} -- Haskell

Class

Type class declaration uses class:

(class (=> (Ord a) (C1 a)) ; Finkel
  (:: m1 (-> a Int))
  (= m1 _ 0))
class Ord a => C1 a where -- Haskell
  m1 :: a -> Int
  m1 _ = 0

Class instance declaration uses instance:

(instance (C1 Int) ; Finkel
  (= m1 n (+ n 1)))
instance C1 Int where -- Haskell
  m1 n = n + 1

Defaults for Overloaded Numeric Operations

Default declaration is done with default:

(default Int Double) ; Finkel
default (Int, Double) -- Haskell

Type Signatures

Type signature uses :::

(:: f (-> Int Int Int)) ; Finkel
f :: Int -> Int -> Int -- Haskell

Single type signature could be used for multiple variables:

(:: f g h (-> Int Int)) ; Finkel
f, g, h :: Int -> Int -- Haskell

Constraints in type signature are expressed with =>. The last element of the form => should be a type:

(:: f (=> (Eq a) (Ord a) (Show a) (Num a) (-> a a))) ; Finkel
f :: (Eq a, Ord a, Show a, Num a) => a -> a -- Haskell

Fixity

It is possible to declare fixity and precedence with infix, infixl, and infixr. Assuming $+$ as a binary operator:

(infixr 6 $+$)
infixr 6 $+$

Note that Finkel syntax is affected by the left and right associativity of operators, but not by the precedence of operators.

Bindings

Function binding declaration uses =. The form after = is the function name, the last form is the expression body. Rest of the forms are argument patterns:

(= f1 x y z (+ x (* y z))) ; Finkel
f1 x y z = x + (y * z) -- Haskell

Keyword where can appear in the right-hand side:

(= f2 n ; Finkel
  (where body
    (= body (+ n 1))))
f2 n = body -- Haskell
  where
    body = n + 1

Pattern bindings are similarly done with =:

(= (Just x) (lookup k vs)) ; Finkel
Just x = lookup k vs -- Haskell

Modules

Top-level module definition does not use where:

(module M1) ; Finkel
(= x 1)
(= y 2)
module M1 where -- Haskell
x = 1
y = 2

See also defmodule in finkel-core.

Export Lists

Module definition can contain an explicit export list. Entities in the export list can contain bindings, type and data constructors, type classes, and modules:

(module M2 ; Finkel
  f1           ; Value, field name, or class method
  T1           ; Type constructor only
  (T2 ..)      ; Type constructor and all of its data constructors
  (T3 T3a T3b) ; Type constructor and specified data constructors
  (T4 t4f1)    ; Type constructor and field label

  (module Data.Char)      ; Module reexport
  (Mb.Maybe Just Nothing) ; Reexport with a qualified name
  )

(import Data.Maybe as Mb)

;; ... more module contents ...
module M2 -- Haskell
  ( f1           -- Value, field name, or class method
  , T1           -- Type constructor only
  , T2(..)       -- Type constructor and all of its data constructors
  , T3(T3a, T3b) -- Type constructor and specified data constructors
  , T4(t4f1)     -- Type constructor and field label

  , module Data.Char        -- Module reexport
  , Mb.Maybe(Just, Nothing) -- Reexport with a qualified name
  ) where

import Data.Maybe as Mb

-- ... more module contents ...

Import Declarations

Module import declarations use import:

(import Data.Maybe) ; Finkel
import Data.Maybe -- Haskell

Qualified import declarations use qualified and optional as:

(import qualified Data.Maybe as Mb) ; Finkel
import qualified Data.Maybe as Mb -- Haskell

Entity lists use list:

(import Data.Maybe (catMaybes fromMaybe)) ; Finkel
import Data.Maybe (catMaybes, fromMaybe) -- Haskell

Hiding specified entities with hiding. Form after hiding is a list of entity names to hide:

(import Data.Maybe hiding (fromJust fromMaybe)) ; Finkel
import Data.Maybe hiding (fromJust, fromMaybe) -- Haskell

Altogether:

(import qualified Data.Maybe as Mb hiding (fromJust)) ; Finkel
import qualified Data.Maybe as Mb hiding (fromJust) -- Haskell

Foreign Function Interfaces

Foreign Import

Foreign import declarations start with foreign import:

(foreign import ccall safe "string.h strlen" ; Finkel
  (:: cstrlen (-> (Ptr CChar) (IO CSize))))
foreign import ccall safe "string.h strlen" -- Haskell
  cstrlen :: Ptr CChar -> IO CSize

Foreign Export

Foreign export declarations start with foreign export:

(foreign export ccall "addInt"
  (:: + (-> Int Int Int)))
foreign export ccall "addInt"
  (+) :: Int -> Int -> Int

Compiler Pragmas

All pragmas use %p(..) form.

Inlining

Pragmas to control inlining of codes use INLINE and NOINLINE:

%p(INLINE foo) ; Finkel
{-# INLINE foo #-} -- Haskell

GHC specific phase controls are also supported:

%p(INLINE [1] bar) ; Finkel
%p(NOINLINE [~2] buzz)
{-# INLINE [1] bar #-} -- Haskell
{-# NOINLINE [~2] buzz #-}

Specialization

Pragmas to control specialization of overloaded function use SPECIALIZE:

%p(SPECIALIZE (:: factorial (-> Int Int))) ; Finkel
{-# SPECIALIZE factorial :: Int -> Int #-} -- Haskell

Language extensions

Pragma for language extensions use LANGUAGE:

%p(LANGUAGE GADTs OverloadedStrings) ; Finkel
{-# LANGUAGE GADTs, OverloadedStrings #-} -- Haskell