hashids-1.0.2.3: Hashids generates short, unique, non-sequential ids from numbers.

Safe HaskellSafe
LanguageHaskell2010

Web.Hashids

Contents

Description

This is a Haskell port of the Hashids library by Ivan Akimov. This is not a cryptographic hashing algorithm. Hashids is typically used to encode numbers to a format suitable to appear in places like urls.

See the official Hashids home page: http://hashids.org

Hashids is a small open-source library that generates short, unique, non-sequential ids from numbers. It converts numbers like 347 into strings like yr8, or a list of numbers like [27, 986] into 3kTMd. You can also decode those ids back. This is useful in bundling several parameters into one or simply using them as short UIDs.

Synopsis

Documentation

data HashidsContext Source #

Opaque data type with various internals required for encoding and decoding.

How to use

Note that most of the examples on this page require the OverloadedStrings extension.

Encoding

Unless you require a minimum length for the generated hash, create a context using hashidsSimple and then call encode and decode with this object.

{-# LANGUAGE OverloadedStrings #-}

import Web.Hashids

main :: IO ()
main = do
    let context = hashidsSimple "oldsaltyswedishseadog"
    print $ encode context 42

This program will output

"kg"

To specify a minimum hash length, use hashidsMinimum instead.

main = do
    let context = hashidsMinimum "oldsaltyswedishseadog" 12
    print $ encode context 42

The output will now be

"W3xbdkgdy42v"

If you only need the context once, you can use one of the provided wrappers to simplify things.

main :: IO ()
main = print $ encodeUsingSalt "oldsaltyswedishseadog" 42

On the other hand, if your implementation invokes the hashing algorithm frequently without changing the configuration, it is probably better to define partially applied versions of encode, encodeList, and decode.

import Web.Hashids

context :: HashidsContext
context = createHashidsContext "oldsaltyswedishseadog" 12 "abcdefghijklmnopqrstuvwxyz"

encode'     = encode context
encodeList' = encodeList context
decode'     = decode context

main :: IO ()
main = print $ encode' 12345

Use a custom alphabet and createHashidsContext if you want to make your hashes "unique".

main = do
    let context = createHashidsContext "oldsaltyswedishseadog" 0 "XbrNfdylm5qtnP19R"
    print $ encode context 1

The output is now

"Rd"

To encode a list of numbers, use encodeList.

let context = hashidsSimple "this is my salt" in encodeList context [0, 1, 2]
"yJUWHx"

Decoding

Decoding a hash returns a list of numbers,

let context = hashidsSimple "this is my salt"
     hash = decode context "rD"        -- == [5]

Decoding will not work if the salt is changed:

main = do
    let context = hashidsSimple "this is my salt"
        hash = encode context 5

    print $ decodeUsingSalt "this is my pepper" hash

When decoding fails, the empty list is returned.

[]

Randomness

Hashids is based on a modified version of the Fisher-Yates shuffle. The primary purpose is to obfuscate ids, and it is not meant for security purposes or compression. Having said that, the algorithm does try to make hashes unguessable and unpredictable. See the official Hashids home page for details: http://hashids.org

Repeating numbers

let context = hashidsSimple "this is my salt" in encodeList context $ replicate 4 5

There are no repeating patterns in the hash to suggest that four identical numbers are used:

"1Wc8cwcE"

The same is true for increasing numbers:

let context = hashidsSimple "this is my salt" in encodeList context [1..10]
"kRHnurhptKcjIDTWC3sx"

Incrementing number sequence

let context = hashidsSimple "this is my salt" in map (encode context) [1..5]
["NV","6m","yD","2l","rD"]

Curses! #$%@

The algorithm tries to avoid generating common curse words in English by never placing the following letters next to each other:

c, C, s, S, f, F, h, H, u, U, i, I, t, T

API

version :: String Source #

Hashids version number.

Context object constructors

createHashidsContext Source #

Arguments

:: ByteString

Salt

-> Int

Minimum required hash length

-> String

Alphabet

-> HashidsContext 

Create a context object using the given salt, a minimum hash length, and a custom alphabet. If you only need to supply the salt, or the first two arguments, use hashidsSimple or hashidsMinimum instead.

Changing the alphabet is useful if you want to make your hashes unique, i.e., create hashes different from those generated by other applications relying on the same algorithm.

hashidsSimple Source #

Arguments

:: ByteString

Salt

-> HashidsContext 

Create a context object using the default alphabet and the provided salt, without any minimum required length.

hashidsMinimum Source #

Arguments

:: ByteString

Salt

-> Int

Minimum required hash length

-> HashidsContext 

Create a context object using the default alphabet and the provided salt. The generated hashes will have a minimum length as specified by the second argument.

Encoding and decoding

encodeHex Source #

Arguments

:: HashidsContext

A Hashids context object

-> String

Hexadecimal number represented as a string

-> ByteString 

Encode a hexadecimal number.

Example use:

encodeHex context "ff83"

decodeHex Source #

Arguments

:: HashidsContext

A Hashids context object

-> ByteString

Hash

-> String 

Decode a hash generated with encodeHex.

Example use:

decodeHex context "yzgwD"

encode Source #

Arguments

:: HashidsContext

A Hashids context object

-> Int

Number to encode

-> ByteString 

Encode a single number.

Example use:

let context = hashidsSimple "this is my salt"
    hash = encode context 5        -- == "rD"

encodeList Source #

Arguments

:: HashidsContext

A Hashids context object

-> [Int]

List of numbers

-> ByteString 

Encode a list of numbers.

Example use:

let context = hashidsSimple "this is my salt"
    hash = encodeList context [2, 3, 5, 7, 11]          -- == "EOurh6cbTD"

decode Source #

Arguments

:: HashidsContext

A Hashids context object

-> ByteString

Hash

-> [Int] 

Decode a hash.

Example use:

let context = hashidsSimple "this is my salt"
    hash = decode context "rD"        -- == [5]

Convenience wrappers

encodeUsingSalt Source #

Arguments

:: ByteString

Salt

-> Int

Number

-> ByteString 

Encode a number using the provided salt.

This convenience function creates a context with the default alphabet. If the same context is used repeatedly, use encode with one of the constructors instead.

encodeListUsingSalt Source #

Arguments

:: ByteString

Salt

-> [Int]

Numbers

-> ByteString 

Encode a list of numbers using the provided salt.

This function wrapper creates a context with the default alphabet. If the same context is used repeatedly, use encodeList with one of the constructors instead.

decodeUsingSalt Source #

Arguments

:: ByteString

Salt

-> ByteString

Hash

-> [Int] 

Decode a hash using the provided salt.

This convenience function creates a context with the default alphabet. If the same context is used repeatedly, use decode with one of the constructors instead.

encodeHexUsingSalt Source #

Arguments

:: ByteString

Salt

-> String

Hexadecimal number represented as a string

-> ByteString 

Shortcut for encodeHex.

decodeHexUsingSalt Source #

Arguments

:: ByteString

Salt

-> ByteString

Hash

-> String 

Shortcut for decodeHex.