Schönfinkel is a pure functional, statically typed (with full type inference), non-strictly evaluated golfing language.
Schönfinkel acts as a golfed "bridge" to the Haskell language.
!!!info!!! Schönfinkel is under active development and is by no means a finished product; as such, expect features to appear and disappear or even full changes in semantics to occur without prior notice. !!!/info!!!
Essentially all Schönfinkel code constructs map directly to Haskell counterparts. Schönfinkel does, however, define alternate syntax for many constructs as well as several builtins. To do this, Schönfinkel defines a custom code page that covers the same range as ASCII (1 byte per character), but with non-printable ASCII characters (including TAB) replaced with custom symbols. See here for the full codepage listed in an easy-to-read format.
Since the Schonfinkel compiler is written in JavaScript, the easiest way to get started is to just hit up the "Try now" here, online. It offers a text editor with buttons for inserting non-ASCII characters, a syntax-highlighted preview, and instant compilation into Haskell.
The Schönfinkel compiler can also be used as a command-line tool, provided that the user has node installed.
!!!button!!! The node version of the compiler can be downloaded here. !!!/button!!!
!!!info!!!
Make sure to set the executable bit on the sch file, that way
$ ./sch
can be directly run from the command line. (The above assumes that the user is in the same directory as the file.) !!!/info!!!
The CLI version of the Schönfinkel compiler offers two methods of decoding the specified file.
$ ./sch -c <inputFile> [outputFile]
Will read in <inputFile> and interpret it using the custom codepage. This
generally isn't useful, but is the official method insofar as it's the only way
for each character in the language to constitute exactly one byte. Once the
compilation is done, it will be output either to [outputFile], or, if that's
not specified, a variation of the input file's name (with a .hs extension)
will be used instead.
$ ./sch -u <inputFile> [outputFile]
...is the more usual use case. The -u flag stands for
Unicode, and reads in the file assuming
UTF-8 encoding. Otherwise this is the
same.
The compiler just emits Haskell, so there's more steps to be taken after the
transpilation. Many will already have access to a Haskell compiler with which
to compile the resulting .hs file for execution (or, which also works, an
interpreter). For those who don't, I recommend the use of
Stack, or just any plain old
installation of the GHC. Some online REPLs exist that could maybe work, like
TryHaskell.
The Schonfinkel compiler really only acts as a syntax-level transpiler to Haskell, so you can expect blatant type errors and other errors like referencing non-existent variables to "compile" to Haskell just fine, only to fail miserably upon hiting the GHC (or Hugs or whatever). Thus:
!!!info!!! Compiling the emitted Haskell code is the real test of program validity! !!!/info!!!
One quirk of Schönfinkel is that all identifiers used by the programmer (i.e.,
that are not pre-defined) must consist solely of lowercase letters (i.e., must
match the regex [a-z]+). The only exception to this rule is programmer-defined
infix functions. Characters in the range [A-Z] are reserved for builtins.
Underscores (_) have only one meaning in Schönfinkel, namely, empty
patterns/throwaway variables. Characters in the range [0-9] are reserved for
numeric literals exclusively.
Additionally, the first 5 lowercase letters as a single identifier (a, b,
c, d, e) are identifiers reserved for implicit input/command-line
arguments. b, c, d, and e are the 1st, 2nd, 3rd, and 4th inputs to the
program, in order, as Strings.
!!!info!!! NOTE: These bindings are only visible inside of "naked" top-level expressions (see the "Whole-program semantics" section), so everywhere else, these identifiers are not reserved. !!!/info!!!
If less than 4 arguments are supplied, the remaining variables are just the
empty string (""). If more than 4 arguments are supplied, b, c, d, and
e are assigned normally, and a is always a list of all arguments supplied
(of type [String]), so all arguments are always accessible.
Infix functions can still be defined normally like in Haskell. The characters
available to be used are slightly different: for one-character infix functions
defined by the programmer, the options are !, ?, #, &, and ~. Infix
functions with more characters (generally 2 at most) can combine those
characters as well as the following other characters: $, <, >, ^, :
(so long as it doesn't start with :), +, -, @, %, ., \, =, and
*.
Because of the restrictions on identifier names and their semantics, Schönfinkel allows omitting whitespace more often than in Haskell:
a=[1..9]
La -- yields `9`L is a pre-defined function (equivalent to Haskell's genericLength), so it
consists only of uppercase letters. This allows it to be differentiated from
a, which is another distinct token. In Haskell this would have to be L a
(note the space in between). Just like in Haskell, function invocations can be
made in infix form even for alphabetically-named functions. In Haskell, this is
achieved by simply surrounding the function identifier with backticks (`).
However, in Schönfinkel there is no backtick on the right side of the
identifier. Instead, the "missing" backtick is "automatically inserted" just
before the next character that either
- isn't alphabetic, or
- is of a different case (lower → upper or vice versa).
For example:
", "`U["one","two","three","four"]U is essentially Haskell's intercalate. Here, it is used as an infix
function where the initial backtick captures the U and then continues on until
it finds a non-alphabetic character or a letter that is of a different case
(lowercase). It immediately runs into the [ character, so the backtick is
inserted just before that, yielding an interpretation of
", "`U`["one","two","three","four"]!!!warn!!! N.B.: The above snippet isn't actually valid Schönfinkel since it would be trying to make the list literal into an infix function. !!!/warn!!!
This is the same thing:
y=["one","two","three","four"]
", "`UyBackticks can also be used on functions that are infix to begin with (i.e. they
take in exactly two arguments and don't have any letters in the name). This
has essentially the same syntax rules as above, but instead of turning into an
infix function, it makes the function behave as if the Haskell function flip
were applied to it. That is, the order of its arguments are reversed:
(+1)↵[1..5] -- [2, 3, 4, 5, 6]
[1..5]\`↵(+1) -- [2, 3, 4, 5, 6]let/where bindings work similarly to Haskell, but have more concise syntax.
Variables are still bound using =, but instead of let ... in ... or
... where ..., Schönfinkel uses curly brackets ({}) and separates bindings
using commas (,). As an example, the following Schönfinkel code:
{x=3,y=1.5}x/y...is identical to the following Haskell code:
let x = 3
y = 1.5
in x / yLeftward-facing bindings (<-) in do blocks, guards, and list comprehensions
work identically as in Haskell, but use a single character (←) instead.
Schönfinkel uses shortened conditional notation for if/else if/else
constructs similar to
the GHC extension "MultiWayIf",
but without the if. To avoid ambiguity, Schönfinkel uses a special character
(¦) for the vertical pipe character found in all list comprehensions (and
additionally in case expressions, as will be seen later). For example,
v=[(-1, 8), (-1, 3), (23, 1), (1, 1)]
[|i>j→-2|i<j→1|→0¦(i,j)←v]yields the list [1, 1, -2, 0]. The equivalent Haskell is:
v=[(-1, 8), (-1, 3), (23, 1), (1, 1)]
[if i > j then -2 else if i < j then 1 else 0 | (i, j) <- v]As you can see, omitting the condition (|→) always matches; it's the same as
matching on True in Haskell (|True->), or just the else keyword.
It's common to get away with not using the && function when logical AND is
needed. Instead, guards and multi-way "if"s like the one above can have multiple
conditions chained together using commas (,). For example, |i>j,i>0→ is the
same as |i>j&&i>0→.
Ranges work essentially the same as in Haskell, with one small change. Descending ranges that don't use comma(s) work as expected in Schönfinkel. That is,
[9..1]is the same as the following Haskell:
[9,8..1]Schönfinkel uses a shortened form of case expressions that otherwise work the
same way as their Haskell counterparts. The following Haskell:
f x =
case x of
0 -> 18
1 -> 15
2 -> 12
_ -> 12 + xcan be translated directly into Schönfinkel as (note the angle brackets,
⟨ ⟩, distinct from less than/greater-than symbols, < >):
f x=⟨x¦0→18¦1→15¦2→12¦→12+x⟩Additionally, multiple possible matches can map to the same expression easily
and without redundancy using commas (,). The following Haskell:
f x =
case x of
0 -> 18
1 -> 16
2 -> 16
_ -> 12 + xcan be translated directly into Schönfinkel as:
f x=⟨x¦0→18¦1,2→16¦→12+x⟩do notation works in Schönfinkel much the same way as in Haskell, but instead
of the word do, the ⟥ character is used instead. This saves the programmer
from having to write the o and the whitespace(s) after it. Additionally, as
mentioned before, monadic bindings use ← instead of <-.
Semicolons (;) are used to separate statements within a do block just like
in Haskell, except that Schönfinkel offers no "sections," i.e. using linefeeds
and indentation to provide separate statements. So you're stuck with semicolons.
The only whitespace that is really significant in Schönfinkel is line feeds
('\n'; LF; codepoint 0x0A). Spaces (' '; codepoint 0x20), the only other
kind of whitespace, are only significant when they are needed to distinguish one
token from another, e.g.
LabApplies the L function to ab, whereas
La bapplies the L function to a and is then followed by b. And of course,
spaces are significant inside of character and string literals.
Line feeds, on the other hand, separate semantic contexts. Once a line feed is inserted, any context (like bindings and their values) is no longer visible except for so-called "top-level bindings", which are bindings made flush to the left (i.e. at the very beginning of a line). Just like in Haskell, this is the only way to define a function visible "globally":
f={i=1}(Δi).L
g=f[0..7]f is visible within the semantic context of g because f is defined as a
top-level binding, but i is not visible; it was bound inside of f's context.
Of course, we might want to have nested contexts. For this, parentheses (( ))
can be used. Bindings made within a pair of parentheses are not visible anywhere
outside of them:
f x=({l=W(<3)x}⊠l)l -- Very bad!The above won't work, because the second time that l is mentioned is outside
of the parentheses that it was bound in. Since the parentheses are dictating the
semantic context in this case, there's no such thing as l outside of them.
Similar to many calculators, Schönfinkel will happily assume that you meant to add any of the following closing brackets:
)]⟩
at the end of a line (i.e. just before a linefeed \n), provided that they
are "expected" (i.e. their left-hand counterparts are still on the stack). As a
very simple example, the following works just fine to define a function that
doubles its argument:
f=(*2It still works even when there's nesting, too. Just treat it like a stack:
f x=⟨x¦0→(+)¦→(*...is the same as:
f x=⟨x¦0→(+)¦→(*)⟩Comments are the same style as Haskell; more precisely, a block comment matches:
/{-[\s\S]*-}/A line comment, then, matches:
/--[^\n]*/Tuple syntax is almost entirely the same as in Haskell, with a small exception. Schönfinkel uses Haskell's "TupleSections" language mode by default. In Haskell:
{-# LANGUAGE TupleSections #-}
t = ("!-", , "-!") <$> [0..2]Here, t is [("!-", 0, "-!"), ("!-", 1, "-!"), ("!-", 2, "-!")]. As you can
see, this essentially means that tuple constructors (normally like (,) or
(,,)) can be partially applied. And, notably, the partial application can
occur anywhere in any n-tuple constructor.
Unlike Haskell, Schönfinkel can have "naked" expressions at top-level. "Naked" here refers to expressions that aren't bound to anything. In Haskell this makes no sense, since the expression is then unusable/useless. In Schönfinkel, however, any top-level naked expressions that are encountered in the source code (reading from top to bottom) are considered the program's main body. If there are multiple such naked expressions (i.e. separated by line feeds), then the expressions are considered in order of occurence.
Naked expressions that don't already have a type of IO a are automatically
wrapped up into expressions of type IO (), by simply printing their values to
stdout, after being shown and having a line feed appended to the resulting
String. Now that all naked expressions have a type of IO a, they are called
as if from the main function, in order of occurence, chained using the >>
function (i.e. any "return values", trivial or nontrivial, are discarded).
!!!codepage!!!
Equivalent of Control.Applicative.<*> in Haskell.
Infix?: yes
Equivalent of Data.Eq.== in Haskell.
Infix?: yes
Equivalent of Data.Eq./= in Haskell.
Infix?: yes
Equivalent of Data.Bool.not in Haskell.
Infix?: no
Equivalent of Data.List.findIndices in Haskell.
Infix?: yes; infixl 8
Splits a list at every occurence of another given list of the same type.
Infix?: yes; infixl 5
Haskell implementation of this function:
import Data.List
infixl 5 ⩖
(⩖) :: Eq a => [a] -> [a] -> [[a]\]
(⩖) l n =
fst $ until (\(_, ll) -> null ll) (\(accu, rest) ->
if genericTake needleLen rest == n then
(accu ++ [[]], genericDrop needleLen rest)
else
(init accu ++ [last accu ++ [head rest]], tail rest)) ([[]], l)
where needleLen = genericLength n
Equivalent of Control.Monad.mapM in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.Foldable.elem in Haskell.
Infix?: yes
Equivalent of Control.Arrow.*** in Haskell.
Infix?: yes
Equivalent of Control.Arrow.&&& in Haskell.
Infix?: yes
Equivalent of Control.Monad.>> in Haskell.
Infix?: yes
Equivalent of Data.List.intersect in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.List.union in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.Foldable.sum in Haskell.
Infix?: no
Equivalent of Control.Applicative.<$> in Haskell.
Infix?: yes
Equivalent of Data.List.partition in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.Foldable.all in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.Foldable.any in Haskell.
Infix?: yes; infixl 5
Equivalent of Data.List.genericIndex in Haskell.
Infix?: yes; infixl 8
Equivalent of Prelude.subtract in Haskell.
Infix?: yes; infixl 6
N.B.: The ASCII hyphen/minus sign (-) cannot be used for subtraction,
since it only serves to negate numbers (e.g. -2.5). Instead, this function
should be used.
Equivalent of Prelude.floor in Haskell.
Infix?: no
Takes the cartesian product of two lists.
Infix?: yes; infixl 5
Haskell implementation of this function:
infixl 5 ×
(×) :: [a] -> [b] -> [(a, b)]
(×) xs ys = [(x, y) | x <- xs, y <- ys]Equivalent of Data.List.zip in Haskell.
Infix?: yes; infixl 5
Equivalent of Prelude.div in Haskell.
Infix?: yes
Unchanged from Haskell.
Equivalent of Prelude.mod in Haskell.
Infix?: yes
Unchanged from Haskell.
Unchanged from Haskell.
Equivalent of Prelude.negate in Haskell.
Infix?: no
N.B.: The ASCII hyphen/minus sign (-) cannot be used for subtraction,
since it only serves to negate numbers (e.g. -2.5). Instead, the Δ function
should be used.
Unchanged from Haskell.
Unchanged from Haskell.
Unchanged from Haskell.
Unchanged from Haskell.
Unchanged from Haskell.
Unchanged from Haskell.
Appends the right argument to the end of the left argument.
Infix?: yes; infixr 5
Haskell implementation of this function:
infixr 5 ⋄
(⋄) :: [a] -> a -> [a]
(⋄) l a = l ++ [a]Equivalent of Data.List.filter in Haskell.
Equivalent of Data.List.sortBy in Haskell.
Mnemonic: sortBy
Equivalent of Data.Foldable.concat in Haskell.
Mnemonic: Concat
Equivalent of Data.List.nub in Haskell.
Mnemonic: Distinct
Equivalent of Data.Foldable.maximum in Haskell.
Mnemonic: Extremum
Equivalent of Data.List.zipWith in Haskell.
Equivalent of Data.Foldable.minimum in Haskell.
Equivalent of Prelude.toEnum in Haskell.
Equivalent of Data.Foldable.null in Haskell.
Mnemonic: unInhabited
Equivalent of Data.List.tail in Haskell.
Equivalent of Data.List.genericTake in Haskell.
Mnemonic: taKe
Equivalent of Data.List.genericLength in Haskell.
Mnemonic: Length
Equivalent of Prelude.show in Haskell.
Equivalent of Prelude.read in Haskell.
Equivalent of Prelude.fromEnum in Haskell.
Mnemonic: Ordinal
Equivalent of System.IO.print in Haskell.
Mnemonic: Print
Replaces the given index of a list with a certain value. Does not change the
length of the list. Accepts negative indices, viz. an index of -1 signifies
the last index of the list, -2 signifies the second-to-last index, etc.
Haskell implementation of this function:
import Data.List
Q :: Integral i => i -> a -> [a] -> [a]
Q i a (b:bs)
| i < 0 = Q (genericLength bs + i + 1) a (b:bs)
| i == 0 = a:bs
| otherwise = b : Q (i - 1) a bsEquivalent of Data.List.reverse in Haskell.
Mnemonic: Reverse
Equivalent of Data.List.sort in Haskell.
Mnemonic: Sort
Equivalent of Data.List.transpose in Haskell.
Mnemonic: Transpose
Equivalent of Data.List.intercalate in Haskell.
Mnemonic: Unwords/Unlines
Equivalent of Data.List.scanl in Haskell.
Equivalent of Data.List.takeWhile in Haskell.
Mnemonic: take While
Equivalent of Data.Foldable.foldl' in Haskell.
Equivalent of Data.Foldable.foldr in Haskell.
Equivalent of Data.List.permutations in Haskell.
Equivalent of Control.Monad.>>= in Haskell.
Infix?: yes
Equivalent of Control.Arrow.>>> in Haskell.
Infix?: yes
Equivalent of Control.Arrow.>>^ in Haskell.
Infix?: yes
Equivalent of Control.Arrow.<<< in Haskell.
Infix?: yes
Equivalent of Control.Arrow.<<^ in Haskell.
Infix?: yes
Equivalent of Prelude.ceiling in Haskell.
Infix?: no
Equivalent of Prelude.round in Haskell.
Infix?: no
Equivalent of Prelude.truncate in Haskell.
Infix?: no
Unchanged from Haskell.
Equivalent of Data.Functor.$> in Haskell.
Equivalent of Control.Applicative.*> in Haskell.
Infix?: yes
Unchanged from Haskell.
Unchanged from Haskell.
Unchanged from Haskell.
Equivalent of Control.Applicative.<$ in Haskell.
Infix?: yes
Equivalent of Control.Applicative.<* in Haskell.
Infix?: yes
Equivalent of Control.Monad.=<< in Haskell.
Infix?: yes
Equivalent of Control.Monad.<=< in Haskell.
Infix?: yes
Equivalent of Control.Monad.>=> in Haskell.
Infix?: yes
Unchanged from Haskell.
Unchanged from Haskell.
Equivalent of Control.Arrow.^>> in Haskell.
Infix?: yes
Equivalent of Control.Arrow.^<< in Haskell.
Infix?: yes
Unchanged from Haskell.
Equivalent of Prelude.abs in Haskell.
Mnemonic: ABsolute value
Equivalent of Control.Arrow.arr in Haskell.
Mnemonic: ARrow
Equivalent of Data.List.break in Haskell.
Mnemonic: BReak
Takes in a list and returns the Cartesian product of that list with itself.
Note that unlike the × function, this function returns the ordered pairs as
lists of length 2, not 2-tuples, since the types of both sides of the pair are
guaranteed to be the same.
Mnemonic: reflexive CArtesian product
Implementation in Haskell:
CA :: [a] -> [[a]]
CA l = [[x, y] | x <- l, y <- l]Equivalent of Data.Ord.comparing in Haskell.
Mnemonic: ComparinG
Equivalent of Data.Ord.compare in Haskell.
Mnemonic: CoMpare
Equivalent of Prelude.cos in Haskell.
Mnemonic: COsine
Equivalent of Data.Tuple.curry in Haskell.
Mnemonic: CuRry
Equivalent of Prelude.const in Haskell.
Mnemonic: ConsTant
Takes in an integer and returns a list of the integers from 0 to that integer, both inclusive. Works for both positive and negative integers.
Mnemonic: CoUnt
Implementation in Haskell:
CU :: Integral i => i -> [i]
CU n | n >= 0 = [0..n]
| otherwise = [0,-1..n]Takes in an integer and returns a list of the integers from 1 to that integer if the integer is positive, and a list of the integers from -1 to that integer if it's negative. Both bounds are inclusive. Returns the empty list when the input is 0.
Mnemonic: CoU+1=Vnt
Implementation in Haskell:
CV :: Integral i => i -> [i]
CV n | n >= 1 = [1..n]
| otherwise = [-1,-2..n]Equivalent of Data.List.cycle in Haskell.
Mnemonic: CYcle
Equivalent of Data.Char.digitToInt in Haskell.
Mnemonic: Digit to Integer
Equivalent of Data.List.genericDrop in Haskell.
Mnemonic: generic DRop
Equivalent of Data.List.dropWhile in Haskell.
Mnemonic: Drop While
Equivalent of Data.List.elemIndex in Haskell.
Mnemonic: Elem Index
Equivalent of Data.List.elemIndices in Haskell.
Mnemonic: Elem I+1=Jndices
Counts occurrences of the first argument in the second argument. Second argument
must be Foldable.
Mnemonic: Enumerate Occurrences
Implementation in Haskell:
import Data.Foldable
EO :: (Eq a, Foldable f, Integral i) => a -> f a -> i
EO needle haystack =
foldl' (\count elem ->
count + if elem == needle then 1 else 0) 0 haystackEquivalent of Prelude.error in Haskell.
Mnemonic: ERror
Equivalent of Prelude.even in Haskell.
Mnemonic: EVen
Equivalent of Prelude.exp in Haskell.
Mnemonic: EXponential
Equivalent of Prelude.False in Haskell.
Mnemonic: FAlse
Similar to Data.Foldable.find in Haskell, but returns undefined on failure
(very dangerous!) instead of using Maybe to represent success/failure.
Mnemonic: FinD-1=C
Haskell implementation of this function:
import Data.List
FC :: (a -> Bool) -> [a] -> a
FC p l =
case find p l of
Just a -> a
_ -> undefinedEquivalent of Data.Foldable.find in Haskell.
Mnemonic: FinD
Similar to Data.List.findIndex in Haskell, but returns -1 on failure instead
of using Maybe to represent success/failure.
Mnemonic: Find I-1=Hndex
Haskell implementation of this function:
import Data.List
FH :: (a -> Bool) -> [a] -> Int
FH p l =
case findIndex p l of
Just i -> i
_ -> -1Equivalent of Data.List.findIndex in Haskell.
Mnemonic: Find Index
Equivalent of Data.Maybe.fromJust in Haskell.
Mnemonic: From Just
Equivalent of Data.List.foldl1' in Haskell.
Mnemonic: Fold Left 1'
Equivalent of Data.Maybe.fromMaybe in Haskell.
Mnemonic: From Maybe
Equivalent of Prelude.flip in Haskell.
Mnemonic: FliP
Equivalent of Data.Foldable.foldr1 in Haskell.
Mnemonic: Fold Right 1
Equivalent of Control.Arrow.first in Haskell.
Mnemonic: FirSt
Equivalent of Data.Tuple.fst in Haskell.
Mnemonic: FirsT
Equivalent of System.IO.getChar in Haskell.
Mnemonic: Get Character
Equivalent of Prelude.gcd in Haskell.
Mnemonic: Greatest common Divisor
Equivalent of System.IO.getLine in Haskell.
Mnemonic: Get Line
Equivalent of Data.Char.isAlpha in Haskell.
Mnemonic: Is Alphabetical
Equivalent of Data.Char.intToDigit in Haskell.
Mnemonic: Integer to D-1=Cigit
Equivalent of Prelude.id in Haskell.
Mnemonic: IDentity
Equivalent of Data.List.iterate in Haskell.
Mnemonic: ItErate
Equivalent of Data.Maybe.isJust in Haskell.
Mnemonic: Is Just
Equivalent of Data.Char.isLower in Haskell.
Mnemonic: Is Lower
Equivalent of Data.Char.isNumber in Haskell.
Mnemonic: Is N-1=Mumber
Equivalent of Data.Maybe.isNothing in Haskell.
Mnemonic: Is Nothing
Equivalent of Data.Char.isPunctuation in Haskell.
Mnemonic: Is Puncuation
Equivalent of System.IO.interact in Haskell.
Mnemonic: InteRact
Equivalent of Data.Char.isSpace in Haskell.
Mnemonic: Is Space
Equivalent of Data.Char.isUpper in Haskell.
Mnemonic: Is Upper
Equivalent of Data.List.last in Haskell.
Mnemonic: LAst
Equivalent of Prelude.lcm in Haskell.
Mnemonic: Least Common multiple
Equivalent of Prelude.log in Haskell.
Mnemonic: LoGarithm
Equivalent of Data.String.lines in Haskell.
Mnemonic: LInes
Equivalent of Control.Monad.liftM in Haskell.
Mnemonic: Lift Monad
Equivalent of Control.Monad.liftM2 in Haskell.
Mnemonic: Lift M+1=Nonad
Equivalent of Control.Monad.liftM3 in Haskell.
Mnemonic: Lift M+2=Oonad
Equivalent of Data.List.lookup in Haskell.
Mnemonic: LookUp
Unsafe version of Data.List.lookup. Returns undefined if no value is found.
Mnemonic: LookU+1=Vp
Haskell implementation of this function:
import Data.List
LV :: Eq a => a -> [(a, b)] -> b
LV k m =
case lookup k m of
Just b -> b
_ -> undefinedWorks like Data.List.map, but instead takes a function that has the element
as the first argument and the element's index in the list as its second
argument.
Mnemonic: Map with Indices
Haskell implementation of this function:
MI :: Integral i => (a -> i -> b) -> [a] -> [b]
MI f xs = zipWith f xs [0..]Equivalent of Data.Foldable.notElem in Haskell.
Mnemonic: Not Element of
Equivalent of Prelude.odd in Haskell.
Mnemonic: ODd
Equivalent of Prelude.pred in Haskell.
Mnemonic: PreDecessor
Equivalent of Prelude.pi in Haskell.
Mnemonic: pi
Takes in an integer and returns a boolean indicating whether or not the integer is a positive prime number.
Mnemonic: is a Prime Number
Haskell implementation of this function:
PN :: Integral i => i -> Bool
PN n = n > 1 && all ((/= 0).(n `mod`)) [2..n `div` 2]A list of positive integers representing all prime numbers, in order.
Mnemonic: PRimes
Haskell implementation of this function:
PR :: Integral i => [i]
PR = 2:3:prs
where
1:p:candidates = [6 * k + r | k <- [0..], r <- [1, 5]]
prs = p : filter isPrime candidates
isPrime n = all (not . divides n)
$ takeWhile (\p' -> p' * p' <= n) prs
divides n p'' = n `mod` p'' == 0Equivalent of System.IO.putStrLn in Haskell.
Mnemonic: Put String line
Equivalent of System.IO.putStr in Haskell.
Mnemonic: Put sTring line
Equivalent of Prelude.quot in Haskell.
Mnemonic: QuoTient
Equivalent of Data.List.genericReplicate in Haskell.
Mnemonic: RepliCate
Equivalent of System.IO.readFile in Haskell.
Mnemonic: Read File
Equivalent of Prelude.rem in Haskell.
Mnemonic: ReMainder
Equivalent of Data.List.repeat in Haskell.
Mnemonic: RePeat
Equivalent of Control.Monad.return in Haskell.
Mnemonic: ReTurn
Equivalent of Control.Arrow.second in Haskell.
Mnemonic: SeCond
Equivalent of Data.Tuple.snd in Haskell.
Mnemonic: SeconD
Equivalent of Prelude.sin in Haskell.
Mnemonic: SIne
Equivalent of Data.List.scanl1 in Haskell.
Mnemonic: Scan Left 1
Equivalent of Data.List.span in Haskell.
Mnemonic: SpaN
Equivalent of Data.List.genericSplitAt in Haskell.
Mnemonic: generic SPlit at
Equivalent of Control.Monad.sequence in Haskell.
Mnemonic: SeQuence
Equivalent of Data.List.scanr in Haskell.
Mnemonic: Scan Right
Equivalent of Data.List.scanr1 in Haskell.
Mnemonic: Scan R+1=Sight 1
Equivalent of Prelude.sqrt in Haskell.
Mnemonic: Square rooT
Equivalent of Prelude.succ in Haskell.
Mnemonic: SUccessor
Equivalent of Prelude.tan in Haskell.
Mnemonic: TAngent
Equivalent of Data.Char.toLower in Haskell.
Mnemonic: To Lower
Equivalent of Prelude.True in Haskell.
Mnemonic: TRue
Equivalent of Data.Char.toUpper in Haskell.
Mnemonic: To Upper
Equivalent of Data.Tuple.uncurry in Haskell.
Mnemonic: UnCurry
Equivalent of Prelude.undefined in Haskell.
Mnemonic: UnDefined
Equivalent of Data.String.unlines in Haskell.
Mnemonic: UnLines
Equivalent of Prelude.until in Haskell.
Mnemonic: UnTil
Equivalent of Data.String.unwords in Haskell.
Mnemonic: UnWords
Equivalent of Data.List.unzip in Haskell.
Mnemonic: UnZip
Equivalent of System.IO.writeFile in Haskell.
Mnemonic: Write File
Equivalent of Data.String.words in Haskell.
Mnemonic: WOrds
Equivalent of Data.List.zip3 in Haskell.
Mnemonic: Zip Three
Equivalent of Data.List.unzip3 in Haskell.
Mnemonic: unZip T+1=Uhree
Equivalent of Data.List.zipWith3 in Haskell.
Mnemonic: Zip With 3