Offers the base 64 encoding and decoding algorithms

Redefined classes

redef class Bytes

base64 :: base64 $ Bytes

A buffer containing Byte-manipulation facilities
redef extern class CString

base64 :: base64 $ CString

C string char *
redef enum Char

base64 :: base64 $ Char

Native characters.
redef abstract class FlatText

base64 :: base64 $ FlatText

All kinds of array-based text representations.
redef enum Int

base64 :: base64 $ Int

Native integer numbers.
redef abstract class Text

base64 :: base64 $ Text

High-level abstraction for all text representations

All class definitions

redef class Bytes

base64 :: base64 $ Bytes

A buffer containing Byte-manipulation facilities
redef extern class CString

base64 :: base64 $ CString

C string char *
redef enum Char

base64 :: base64 $ Char

Native characters.
redef abstract class FlatText

base64 :: base64 $ FlatText

All kinds of array-based text representations.
redef enum Int

base64 :: base64 $ Int

Native integer numbers.
redef abstract class Text

base64 :: base64 $ Text

High-level abstraction for all text representations
package_diagram base64::base64 base64 core core base64::base64->core crapto::repeating_key_xor_solve repeating_key_xor_solve crapto::repeating_key_xor_solve->base64::base64 github::api api github::api->base64::base64 nitcorn::token token nitcorn::token->base64::base64 sendmail::sendmail sendmail sendmail::sendmail->base64::base64 websocket::websocket websocket websocket::websocket->base64::base64 a_star-m a_star-m a_star-m->crapto::repeating_key_xor_solve a_star-m->sendmail::sendmail a_star-m... ... a_star-m...->a_star-m github::cache cache github::cache->github::api github::events events github::events->github::api github::cache... ... github::cache...->github::cache github::events... ... github::events...->github::events nitcorn::sessions sessions nitcorn::sessions->nitcorn::token nitcorn::sessions... ... nitcorn::sessions...->nitcorn::sessions websocket::websocket_server websocket_server websocket::websocket_server->websocket::websocket websocket::websocket_server... ... websocket::websocket_server...->websocket::websocket_server

Ancestors

module abstract_collection

core :: abstract_collection

Abstract collection classes and services.
module abstract_text

core :: abstract_text

Abstract class for manipulation of sequences of characters
module array

core :: array

This module introduces the standard array structure.
module bitset

core :: bitset

Services to handle BitSet
module bytes

core :: bytes

Services for byte streams and arrays
module circular_array

core :: circular_array

Efficient data structure to access both end of the sequence.
module codec_base

core :: codec_base

Base for codecs to use with streams
module codecs

core :: codecs

Group module for all codec-related manipulations
module collection

core :: collection

This module define several collection classes.
module environ

core :: environ

Access to the environment variables of the process
module error

core :: error

Standard error-management infrastructure.
module exec

core :: exec

Invocation and management of operating system sub-processes.
module file

core :: file

File manipulations (create, read, write, etc.)
module fixed_ints

core :: fixed_ints

Basic integers of fixed-precision
module fixed_ints_text

core :: fixed_ints_text

Text services to complement fixed_ints
module flat

core :: flat

All the array-based text representations
module gc

core :: gc

Access to the Nit internal garbage collection mechanism
module hash_collection

core :: hash_collection

Introduce HashMap and HashSet.
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module list

core :: list

This module handle double linked lists
module math

core :: math

Mathematical operations
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module protocol

core :: protocol

module queue

core :: queue

Queuing data structures and wrappers
module range

core :: range

Module for range of discrete objects.
module re

core :: re

Regular expression support for all services based on Pattern
module ropes

core :: ropes

Tree-based representation of a String.
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module stream

core :: stream

Input and output streams of characters
module text

core :: text

All the classes and methods related to the manipulation of text entities
module time

core :: time

Management of time and dates
module union_find

core :: union_find

union–find algorithm using an efficient disjoint-set data structure
module utf8

core :: utf8

Codec for UTF-8 I/O

Parents

module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.

Children

module api

github :: api

Nit object oriented interface to Github api.
module sendmail

sendmail :: sendmail

Send emails using the sendmail program
module token

nitcorn :: token

Simple generate_token service, independent of the rest of the nitcorn framework
module websocket

websocket :: websocket

Adds support for a websocket connection in Nit

Descendants

module a_star-m

a_star-m

module cache

github :: cache

Enable caching on Github API accesses.
module events

github :: events

Events are emitted by Github Hooks.
module example_angular

popcorn :: example_angular

This is an example of how to use angular.js with popcorn
module file_server

nitcorn :: file_server

Provides the FileServer action, which is a standard and minimal file server
module github

github :: github

Nit wrapper for Github API
module hooks

github :: hooks

