Real Fast Nora's Hair Salon 3: Shear Disaster Download

From Esolang
Jump to navigation Jump to search

Real Fast Nora's Hair Salon 3: Shear Disaster Download is a functional esoteric programming language created by Nathan van Doorn in 2012. It is based on the lambda calculus.

Structure of a program

The program is a function that maps input (as a Church list of Church numerals) to output (ditto), similar to Lazy K.

All text in a program's source that is not upper-case text of the English alphabet is ignored, as this can be hard to read. The program is in reality a bunch of expressions all knotted together. There are only a handful of key words:

Keyword Purpose
LAMBDA Introduces a lambda expression.
APPLY Combines two expressions through application.
ZERO The smallest number.
ONE MORE THAN When followed by a number, forms a number equivalent to one more than the number following it with that number.

Lambda expressions

A lambda expression is started with the LAMBDA key word. It then takes the next complete expression and wraps it in a lambda.

Numbers are what makes the lambda expression useful: A number n denotes the argument of the nth surrounding lambda expression, starting at the innermost as the 0'th.

When a lambda expression is applied to something, all the (one-more-than-)nzeros in nth level nested lambda expressions are replaced by what it has been applied to, for n≥0. While replacing, some numbers need to be adjusted in order to keep referring to the same argument. (These are de Bruijn indices, except zero indexed.)

An APPLY reads the next two complete expressions, and applies the first to the second.

Possible pitfalls

An error may occur:

  • if the program begins with two consecutive lambda expressions, or equivalent, as this would require there to be more than one IO input, which is not required by an implementation;
  • if a ONE MORE THAN is not followed by a ZERO or another ONE MORE THAN;
  • if there are insufficient lambdas for a number expression to be fulfilled;
  • if the program ends with an uncompleted expression.

Infinite loops may occur.

Examples

Cat program

LAMBDA ZERO

Church addition excerpt

LAMBDA LAMBDA LAMBDA LAMBDA APPLY APPLY ONE MORE THAN ONE MORE THAN ONE MORE THAN ZERO
ONE MORE THAN ZERO APPLY APPLY ONE MORE THAN ONE MORE THAN ZERO ONE MORE THAN ZERO ZERO

Church decrementation excerpt

LAMBDA LAMBDA LAMBDA APPLY APPLY APPLY ONE MORE THAN ONE MORE THAN ZERO LAMBDA LAMBDA
APPLY ZERO APPLY ONE MORE THAN ZERO ONE MORE THAN ONE MORE THAN ONE MORE THAN ZERO LAMBDA
ONE MORE THAN ZERO LAMBDA ZERO

Prime sieve

User:Tromp points out that apart from I/O, Real Fast Nora's Hair Salon 3: Shear Disaster Download is isomorphic to Binary lambda calculus by the substitutions

LAMBDA=00, APPLY=01, ZERO=10, ONEMORETHAN=1

The following is his conversion of his BLC prime sieve, which also adjusts the output convention.

LAMBDA APPLY LAMBDA APPLY LAMBDA APPLY LAMBDA APPLY LAMBDA APPLY ZERO
APPLY ZERO APPLY APPLY LAMBDA APPLY ZERO ZERO LAMBDA LAMBDA LAMBDA
APPLY APPLY ZERO LAMBDA LAMBDA APPLY ONE MORE THAN ZERO APPLY APPLY
ONE MORE THAN ONE MORE THAN ONE MORE THAN ONE MORE THAN ONE MORE THAN
ONE MORE THAN ZERO ONE MORE THAN ZERO ZERO APPLY LAMBDA APPLY APPLY
APPLY ONE MORE THAN ONE MORE THAN ONE MORE THAN ZERO ONE MORE THAN ONE
MORE THAN ONE MORE THAN ZERO ZERO APPLY LAMBDA APPLY ZERO ZERO LAMBDA
APPLY ONE MORE THAN ZERO APPLY ZERO ZERO LAMBDA LAMBDA LAMBDA LAMBDA
APPLY APPLY ZERO ONE MORE THAN ONE MORE THAN ZERO APPLY ONE MORE THAN
ZERO APPLY ONE MORE THAN ONE MORE THAN ONE MORE THAN ONE MORE THAN ONE
MORE THAN ZERO ONE MORE THAN ONE MORE THAN ONE MORE THAN ZERO LAMBDA
LAMBDA LAMBDA APPLY ONE MORE THAN ONE MORE THAN ONE MORE THAN ZERO
APPLY ZERO ONE MORE THAN ONE MORE THAN ZERO LAMBDA LAMBDA APPLY APPLY
ZERO ONE MORE THAN ONE MORE THAN ZERO ONE MORE THAN ZERO LAMBDA APPLY
ONE MORE THAN ONE MORE THAN ZERO APPLY ONE MORE THAN ZERO APPLY APPLY
ONE MORE THAN ZERO ONE MORE THAN ONE MORE THAN ZERO ZERO LAMBDA LAMBDA
APPLY ONE MORE THAN ZERO APPLY ONE MORE THAN ZERO APPLY ONE MORE THAN
ZERO ZERO LAMBDA LAMBDA APPLY ONE MORE THAN ZERO APPLY ONE MORE THAN
ZERO ZERO

