[Haskell-cafe] Applying Data.Map

Toby Hutton toby.hutton at gmail.com
Mon Jun 8 20:57:21 EDT 2009


Although in this example using Data.Map is overkill, if the alphabet was
very large then Data.Map probably would be the way to go. In that case I'd
use:

map head . group . sort instead of nub . sort

since it's noticeably quicker for large lists.  This is because nub needs to
preserve the order of input, removing redundancies, but you're sorting it
anyway.

Also, in map (\c -> m Map.! c) s you can use the 'section' (m
Map.!)instead.  e.g., map
(m Map.!) s

The Map.! is ugly though.  As you're only using fromList and (!) from
Data.Map, I'd just import those explicitly since they don't clash with
Prelude.  Then you'd have map (m !) s

Toby.


On Tue, Jun 9, 2009 at 4:59 AM, michael rice <nowgate at yahoo.com> wrote:

> I wrote a Haskell solution for the Prolog problem stated below. I had
> written a function SQUISH before discovering that NUB does the same thing.
> While the solution works, I thought maybe I could apply some functions in
> the Data.Map module, and so wrote a second version of SERIALIZE, one no
> longer needing TRANSLATE. Using the Data.Map module is probably overkill for
> this particular problem, but wanted to familiarize myself with Map type.
> Suggestions welcome. Prolog code also included below for those interested.
>
> Michael
>
> ===========
>
> {-
>  From "Prolog By Example", Coelho, Cotta, Problem 42, pg. 63
>
>    Verbal statement:
>    Generate a list of serial numbers for the items of a given list,
>    the members of which are to be numbered in alphabetical order.
>
>    For example, the list [p,r,o,l,o,g] must generate [4,5,3,2,3,1]
> -}
>
> {-
> Prelude> :l serialize
> [1 of 1] Compiling Main             ( serialize.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> serialize "prolog"
> [4,5,3,2,3,1]
> *Main>
> -}
>
> ===========Haskell code==========
>
> import Data.Char
> import Data.List
> import Data.Map (Map)
> import qualified Data.Map as Map
>
> {-
> translate :: [Char] -> [(Char,Int)] -> [Int]
> translate [] _ = []
> translate (x:xs) m = (fromJust (lookup x m)) : (translate xs m )
> -}
>
> {-
> serialize :: [Char] -> [Int]
> serialize s = let c = nub $ sort s
>                   n = [1..(length c)]
>               in translate s (zip c n)
> -}
>
> serialize :: [Char] -> [Int]
> serialize s = let c = nub $ sort s
>                   n = [1..(length c)]
>                   m = Map.fromList $ zip c n
>               in map (\c -> m Map.! c) s
>
> ============Prolog code============
>
> serialize(L,R) :- pairlists(L,R,A),arrange(A,T),
>                   numbered(T,1,N).
>                                                 ?  <- typo?
> pairlists([X|L],[Y|R],[pair(X,Y)|A]) :- pairlist(L,R,A).
> pairlists([],[],[]).
>
> arrange([X|L],tree(T1,X,T2)) :- partition(L,X,L1,L2),
>                                 arrange(L1,T1),
>                                 arrange(L2,T2).
> arrange([],_).
>
> partition([X|L],X,L1,L2) :- partition(L,X,L1,L2).
> partition([X|L],Y,[X|L1],L2) :- before(X,Y),
>                                 partition(L,Y,L1,L2).
> partition([X|L],Y,L1,[X|L2]) :- before(Y,X),
>                                 partition(L,Y,L1,L2).
> partition([],_,[],[]).
>
> before(pair(X1,Y1),pair(X2,Y2)) :- X1<X2.
>
> numbered(tree(T1,pair(X,N1),T2),N0,N) :- numbered(T1,N0,N1),
>                                          N2 is N1+1,
>                                          numbered(T2,N2,N).
> numbered(void,N,N).
>
> ============Prolog examples========
> Execution:
>
> ?- serialize([p,r,o,l,o,g]).
>    [4,5,3,2,3,1]
> ?- serialize ([i,n,t,.,a,r,t,i,f,i,c,i,a,l]).
>   [5,7,9,1,2,8,9,5,4,5,3,5,2,6]
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090608/a2d06c72/attachment.html


More information about the Haskell-Cafe mailing list