Github hook event listening with nitcorn.
module htcpcp_server

nitcorn :: htcpcp_server

A server that implements HTCPCP. At the moment there are no additions.
module loader

github :: loader

module nitcorn

nitcorn :: nitcorn

The nitcorn Web server framework creates server-side Web apps in Nit
module nitcorn_hello_world

nitcorn :: nitcorn_hello_world

Hello World Web server example
module pop_auth

popcorn :: pop_auth

Authentification handlers.
module pop_handlers

popcorn :: pop_handlers

Route handlers.
module pop_json

popcorn :: pop_json

Introduce useful services for JSON REST API handlers.
module pop_routes

popcorn :: pop_routes

Internal routes representation.
module pop_sessions

popcorn :: pop_sessions

Session handlers
module pop_tasks

popcorn :: pop_tasks

Popcorn threaded tasks
module pop_templates

popcorn :: pop_templates

Template rendering for popcorn
module pop_tests

popcorn :: pop_tests

Popcorn testing services
module popcorn

popcorn :: popcorn

Application server abstraction on top of nitcorn.
module pthreads

nitcorn :: pthreads

Activate the use of pthreads with nitcorn
module restful

nitcorn :: restful

Support module for the nitrestful tool and the restful annotation
module restful_annot

nitcorn :: restful_annot

Example for the restful annotation documented at lib/nitcorn/restful.nit
module sessions

nitcorn :: sessions

Automated session management
module simple_file_server

nitcorn :: simple_file_server

Basic file server on port 80 by default, may require root to execute
module wallet

github :: wallet

Github OAuth tokens management
module websocket_server

websocket :: websocket_server

Sample module for a minimal chat server using Websockets on port 8088
# Offers the base 64 encoding and decoding algorithms
module base64

redef class Char
	# Is `self` a valid Base64 character ?
	fun is_base64_char: Bool do
		if code_point >= 127 then return false
		return code_point.is_base64_char
	end
end

redef class Int
	# Is `self` a valid Base64 character ?
	fun is_base64_char: Bool do
		if self == u'+' then return true
		if self == u'/' then return true
		if self > u'Z' then
			if self < u'a' then return false
			if self <= u'z' then return true
			return false
		end
		if self >= u'A' then return true
		if self <= u'9' and self >= u'0' then return true
		return false
	end

	# Returns the `base64` equivalent of `self`
	#
	# REQUIRE `self`.`is_base64_char`
	fun to_base64_char: Int do
		if self == u'+' then return 62
		if self == u'/' then return 63
		if self > u'Z' then
			if self < u'a' then abort
			if self <= u'z' then return self - 71
			abort
		end
		if self >= u'A' then return self - 0x41
		if self <= u'9' and self >= u'0' then return self + 4
		abort
	end
end

