Skip to content

Instantly share code, notes, and snippets.

@throughnothing
Last active August 12, 2018 07:55
Show Gist options
  • Save throughnothing/fd5064ab18827390414eb5fd909ce07b to your computer and use it in GitHub Desktop.
Save throughnothing/fd5064ab18827390414eb5fd909ce07b to your computer and use it in GitHub Desktop.
Words Tries where Tries are Monoids
module Main where
import Prelude (($), (<>), map, (<<<))
import Data.Map as M
import Data.Ord (class Ord)
import Data.Semigroup (class Semigroup)
import Data.Monoid (class Monoid, mempty)
import Data.Show (class Show, show)
import Data.String.CodeUnits (toCharArray)
import Data.Foldable as F
import Data.List (List, fromFoldable)
newtype Trie a = Trie (M.Map a (Trie a))
instance semigroupTrie :: Ord a => Semigroup (Trie a) where
append (Trie t) (Trie t') = Trie $ M.unionWith (<>) t t'
instance monoidTrie :: Ord a => Monoid (Trie a) where
mempty = Trie M.empty
instance showTrie :: Show a => Show (Trie a) where
show (Trie t) = show t
makeTrie :: ∀ c. Ord c => List c -> Trie c
makeTrie = F.foldr (\c t -> Trie (M.singleton c t)) mempty
wordz :: List String -> Trie Char
wordz ws = F.foldMap makeTrie $ map (fromFoldable <<< toCharArray) ws
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment