previndexinfonext

code guessing, round #20 (completed)

started at ; stage 2 at ; ended at

specification

now that we're all full (or mildly satiated) from the buffet, let's play tic-tac-toe. submissions can be written in d, brainfuck, haskell, or lua.

tic-tac-toe is a simple game that I hope you already know the rules to where two players, X and O, take turns making marks on a 3x3 board until one player places 3 of their symbol in a row and wins the game.

your challenge is simply to take a tic-tac-toe board, make any valid move and return a new board. the input will always be a valid, in-progress board, but the roles of X and O may be mirrored; there will either be an equal number of x and o or one less x. your program plays as X.

the IO is text-based. input consists of 9 cells, either ., x, or o, with the rows separated with newlines (2 newlines in total) like so:

..x
.o.
.xo

output is the same 9 cells in order, with one of the . changed to an x. characters that are not ., x, or o are ignored. for example:

     different
       -----
     | x . x |
fine | . o . | characters
     | . x o |
       -----
        are

here are your APIs:

results

  1. 👑 LyricLy +7 -4 = 3
    1. IFcoltransG (was Palaiologos)
    2. deadbraincoral (was IFcoltransG)
    3. Palaiologos (was deadbraincoral)
    4. Rou_bi
    5. olus2000
    6. Hildegunst Taillemythes
    7. gollark
    8. Olivia
    9. razetime
    10. SoundOfSpouting
  2. razetime +4 -1 = 3
    1. Palaiologos
    2. gollark (was IFcoltransG)
    3. Olivia (was deadbraincoral)
    4. IFcoltransG (was LyricLy)
    5. Rou_bi
    6. olus2000
    7. deadbraincoral (was Hildegunst Taillemythes)
    8. LyricLy (was gollark)
    9. Hildegunst Taillemythes (was Olivia)
    10. SoundOfSpouting
  3. Hildegunst Taillemythes +4 -1 = 3
    1. IFcoltransG (was Palaiologos)
    2. gollark (was IFcoltransG)
    3. deadbraincoral
    4. LyricLy
    5. olus2000 (was Rou_bi)
    6. Palaiologos (was olus2000)
    7. razetime (was gollark)
    8. Olivia
    9. Rou_bi (was razetime)
    10. SoundOfSpouting
  4. gollark +4 -2 = 2
    1. razetime (was Palaiologos)
    2. Hildegunst Taillemythes (was IFcoltransG)
    3. Palaiologos (was deadbraincoral)
    4. LyricLy
    5. Rou_bi
    6. IFcoltransG (was olus2000)
    7. deadbraincoral (was Hildegunst Taillemythes)
    8. Olivia
    9. olus2000 (was razetime)
    10. SoundOfSpouting
  5. deadbraincoral +3 -1 = 2
    1. Olivia (was Palaiologos)
    2. Hildegunst Taillemythes (was IFcoltransG)
    3. IFcoltransG (was LyricLy)
    4. Rou_bi
    5. razetime (was olus2000)
    6. olus2000 (was Hildegunst Taillemythes)
    7. gollark
    8. Palaiologos (was Olivia)
    9. LyricLy (was razetime)
    10. SoundOfSpouting
  6. Palaiologos +2 -2 = 0
    1. Rou_bi (was IFcoltransG)
    2. Hildegunst Taillemythes (was deadbraincoral)
    3. LyricLy
    4. SoundOfSpouting (was Rou_bi)
    5. deadbraincoral (was olus2000)
    6. razetime (was Hildegunst Taillemythes)
    7. IFcoltransG (was gollark)
    8. Olivia
    9. gollark (was razetime)
    10. olus2000 (was SoundOfSpouting)
  7. IFcoltransG +1 -1 = 0
    1. razetime (was Palaiologos)
    2. Palaiologos (was deadbraincoral)
    3. olus2000 (was LyricLy)
    4. deadbraincoral (was Rou_bi)
    5. Rou_bi (was olus2000)
    6. LyricLy (was Hildegunst Taillemythes)
    7. SoundOfSpouting (was gollark)
    8. Olivia
    9. Hildegunst Taillemythes (was razetime)
    10. gollark (was SoundOfSpouting)
  8. Olivia +4 -6 = -2
    1. Palaiologos
    2. razetime (was IFcoltransG)
    3. LyricLy (was deadbraincoral)
    4. IFcoltransG (was LyricLy)
    5. Rou_bi
    6. olus2000
    7. deadbraincoral (was Hildegunst Taillemythes)
    8. Hildegunst Taillemythes (was gollark)
    9. gollark (was razetime)
    10. SoundOfSpouting
  9. olus2000 +2 -4 = -2
    1. Hildegunst Taillemythes (was Palaiologos)
    2. razetime (was IFcoltransG)
    3. SoundOfSpouting (was deadbraincoral)
    4. LyricLy
    5. deadbraincoral (was Rou_bi)
    6. Palaiologos (was Hildegunst Taillemythes)
    7. IFcoltransG (was gollark)
    8. Olivia
    9. Rou_bi (was razetime)
    10. gollark (was SoundOfSpouting)
  10. SoundOfSpouting +2 -6 = -4
    1. Hildegunst Taillemythes (was Palaiologos)
    2. IFcoltransG
    3. Palaiologos (was deadbraincoral)
    4. Olivia (was LyricLy)
    5. gollark (was Rou_bi)
    6. olus2000
    7. razetime (was Hildegunst Taillemythes)
    8. deadbraincoral (was gollark)
    9. LyricLy (was Olivia)
    10. Rou_bi (was razetime)
  11. Rou_bi +0 -5 = -5

    entries

    you can download all the entries

    entry #1

    written by Palaiologos
    submitted at
    4 likes

    guesses
    comments 0

    post a comment


    moon.lua ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    17
    18
    19
    20
    21
    22
    23
                                                 load(([[f
                                                unction@I(s
                             ,p,v)re           turn@s:sub(#"
                       -",p-#"$")..v..s:su     b(p+#"#")end;
                    function@M(b,p)local@v,c=   -#"#",-#"$_
                 ";for@i=#"#",#'_$(.)(.)$'do@if@ b:sub(i,i
               )=="."then@b=I(b,i,p);l      ocal@
              a=-m(b,p=="x"and"o"or"          x")if
             @a>c@then@v,c=i,a@end@b           =I(b,
            i,".")end@end@return@v,c          @end;fu
            nction@m(S,p)local@w,A,B,C       ='.',{1,
           4,7,1,2,3,1,3},{2,5,8,4,5,6,5,5},{3,6,9,7,8
           ,9,9,7};for@i=#"#",#'#&*!__[]'@do@local@a,b
           ,c=S:sub(A[i],A[i]),S:sub(B[i],B[i]),S:sub(
           C[i],C[i]);if@a==b@and@a==c@and@a~="."then@
            w=a@end@end@if@w~='.'then@return@w==p@and
            #"."or-#"."end@return({M(S,p)})[#"[]"]end
             ;function@entry(s)local@b=s:gsub("%\n",
              '');return@I(b,M(b,'x'),"x")end]]):--
                gsub("[ \n]",""):gsub("@"," "))()
                  --[=[[_](#_-_[_._]/_[_._]).._
                    [_[#_]_)]+#_/_[_._],_[_[_
                        [#_]](#_)]+#_-]=]
    

    entry #2

    written by IFcoltransG
    submitted at
    3 likes

    guesses
    comments 0

    post a comment


    Win.hs ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    17
    18
    19
    20
    21
    22
    23
    24
    25
    26
    27
    28
    29
    30
    31
    32
    33
    34
    35
    36
    37
    38
    39
    40
    41
    42
    43
    44
    45
    46
    47
    48
    49
    50
    51
    52
    53
    54
    55
    56
    57
    58
    59
    60
    61
    62
    63
    64
    65
    66
    67
    68
    69
    70
    71
    72
    73
    74
    75
    76
    77
    78
    module Win (precompute, form, pre) where
    
    import Data.Foldable (maximumBy)
    import Data.Function (on)
    import Data.List (nub)
    import Data.Maybe (fromMaybe)
    import Language.Haskell.TH
    
    won :: Char -> String -> Bool
    won p [north_west, north, north_east, '\n', west, up, east, '\n', south_west, south, south_east] = line p [north_west, north, north_east, '\n', west, up, east, '\n', south_west, south, south_east] || line p [south_west, west, north_west, '\n', south, up, north, '\n', south_east, east, north_east]
      where
        line p (_ : _ : _ : '\n' : xs) | line p xs = True
        line p ('x' : 'x' : 'x' : _) | p == 'x' = True
        line p ('o' : 'o' : 'o' : _) | p == 'o' = True
        line p (_ : _ : 'x' : '\n' : _ : 'x' : _ : '\n' : 'x' : _) | p == 'x' = True
        line p (_ : _ : 'o' : '\n' : _ : 'o' : _ : '\n' : 'o' : _) | p == 'o' = True
        line _ _ = False
    
    winning :: String -> Maybe (Maybe Char)
    winning xs
      | won 'x' xs = Just (Just 'x')
      | won 'o' xs = Just (Just 'o')
      | '.' `notElem` xs = Just Nothing
    winning _ = Nothing
    
    turns :: Char -> String -> [String]
    turns p xs = go p [] ([], xs)
      where
        go _ options (_, []) = map dezip options
          where
            dezip (hs, ts) = reverse hs ++ ts
        go p options (hs, h : ts) = go p (flex h options) (h : hs, ts)
          where
            flex '.' = ((hs, p : ts) :)
            flex c = id
    
    form :: [String]
    form = nub $ blank : concat [turns 'o' blank, turns 'x' blank >>= turns 'o', turns 'o' blank >>= turns 'x' >>= turns 'o']
      where
        blank = "...\n...\n..."
    
    eval :: (Char, Char) -> String -> Either (Either Integer Integer) Integer
    eval (p, o) xs = case winning xs of
      Just (Just best)
        | best == p -> Left $ Left 0
        | best == o -> Left $ Right 0
      Just Nothing -> Right 0
      Nothing -> next $ eval (o, p) $ move (o, p) xs
        where
          next (Right a) = Right $ pred a
          next (Left (Left a)) = Left $ Right $ pred a
          next (Left (Right a)) = Left $ Left $ pred a
    
    move :: (Char, Char) -> String -> String
    move (p, o) xs = maximumBy (test `on` eval (p, o)) $ turns p xs
      where
        test (Left (Left a)) (Left (Left b)) = compare b a
        test (Left (Right a)) (Left (Right b)) = compare a b
        test (Right a) (Right b) = compare b a
        test (Left (Left _)) _ = LT
        test (Left (Right _)) _ = GT
        test a b = compare EQ $ test b a
    
    play :: (Char, Char) -> String -> [String]
    play (p, o) xs = fromMaybe (xs : play (o, p) (move (p, o) xs)) $ [xs] <$ winning xs
    
    pre :: String -> String
    pre = move ('x', 'o')
    
    precompute :: [String] -> DecsQ
    precompute xs = pure [FunD (mkName "entry") $ clauses ++ [fallback]]
      where
        patterns = map (LitP . StringL) xs
        table = map (LitE . StringL . pre) xs
        clauses = zipWith (\body pattern -> Clause [pattern] (NormalB body) []) table patterns
        var = mkName "xs"
        body = AppE (VarE (mkName "pre")) (VarE var)
        fallback = Clause [VarP var] (NormalB body) []
    
    ZoomZoom.hs ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    {-# LANGUAGE TemplateHaskell #-}
    
    -- Recommended to compile not interpret
    
    module ZoomZoom (entry, main) where
    
    import Win (pre, precompute, form)
    
    precompute form
    
    main = interact entry
    

    entry #3

    written by deadbraincoral
    submitted at
    4 likes

    guesses
    comments 0

    post a comment


    sub.bf ASCII text, with very long lines (65536), with no line terminators

    entry #4

    written by LyricLy
    submitted at
    2 likes

    guesses
    comments 0

    post a comment


    misere.hs ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    17
    18
    19
    20
    21
    22
    23
    24
    25
    26
    27
    28
    29
    30
    31
    32
    33
    34
    35
    36
    37
    38
    39
    40
    41
    42
    43
    44
    45
    46
    47
    48
    49
    50
    51
    52
    53
    54
    55
    56
    57
    58
    59
    60
    61
    62
    63
    64
    65
    {-# LANGUAGE TupleSections #-}
    
    import Control.Monad
    import Data.Array.IArray
    import Data.Function
    import Data.Maybe
    import Data.List
    
    type Point = (Int, Int)
    type Board = Array Point (Maybe Bool)
    
    parseBoard :: String -> Board
    parseBoard (a:b:c:'\n'
               :d:e:f:'\n'
               :g:h:i:_
               ) = listArray ((0, 0), (2, 2)) $ map charToCell [a, b, c, d, e, f, g, h, i]
      where
        charToCell 'x' = Just True
        charToCell 'o' = Just False
        charToCell '.' = Nothing
    
    sayBoard :: Board -> String
    sayBoard = map cellToChar . elems
      where
        cellToChar (Just True) = 'x'
        cellToChar (Just False) = 'o'
        cellToChar Nothing = '.'
    
    mirror :: Board -> Maybe Point
    mirror b = guard (b ! (1, 1) == Just True) >> (join . fmap msum . mapM hasMirror $ assocs b)
      where
        hasMirror (p@(x, y), c) | p == (1, 1) = Just Nothing
                                | otherwise =
          case c of
            Just False ->
              let i = (2-x, 2-y)
              in case b ! i of
                Just True -> Just Nothing
                Just False -> Nothing
                Nothing -> Just (Just i)
            _ -> Just Nothing
    
    inARows :: Point -> [[Point]]
    inARows (x, y) = map (x,) [0..2] : map (,y) [0..2] : diag 0 ++ diag 2
      where diag n = map ((,) <*> (n-)) [0..2] <$ (guard (x == n-y))
    
    rowLength :: Board -> [Point] -> Int
    rowLength b r
      | any ((==Just False) . (b !)) r = 0
      | otherwise = length $ filter ((==Just True) . (b !)) r
    
    play :: Board -> Point
    play b = case filter (isJust . snd) $ assocs b of
      [] -> (1, 1)
      [((x, y), _)]
        | odd (x + y) -> (y, x)
        | otherwise -> (0, 1)
      _ -> case mirror b of
        Just p -> p
        Nothing -> minimumBy (compare `on` (\p -> maximum . map (rowLength b) $ inARows p)) . map fst . filter (isNothing . snd) $ assocs b
    
    entry :: String -> String
    entry s = let b = parseBoard s in sayBoard $ b // [(play b, Just True)]
    
    main = interact entry
    

    entry #5

    written by Rou_bi
    submitted at
    1 like

    guesses
    comments 0

    post a comment


    TicPutATacOnMyToe.lua ASCII text
      1
      2
      3
      4
      5
      6
      7
      8
      9
     10
     11
     12
     13
     14
     15
     16
     17
     18
     19
     20
     21
     22
     23
     24
     25
     26
     27
     28
     29
     30
     31
     32
     33
     34
     35
     36
     37
     38
     39
     40
     41
     42
     43
     44
     45
     46
     47
     48
     49
     50
     51
     52
     53
     54
     55
     56
     57
     58
     59
     60
     61
     62
     63
     64
     65
     66
     67
     68
     69
     70
     71
     72
     73
     74
     75
     76
     77
     78
     79
     80
     81
     82
     83
     84
     85
     86
     87
     88
     89
     90
     91
     92
     93
     94
     95
     96
     97
     98
     99
    100
    101
    102
    103
    104
    105
    106
    107
    108
    109
    110
    111
    112
    113
    114
    115
    116
    117
    118
    119
    120
    121
    122
    123
    124
    125
    126
    127
    128
    129
    130
    131
    132
    133
    134
    135
    136
    137
    138
    139
    140
    141
    142
    143
    144
    145
    146
    147
    148
    149
    150
    151
    152
    153
    154
    155
    156
    157
    158
    159
    160
    161
    162
    163
    164
    165
    166
    167
    168
    169
    170
    171
    172
    173
    174
    175
    176
    177
    178
    179
    180
    181
    182
    183
    184
    185
    186
    187
    188
    189
    190
    191
    192
    193
    194
    195
    196
    197
    198
    199
    200
    201
    -- aaden
    
    print("Input current board")
    
    local h = io.read()
    
    local s = ""
    
    local count = {
        ["."] = 0,
        ["x"] = 0,
        ["o"] = 0,
    }
    
    for i in string.gmatch(h, "([%.xo])") do
        s = s..i
        count[i] = count[i] + 1
    end
    
    function entry(board)
        local function format(string)
            return string.sub(string, 1, 3).."\n"..string.sub(string, 4, 6).."\n"..string.sub(string, 7, 9)
        end
        local function tile(x, y)
            return string.sub(board, x + ((y - 1) * 3), x + ((y - 1) * 3))
        end
        -- checking for valid horizontal wins
        for i=1, 3 do
            local period = 0
            for j=1, 3 do
                local slot = tile(j, i)
                if slot == "o" then
                    period = -1
                    break
                elseif slot == "." then
                    period = period + 1
                end
            end
    
            if period == 1 then
                return format(string.sub(board, 0, (i - 1) * 3).."xxx"..string.sub(board, ((i + 1) * 3) + 1, -1))
            end
        end
        -- checking for valid vertical wins
        for i=1, 3 do
            local period = 0
            for j=1, 3 do
                local slot = tile(i, j)
                if slot == "o" then
                    period = -1
                    break
                elseif slot == "." then
                    period = period + 1
                end
            end
    
            if period == 1 then
                return format(string.sub(board, 0, i - 1).."x"..string.sub(board, i + 1, i + 2).."x"..string.sub(board, i + 4, i + 5).."x"..string.sub(board, i + 7, -1))
            end
        end
        -- diagonal 1
        local period = 0
        for i=1, 3 do
            local slot = tile(4 - i, i)
            if slot == "o" then
                break
            elseif slot == "." then
                period = period + 1
            end
    
            if i == 3 and period == 1 then
                return format(string.sub(board, 1, 2).."x"..string.sub(board, 4, 4).."x"..string.sub(board, 6, 6).."x"..string.sub(board, 8, 9))
            end
        end
        -- diagonal 2
        period = 0
        for i=1, 3 do
            local slot = tile(i, i)
            if slot == "o" then
                break
            elseif slot == "." then
                period = period + 1
            end
    
            if i == 3 and period == 1 then
                return format("x"..string.sub(board, 2, 4).."x"..string.sub(board, 6, 8).."x")
            end
        end
        -- doing the same for player O so player X can prevent it
        -- checking for valid horizontal wins
        for i=1, 3 do
            local period = 0
            local periodpos = {0, 0}
            for j=1, 3 do
                local slot = tile(j, i)
                if slot == "x" then
                    period = -1
                    break
                elseif slot == "." then
                    period = period + 1
                    periodpos = {j, i}
                end
            end
    
            if period == 1 then
                return format(string.sub(board, 0, (periodpos[1] - 1) + ((periodpos[2] - 1) * 3)).."x"..string.sub(board, (periodpos[1] + 1) + ((periodpos[2] - 1) * 3), -1))
            end
        end
        -- checking for valid vertical wins
        for i=1, 3 do
            local period = 0
            local periodpos = {0, 0}
            for j=1, 3 do
                local slot = tile(i, j)
                if slot == "x" then
                    period = -1
                    break
                elseif slot == "." then
                    period = period + 1
                    periodpos = {i, j}
                end
            end
    
            if period == 1 then
                return format(string.sub(board, 0, (periodpos[1] - 1) + ((periodpos[2] - 1) * 3)).."x"..string.sub(board, (periodpos[1] + 1) + ((periodpos[2] - 1) * 3), -1))
            end
        end
        -- diagonal 1
        period = 0
        local periodpos = {0, 0}
        for i=1, 3 do
            local slot = tile(4 - i, i)
            if slot == "x" then
                break
            elseif slot == "." then
                period = period + 1
                periodpos = {4 - i, i}
            end
    
            if i == 3 and period == 1 then
                return format(string.sub(board, 0, (periodpos[1] - 1) + ((periodpos[2] - 1) * 3)).."x"..string.sub(board, (periodpos[1] + 1) + ((periodpos[2] - 1) * 3), -1))
            end
        end
        -- diagonal 2
        period = 0
        periodpos = {0, 0}
        for i=1, 3 do
            local slot = tile(i, i)
            if slot == "x" then
                break
            elseif slot == "." then
                period = period + 1
                periodpos = {i, i}
            end
    
            if i == 3 and period == 1 then
                return format(string.sub(board, 0, (periodpos[1] - 1) + ((periodpos[2] - 1) * 3)).."x"..string.sub(board, (periodpos[1] + 1) + ((periodpos[2] - 1) * 3), -1))
            end
        end
    
        -- method 1
        if tile(3, 1) == "." and tile(3, 2) == "." and tile(1, 3) ~= "o" and tile(1, 2) ~= "o" and tile(2, 2) ~= "o" then
            if tile(1, 3) == "." then
                return format(string.sub(board, 1, 6).."x"..string.sub(board, 8, 9))
            elseif tile(1, 2) == "." then
                return format(string.sub(board, 1, 3).."x"..string.sub(board, 5, 9))
            elseif tile(2, 2) == "." then
                return format(string.sub(board, 1, 4).."x"..string.sub(board, 6, 9))
            end
        end
        -- method 2
        if tile(2, 2) == "o" then
            if tile(3, 1) == "." then
                return format(string.sub(board, 1, 2).."x"..string.sub(board, 4, 9))
            elseif tile(1, 1) == "." then
                return format("x"..string.sub(board, 2, 9))
            elseif tile(3, 3) == "." then
                return format(string.sub(board, 1, 8).."x")
            elseif tile(1, 3) == "." then
                return format(string.sub(board, 1, 6).."x"..string.sub(board, 8, 9))
            end
        end
    
        local candidates = {}
    
        for i=1, 9 do
            if string.sub(board, i, i) == "." then
                candidates[#candidates+1] = i
            end
        end
    
        if #candidates > 0 then
            local chosen = candidates[math.random(1, #candidates)]
    
            return format(string.sub(board, 0, chosen - 1).."x"..string.sub(board, chosen + 1, 9))
        else
            return "Nothing to do..."
        end
    end
    
    print(entry(s))
    

    entry #6

    written by olus2000
    submitted at
    3 likes

    guesses
    comments 0

    post a comment


    tictactoe.lua ASCII text
      1
      2
      3
      4
      5
      6
      7
      8
      9
     10
     11
     12
     13
     14
     15
     16
     17
     18
     19
     20
     21
     22
     23
     24
     25
     26
     27
     28
     29
     30
     31
     32
     33
     34
     35
     36
     37
     38
     39
     40
     41
     42
     43
     44
     45
     46
     47
     48
     49
     50
     51
     52
     53
     54
     55
     56
     57
     58
     59
     60
     61
     62
     63
     64
     65
     66
     67
     68
     69
     70
     71
     72
     73
     74
     75
     76
     77
     78
     79
     80
     81
     82
     83
     84
     85
     86
     87
     88
     89
     90
     91
     92
     93
     94
     95
     96
     97
     98
     99
    100
    101
    102
    103
    104
    105
    106
    107
    108
    109
    110
    111
    112
    113
    114
    115
    116
    117
    118
    119
    120
    121
    122
    123
    124
    125
    126
    127
    128
    129
    130
    131
    132
    133
    134
    135
    136
    137
    138
    139
    140
    141
    142
    143
    144
    145
    146
    147
    148
    149
    150
    151
    152
    153
    154
    155
    156
    157
    158
    159
    160
    161
    162
    163
    164
    165
    166
    167
    168
    169
    170
    171
    172
    173
    174
    175
    176
    177
    178
    179
    180
    181
    182
    183
    184
    185
    186
    187
    188
    189
    190
    191
    192
    193
    194
    195
    196
    197
    198
    199
    200
    201
    202
    203
    204
    205
    206
    207
    208
    209
    210
    211
    212
    213
    214
    215
    216
    217
    218
    219
    220
    221
    222
    223
    224
    225
    226
    227
    228
    229
    230
    231
    232
    233
    234
    235
    236
    237
    238
    239
    240
    241
    242
    243
    244
    245
    246
    247
    248
    249
    250
    251
    252
    253
    254
    255
    256
    257
    258
    259
    260
    261
    262
    263
    264
    265
    266
    267
    268
    269
    270
    271
    272
    273
    274
    275
    276
    277
    278
    279
    280
    281
    282
    283
    284
    285
    286
    287
    288
    289
    290
    291
    292
    293
    294
    295
    296
    297
    298
    299
    300
    301
    302
    303
    304
    305
    306
    307
    308
    309
    310
    311
    312
    313
    314
    315
    316
    317
    318
    319
    320
    321
    322
    323
    324
    325
    326
    327
    328
    329
    330
    331
    332
    333
    334
    335
    336
    337
    338
    339
    340
    341
    342
    343
    344
    345
    346
    347
    348
    349
    350
    351
    352
    353
    354
    355
    356
    357
    358
    359
    360
    361
    362
    363
    364
    365
    366
    367
    368
    369
    370
    371
    372
    373
    374
    375
    376
    377
    378
    379
    380
    381
    382
    383
    384
    385
    386
    387
    ---- Environment ----
    
    data_s, return_s, dip_s, current, ip = {}, {}, {}, {}, 1
    
    
    ---- Operators ----
    
    function nop () end
    
    function drop ()
        table.remove(data_s)
    end
    
    function dup ()
        table.insert(data_s, data_s[#data_s])
    end
    
    function over ()
        table.insert(data_s, data_s[#data_s-1])
    end
    
    function swap ()
        data_s[#data_s-1], data_s[#data_s]
        = data_s[#data_s], data_s[#data_s-1]
    end
    
    function rot ()
        data_s[#data_s-2], data_s[#data_s-1], data_s[#data_s]
        = data_s[#data_s-1], data_s[#data_s], data_s[#data_s-2]
    end
    
    function dip ()
        local v = current[ip]
        ip = ip + 1
        table.insert(return_s, {current, ip})
        table.insert(return_s, {{undip}, 1})
        table.insert(dip_s, table.remove(data_s))
        current, ip = v, 1
    end
    
    function undip ()
        table.insert(data_s, table.remove(dip_s))
    end
    
    function op_not ()
        table.insert(data_s, not table.remove(data_s))
    end
    
    function suc ()
        table.insert(data_s, table.remove(data_s) + 1)
    end
    
    function add ()
        table.insert(data_s, table.remove(data_s) + table.remove(data_s))
    end
    
    function mul ()
        table.insert(data_s, table.remove(data_s) * table.remove(data_s))
    end
    
    function eq ()
        table.insert(data_s, table.remove(data_s) == table.remove(data_s))
    end
    
    function cat ()
        local v2, v1 = table.remove(data_s), table.remove(data_s)
        table.insert(data_s, v1 .. v2)
    end
    
    function get ()
        table.insert(data_s, table.remove(data_s)[table.remove(data_s)])
    end
    
    function set ()
        local v = table.remove(data_s)
        table.remove(data_s)[table.remove(data_s)] = v
    end
    
    function to_list ()
        local s, v = table.remove(data_s), {}
        for i = 1, #s do
            table.insert(v, s:sub(i, i))
        end
        table.insert(data_s, v)
    end
    
    function new_list ()
        table.insert(data_s, {})
    end
    
    function length ()
        table.insert(data_s, #table.remove(data_s))
    end
    
    function random ()
        table.insert(data_s, math.random(table.remove(data_s)))
    end
    
    function iff ()
        if not table.remove(data_s) then
            ip = ip + 2
        end
    end
    
    function elsef ()
        ip = ip + 1
    end
    
    function op_while ()
        if not table.remove(data_s) then
            ip = #current + 1
        end
    end
    
    function again ()
        ip = 1
    end
    
    function dump ()
        print(l_to_s(data_s))
    end
    
    
    ---- Words ----
    
    -- ( x y -- x y x y )
    dup2 = {
        over, over
    }
    
    -- ( x y -- y )
    nip = {
        swap, drop
    }
    
    -- ( -- value )
    x = 1
    o = -1
    empty = 0
    
    -- ( n -- bool )
    not_zero = {
        0, eq, op_not,
    }
    
    -- ( value -- bool )
    not_empty = not_zero
    
    -- ( -- position )
    random_position = {
        9, random
    }
    
    -- ( sign -- value )
    from_sign = {
        dup, 'x', eq, iff,
        { drop, x }, elsef,
        { dup, 'o', eq, iff,
          { drop, o }, elsef,
          { dup, '.', eq, iff,
            { drop, empty }, elsef,
            { drop, false } } }
    }
    
    -- ( value -- sign )
    to_sign = {
        dup, x, eq, iff,
        drop, 'x',
        dup, o, eq, iff,
        drop, 'o',
        dup, empty, eq, iff,
        drop, '.'
    }
    -- ( prev a b c -- next )
    row_winner = {
        add, add, dup,
        x, 3, mul, eq, iff,
        { nip, x, swap }, nop,
        o, 3, mul, eq, iff,
        { drop, o }
    }
    
    -- ( board -- sign ) hideous but works
    winner = {
        empty, swap,
        1, over, get, swap,
        2, over, get, swap,
        3, over, get, swap,
        dip, row_winner,
        4, over, get, swap,
        5, over, get, swap,
        6, over, get, swap,
        dip, row_winner,
        7, over, get, swap,
        8, over, get, swap,
        9, over, get, swap,
        dip, row_winner,
        1, over, get, swap,
        4, over, get, swap,
        7, over, get, swap,
        dip, row_winner,
        2, over, get, swap,
        5, over, get, swap,
        8, over, get, swap,
        dip, row_winner,
        3, over, get, swap,
        6, over, get, swap,
        9, over, get, swap,
        dip, row_winner,
        1, over, get, swap,
        5, over, get, swap,
        9, over, get, swap,
        dip, row_winner,
        3, over, get, swap,
        5, over, get, swap,
        7, over, get, swap,
        dip, row_winner,
        drop
    }
    
    -- ( board -- move true | false ) TODO
    can_win = {
        dip, { false, 1 },
        { dup2, get,
          empty, eq, iff,
          { dup2, x, set,
            dup, winner, x, eq, iff,
            { dup2, empty, set, dip,
              { nip, true, 9 } },
            elsef, { dup2, empty, set } },
          nop,
          over, 9, eq, op_not, op_while,
          swap, suc, swap, again },
        drop, drop
    }
    
    -- ( board -- move true | false ) TODO
    can_loose = {
        dip, { false, 1 },
        { dup2, get,
          empty, eq, iff,
          { dup2, o, set,
            dup, winner, o, eq, iff,
            { dup2, empty, set, dip,
              { nip, true, 9 } },
            elsef, { dup2, empty, set } },
          nop,
          over, 9, eq, op_not, op_while,
          swap, suc, swap, again },
        drop, drop
    }
    
    -- ( board -- board )
    random_move = {
        { random_position,
          dup2, swap, get,
          not_empty, op_while,
          drop, again },
        over, x, set
    }
    
    -- ( board_str -- board )
    parse_board = {
        to_list, new_list, swap, 1,
        { over, length, suc, over,
          eq, op_not, op_while,
          dup2, swap, get, from_sign,
          dup, iff,
          { swap, dip,
            { dip,
              { over, dup, length,
                suc, swap }, set } },
          elsef, { drop },
          suc, again },
        drop, drop
    }
    
    
    -- ( board -- board )
    make_move = {
        dup, can_win, iff,
        { over, x, set }, elsef,
        { dup, can_loose, iff,
          { over, x, set }, elsef,
          { random_move } }
    }
    
    -- ( board -- board_str )
    encode_board = {
        '', swap, 1,
        { dup, 10, eq, op_not, op_while,
          dup2, swap, get, to_sign,
          swap, dip,
          { rot, swap, cat, swap },
          suc, again },
        drop, drop
    }
    
    -- ( board_str -- board_str )
    tictactoe = {
        parse_board,
        make_move,
        encode_board
    }
    
    
    ---- Interpreter ----
    
    function eval (word)
        return_s, ip, current = {}, 1, word
        while true do
            -- return from any finished threads
            while ip > #current do
                if #return_s == 0 then
                    return
                else
                    current, ip = table.unpack(table.remove(return_s))
                end
            end
            -- get current command
            com = current[ip]
            ip = ip + 1
            -- execute command
            if type(com) == 'function' then
                com()
            elseif type(com) == 'table' then
                table.insert(return_s, {current, ip})
                current, ip = com, 1
            else
                table.insert(data_s, com)
            end
        end
    end
    
    
    function better_entry (s)
        data_s = {s}
        eval(tictactoe)
        return table.remove(data_s)
    end
    
    
    ---- Helpers ----
    
    function l_to_s (l, d)
        d = d or 3 -- how deep will the printing go
        ans = '['
        for i = 1, #l do
            if type(l[i]) == 'function' then
                ans = ans .. ' [op]'
            elseif type(l[i]) == 'table' then
                if d > 0 then
                    ans = ans .. ' ' .. l_to_s(l[i], d - 1)
                else
                    ans = ans .. ' [...]'
                end
            else
                ans = ans .. ' ' .. tostring(l[i])
            end
        end
        return ans .. ' ]'
    end
    
    function print_stack ()
        print(l_to_s(data_s))
    end
    
    
    ---- Dumb version ----
    
    function bad_entry (s)
        local answer, moved, cell = '', false
        for i = 1, #s do
            cell = s:sub(i, i)
            if cell == '.' and not moved then
                cell = 'x'
                moved = true
            end
            answer = answer .. cell
        end
        return answer
    end
    
    
    ---- Entry ----
    
    entry = better_entry
    

    entry #7

    written by Hildegunst Taillemythes
    submitted at
    1 like

    guesses
    comments 0

    post a comment


    cg-20.hs ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    module Main where
    
    freplace :: String -> Maybe String
    freplace [] = Nothing
    freplace ('.':xs) = Just ('x':xs)
    freplace (x:xs) = (x:) <$> freplace xs
    
    entry :: String -> String
    entry = unlines . aux . lines
      where
        aux :: [String] -> [String]
        aux [] = []
        aux (x:xs) = maybe (x:aux xs) (:xs) (freplace x)
    
    main :: IO ()
    main = interact entry
    

    entry #8

    written by gollark
    submitted at
    2 likes

    guesses
    comments 0

    post a comment


    tacnet.lua ASCII text, with very long lines (24183)

    entry #9

    written by Olivia
    submitted at
    4 likes

    guesses
    comments 0

    post a comment


    this is what the code should look like.PNG PNG image data, 1722 x 1790, 8-bit/color RGBA, non-interlaced
    tic tac toesy woesy.hs Unicode text, UTF-8 text
      1
      2
      3
      4
      5
      6
      7
      8
      9
     10
     11
     12
     13
     14
     15
     16
     17
     18
     19
     20
     21
     22
     23
     24
     25
     26
     27
     28
     29
     30
     31
     32
     33
     34
     35
     36
     37
     38
     39
     40
     41
     42
     43
     44
     45
     46
     47
     48
     49
     50
     51
     52
     53
     54
     55
     56
     57
     58
     59
     60
     61
     62
     63
     64
     65
     66
     67
     68
     69
     70
     71
     72
     73
     74
     75
     76
     77
     78
     79
     80
     81
     82
     83
     84
     85
     86
     87
     88
     89
     90
     91
     92
     93
     94
     95
     96
     97
     98
     99
    100
    101
    102
    103
    104
    105
    106
    107
    108
    109
    110
    111
    112
    113
    114
    115
    116
    117
    118
    119
    120
    121
    122
    123
    124
    125
    126
    127
    128
    129
    130
    131
    132
    133
    134
    135
    136
    137
    138
    139
    140
    141
    142
    143
    144
    145
    146
    147
    148
    149
    150
    151
    152
    153
    154
    155
    156
    157
    158
    159
    160
    161
    162
    163
    164
    165
    166
    167
    168
    169
    170
    171
    172
    173
    174
    175
    176
    177
    178
    179
    180
    181
    182
    183
    184
    185
    186
    187
    188
    189
    190
    191
    192
    193
    194
    195
    196
    197
    198
    199
    200
    201
    202
    203
    204
    205
    206
    207
    208
    209
    210
    211
    212
    213
    214
    215
    216
    217
    218
    219
    220
    221
    222
    223
    224
    225
    226
    227
    228
    229
    230
    231
    232
    233
    234
    235
    236
    237
    238
    239
    240
    241
    242
    243
    244
    245
    246
    247
    248
    249
    250
    251
    252
    253
    254
    255
    256
    257
    258
    259
    260
    261
    262
    263
    264
    265
    266
    267
    268
    269
    270
    271
    272
    273
    274
    275
    276
    277
    278
    279
    280
    281
    282
    283
    284
    285
    286
    287
    288
    289
    290
    291
    292
    293
    294
    295
    296
    297
    298
    299
    300
    301
    302
    303
    304
    305
    306
    import Data.List as L
    import Control.Monad.Identity as I
    
    main = pure 
    
    -- blame me for: motation 
     :: ()
     = ()
    infixr 0 
    () :: () -> a -> I.Identity a
    ㅤ⠀x = return x
    infixr 0 ⠀⠀
    (⠀⠀) :: () -> I.Identity a -> a
    ㅤ⠀⠀x = I.runIdentity x
    infixr 7 ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀) :: (b -> c -> d) -> (a -> c) -> a -> b -> d
    g⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀h = \w x -> g x (h w) 
    infixr 7 ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀) :: () -> (a -> a -> c) -> a -> c
    ㅤ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀g = \x -> x `g` x
    infixr 7 ⠀⠀⠀⠀
    (⠀⠀⠀⠀) :: (a -> b) -> (a -> b -> d) -> a -> d
    f⠀⠀⠀⠀g = \x -> g x (f x)
    infixr 7 ⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀) :: (c -> d -> e) -> (a -> b -> d) -> a -> b -> c -> e
    g⠀⠀⠀⠀⠀h = \w x y -> g y (h w x)
    infixr 7 ⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀) :: (a -> b -> c) -> (a -> b -> c -> e) -> a -> b -> e
    f⠀⠀⠀⠀⠀⠀g = \w x -> g w x (f w x)
    infixr 7 ⠀⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀⠀) :: (b -> c) -> (a -> b) -> a -> c
    f⠀⠀⠀⠀⠀⠀⠀g = f . g
    infixr 7 ⠀⠀⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀⠀⠀) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
    f⠀⠀⠀⠀⠀⠀⠀⠀g = \w x -> f (g w x)
    infixl 1 ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀
    (⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀) :: (a -> b) -> a -> b
    f⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀x = f x
    infixl 9 ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀ -- for fake infix
    (⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀) :: a -> b -> (a, b)
    (⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀)=(,)
    infixr 8 ⠀⠀⠀
    (⠀⠀⠀) :: a -> () -> [a]
    x⠀⠀⠀ㅤ = [x]
    infixr 8 
    () :: a -> [a] -> [a]
    wx = w:x
    infixr 9 ¯
    (¯) :: () -> Int -> Int
    ㅤ¯i = 0 - i
    infixr 2  -- ⟨invalid⟩
    () :: () -> [a] -> [a]
    ㅤ<x = x
    infixr 2 
    () :: a -> () -> [a]
    x>ㅤ=[x]
    infixr 2 
    () :: a -> [a] -> [a]
    () = ()
    infixl 8 
    () :: (b -> c) -> (a -> b) -> a -> c
    f  g = \x -> f (g x)
    infixl 5 ∘⠀
    (∘⠀) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
    f ∘⠀g = \w x -> f (g w x)
    infixl 5 ˜
    (˜ ) :: (a -> a -> b) -> () -> (a -> b)
    f ˜ㅤ = \x -> f x x 
    infixl 5 ˜⠀
    (˜⠀) :: (a -> b -> c) -> () -> (b -> a -> c)
    f ˜⠀ㅤ= \w x -> f x w
    infixl 5 ˙
    (˙ ) :: a -> () -> (b -> a)
    f ˙ㅤ = \x -> f
    infixl 5 ˙⠀
    (˙⠀) :: a -> () -> (b -> c -> a)
    f ˙⠀ㅤ= \w x -> f
    infixl 5 
    ( ) :: (b -> c) -> (a -> b) -> a -> c
    f  g = \x -> f (g x)
    infixl 5 ○⠀
    (○⠀) :: (b -> b -> c) -> (a -> b) -> a -> a -> c
    f ○⠀g = \w x -> f (g w) (g x)
    infixl 5 
    ( ) :: b -> (b -> a -> c) -> a -> c
    f  g = g f
    infixl 5 ⊸⠀
    (⊸⠀) :: (a -> b) -> (b -> c -> d) -> a -> c -> d
    f ⊸⠀g = \w x -> g (f w) x
    infixl 5 
    ( ) :: (a -> b -> c) -> b -> a -> c
    f  g = \x -> f x g
    infixl 5 ⟜⠀
    (⟜⠀) :: (a -> c -> d) -> (b -> c) -> a -> b -> d
    f ⟜⠀g = \w x -> f w (g x)
    infixl 5 
    () :: (a -> Int) -> [a -> b] -> a -> b
    f  g = \x -> (g !! f x) x
    infixl 5 ◶⠀
    (◶⠀) :: (a -> b -> Int) -> [a -> b -> c] -> a -> b -> c
    f ◶⠀g = \w x -> (g !! f w x) w x
    infixl 5 ˘
    (˘) :: (a -> b -> c) -> () -> a -> [b] -> [c]
    f˘ㅤ = fmap . f
    infixl 5 ¨
    (¨) :: (a -> b) -> () -> [a] -> [b]
    f¨ㅤ = fmap f
    infixl 5 ´
    (´) :: (a -> b -> b) -> () -> b -> [a] -> b
    f´ㅤ = foldr f
    infixl 5 
    () :: ([a], (a -> b -> c)) -> () -> [b] -> [[c]]
    (ws,f)⌜ㅤ= \xs -> [[f w x | x <- xs] | w <- ws]
    infixl 5 ¨⠀⠀
    (¨⠀⠀) :: ([a], (a -> b -> c)) -> [b] -> [c] -- inconsistent
    (ws,f)¨⠀⠀xs = uncurry (f) <$> zip ws xs
    infixr 3 
    () :: [Int] -> [a] -> [[a]]
    [a,b]x = take b <$> (take a $ iterate (drop b) (x++x)) -- fill
    _x = undefined
    infixr 3 ⠀⥊
    (⠀⥊) :: () -> [[a]] -> [a]
    ㅤ⠀⥊x = L.concat x
    infixr 3 
    () :: Int -> [a] -> [a]
    wx = let op = case compare w 0 of 
                LT -> reverse . drop (0-w) . reverse
                EQ -> id
                GT -> drop w
            in 
                op x
    infixr 3 
    () :: Eq a => a -> [a] -> [Int]
    wx = fromEnum . (==) w <$> x
    infixr 3 ⠀=
    (⠀=) :: Eq a => a -> a -> Int
    w⠀=x = fromEnum (w == x)
    infixr 3 
    () :: () -> [Int] -> [Int] 
    ㅤ/x = elemIndices 1 x -- boolean
    infixr 3 
    () :: () -> [a] -> a
    ㅤ⊑x = head x
    infixr 3 ⠀⊑
    (⠀⊑) :: Int -> [a] -> a -- vector
    w⠀⊑x = x !! w
    infixr 3 
    () :: () -> Int -> [Int]
    ㅤ↕x = [0..x-1]
    infixr 3  -- arity hack
    () :: a -> a
    () = id
    infixr 3 
    () :: a -> b -> b
    () = const id
    infixr 3 
    () :: Int -> Int -> Int
    wx = fromEnum $ w/=0 && x/=0
    infixr 3 
    () :: a -> a -> [a]
    xy = [x,y]
    infixr 3 
    () :: Int -> Int -> Int
    wx = fromEnum $ w/=0 || x/=0
    infixr 3 
    () :: [Int] -> [Int] -> Int
    [][] = 1
    w:wsx:xs = (fromEnum $ w == x) * (wsxs)
    __=undefined
    infixr 3  -- fake
    () :: () -> a -> a
    ㅤ﹤x=x
    infixr 3  -- specialize
    () :: Eq a => a -> [[a]] -> [[Int]]
    wxss = fmap (fromEnum . (==) w) <$> xss
    infixr 3 ×
    (×) :: Int -> Int -> Int
    (×) = (*)
    infixr 3  -- unshadow
    () :: Int -> Int -> Int
    () = (+)
    infixr 3 ⊣⠀ -- yay
    (⊣⠀) :: a -> b -> a
    w⊣⠀_=w
    infixr 3 ∨⠀
    (∨⠀) :: Ord a => () -> [a] -> [a]
    ㅤ∨⠀x = reverse $ sort x
    
    -- blame haskell for: bad motation
    infixr 3 ‿⊣
    (‿⊣) :: a -> () -> [(a -> a)] -- scalar autoconst w
    w‿⊣ㅤ = (const w)()⠀⠀⠀ㅤ
    infixr 3 ↓˘ 
    (↓˘) :: Int -> [[a]] -> [[a]]
    w↓˘x = (()˘ㅤ) w x
    infixl 4 ⊑⟜
    (⊑⟜) :: () -> [a] -> Int -> a
    ㅤ⊑⟜g = (⠀⊑)g
    infixr 3 ⊸=∘
    (⊸=∘) :: Eq a => a -> (b -> b -> a) -> b -> b -> Int -- clean
    w⊸=∘x = (w(⠀=))∘⠀x
    infixr 3 ¨⠀
    (¨⠀) :: (a -> b) -> [a] -> [b]
    (¨⠀) = fmap
    infixl 4 ∘⊢
    (∘⊢) :: (b -> c) -> () -> a -> b -> c
    f∘⊢ㅤ = f∘⠀()
    infixl 4 ˙⊸⋈
    (˙⊸⋈) :: (a -> a -> b) -> () -> b -> [a -> a -> b]
    f˙⊸⋈ㅤ = \x -> (f()) (const.const x) -- autoconst v2
    infixr 3 ∨´
    (∨´) :: Int -> [Int] -> Int
    w∨´x = (()´ㅤ) w x
    infixr 3 ⊸∧
    (⊸∧) :: [Int] -> () -> [Int] -> [Int]
    w⊸∧ㅤ = \x -> uncurry () <$> zip w x
    infixr 3 ⊣≡
    (⊣≡) :: () -> ([Int] -> [Int]) -> [Int] -> Int
    ㅤ⊣≡f = \x -> (()x)(f x)
    infixr 3 ﹤˘ -- fake because flat
    (﹤˘) :: () -> a -> a
    ㅤ﹤˘x=x
    infixr 3 ⌜↕ -- cheater
    (⌜↕) :: ([a], (a -> Int -> c)) -> Int -> [[c]]
    (w,f)⌜↕x = ((w,f)⌜ㅤ)(ㅤ↕x)
    infixr 3 ⊸×⊣ -- no train
    (⊸×⊣) :: Int -> () -> Int -> Int -> Int
    w⊸×⊣ㅤ = (w(×))∘⠀(⊣⠀)
    infixr 3 ⋈¨
    (⋈¨) :: [a] -> [a] -> [[a]]
    w⋈¨x = w ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀()¨⠀⠀ x -- zoop
    
    
    {------------------------------------------------
     - PROGRAM STARTS HERE                          -
     -                                              -
     -                                              -
     -                                              -
     -----------------------------------------------}
    
    entry    :: [Char] ->    [Char]
    entry = (\𝕩 ->ㅤ⠀⠀(do -- {
            grid <-ㅤ⠀ㅤ⠀⥊ㅤ¯1↓˘34⠀⠀⠀ㅤ⥊𝕩
            wins <-ㅤ⠀(
                ㅤ<               
                    111000000⠀⠀⠀ㅤ 
                    000111000⠀⠀⠀ㅤ 
                    000000111⠀⠀⠀ㅤ 
                    100100100⠀⠀⠀ㅤ 
                    010010010⠀⠀⠀ㅤ 
                    001001001⠀⠀⠀ㅤ 
                    100010001⠀⠀⠀ㅤ 
                    001010100⠀⠀⠀ㅤ
                >ㅤ
                )
            
            first <-ㅤ⠀ㅤ⊑ㅤ/'.'grid
            opts <-ㅤ⠀first‿⊣ㅤ
            Get <-ㅤ⠀ㅤ⊑⟜grid∘⊢ㅤ
            Free <-ㅤ⠀'.'⊸=∘ㅤGet
            picks <-ㅤ⠀ㅤ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀ㅤFreeopts¨ㅤ⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀ㅤ↕9
            Selected <-ㅤ⠀(⠀=)⠀⠀⠀⠀⠀⠀()⠀⠀⠀⠀⠀ Free
            Or <-ㅤ⠀ㅤGet˙⊸⋈ㅤ
            
            Ending <-ㅤ⠀ (\𝕩 -> -- {
                (0∨´(ㅤ⊣≡𝕩⊸∧ㅤ)¨⠀wins)
                ) -- }
            -- tacify into Futures 'x' and Winning 'x'
            futuresX <-ㅤ⠀ㅤ﹤˘picks⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀((Selected)◶⠀(Or 'x'))⌜↕9
            futuresO <-ㅤ⠀ㅤ﹤˘picks⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀((Selected)◶⠀(Or 'o'))⌜↕9
            winningX <-ㅤ⠀ㅤEnding¨⠀'x'futuresX
            winningO <-ㅤ⠀ㅤEnding¨⠀'o'futuresO
    
            Weight <-ㅤ⠀(2⊸×⊣ㅤ)⠀⠀⠀⠀⠀⠀(+)⠀⠀⠀⠀⠀()
            values <-ㅤ⠀winningX⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀ㅤWeight¨⠀⠀ winningO
            choice <-ㅤ⠀1⠀⊑ㅤ⊑ㅤ∨⠀values⋈¨picks
            ㅤ⠀choice ⠀⊑ futuresX
        )) -- }
    
    (⣿⣿⣿⣿⣿⣿⣿⣿⡿⠟⠛⠉⠉⠉⠉⠉⠉⠛⠻⢿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡿⠟⠛⠉⠉⠉⠉⠉⠉⠛⠻⢿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡿⠟⠛⠉⠉⠉⠉⠉⠉⠛⠻⢿⣿⣿⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⣿⠋⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠙⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⠋⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠙⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⠋⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠀⠙⣿⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⡇⠀⢀⣀⣀⣀⠀⠀⠀⠀⣀⣀⣀⡀⠀⢸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⠀⢀⣀⣀⣀⠀⠀⠀⠀⣀⣀⣀⡀⠀⢸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⠀⢀⣀⣀⣀⠀⠀⠀⠀⣀⣀⣀⡀⠀⢸⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⡇⢰⣿⣿⠛⣿⡇⠀⠀⢸⣿⠛⣿⣿⡆⢸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⢰⣿⣿⠛⣿⡇⠀⠀⢸⣿⠛⣿⣿⡆⢸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⢰⣿⣿⠛⣿⡇⠀⠀⢸⣿⠛⣿⣿⡆⢸⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⣷⠄⠉⠛⣛⠟⠀⣼⣧⠀⠻⣛⠛⠉⠀⣾⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣷⠄⠉⠛⣛⠟⠀⣼⣧⠀⠻⣛⠛⠉⠀⣾⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣷⠄⠉⠛⣛⠟⠀⣼⣧⠀⠻⣛⠛⠉⠀⣾⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⣿⠀⠤⡖⡤⣀⣀⣉⣉⣀⣀⡠⣴⠦⠀⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⠀⠤⡖⡤⣀⣀⣉⣉⣀⣀⡠⣴⠦⠀⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⠀⠤⡖⡤⣀⣀⣉⣉⣀⣀⡠⣴⠦⠀⣿⣿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⡿⠛⢻⣆⠀⠈⠃⠤⡇⢸⠀⢸⠠⠗⠉⠀⣠⠟⠉⢻⣿⣿⣿⣿⣿⣿⣿⣿⡿⠛⢻⣆⠀⠈⠃⠤⡇⢸⠀⢸⠠⠗⠉⠀⣠⠟⠉⢻⣿⣿⣿⣿⣿⣿⣿⣿⡿⠛⢻⣆⠀⠈⠃⠤⡇⢸⠀⢸⠠⠗⠉⠀⣠⠟⠉⢻⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣴⣦⣤⡉⠳⣶⣦⣤⣄⣤⣤⣤⣤⣴⣶⡾⠁⣠⣾⣯⠻⣿⣿⣿⣿⣿⣿⣿⣴⣦⣤⡉⠳⣶⣦⣤⣄⣤⣤⣤⣤⣴⣶⡾⠁⣠⣾⣯⠻⣿⣿⣿⣿⣿⣿⣿⣴⣦⣤⡉⠳⣶⣦⣤⣄⣤⣤⣤⣤⣴⣶⡾⠁⣠⣾⣯⠻⣿⣿⣿)=
    (⣿⣿⢟⣽⣿⡟⢻⣿⣶⡌⣙⠛⣄⠉⠁⡼⠛⢛⣡⣤⣾⡟⢹⣿⣷⡜⢿⣿⣿⣿⢟⣽⣿⡟⢻⣿⣶⡌⣙⠛⣄⠉⠁⡼⠛⢛⣡⣤⣾⡟⢹⣿⣷⡜⢿⣿⣿⣿⢟⣽⣿⡟⢻⣿⣶⡌⣙⠛⣄⠉⠁⡼⠛⢛⣡⣤⣾⡟⢹⣿⣷⡜⢿⣿)=
    (⣿⢣⣿⣿⣿⡇⠸⡿⠿⠃⣋⢸⡏⠉⠙⡟⢈⢸⣿⡿⠟⡁⢸⣿⣿⣿⡆⢻⣿⢣⣿⣿⣿⡇⠸⡿⠿⠃⣋⢸⡏⠉⠙⡟⢈⢸⣿⡿⠟⡁⢸⣿⣿⣿⡆⢻⣿⢣⣿⣿⣿⡇⠸⡿⠿⠃⣋⢸⡏⠉⠙⡟⢈⢸⣿⡿⠟⡁⢸⣿⣿⣿⡆⢻)=
    (⣇⠸⣿⣿⣿⠃⣴⣾⣿⣿⢘⡅⡇⠀⠀⡇⣭⢸⢱⣶⣿⣧⠈⣿⣿⣿⣿⢸⣇⠸⣿⣿⣿⠃⣴⣾⣿⣿⢘⡅⡇⠀⠀⡇⣭⢸⢱⣶⣿⣧⠈⣿⣿⣿⣿⢸⣇⠸⣿⣿⣿⠃⣴⣾⣿⣿⢘⡅⡇⠀⠀⡇⣭⢸⢱⣶⣿⣧⠈⣿⣿⣿⣿⢸)=
    (⣿⣷⣌⠛⢿⠀⣿⣿⣿⣿⡎⡄⣇⣀⣀⡇⡆⢣⣿⣿⣿⣿⠀⣿⣿⠟⣡⣾⣿⣷⣌⠛⢿⠀⣿⣿⣿⣿⡎⡄⣇⣀⣀⡇⡆⢣⣿⣿⣿⣿⠀⣿⣿⠟⣡⣾⣿⣷⣌⠛⢿⠀⣿⣿⣿⣿⡎⡄⣇⣀⣀⡇⡆⢣⣿⣿⣿⣿⠀⣿⣿⠟⣡⣾)=
    (⣿⣿⣿⣷⣾⣄⣈⣛⣛⣛⣣⣤⣤⣶⣶⣶⣤⣭⣭⣭⣭⣁⣰⣥⣴⣿⣿⣿⣿⣿⣿⣷⣾⣄⣈⣛⣛⣛⣣⣤⣤⣶⣶⣶⣤⣭⣭⣭⣭⣁⣰⣥⣴⣿⣿⣿⣿⣿⣿⣷⣾⣄⣈⣛⣛⣛⣣⣤⣤⣶⣶⣶⣤⣭⣭⣭⣭⣁⣰⣥⣴⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⢟⣿⠛⣿⣿⣿⣿⣿⣿⣿⣿⣿⠉⣿⣿⣏⢿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⢟⣿⠛⣿⣿⣿⣿⣿⣿⣿⣿⣿⠉⣿⣿⣏⢿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⢟⣿⠛⣿⣿⣿⣿⣿⣿⣿⣿⣿⠉⣿⣿⣏⢿⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣿⢸⡇⢀⣿⣿⣿⣿⠉⡎⣿⣿⣿⠀⢻⣿⣿⡸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⢸⡇⢀⣿⣿⣿⣿⠉⡎⣿⣿⣿⠀⢻⣿⣿⡸⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⢸⡇⢀⣿⣿⣿⣿⠉⡎⣿⣿⣿⠀⢻⣿⣿⡸⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⡇⣿⠁⣾⣿⣿⣿⣿⣠⣿⢹⣿⣿⡄⢸⣿⣿⡇⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⣿⠁⣾⣿⣿⣿⣿⣠⣿⢹⣿⣿⡄⢸⣿⣿⡇⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⡇⣿⠁⣾⣿⣿⣿⣿⣠⣿⢹⣿⣿⡄⢸⣿⣿⡇⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⣿⣇⣉⣀⠻⠿⠿⠿⠟⣿⣿⡸⠿⠿⠇⠈⠿⣋⣁⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣇⣉⣀⠻⠿⠿⠿⠟⣿⣿⡸⠿⠿⠇⠈⠿⣋⣁⣿⣿⣿⣿⣿⣿⣿⣿⣿⣿⣇⣉⣀⠻⠿⠿⠿⠟⣿⣿⡸⠿⠿⠇⠈⠿⣋⣁⣿⣿⣿⣿⣿)=
    (⣿⣿⣿⣿⡿⠛⠛⠿⣛⠛⢿⣿⣿⣿⣿⣿⣿⠋⠛⠛⢛⡿⠟⠛⠿⣿⣿⣿⣿⣿⣿⣿⡿⠛⠛⠿⣛⠛⢿⣿⣿⣿⣿⣿⣿⠋⠛⠛⢛⡿⠟⠛⠿⣿⣿⣿⣿⣿⣿⣿⡿⠛⠛⠿⣛⠛⢿⣿⣿⣿⣿⣿⣿⠋⠛⠛⢛⡿⠟⠛⠿⣿⣿⣿)=
    (⣿⣿⣿⣿⣀⣀⣀⣀⣀⣖⣻⣿⣿⣿⣿⣿⣟⣒⣒⣲⣁⣀⣀⣀⣀⣼⣿⣿⣿⣿⣿⣿⣀⣀⣀⣀⣀⣖⣻⣿⣿⣿⣿⣿⣟⣒⣒⣲⣁⣀⣀⣀⣀⣼⣿⣿⣿⣿⣿⣿⣀⣀⣀⣀⣀⣖⣻⣿⣿⣿⣿⣿⣟⣒⣒⣲⣁⣀⣀⣀⣀⣼⣿⣿)=
    ㅤㅤㅤㅤㅤㅤㅤㅤㅤㅤㅤㅤㅤsansㅤundertale                                                                 =
    
    {------------------------------------------------
     - PROGRAM ENDS HERE                            -
     -                                              -
     -                                              -
     -                                              -
     -----------------------------------------------}
    

    entry #10

    written by razetime
    submitted at
    1 like

    guesses
    comments 0

    post a comment


    kil.lua ASCII text
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    17
    18
    19
    20
    21
    22
    23
    24
    25
    26
    27
    28
    29
    30
    31
    32
    33
    34
    35
    36
    37
    38
    39
    40
    41
    42
    43
    44
    45
    46
    47
    48
    49
    50
    51
    52
    53
    54
    55
    56
    57
    58
    59
    60
    61
    62
    63
    64
    65
    66
    67
    68
    getmetatable('').__index = function(str,i) return string.sub(str,i,i) end
    
    function print_r(arr, indentLevel)
        local str = ""
        local indentStr = "#"
    
        if(indentLevel == nil) then
            print(print_r(arr, 0))
            return
        end
    
        for i = 0, indentLevel do
            indentStr = indentStr.."\t"
        end
    
        for index,value in pairs(arr) do
            if type(value) == "table" then
                str = str..indentStr..index..": \n"..print_r(value, (indentLevel + 1))
            else 
                str = str..indentStr..index..": "..value.."\n"
            end
        end
        return str
    end
    
    a,b,c=io.read("*l","*l","*l")
    d={a,b,c}
    e={
      {{1,1},{1,2},{1,3}},
      {{2,1},{2,2},{2,3}},
      {{3,1},{3,2},{3,3}},
      {{1,1},{2,1},{3,1}},
      {{1,2},{2,2},{3,2}},
      {{1,3},{2,3},{3,3}},
      {{1,1},{2,2},{3,3}},
      {{1,3},{2,2},{3,1}}
    }
    
    --print_r(d)
    ps={1,1}
    for i,v in pairs(e) do
      c=0
      b=false
      for j,w in pairs(v) do
        ch=d[w[1]][w[2]]
        if ch=='o' then
          c=c+1
        elseif ch=='.' then
          --print
          ps=w
        end
      end
      if c==2 then
        break
      end
    end
    print(ps[1],ps[2])
    for i,v in pairs(d) do
      for j=1,#v do
        --print(i==ps[0],j==ps[1])
        if i==ps[1] and j==ps[2] then
          io.write('x')
        else
          io.write(d[i][j])
        end
      end
      print("")
    end
    

    entry #11

    written by SoundOfSpouting
    submitted at
    2 likes

    guesses
    comments 0

    post a comment


    olus2000.lua ASCII text, with CRLF line terminators
     1
     2
     3
     4
     5
     6
     7
     8
     9
    10
    11
    12
    13
    14
    15
    16
    17
    18
    19
    20
    21
    22
    23
    24
    25
    26
    27
    28
    29
    30
    31
    32
    33
    34
    35
    36
    37
    38
    39
    40
    41
    42
    43
    44
    45
    46
    47
    48
    49
    50
    51
    52
    53
    54
    55
    56
    57
    58
    59
    60
    61
    62
    63
    64
    65
    66
    67
    68
    69
    70
    -- // Code by SoundOfSpouting#6980 (UID: 151149148639330304)
    
    STATE_X, STATE_O, STATE_N = "X", "O", "."
    
    function entry(str) return serialize(best(parse(str), STATE_X, STATE_O)) end
    
    function parse(str)
      local board, x, y = {{},{},{}}, 1, 1
      for i=1,#str do
        local char = str:sub(i,i)
        if char == "\n" then y, x = y + 1, 1 else board[y][x], x = char, x + 1 end
      end
      return board
    end
    
    -- Returns the application of the first optimal move of the given position.
    -- Notice: Does not care about the runtime of the game. The only criteria considered is the favorability of the final position.
    function best(board, turn, next)
      local nboard, res = nil, winner(board)
      if res ~= STATE_N then return nil, res end
      local t = moves(board)
      for _, move in ipairs(t) do
        local x, y, _nboard = move.x, move.y, copy(board)
        _nboard[y][x] = turn
    
        local _, _res = best(_nboard, next, turn)
        if _res == turn then return _nboard, _res
        elseif nboard == nil or res == next and _res == STATE_N then nboard, res = _nboard, _res end
      end
      return nboard, res
    end
    
    function winner(board)
      for y=1,3 do if board[y][1] == board[y][2] and board[y][2] == board[y][3] or board[1][y] == board[2][y] and board[2][y] == board[3][y] then return board[y][y] end end
      if board[1][1] == board[2][2] and board[2][2] == board[3][3] or board[1][3] == board[2][2] and board[2][2] == board[3][1] then return board[2][2] end
      return STATE_N
    end
    
    function moves(board)
      local t = {}
      for y=1,3 do for x=1,3 do if board[y][x] == STATE_N then table.insert(t, {x = x, y = y}) end end end
      return t
    end
    
    function copy(board)
      _board = {{},{},{}}
      for y=1,3 do for x=1,3 do _board[y][x] = board[y][x] end end
      return _board
    end
    
    function serialize(board)
      local str = ""
      for y=1,3 do
        for x=1,3 do str = str .. board[y][x] end
        str = str .. "\n"
      end
      return str
    end
    
    -- Notice: Calculates future optimal moves repeatedly.
    function play(str, turn, next, count)
      board = parse(str)
      print(serialize(board))
      for i=1,count do
        board, turn, next = best(board, turn, next), next, turn
        print(serialize(board))
        if winner(board) ~= STATE_N then break end
      end
      print(({[STATE_X] = "First player", [STATE_O] = "Second player", [STATE_N] = "Nobody"})[winner(board)] .. " wins!")
    end