Implementation

The following implementation in Haskell attempts to follow Lazy K's I/O format (except for the exit code), and probably leaks memory like a sieve due to the explicit lists of outer arguments passed.

import Control.Applicative hiding ((<|>), many)
import Data.List (unfoldr)
import System.Environment (getArgs)
import System.IO (stdin, stdout, hSetEncoding, latin1,
    hSetBuffering, BufferMode (NoBuffering))
import Text.Parsec

data WHNF a = WHNF { ann :: Maybe a, fun :: (WHNF a -> WHNF a) }
type EXPR a = [WHNF a] -> WHNF a

isJunk :: Char -> Bool
isJunk c = c < 'A' || c > 'Z'

junk :: Parsec String () ()
junk = skipMany $ satisfy isJunk

keyword :: String -> Parsec String () ()
keyword k = sequence_ [ char c *> junk | c <- k, not (isJunk c) ] <?> k

expr :: Int -> Parsec String () (EXPR a)
expr d = buildLambda <$ keyword "LAMBDA" <*> expr (d+1)
  <|>  buildApply <$ keyword "APPLY" <*> expr d <*> expr d
  <|>  buildVar <$> do
        n <- try $ length <$> many (keyword "ONE MORE THAN") <* keyword "ZERO"
        if n < d then return n
                 else unexpected "number bigger than lambda nesting level"

buildLambda e env = WHNF Nothing $ \arg -> e (arg:env)
buildApply e1 e2 env = fun (e1 env) (e2 env)
buildVar n env = env !! n

churchToList :: WHNF a -> [WHNF a]
churchToList = unfoldr (Just . churchToPair)

listToChurch :: [WHNF a] -> WHNF a
listToChurch = foldr pairToChurch $ error "Only infinite lists may be converted"

churchToPair :: WHNF a -> (WHNF a, WHNF a)
churchToPair (WHNF _ f)
    = (f (WHNF Nothing $ \xw -> WHNF Nothing $ const xw),
       f (WHNF Nothing $ \xw -> WHNF Nothing id))

pairToChurch :: WHNF a -> WHNF a -> WHNF a
pairToChurch fw gw = WHNF Nothing $ \hw -> fun (fun hw fw) gw

intToChurch :: Int -> WHNF a
intToChurch n
    = WHNF Nothing $ \fw -> WHNF Nothing $ \xw -> iterate (fun fw) xw !! n

churchToInt :: WHNF Int -> Int
churchToInt iw = case fun (fun iw $ WHNF Nothing incr) (WHNF (Just 0) v) of
    WHNF (Just n) _ -> n
    _               -> error $ "Output list contains non-number"
  where
    incr (WHNF mn f) = WHNF (succ <$> mn) v
    v x = WHNF Nothing v

-- NB: Only characters < 256 should be in String
stringToChurch :: String -> WHNF a
stringToChurch s
    = listToChurch $ map (intToChurch . fromEnum) s ++ repeat (intToChurch 256)

churchToString :: WHNF Int -> String
churchToString = map toEnum . takeWhile (< 256) . map churchToInt . churchToList

main = do
    args <- getArgs
    (name, prog) <- case args of
        [filename]      -> (,) filename <$> readFile filename
        ["-e", expr]    -> return ("-e option", expr)
        _               -> error "Needs filename or -e <expr> option"
    case parse (junk *> expr 0 <* eof) name prog of
        Left err    -> error $ "Parse error " ++ show err
        Right e     -> do
            hSetEncoding stdin latin1
            hSetEncoding stdout latin1
            hSetBuffering stdout NoBuffering
            interact $ churchToString . fun (e []) . stringToChurch

See also