redef class CString
	# Alphabet used by the base64 algorithm
	private fun base64_chars : Bytes
	do
		return b"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"
	end

	# Encodes `self` to base64.
	#
	# By default, uses "=" for padding.
	#
	#     assert "string".encode_base64 == "c3RyaW5n"
	private fun encode_base64(length: Int): Bytes do
		var base64_bytes = once base64_chars
		var steps = length / 3
		var bytes_in_last_step = length % 3
		var result_length = steps * 4
		if bytes_in_last_step > 0 then result_length += 4
		var result = new Bytes.with_capacity(result_length)

		var in_off = 0
		for s in [0 .. steps[ do
			var ind = (self[in_off] & 0b1111_1100) >> 2
			result.add base64_bytes[ind]
			ind = ((self[in_off] & 0b0000_0011) << 4) | ((self[in_off + 1] & 0b1111_0000) >> 4)
			result.add base64_bytes[ind]
			ind = ((self[in_off + 1] & 0b0000_1111) << 2) | ((self[in_off + 2] & 0b1100_0000) >> 6)
			result.add base64_bytes[ind]
			ind = (self[in_off + 2] & 0b0011_1111)
			result.add base64_bytes[ind]
			in_off += 3
		end
		if bytes_in_last_step == 1 then
			result.add base64_bytes[(self[in_off] & 0b1111_1100) >> 2]
			result.add base64_bytes[(self[in_off] & 0b0000_0011) << 4]
		else if bytes_in_last_step == 2 then
			result.add base64_bytes[(self[in_off] & 0b1111_1100) >> 2]
			result.add base64_bytes[((self[in_off] & 0b0000_0011) << 4) | ((self[in_off + 1] & 0b1111_0000) >> 4)]
			result.add base64_bytes[(self[in_off + 1] & 0b0000_1111) << 2]
		end
		var rempad = if bytes_in_last_step > 0 then 3 - bytes_in_last_step else 0
		for i in [0 .. rempad[ do result.add u'='

		return result
	end

	# Decodes `self` from base64
	#
	#      assert "c3RyaW5n".decode_base64.to_s == "string"
	#      assert "c3Rya\nW5n".decode_base64.to_s == "string"
	#      assert "c3RyaW5nCg==".decode_base64.to_s == "string\n"
	#      assert "c3RyaW5nCg".decode_base64.to_s == "string\n"
	#      assert "c3RyaW5neQo=".decode_base64.to_s == "stringy\n"
	#      assert "c3RyaW5neQo".decode_base64.to_s == "stringy\n"
	#
	private fun decode_base64(length: Int): Bytes do
		if length == 0 then return new Bytes.empty

		# Avoids constant unboxing
		var pad = '='

		var result = new Bytes.with_capacity((length / 4 + 1) * 3)

		var curr = 0
		var cnt = 0
		var endpos = -1
		for i in [0 .. length[ do
			var b = self[i]
			if b == pad then
				endpos = i
				break
			end
			# Ignore whitespaces
			if b <= 0x20 then continue
			if not b.is_base64_char then continue
			curr <<= 6
			curr += b.to_base64_char.to_i
			cnt += 1
			if cnt == 4 then
				result.add ((curr & 0xFF0000) >> 16)
				result.add ((curr & 0xFF00) >> 8)
				result.add (curr & 0xFF)
				curr = 0
				cnt = 0
			end
		end
		if endpos != -1 or cnt != 0 then
			var pads = 0
			for i in [endpos .. length[ do
				var b = self[i]
				if b <= 0x20 then continue
				pads += 1
			end
			if cnt == 2 then
				curr >>= 4
				result.add(curr)
			else if cnt == 3 then
				curr >>= 2
				result.add ((curr & 0xFF00) >> 8)
				result.add (curr & 0xFF)
			end
		end
		return result
	end

	# Is `self` a well-formed Base64 entity ?
	#
	# ~~~nit
	#	assert "Qn03".is_base64
	#	assert not "#sd=".is_base64
	# ~~~
	fun is_base64(length: Int): Bool do return check_base64(length) == null

	# Is `self` a well-formed Base64 entity ?
	#
	# Will return an Error otherwise with info on which part is erroneous.
	fun check_base64(length: Int): nullable Error do
		var rlen = 0
		var opos = length
		for i in [0 .. length[ do
			if self[i] == u'=' then
				opos = i
				break
			end
			if self[i].is_whitespace then continue
			if not self[i].is_base64_char then return new Error("Invalid Base64 character at position {i}: {self[i].code_point}")
			rlen += 1
			if rlen > 4 then rlen -= 4
		end
		var pad = 0
		for i in [opos .. length[ do
			if self[i].is_whitespace then continue
			if self[i] != u'=' then return new Error("Invalid padding character {self[i].code_point} at position {i}")
			pad += 1
		end
		if rlen + pad != 4 then return new Error("Invalid padding length")
		return null
	end
end

redef class Bytes

	# Encodes the receiver string to base64 using a custom padding character.
	#
	# If using the default padding character `=`, see `encode_base64`.
	fun encode_base64: Bytes do return items.encode_base64(length)

	# Decodes the receiver string to base64 using a custom padding character.
	#
	# Default padding character `=`
	fun decode_base64: Bytes do return items.decode_base64(length)

	# Is `self` a well-formed Base64 entity ?
	fun is_base64: Bool do return items.is_base64(length)

	# Is `self` a well-formed Base64 entity ?
	#
	# Will return an Error otherwise with info on which part is erroneous.
	fun check_base64: nullable Error do return items.check_base64(length)
end

redef class Text

	# Encodes the receiver string to base64 using a custom padding character.
	#
	# If using the default padding character `=`, see `encode_base64`.
	fun encode_base64: String do return to_cstring.encode_base64(byte_length).to_s

	# Decodes the receiver string to base64 using a custom padding character.
	#
	# Default padding character `=`
	fun decode_base64: Bytes do return to_cstring.decode_base64(byte_length)

	# Is `self` a well-formed Base64 entity ?
	fun is_base64: Bool do return to_cstring.is_base64(byte_length)

	# Is `self` a well-formed Base64 entity ?
	#
	# Will return an Error otherwise with info on which part is erroneous.
	fun check_base64: nullable Error do return to_cstring.check_base64(byte_length)
end

redef class FlatText
	redef fun encode_base64 do return fast_cstring.encode_base64(byte_length).to_s

	redef fun decode_base64 do return fast_cstring.decode_base64(byte_length)

	redef fun is_base64 do return fast_cstring.is_base64(byte_length)

	redef fun check_base64 do return fast_cstring.check_base64(byte_length)
end
lib/base64/base64.nit:17,1--250,3