Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  constant set (Ovidiu Deac)
   2. Re:  constant set (Antoine Latter)
   3. Re:  constant set (Ovidiu Deac)
   4. Re:  Parsec, parsing 'free text' (Stephen Tetley)
   5. Re:  constant set (Brandon Allbery)
   6. Re:  Parsec, parsing 'free text' (Stephen Tetley)


----------------------------------------------------------------------

Message: 1
Date: Sat, 10 Mar 2012 19:13:04 +0200
From: Ovidiu Deac <ovidiud...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Lyndon Maydwell <maydw...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAKVsE7ta1wNU_cDKnRw7AVdyoXYi0wTX5DP=orzw0fojydb...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

> What are you trying to gain here by having the color namespace?
>

I want to avoid polluting the global namespace and to avoid name
collisions.

As I said, the example with the colours wasn't probably a good one.

Let me change the question: How can I create a sub-namespace in the same
file?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120310/8d57ffd1/attachment-0001.htm>

------------------------------

Message: 2
Date: Sat, 10 Mar 2012 11:30:08 -0600
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Ovidiu Deac <ovidiud...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cakjsnqhvrbswcvvkd8cvnbsxgcvbpwk2wadtpnaalfsta5b...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

A name space in Haskell is a module, and GHC only allows one module per
file.

So I would put these in a separate file, or do manual namespacing using
prefixes, as in "colorRed".
On Mar 10, 2012 11:14 AM, "Ovidiu Deac" <ovidiud...@gmail.com> wrote:

>
> What are you trying to gain here by having the color namespace?
>>
>
> I want to avoid polluting the global namespace and to avoid name
> collisions.
>
> As I said, the example with the colours wasn't probably a good one.
>
> Let me change the question: How can I create a sub-namespace in the same
> file?
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120310/3887da83/attachment-0001.htm>

------------------------------

Message: 3
Date: Sat, 10 Mar 2012 20:29:03 +0200
From: Ovidiu Deac <ovidiud...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Antoine Latter <aslat...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cakvse7ubbfe8zmei-amruq367-spgudswi-uokj+by6d0x4...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

OK. Thanks for the answers

On Sat, Mar 10, 2012 at 7:30 PM, Antoine Latter <aslat...@gmail.com> wrote:

> A name space in Haskell is a module, and GHC only allows one module per
> file.
>
> So I would put these in a separate file, or do manual namespacing using
> prefixes, as in "colorRed".
> On Mar 10, 2012 11:14 AM, "Ovidiu Deac" <ovidiud...@gmail.com> wrote:
>
>>
>> What are you trying to gain here by having the color namespace?
>>>
>>
>> I want to avoid polluting the global namespace and to avoid name
>> collisions.
>>
>> As I said, the example with the colours wasn't probably a good one.
>>
>> Let me change the question: How can I create a sub-namespace in the same
>> file?
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120310/edfe4cc8/attachment-0001.htm>

------------------------------

Message: 4
Date: Sat, 10 Mar 2012 23:33:04 +0000
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Parsec, parsing 'free text'
To: Franco <franc...@gmx.com>
Cc: beginners@haskell.org
Message-ID:
        <CAB2TPRDXzniXS_z=TNV7KZFyzd9YH4OWSGTHG4+dOK=ep2-...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Franco

The best "solution" is really to work out a grammar of text strings
and write simpler productions that handle it.

Otherwise you can treat it as a "lexing" problem but then the results
get messy as you have found out.

It's a bit late in the UK and I though I've looked at the code I
haven't worked out an answer yet, I'll have a proper look tomorrow if
no one else has answered but here is my first step, this is a "lexing"
solution but written directly rather than with Parsec. It is easier to
write a "lexing" solution this as two mutually recursive functions for
the lexer states - consuming free text, or consuming a format string.


data Text1 = FreeText String | Formatted String
  deriving (Eq,Ord,Show)

type Text = [Text1]


-- The type of /accumulator/.
type Acc  = ShowS

-- We want to grow Strings from the right.
snoc :: Acc -> Char -> Acc
snoc ss c = ss . (c:)

toString :: Acc -> String
toString = ($ "")

empty :: Acc
empty = id


runText :: String -> Text
runText = text empty


-- Minor problem - generates empty FreeText if the accumulator is
-- empty, this can be easily fixed at some loss of clarity.
--
text :: Acc -> String -> Text
text ac []       = [FreeText (toString ac)]
text ac ('<':cs) = FreeText (toString ac) : formatted empty cs
text ac (c:cs)   = text (ac `snoc` c) cs


formatted :: Acc -> String -> Text
formatted _  []       = error "missing terminator for formatting"
formatted ac ('>':cs) = Formatted (toString ac) : text empty cs
formatted ac (c:cs)   = formatted (ac `snoc` c) cs


demo01 = runText "[ someconditions | this is some <red - formatted> text.]"



------------------------------

Message: 5
Date: Sat, 10 Mar 2012 22:41:10 -0500
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Ovidiu Deac <ovidiud...@gmail.com>
Cc: beginners@haskell.org, Ertugrul S?ylemez <e...@ertes.de>
Message-ID:
        <CAKFCL4Wm=o=zT1woem=51Or2ufFbLCkn02Oh_wETNZm=njq...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

2012/3/10 Ovidiu Deac <ovidiud...@gmail.com>

> I already tried this approach:
>
> module Main where
>
> import ....
>
> module Colors where
>   red = 1
>   blue = 2
> .....
>
> but the compiler complains at the line "module Colors where". It says:
> parse error on input `module'
>

Right, you can have only one module per file.  You would define them in a
separate file, possibly making use of qualified imports:

> module Constants.AColors where
> red = 1
> blue = 2

> module Constants.BColors where
> yellow = 1
> red = 2

> module Main where
> import qualified Constants.AColors as AC
> import qualified Constants.BColors as BC
> ...
> -- code that uses AC.red and BC.red

This is not entirely ideal from the standpoint of using types to help
manage your data, but without more details as to how you're using them,
it's hard to present appropriate solutions.

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120310/205677e5/attachment-0001.htm>

------------------------------

Message: 6
Date: Sun, 11 Mar 2012 10:53:50 +0000
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Parsec, parsing 'free text'
To: Franco <franc...@gmx.com>
Cc: beginners@haskell.org
Message-ID:
        <cab2tprahkqft9tukbwkxbuhokamnzufahkhyafq4mqbj-qw...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Franco

Actually the simple case of finding formatting tags in free text was
easier in Parsec than my email last night suggested. Perhaps it is
artificially easy because you can identify tag start and ends with a
single character so you can use `satisfy`.

import Text.Parsec
import Text.Parsec.String
import Control.Applicative hiding ( (<|>), many )


data Text1 = FreeText String | Formatted String
  deriving (Eq,Ord,Show)

type Text = [Text1]

runText :: String -> Either ParseError Text
runText = runP lexer () "no-input"


notLAngle :: Char -> Bool
notLAngle = (/= '<')

notRAngle :: Char -> Bool
notRAngle = (/= '>')

lexer :: Parser Text
lexer = many (formatted <|> free)

formatted :: Parser Text1
formatted = Formatted <$>
    between (char '<') (char '>') (many1 (satisfy notRAngle))

free :: Parser Text1
free = FreeText <$> many1 (satisfy notLAngle)



demo01 = runText "[ someconditions | this is some <red - formatted> text.]"
demo02 = runText "<red - formatted> more text."



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 45, Issue 13
*****************************************

Reply via email to